X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=utils%2Fext-core%2FPrinter.hs;h=2649a0015a92ee5983267f40974761e438458529;hp=ded48aadc201cd7cf4c5e5b2ff4b24aa20875bfb;hb=10704b34c1928dde3d0ef33fe37c3eb7b948975f;hpb=0065d5ab628975892cea1ec7303f968c3338cbe1 diff --git a/utils/ext-core/Printer.hs b/utils/ext-core/Printer.hs index ded48aa..2649a00 100644 --- a/utils/ext-core/Printer.hs +++ b/utils/ext-core/Printer.hs @@ -1,65 +1,111 @@ +{-# OPTIONS -Werror -Wall -fno-warn-missing-signatures #-} + module Printer where -import Pretty -import Core +import Text.PrettyPrint.HughesPJ import Char -import Numeric (fromRat) + +import Core +import Encoding +import PrimCoercions instance Show Module where - showsPrec d m = shows (pmodule m) + showsPrec _ m = shows (pmodule m) instance Show Tdef where - showsPrec d t = shows (ptdef t) + showsPrec _ t = shows (ptdef t) instance Show Cdef where - showsPrec d c = shows (pcdef c) + showsPrec _ c = shows (pcdef c) instance Show Vdefg where - showsPrec d v = shows (pvdefg v) + showsPrec _ v = shows (pvdefg v) instance Show Vdef where - showsPrec d v = shows (pvdef v) + showsPrec _ v = shows (pvdef v) instance Show Exp where - showsPrec d e = shows (pexp e) + showsPrec _ e = shows (pexp e) instance Show Alt where - showsPrec d a = shows (palt a) + showsPrec _ a = shows (palt a) instance Show Ty where - showsPrec d t = shows (pty t) + showsPrec _ t = shows (pty t) instance Show Kind where - showsPrec d k = shows (pkind k) + showsPrec _ k = shows (pkind k) instance Show Lit where - showsPrec d l = shows (plit l) + showsPrec _ l = shows (plit l) + +instance Show CoreLit where + showsPrec _ l = shows (pclit l) + +instance Show KindOrCoercion where + showsPrec _ (Kind k) = shows (text " pkind k <> text ">") + showsPrec _ (Coercion (DefinedCoercion tbs (t1,t2))) = + shows (text " hsep (map ptbind tbs) <+> + parens (pkind (Keq t1 t2)) <> text ">") +instance Show AnMname where + showsPrec _ mn = shows (panmname mn) indent = nest 2 +-- seems like this is asking for a type class... + pmodule (Module mname tdefs vdefgs) = - (text "%module" <+> text mname) + (text "%module" <+> panmname mname) $$ indent ((vcat (map ((<> char ';') . ptdef) tdefs)) $$ (vcat (map ((<> char ';') . pvdefg) vdefgs))) + <> (if ((not.null) tdefs) || ((not.null) vdefgs) then char '\n' else empty) + -- add final newline; sigh. ptdef (Data qtcon tbinds cdefs) = (text "%data" <+> pqname qtcon <+> (hsep (map ptbind tbinds)) <+> char '=') $$ indent (braces ((vcat (punctuate (char ';') (map pcdef cdefs))))) -ptdef (Newtype qtcon tbinds tyopt ) = - text "%newtype" <+> pqname qtcon <+> (hsep (map ptbind tbinds)) <+> - (case tyopt of - Just ty -> char '=' <+> pty ty - Nothing -> empty) +ptdef (Newtype qtcon tbinds (coercion,cTbs,k) tyopt) = + text "%newtype" <+> pqname qtcon <+> (hsep (map ptbind tbinds)) + $$ indent (axiomclause $$ repclause) + where axiomclause = char '^' <+> parens (pqname coercion <+> + (hsep (map ptbind cTbs)) <+> + text "::" + <+> peqkind k) + repclause = case tyopt of + Just ty -> char '=' <+> pty ty + Nothing -> empty pcdef (Constr qdcon tbinds tys) = (pqname qdcon) <+> (sep [hsep (map pattbind tbinds),sep (map paty tys)]) -pname id = text id - -pqname ("",id) = pname id -pqname (m,id) = pname m <> char '.' <> pname id +pname = text + +pqname (m,v) = pmname m <> pname v + +-- be sure to print the '.' here so we don't print out +-- ".foo" for unqualified foo... +pmname Nothing = empty +pmname (Just m) = panmname m <> char '.' + +panmname (M (pkgName, parents, name)) = + let parentStrs = map pname parents in + pname pkgName <> char ':' <> + -- This is to be sure to not print out: + -- main:.Main for when there's a single module name + -- with no parents. + (case parentStrs of + [] -> empty + _ -> hcat (punctuate hierModuleSeparator + (map pname parents)) + <> hierModuleSeparator) + <> pname name + +-- note that this is not a '.' but a Z-encoded '.': +-- GHCziIOBase.IO, not GHC.IOBase.IO. +-- What a pain. +hierModuleSeparator = text (zEncodeString ".") ptbind (t,Klifted) = pname t ptbind (t,k) = parens (pname t <> text "::" <> pkind k) @@ -72,8 +118,11 @@ pakind (Kopen) = char '?' pakind k = parens (pkind k) pkind (Karrow k1 k2) = parens (pakind k1 <> text "->" <> pkind k2) +pkind (Keq from to) = peqkind (from,to) pkind k = pakind k +peqkind (t1, t2) = parens (parens (pty t1) <+> text ":=:" <+> parens (pty t2)) + paty (Tvar n) = pname n paty (Tcon c) = pqname c paty t = parens (pty t) @@ -84,6 +133,18 @@ pbty t = paty t pty (Tapp(Tapp(Tcon tc) t1) t2) | tc == tcArrow = fsep [pbty t1, text "->",pty t2] pty (Tforall tb t) = text "%forall" <+> pforall [tb] t +pty (TransCoercion t1 t2) = + (sep ([pqname transCoercion, paty t1, paty t2])) +pty (SymCoercion t) = + (sep [pqname symCoercion, paty t]) +pty (UnsafeCoercion t1 t2) = + (sep [pqname unsafeCoercion, paty t1, paty t2]) +pty (LeftCoercion t) = + (pqname leftCoercion <+> paty t) +pty (RightCoercion t) = + (pqname rightCoercion <+> paty t) +pty (InstCoercion t1 t2) = + (sep [pqname instCoercion, paty t1, paty t2]) pty t = pbty t pappty (Tapp t1 t2) ts = pappty t1 (t2:ts) @@ -117,17 +178,18 @@ pfexp e = paexp e pappexp (App e1 e2) as = pappexp e1 (Left e2:as) pappexp (Appt e t) as = pappexp e (Right t:as) pappexp e as = fsep (paexp e : map pa as) - where pa (Left e) = paexp e + where pa (Left ex) = paexp ex pa (Right t) = char '@' <+> paty t pexp (Lam b e) = char '\\' <+> plamexp [b] e pexp (Let vd e) = (text "%let" <+> pvdefg vd) $$ (text "%in" <+> pexp e) -pexp (Case e vb alts) = sep [text "%case" <+> paexp e, +pexp (Case e vb t alts) = sep [text "%case" <+> paty t <+> paexp e, text "%of" <+> pvbind vb] $$ (indent (braces (vcat (punctuate (char ';') (map palt alts))))) -pexp (Coerce t e) = (text "%coerce" <+> paty t) $$ pexp e +pexp (Cast e t) = (text "%cast" <+> parens (pexp e)) $$ paty t pexp (Note s e) = (text "%note" <+> pstring s) $$ pexp e -pexp (External n t) = (text "%extcall" <+> pstring n) $$ paty t +-- TODO: ccall shouldn't really be there +pexp (External n t) = (text "%external ccall" <+> pstring n) $$ paty t pexp e = pfexp e @@ -145,19 +207,28 @@ palt (Adefault e) = (text "%_ ->") $$ indent (pexp e) -plit (Lint i t) = parens (integer i <> text "::" <> pty t) -plit (Lrational r t) = parens (text (show (fromRat r)) <> text "::" <> pty t) -plit (Lchar c t) = parens (text ("\'" ++ escape [c] ++ "\'") <> text "::" <> pty t) -plit (Lstring s t) = parens (pstring s <> text "::" <> pty t) +plit (Literal cl t) = parens (pclit cl <> text "::" <> pty t) + +pclit (Lint i) = integer i +-- makes sure to print it out as n % d +pclit (Lrational r) = text (show r) +pclit (Lchar c) = text ("\'" ++ escape [c] ++ "\'") +pclit (Lstring s) = pstring s pstring s = doubleQuotes(text (escape s)) +escape :: String -> String escape s = foldr f [] (map ord s) where - f cv rest | (cv < 0x20 || cv > 0x7e || cv == 0x22 || cv == 0x27 || cv == 0x5c) = + f cv rest + | cv > 0xFF = '\\':'x':hs ++ rest + | (cv < 0x20 || cv > 0x7e || cv == 0x22 || cv == 0x27 || cv == 0x5c) = '\\':'x':h1:h0:rest where (q1,r1) = quotRem cv 16 h1 = intToDigit q1 h0 = intToDigit r1 + hs = dropWhile (=='0') $ reverse $ mkHex cv + mkHex 0 = "" + mkHex num = intToDigit r : mkHex q + where (q,r) = quotRem num 16 f cv rest = (chr cv):rest -