680814418294bab6d0556887c4b3a2c56b342f2a
[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 Pretty
9 import ExternalCore
10 import Char
11 import Encoding
12
13 instance Show Module where
14   showsPrec _ m = shows (pmodule m)
15
16 instance Show Tdef where
17   showsPrec _ t = shows (ptdef t)
18
19 instance Show Cdef where
20   showsPrec _ c = shows (pcdef c)
21
22 instance Show Vdefg where
23   showsPrec _ v = shows (pvdefg v)
24
25 instance Show Exp where
26   showsPrec _ e = shows (pexp e)
27
28 instance Show Alt where
29   showsPrec _ a = shows (palt a)
30
31 instance Show Ty where
32   showsPrec _ t = shows (pty t)
33
34 instance Show Kind where
35   showsPrec _ k = shows (pkind k)
36
37 instance Show Lit where
38   showsPrec _ l = shows (plit l)
39
40
41 indent :: Doc -> Doc
42 indent = nest 2
43
44 pmodule :: Module -> Doc
45 pmodule (Module mname tdefs vdefgs) =
46   (text "%module" <+> text mname)
47     $$ indent ((vcat (map ((<> char ';') . ptdef) tdefs))
48                $$ (vcat (map ((<> char ';') . pvdefg) vdefgs)))
49
50 ptdef :: Tdef -> Doc
51 ptdef (Data tcon tbinds cdefs) =
52   (text "%data" <+> pqname tcon <+> (hsep (map ptbind tbinds)) <+> char '=')
53   $$ indent (braces ((vcat (punctuate (char ';') (map pcdef cdefs)))))
54
55 ptdef (Newtype tcon tbinds rep ) =
56   text "%newtype" <+> pqname tcon <+> (hsep (map ptbind tbinds)) <+> repclause
57        where repclause = case rep of
58                            Just ty -> char '=' <+> pty ty 
59                            Nothing -> empty
60
61 pcdef :: Cdef -> Doc
62 pcdef (Constr dcon tbinds tys)  =
63   (pname dcon) <+> (sep [hsep (map pattbind tbinds),sep (map paty tys)])
64 pcdef (GadtConstr dcon ty)  =
65   (pname dcon) <+> text "::" <+> pty ty
66
67 pname :: Id -> Doc
68 pname id = text (zEncodeString id)
69
70 pqname :: Qual Id -> Doc
71 pqname ("",id) = pname id
72 pqname (m,id)  = text m <> char '.' <> pname id
73
74 ptbind, pattbind :: Tbind -> Doc
75 ptbind (t,Klifted) = pname t
76 ptbind (t,k) = parens (pname t <> text "::" <> pkind k)
77
78 pattbind (t,k) = char '@' <> ptbind (t,k)
79
80 pakind, pkind :: Kind -> Doc
81 pakind (Klifted) = char '*'
82 pakind (Kunlifted) = char '#'
83 pakind (Kopen) = char '?'
84 pakind k = parens (pkind k)
85
86 pkind (Karrow k1 k2) = parens (pakind k1 <> text "->" <> pkind k2)
87 pkind (Keq t1 t2) = parens (pty t1 <> text ":=:" <> pty t2)
88 pkind k = pakind k
89
90 paty, pbty, pty :: Ty -> Doc
91 paty (Tvar n) = pname n
92 paty (Tcon c) = pqname c
93 paty t = parens (pty t)
94
95 pbty (Tapp(Tapp(Tcon tc) t1) t2) | tc == tcArrow = parens(fsep [pbty t1, text "->",pty t2])
96 pbty (Tapp t1 t2) = pappty t1 [t2] 
97 pbty t = paty t
98
99 pty (Tapp(Tapp(Tcon tc) t1) t2) | tc == tcArrow = fsep [pbty t1, text "->",pty t2]
100 pty (Tforall tb t) = text "%forall" <+> pforall [tb] t
101 pty t = pbty t
102
103 pappty :: Ty -> [Ty] -> Doc
104 pappty (Tapp t1 t2) ts = pappty t1 (t2:ts)
105 pappty t ts = sep (map paty (t:ts))
106
107 pforall :: [Tbind] -> Ty -> Doc
108 pforall tbs (Tforall tb t) = pforall (tbs ++ [tb]) t
109 pforall tbs t = hsep (map ptbind tbs) <+> char '.' <+> pty t
110
111 pvdefg :: Vdefg -> Doc
112 pvdefg (Rec vdefs) = text "%rec" $$ braces (indent (vcat (punctuate (char ';') (map pvdef vdefs))))
113 pvdefg (Nonrec vdef) = pvdef vdef
114
115 pvdef :: Vdef -> Doc
116 pvdef (l,v,t,e) = sep [plocal l <+> pname v <+> text "::" <+> pty t <+> char '=',
117                     indent (pexp e)]
118
119 plocal :: Bool -> Doc
120 plocal True  = text "%local"
121 plocal False = empty
122
123 paexp, pfexp, pexp :: Exp -> Doc
124 paexp (Var x) = pqname x
125 paexp (Dcon x) = pqname x
126 paexp (Lit l) = plit l
127 paexp e = parens(pexp e)
128
129 plamexp :: [Bind] -> Exp -> Doc
130 plamexp bs (Lam b e) = plamexp (bs ++ [b]) e
131 plamexp bs e = sep [sep (map pbind bs) <+> text "->",
132                     indent (pexp e)]
133
134 pbind :: Bind -> Doc
135 pbind (Tb tb) = char '@' <+> ptbind tb
136 pbind (Vb vb) = pvbind vb
137
138 pfexp (App e1 e2) = pappexp e1 [Left e2]
139 pfexp (Appt e t) = pappexp e [Right t]
140 pfexp e = paexp e
141
142 pappexp :: Exp -> [Either Exp Ty] -> Doc
143 pappexp (App e1 e2) as = pappexp e1 (Left e2:as)
144 pappexp (Appt e t) as = pappexp e (Right t:as)
145 pappexp e as = fsep (paexp e : map pa as)
146            where pa (Left e) = paexp e
147                  pa (Right t) = char '@' <+> paty t
148
149 pexp (Lam b e) = char '\\' <+> plamexp [b] e
150 pexp (Let vd e) = (text "%let" <+> pvdefg vd) $$ (text "%in" <+> pexp e)
151 pexp (Case e vb ty alts) = sep [text "%case" <+> parens (paty ty) <+> paexp e,
152                              text "%of" <+> pvbind vb]
153                         $$ (indent (braces (vcat (punctuate (char ';') (map palt alts)))))
154 pexp (Cast e co) = (text "%cast" <+> parens (pexp e)) $$ paty co
155 pexp (Note s e) = (text "%note" <+> pstring s) $$ pexp e
156 pexp (External n cc t) = (text "%external" <+> text cc <+> pstring n) $$ paty t
157 pexp (DynExternal cc t) = (text "%dynexternal" <+> text cc) $$ paty t
158 pexp (Label n) = (text "%label" <+> pstring n)
159 pexp e = pfexp e
160
161 pvbind :: Vbind -> Doc
162 pvbind (x,t) = parens(pname x <> text "::" <> pty t)
163
164 palt :: Alt -> Doc
165 palt (Acon c tbs vbs e) =
166         sep [pqname c, 
167              sep (map pattbind tbs),
168              sep (map pvbind vbs) <+> text "->"]
169         $$ indent (pexp e)
170 palt (Alit l e) = 
171         (plit l <+>  text "->")
172         $$ indent (pexp e)
173 palt (Adefault e) = 
174         (text "%_ ->")
175         $$ indent (pexp e)
176
177 plit :: Lit -> Doc
178 plit (Lint i t) = parens (integer i <> text "::" <> pty t)
179 plit (Lrational r t) = parens (rational r <>  text "::" <> pty t)  -- might be better to print as two integers
180 plit (Lchar c t) = parens (text ("\'" ++ escape [c] ++ "\'") <> text "::" <> pty t)
181 plit (Lstring s t) = parens (pstring s <> text "::" <> pty t)
182
183 pstring :: String -> Doc
184 pstring s = doubleQuotes(text (escape s))
185
186 escape :: String -> String
187 escape s = foldr f [] (map ord s)
188     where 
189      f cv rest
190         | cv > 0xFF = '\\':'x':hs ++ rest
191         | (cv < 0x20 || cv > 0x7e || cv == 0x22 || cv == 0x27 || cv == 0x5c) = 
192          '\\':'x':h1:h0:rest
193            where (q1,r1) = quotRem cv 16
194                  h1 = intToDigit q1
195                  h0 = intToDigit r1
196                  hs = dropWhile (=='0') $ reverse $ mkHex cv
197                  mkHex 0 = ""
198                  mkHex cv = intToDigit r : mkHex q
199                     where (q,r) = quotRem cv 16
200      f cv rest = (chr cv):rest
201
202 \end{code}
203
204
205
206