{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-} module Sit.Print where -- pretty-printer generated by the BNF converter import Sit.Abs 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 ";" :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 = showString t . (\s -> if null s then "" else ' ':s) closingOrPunctuation [c] = c `elem` ")],;." closingOrPunctuation _ = False 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 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 prPrec i 0 (concatD [prt 0 decls]) instance Print Decl where prt i e = case e of Sig id exp -> prPrec i 0 (concatD [prt 0 id, doc (showString ":"), prt 0 exp]) Def id exp -> prPrec i 0 (concatD [prt 0 id, doc (showString "="), prt 0 exp]) Open qualid -> prPrec i 0 (concatD [doc (showString "open"), doc (showString "import"), prt 0 qualid]) Blank -> prPrec i 0 (concatD []) prtList _ [x] = (concatD [prt 0 x]) prtList _ (x:xs) = (concatD [prt 0 x, doc (showString "--;"), prt 0 xs]) instance Print QualId where prt i e = case e of Sg id -> prPrec i 0 (concatD [prt 0 id]) Cons qualid id -> prPrec i 0 (concatD [prt 0 qualid, doc (showString "."), prt 0 id]) instance Print IdU where prt i e = case e of Id id -> prPrec i 0 (concatD [prt 0 id]) Under -> prPrec i 0 (concatD [doc (showString "_")]) prtList _ [x] = (concatD [prt 0 x]) prtList _ (x:xs) = (concatD [prt 0 x, prt 0 xs]) instance Print Bind where prt i e = case e of BIrrel id -> prPrec i 0 (concatD [doc (showString "."), prt 0 id]) BRel id -> prPrec i 0 (concatD [doc (showString ".."), prt 0 id]) BAnn ids exp -> prPrec i 0 (concatD [doc (showString "("), prt 0 ids, doc (showString ":"), prt 0 exp, doc (showString ")")]) prtList _ [x] = (concatD [prt 0 x]) prtList _ (x:xs) = (concatD [prt 0 x, prt 0 xs]) instance Print Exp where prt i e = case e of Var idu -> prPrec i 2 (concatD [prt 0 idu]) Int n -> prPrec i 2 (concatD [prt 0 n]) Infty -> prPrec i 2 (concatD [doc (showString "oo")]) Nat -> prPrec i 2 (concatD [doc (showString "Nat")]) Set -> prPrec i 2 (concatD [doc (showString "Set")]) Set1 -> prPrec i 2 (concatD [doc (showString "Set1")]) Set2 -> prPrec i 2 (concatD [doc (showString "Set2")]) Zero -> prPrec i 2 (concatD [doc (showString "zero")]) Suc -> prPrec i 2 (concatD [doc (showString "suc")]) Fix -> prPrec i 2 (concatD [doc (showString "fix")]) LZero -> prPrec i 2 (concatD [doc (showString "lzero")]) LSuc -> prPrec i 2 (concatD [doc (showString "lsuc")]) Size -> prPrec i 0 (concatD [doc (showString "Size")]) App exp1 exp2 -> prPrec i 1 (concatD [prt 1 exp1, prt 2 exp2]) Lam idus exp -> prPrec i 0 (concatD [doc (showString "\\"), prt 0 idus, doc (showString "->"), prt 0 exp]) Forall binds exp -> prPrec i 0 (concatD [doc (showString "forall"), prt 0 binds, doc (showString "->"), prt 0 exp]) Pi exp1 exp2 exp3 -> prPrec i 0 (concatD [doc (showString "("), prt 0 exp1, doc (showString ":"), prt 0 exp2, doc (showString ")"), doc (showString "->"), prt 0 exp3]) Arrow exp1 exp2 -> prPrec i 0 (concatD [prt 1 exp1, doc (showString "->"), prt 0 exp2]) Case exp1 exp2 exp3 -> prPrec i 0 (concatD [doc (showString "case"), prt 0 exp1, doc (showString "return"), prt 0 exp2, doc (showString "of"), prt 0 exp3]) Plus exp n -> prPrec i 0 (concatD [prt 1 exp, doc (showString "+"), prt 0 n]) ELam exp1 idu exp2 -> prPrec i 0 (concatD [doc (showString "\\"), doc (showString "{"), doc (showString "("), doc (showString "zero"), doc (showString "_"), doc (showString ")"), doc (showString "->"), prt 0 exp1, doc (showString ";"), doc (showString "("), doc (showString "suc"), doc (showString "_"), prt 0 idu, doc (showString ")"), doc (showString "->"), prt 0 exp2, doc (showString "}")])