lang/src/Language/Lang/PrintGrammer.hs

179 lines
7.4 KiB
Haskell

{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ <= 708
{-# LANGUAGE OverlappingInstances #-}
#endif
{-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
-- | Pretty-printer for Language.
-- Generated by the BNF converter.
module Language.Lang.PrintGrammer where
import qualified Language.Lang.AbsGrammer
import Data.Char
-- | The top-level printing method.
printTree :: Print a => a -> String
printTree = render . prt 0
type Doc = [ShowS] -> [ShowS]
doc :: ShowS -> Doc
doc = (:)
render :: Doc -> String
render d = rend 0 (map ($ "") $ d []) "" where
rend i ss = case ss of
"[" :ts -> showChar '[' . rend i ts
"(" :ts -> showChar '(' . rend i ts
"{" :ts -> showChar '{' . new (i+1) . rend (i+1) ts
"}" : ";":ts -> new (i-1) . space "}" . showChar ';' . new (i-1) . rend (i-1) ts
"}" :ts -> new (i-1) . showChar '}' . new (i-1) . rend (i-1) ts
[";"] -> showChar ';'
";" :ts -> showChar ';' . new i . rend i ts
t : ts@(p:_) | closingOrPunctuation p -> showString t . rend i ts
t :ts -> space t . rend i ts
_ -> id
new i = showChar '\n' . replicateS (2*i) (showChar ' ') . dropWhile isSpace
space t s =
case (all isSpace t', null spc, null rest) of
(True , _ , True ) -> [] -- remove trailing space
(False, _ , True ) -> t' -- remove trailing space
(False, True, False) -> t' ++ ' ' : s -- add space if none
_ -> t' ++ s
where
t' = showString t []
(spc, rest) = span isSpace s
closingOrPunctuation :: String -> Bool
closingOrPunctuation [c] = c `elem` closerOrPunct
closingOrPunctuation _ = False
closerOrPunct :: String
closerOrPunct = ")],;"
parenth :: Doc -> Doc
parenth ss = doc (showChar '(') . ss . doc (showChar ')')
concatS :: [ShowS] -> ShowS
concatS = foldr (.) id
concatD :: [Doc] -> Doc
concatD = foldr (.) id
replicateS :: Int -> ShowS -> ShowS
replicateS n f = concatS (replicate n f)
-- | The printer class does the job.
class Print a where
prt :: Int -> a -> Doc
prtList :: Int -> [a] -> Doc
prtList i = concatD . map (prt i)
instance {-# OVERLAPPABLE #-} Print a => Print [a] where
prt = prtList
instance Print Char where
prt _ s = doc (showChar '\'' . mkEsc '\'' s . showChar '\'')
prtList _ s = doc (showChar '"' . concatS (map (mkEsc '"') s) . showChar '"')
mkEsc :: Char -> Char -> ShowS
mkEsc q s = case s of
_ | s == q -> showChar '\\' . showChar s
'\\'-> showString "\\\\"
'\n' -> showString "\\n"
'\t' -> showString "\\t"
_ -> showChar s
prPrec :: Int -> Int -> Doc -> Doc
prPrec i j = if j < i then parenth else id
instance Print Integer where
prt _ x = doc (shows x)
instance Print Double where
prt _ x = doc (shows x)
instance Print Language.Lang.AbsGrammer.Name where
prt _ (Language.Lang.AbsGrammer.Name i) = doc $ showString $ i
prtList _ [x] = concatD [prt 0 x, doc (showString " ")]
prtList _ (x:xs) = concatD [prt 0 x, doc (showString " "), prt 0 xs]
instance Print Language.Lang.AbsGrammer.NumericLiteral where
prt _ (Language.Lang.AbsGrammer.NumericLiteral i) = doc $ showString $ i
instance Print Language.Lang.AbsGrammer.Module where
prt i e = case e of
Language.Lang.AbsGrammer.Module bindings -> prPrec i 0 (concatD [prt 0 bindings])
instance Print Language.Lang.AbsGrammer.Binding where
prt i e = case e of
Language.Lang.AbsGrammer.BindingDeclaration declaration -> prPrec i 0 (concatD [prt 0 declaration])
Language.Lang.AbsGrammer.BindingDefinition definition -> prPrec i 0 (concatD [prt 0 definition])
Language.Lang.AbsGrammer.BindingPragma pragma -> prPrec i 0 (concatD [doc (showString "{#"), prt 0 pragma, doc (showString "#}")])
prtList _ [] = concatD []
prtList _ [x] = concatD [prt 0 x]
prtList _ (x:xs) = concatD [prt 0 x, doc (showString ","), prt 0 xs]
instance Print Language.Lang.AbsGrammer.Declaration where
prt i e = case e of
Language.Lang.AbsGrammer.DeclarationNamed name type_ -> prPrec i 0 (concatD [prt 0 name, doc (showString ":"), prt 0 type_])
Language.Lang.AbsGrammer.DeclarationAnonymous type_ -> prPrec i 0 (concatD [prt 0 type_])
prtList _ [] = concatD []
prtList _ [x] = concatD [prt 0 x]
prtList _ (x:xs) = concatD [prt 0 x, doc (showString ","), prt 0 xs]
instance Print Language.Lang.AbsGrammer.Definition where
prt i e = case e of
Language.Lang.AbsGrammer.DefinitionNamed name expression -> prPrec i 0 (concatD [prt 0 name, doc (showString "="), prt 0 expression])
Language.Lang.AbsGrammer.DefinitionAnonymous expression -> prPrec i 0 (concatD [prt 0 expression])
prtList _ [] = concatD []
prtList _ [x] = concatD [prt 0 x]
prtList _ (x:xs) = concatD [prt 0 x, doc (showString ","), prt 0 xs]
instance Print Language.Lang.AbsGrammer.Type where
prt i e = case e of
Language.Lang.AbsGrammer.TypeName name -> prPrec i 0 (concatD [prt 0 name])
Language.Lang.AbsGrammer.TypeApplication type_1 type_2 -> prPrec i 0 (concatD [prt 0 type_1, prt 0 type_2])
Language.Lang.AbsGrammer.TypeAbstraction type_1 type_2 -> prPrec i 0 (concatD [prt 0 type_1, doc (showString "->"), prt 0 type_2])
Language.Lang.AbsGrammer.TypeImplicit declarations -> prPrec i 0 (concatD [doc (showString "{{"), prt 0 declarations, doc (showString "}}")])
Language.Lang.AbsGrammer.TypeRecord declarations -> prPrec i 0 (concatD [doc (showString "{"), prt 0 declarations, doc (showString "}")])
Language.Lang.AbsGrammer.TypeAlternative declarations -> prPrec i 0 (concatD [doc (showString "["), prt 0 declarations, doc (showString "]")])
Language.Lang.AbsGrammer.TypeParens type_ -> prPrec i 0 (concatD [doc (showString "("), prt 0 type_, doc (showString ")")])
prtList _ [x] = concatD [prt 0 x]
prtList _ (x:xs) = concatD [prt 0 x, doc (showString ","), prt 0 xs]
instance Print Language.Lang.AbsGrammer.Pragma where
prt i e = case e of
Language.Lang.AbsGrammer.Pragma names -> prPrec i 0 (concatD [prt 0 names])
instance Print [Language.Lang.AbsGrammer.Binding] where
prt = prtList
instance Print [Language.Lang.AbsGrammer.Declaration] where
prt = prtList
instance Print [Language.Lang.AbsGrammer.Definition] where
prt = prtList
instance Print [Language.Lang.AbsGrammer.Type] where
prt = prtList
instance Print [Language.Lang.AbsGrammer.Name] where
prt = prtList
instance Print Language.Lang.AbsGrammer.Expression where
prt i e = case e of
Language.Lang.AbsGrammer.ExpressionName name -> prPrec i 0 (concatD [prt 0 name])
Language.Lang.AbsGrammer.ExpressionLiteral numericliteral -> prPrec i 0 (concatD [prt 0 numericliteral])
Language.Lang.AbsGrammer.ExpressionApplication expression1 expression2 -> prPrec i 0 (concatD [prt 0 expression1, prt 0 expression2])
Language.Lang.AbsGrammer.ExpressionAbstraction expression1 expression2 -> prPrec i 0 (concatD [prt 0 expression1, doc (showString "->"), prt 0 expression2])
Language.Lang.AbsGrammer.ExpressionImplicit module_ -> prPrec i 0 (concatD [doc (showString "{{"), prt 0 module_, doc (showString "}}")])
Language.Lang.AbsGrammer.ExpressionRecord module_ -> prPrec i 0 (concatD [doc (showString "{"), prt 0 module_, doc (showString "}")])
Language.Lang.AbsGrammer.ExpressionAlternative module_ -> prPrec i 0 (concatD [doc (showString "["), prt 0 module_, doc (showString "]")])
Language.Lang.AbsGrammer.ExpressionParens expression -> prPrec i 0 (concatD [doc (showString "("), prt 0 expression, doc (showString ")")])