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