Another round of External Core fixes
[ghc-hetmet.git] / compiler / coreSyn / PprExternalCore.lhs
1 %
2 % (c) The University of Glasgow 2001-2006
3 %
4
5 \begin{code}
6 module PprExternalCore () where
7
8 import ExternalCore
9 import Encoding
10
11 import Pretty
12 import Char
13
14
15 instance Show Module where
16   showsPrec _ m = shows (pmodule m)
17
18 instance Show Tdef where
19   showsPrec _ t = shows (ptdef t)
20
21 instance Show Cdef where
22   showsPrec _ c = shows (pcdef c)
23
24 instance Show Vdefg where
25   showsPrec _ v = shows (pvdefg 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
43 indent :: Doc -> Doc
44 indent = nest 2
45
46 pmodule :: Module -> Doc
47 pmodule (Module mname tdefs vdefgs) =
48   (text "%module" <+> text mname)
49     $$ indent ((vcat (map ((<> char ';') . ptdef) tdefs))
50                $$ (vcat (map ((<> char ';') . pvdefg) vdefgs)))
51
52 ptdef :: Tdef -> Doc
53 ptdef (Data tcon tbinds cdefs) =
54   (text "%data" <+> pqname tcon <+> (hsep (map ptbind tbinds)) <+> char '=')
55   $$ indent (braces ((vcat (punctuate (char ';') (map pcdef cdefs)))))
56
57 ptdef (Newtype tcon tbinds (coercion,tbs,k) rep) =
58 -- Here we take apart the newtype tycon in order to get the newtype coercion,
59 -- which needs to be represented in the External Core file because it's not
60 -- straightforward to derive its definition from the newtype declaration alone.
61 -- At the same time, we need the newtype decl to declare the tycon itself.
62 -- Sigh.
63   text "%newtype" <+> pqname tcon <+> (hsep (map ptbind tbinds)) 
64     $$ indent (axiomclause $$ repclause)
65        where  axiomclause = char '^' 
66                  <+> parens (pqname coercion <+> (hsep (map ptbind tbs))
67                               <+> text "::"
68                               <+> pkind k)
69               repclause   = case rep of
70                               Just ty -> char '=' <+> pty ty 
71                               Nothing -> empty
72              
73
74 pcdef :: Cdef -> Doc
75 pcdef (Constr dcon tbinds tys)  =
76   (pqname dcon) <+> (sep [hsep (map pattbind tbinds),sep (map paty tys)])
77 pcdef (GadtConstr dcon ty)  =
78   (pqname dcon) <+> text "::" <+> pty ty
79
80 pname :: Id -> Doc
81 pname id = text (zEncodeString id)
82
83 pqname :: Qual Id -> Doc
84 pqname ("",id) = pname id
85 -- We print out a special character before a qualified name so as to
86 -- disambiguate unqualified names like "m" from qualified names like
87 -- "m:Foo.Bar.y". This makes the ext-core parser easier.
88 pqname (m,id)  = char '^' <> text m <> char '.' <> pname id
89
90 ptbind, pattbind :: Tbind -> Doc
91 ptbind (t,Klifted) = pname t
92 ptbind (t,k) = parens (pname t <> text "::" <> pkind k)
93
94 pattbind (t,k) = char '@' <> ptbind (t,k)
95
96 pakind, pkind :: Kind -> Doc
97 pakind (Klifted) = char '*'
98 pakind (Kunlifted) = char '#'
99 pakind (Kopen) = char '?'
100 pakind k = parens (pkind k)
101
102 pkind (Karrow k1 k2) = parens (pakind k1 <> text "->" <> pkind k2)
103 pkind (Keq t1 t2) = parens (parens (pty t1) <+> text ":=:" <+> 
104                             parens (pty t2))
105 pkind k = pakind k
106
107 paty, pbty, pty :: Ty -> Doc
108 paty (Tvar n) = pname n
109 paty (Tcon c) = pqname c
110 paty t = parens (pty t)
111
112 pbty (Tapp(Tapp(Tcon tc) t1) t2) | tc == tcArrow = parens(fsep [pbty t1, text "->",pty t2])
113 pbty (Tapp t1 t2) = pappty t1 [t2] 
114 pbty t = paty t
115
116 pty (Tapp(Tapp(Tcon tc) t1) t2) | tc == tcArrow = fsep [pbty t1, text "->",pty t2]
117 pty (Tforall tb t) = text "%forall" <+> pforall [tb] t
118 pty t = pbty t
119
120 pappty :: Ty -> [Ty] -> Doc
121 pappty (Tapp t1 t2) ts = pappty t1 (t2:ts)
122 pappty t ts = sep (map paty (t:ts))
123
124 pforall :: [Tbind] -> Ty -> Doc
125 pforall tbs (Tforall tb t) = pforall (tbs ++ [tb]) t
126 pforall tbs t = hsep (map ptbind tbs) <+> char '.' <+> pty t
127
128 pvdefg :: Vdefg -> Doc
129 pvdefg (Rec vdefs) = text "%rec" $$ braces (indent (vcat (punctuate (char ';') (map pvdef vdefs))))
130 pvdefg (Nonrec vdef) = pvdef vdef
131
132 pvdef :: Vdef -> Doc
133 -- TODO: Think about whether %local annotations are actually needed.
134 -- Right now, the local flag is never used, because the Core doc doesn't
135 -- explain the meaning of %local.
136 pvdef (_l,v,t,e) = sep [(pqname v <+> text "::" <+> pty t <+> char '='),
137                     indent (pexp e)]
138
139 paexp, pfexp, pexp :: Exp -> Doc
140 paexp (Var x) = pqname x
141 paexp (Dcon x) = pqname x
142 paexp (Lit l) = plit l
143 paexp e = parens(pexp e)
144
145 plamexp :: [Bind] -> Exp -> Doc
146 plamexp bs (Lam b e) = plamexp (bs ++ [b]) e
147 plamexp bs e = sep [sep (map pbind bs) <+> text "->",
148                     indent (pexp e)]
149
150 pbind :: Bind -> Doc
151 pbind (Tb tb) = char '@' <+> ptbind tb
152 pbind (Vb vb) = pvbind vb
153
154 pfexp (App e1 e2) = pappexp e1 [Left e2]
155 pfexp (Appt e t) = pappexp e [Right t]
156 pfexp e = paexp e
157
158 pappexp :: Exp -> [Either Exp Ty] -> Doc
159 pappexp (App e1 e2) as = pappexp e1 (Left e2:as)
160 pappexp (Appt e t) as = pappexp e (Right t:as)
161 pappexp e as = fsep (paexp e : map pa as)
162            where pa (Left e) = paexp e
163                  pa (Right t) = char '@' <+> paty t
164
165 pexp (Lam b e) = char '\\' <+> plamexp [b] e
166 pexp (Let vd e) = (text "%let" <+> pvdefg vd) $$ (text "%in" <+> pexp e)
167 pexp (Case e vb ty alts) = sep [text "%case" <+> paty ty <+> paexp e,
168                              text "%of" <+> pvbind vb]
169                         $$ (indent (braces (vcat (punctuate (char ';') (map palt alts)))))
170 pexp (Cast e co) = (text "%cast" <+> parens (pexp e)) $$ paty co
171 pexp (Note s e) = (text "%note" <+> pstring s) $$ pexp e
172 pexp (External n cc t) = (text "%external" <+> text cc <+> pstring n) $$ paty t
173 pexp (DynExternal cc t) = (text "%dynexternal" <+> text cc) $$ paty t
174 pexp (Label n) = (text "%label" <+> pstring n)
175 pexp e = pfexp e
176
177 pvbind :: Vbind -> Doc
178 pvbind (x,t) = parens(pname x <> text "::" <> pty t)
179
180 palt :: Alt -> Doc
181 palt (Acon c tbs vbs e) =
182         sep [pqname c, 
183              sep (map pattbind tbs),
184              sep (map pvbind vbs) <+> text "->"]
185         $$ indent (pexp e)
186 palt (Alit l e) = 
187         (plit l <+>  text "->")
188         $$ indent (pexp e)
189 palt (Adefault e) = 
190         (text "%_ ->")
191         $$ indent (pexp e)
192
193 plit :: Lit -> Doc
194 plit (Lint i t) = parens (integer i <> text "::" <> pty t)
195 -- we use (text (show r)) because "(rational r)" was printing out things
196 -- like "2.0e-2" (which isn't External Core)
197 plit (Lrational r t) = parens (text (show r) <>  text "::" <> pty t)
198 plit (Lchar c t) = parens (text ("\'" ++ escape [c] ++ "\'") <> text "::" <> pty t)
199 plit (Lstring s t) = parens (pstring s <> text "::" <> pty t)
200
201 pstring :: String -> Doc
202 pstring s = doubleQuotes(text (escape s))
203
204 escape :: String -> String
205 escape s = foldr f [] (map ord s)
206     where 
207      f cv rest
208         | cv > 0xFF = '\\':'x':hs ++ rest
209         | (cv < 0x20 || cv > 0x7e || cv == 0x22 || cv == 0x27 || cv == 0x5c) = 
210          '\\':'x':h1:h0:rest
211            where (q1,r1) = quotRem cv 16
212                  h1 = intToDigit q1
213                  h0 = intToDigit r1
214                  hs = dropWhile (=='0') $ reverse $ mkHex cv
215                  mkHex 0 = ""
216                  mkHex cv = intToDigit r : mkHex q
217                     where (q,r) = quotRem cv 16
218      f cv rest = (chr cv):rest
219
220 \end{code}
221
222
223
224