Revive External Core parser
[ghc-hetmet.git] / utils / ext-core / Printer.hs
1 module Printer where
2
3 import Text.PrettyPrint.HughesPJ
4 import Numeric (fromRat)
5 import Char
6
7 import Core
8 import Encoding
9
10 instance Show Module where
11   showsPrec d m = shows (pmodule m)
12
13 instance Show Tdef where
14   showsPrec d t = shows (ptdef t)
15
16 instance Show Cdef where
17   showsPrec d c = shows (pcdef c)
18
19 instance Show Vdefg where
20   showsPrec d v = shows (pvdefg v)
21
22 instance Show Vdef where
23   showsPrec d v = shows (pvdef v)
24
25 instance Show Exp where
26   showsPrec d e = shows (pexp e)
27
28 instance Show Alt where
29   showsPrec d a = shows (palt a)
30
31 instance Show Ty where
32   showsPrec d t = shows (pty t)
33
34 instance Show Kind where
35   showsPrec d k = shows (pkind k)
36
37 instance Show Lit where
38   showsPrec d l = shows (plit l)
39
40 instance Show CoreLit where
41   showsPrec d l = shows (pclit l)
42
43 indent = nest 2
44
45 -- seems like this is asking for a type class...
46
47 pmodule (Module mname tdefs vdefgs) =
48   (text "%module" <+> panmname mname)
49   $$ indent ((vcat (map ((<> char ';') . ptdef) tdefs))
50              $$ (vcat (map ((<> char ';') . pvdefg) vdefgs)))
51   <> (if ((not.null) tdefs) || ((not.null) vdefgs) then char '\n' else empty)
52          -- add final newline; sigh.
53
54 ptdef (Data qtcon tbinds cdefs) =
55   (text "%data" <+> pqname qtcon <+> (hsep (map ptbind tbinds)) <+> char '=')
56   $$ indent (braces ((vcat (punctuate (char ';') (map pcdef cdefs)))))
57
58 ptdef (Newtype qtcon tbinds (coercion,k) tyopt) =
59   text "%newtype" <+> pqname qtcon <+> (hsep (map ptbind tbinds))
60     $$ indent (axiomclause $$ repclause)
61        where axiomclause = char '^' <+> parens (pqname coercion <+> text "::"
62                                     <+> pkind k)
63              repclause = case tyopt of
64                            Just ty -> char '=' <+> pty ty 
65                            Nothing -> empty
66
67 pcdef (Constr qdcon tbinds tys)  =
68   (pqname qdcon) <+> (sep [hsep (map pattbind tbinds),sep (map paty tys)])
69
70 pname id = text id
71
72 pqname (m,id) = pmname m <> pname id
73
74 -- be sure to print the '.' here so we don't print out
75 -- ".foo" for unqualified foo...
76 pmname Nothing = empty
77 -- Notice that we print the "^" here; this is so that
78 -- "%module foo" doesn't get printed as "%module ^foo"
79 pmname (Just m) = char '^' <> panmname m <> char '.'
80
81 panmname p@(pkgName, parents, name) =
82   let parentStrs = map pname parents in
83          pname pkgName <> char ':' <>
84          -- This is to be sure to not print out:
85          -- main:.Main for when there's a single module name
86          -- with no parents.
87              (case parentStrs of
88                 [] -> empty
89                 _  -> hcat (punctuate hierModuleSeparator 
90                         (map pname parents)) 
91                       <> hierModuleSeparator)
92              <> pname name
93
94 -- note that this is not a '.' but a Z-encoded '.':
95 -- GHCziIOBase.IO, not GHC.IOBase.IO.
96 -- What a pain.
97 hierModuleSeparator = text (zEncodeString ".")
98
99 ptbind (t,Klifted) = pname t
100 ptbind (t,k) = parens (pname t <> text "::" <> pkind k)
101
102 pattbind (t,k) = char '@' <> ptbind (t,k)
103
104 pakind (Klifted) = char '*'
105 pakind (Kunlifted) = char '#'
106 pakind (Kopen) = char '?'
107 pakind k = parens (pkind k)
108
109 pkind (Karrow k1 k2) = parens (pakind k1 <> text "->" <> pkind k2)
110 pkind (Keq t1 t2) = parens (parens (pty t1) <+> text ":=:" <+> parens (pty t2)) 
111 pkind k = pakind k
112
113 paty (Tvar n) = pname n
114 paty (Tcon c) = pqname c
115 paty t = parens (pty t)
116
117 pbty (Tapp(Tapp(Tcon tc) t1) t2) | tc == tcArrow = parens(fsep [pbty t1, text "->",pty t2])
118 pbty (Tapp t1 t2) = pappty t1 [t2] 
119 pbty t = paty t
120
121 pty (Tapp(Tapp(Tcon tc) t1) t2) | tc == tcArrow = fsep [pbty t1, text "->",pty t2]
122 pty (Tforall tb t) = text "%forall" <+> pforall [tb] t
123 pty t = pbty t
124
125 pappty (Tapp t1 t2) ts = pappty t1 (t2:ts)
126 pappty t ts = sep (map paty (t:ts))
127
128 pforall tbs (Tforall tb t) = pforall (tbs ++ [tb]) t
129 pforall tbs t = hsep (map ptbind tbs) <+> char '.' <+> pty t
130
131 pvdefg (Rec vdefs) = text "%rec" $$ braces (indent (vcat (punctuate (char ';') (map pvdef vdefs))))
132 pvdefg (Nonrec vdef) = pvdef vdef
133
134 pvdef (Vdef (qv,t,e)) = sep [pqname qv <+> text "::" <+> pty t <+> char '=',
135                      indent (pexp e)]
136
137 paexp (Var x) = pqname x
138 paexp (Dcon x) = pqname x
139 paexp (Lit l) = plit l
140 paexp e = parens(pexp e)
141
142 plamexp bs (Lam b e) = plamexp (bs ++ [b]) e
143 plamexp bs e = sep [sep (map pbind bs) <+> text "->",
144                     indent (pexp e)]
145
146 pbind (Tb tb) = char '@' <+> ptbind tb
147 pbind (Vb vb) = pvbind vb
148
149 pfexp (App e1 e2) = pappexp e1 [Left e2]
150 pfexp (Appt e t) = pappexp e [Right t]
151 pfexp e = paexp e
152
153 pappexp (App e1 e2) as = pappexp e1 (Left e2:as)
154 pappexp (Appt e t) as = pappexp e (Right t:as)
155 pappexp e as = fsep (paexp e : map pa as)
156            where pa (Left e) = paexp e
157                  pa (Right t) = char '@' <+> paty t
158
159 pexp (Lam b e) = char '\\' <+> plamexp [b] e
160 pexp (Let vd e) = (text "%let" <+> pvdefg vd) $$ (text "%in" <+> pexp e)
161 pexp (Case e vb t alts) = sep [text "%case" <+> paty t <+> paexp e,
162                              text "%of" <+> pvbind vb]
163                         $$ (indent (braces (vcat (punctuate (char ';') (map palt alts)))))
164 pexp (Cast e t) = (text "%cast" <+> parens (pexp e)) $$ paty t
165 pexp (Note s e) = (text "%note" <+> pstring s) $$ pexp e
166 -- TODO: ccall shouldn't really be there
167 pexp (External n t) = (text "%external ccall" <+> pstring n) $$ paty t
168 pexp e = pfexp e
169
170
171 pvbind (x,t) = parens(pname x <> text "::" <> pty t)
172
173 palt (Acon c tbs vbs e) =
174         sep [pqname c, 
175              sep (map pattbind tbs),
176              sep (map pvbind vbs) <+> text "->"]
177         $$ indent (pexp e)
178 palt (Alit l e) = 
179         (plit l <+>  text "->")
180         $$ indent (pexp e)
181 palt (Adefault e) = 
182         (text "%_ ->")
183         $$ indent (pexp e)
184
185 plit (Literal cl t) = parens (pclit cl <> text "::" <> pty t)
186
187 pclit (Lint i) = integer i
188 -- makes sure to print it out as n % d
189 pclit (Lrational r) = text (show r)
190 pclit (Lchar c) = text ("\'" ++ escape [c] ++ "\'")
191 pclit (Lstring s) = pstring s
192
193 pstring s = doubleQuotes(text (escape s))
194
195 escape :: String -> String
196 escape s = foldr f [] (map ord s)
197     where 
198      f cv rest
199         | cv > 0xFF = '\\':'x':hs ++ rest
200         | (cv < 0x20 || cv > 0x7e || cv == 0x22 || cv == 0x27 || cv == 0x5c) = 
201          '\\':'x':h1:h0:rest
202            where (q1,r1) = quotRem cv 16
203                  h1 = intToDigit q1
204                  h0 = intToDigit r1
205                  hs = dropWhile (=='0') $ reverse $ mkHex cv
206                  mkHex 0 = ""
207                  mkHex cv = intToDigit r : mkHex q
208                     where (q,r) = quotRem cv 16
209      f cv rest = (chr cv):rest