module PrintDep where

-- pretty-printer generated by the BNF converter

import AbsDep
import 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 -> showString t . space "," . rend i ts
    t  : ")" :ts -> showString t . showChar ')' . rend i ts
    t  : "]" :ts -> showString t . showChar ']' . 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))

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 :: [a] -> Doc
  prtList = concatD . map (prt 0)

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<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 Ident where
  prt _ (Ident i) = doc (showString i)



instance Print Module where
  prt i e = case e of
   Module imports decls -> prPrec i 0 (concatD [prt 0 imports , prt 0 decls])


instance Print Import where
  prt i e = case e of
   Import id -> prPrec i 0 (concatD [doc (showString "import") , prt 0 id])

  prtList es = case es of
   [] -> (concatD [])
   x:xs -> (concatD [prt 0 x , doc (showString ";") , prt 0 xs])

instance Print Decl where
  prt i e = case e of
   TypeDecl id eexp -> prPrec i 0 (concatD [prt 0 id , doc (showString ":") , prt 0 eexp])
   PattDecl id patterns eexp -> prPrec i 0 (concatD [prt 0 id , prt 0 patterns , doc (showString "=") , prt 0 eexp])

  prtList es = case es of
   [] -> (concatD [])
   x:xs -> (concatD [prt 0 x , doc (showString ";") , prt 0 xs])

instance Print Pattern where
  prt i e = case e of
   PCons id patterns -> prPrec i 0 (concatD [doc (showString "(") , prt 0 id , prt 0 patterns , doc (showString ")")])
   PVar id -> prPrec i 0 (concatD [prt 0 id])
   PType  -> prPrec i 0 (concatD [doc (showString "Type")])
   PWild  -> prPrec i 0 (concatD [doc (showString "_")])

  prtList es = case es of
   [] -> (concatD [])
   x:xs -> (concatD [prt 0 x , prt 0 xs])

instance Print EExp where
  prt i e = case e of
   ELet id eexp0 eexp1 eexp -> prPrec i 0 (concatD [doc (showString "let") , prt 0 id , doc (showString "=") , prt 0 eexp0 , doc (showString ":") , prt 0 eexp1 , doc (showString "in") , prt 0 eexp])
   EAbs id eexp -> prPrec i 2 (concatD [doc (showString "\\") , prt 0 id , doc (showString "->") , prt 0 eexp])
   EPi id eexp0 eexp -> prPrec i 2 (concatD [doc (showString "(") , prt 0 id , doc (showString ":") , prt 0 eexp0 , doc (showString ")") , prt 2 eexp])
   EApp eexp0 eexp -> prPrec i 3 (concatD [prt 3 eexp0 , prt 4 eexp])
   EVar id -> prPrec i 4 (concatD [prt 0 id])
   EType  -> prPrec i 4 (concatD [doc (showString "Type")])
   EMeta  -> prPrec i 4 (concatD [doc (showString "?")])