[project @ 2001-06-01 17:14:07 by apt]
[ghc-hetmet.git] / ghc / compiler / coreSyn / PprExternalCore.lhs
1 %
2 % (c) The University of Glasgow 2001
3 %
4 \begin{code}
5
6 module PprExternalCore where
7
8 import Pretty
9 import ExternalCore
10 import Char
11
12 instance Show Module where
13   showsPrec d m = shows (pmodule m)
14
15 instance Show Tdef where
16   showsPrec d t = shows (ptdef t)
17
18 instance Show Cdef where
19   showsPrec d c = shows (pcdef c)
20
21 instance Show Vdefg where
22   showsPrec d v = shows (pvdefg v)
23
24 instance Show Exp where
25   showsPrec d e = shows (pexp e)
26
27 instance Show Alt where
28   showsPrec d a = shows (palt a)
29
30 instance Show Ty where
31   showsPrec d t = shows (pty t)
32
33 instance Show Kind where
34   showsPrec d k = shows (pkind k)
35
36 instance Show Lit where
37   showsPrec d l = shows (plit l)
38
39
40 indent = nest 2
41
42 pmodule (Module mname {- (texports,dexports,vexports) -}  tdefs vdefs) =
43   (text "%module" <+> text mname)
44 {-  $$ indent (parens (((fsep (map pname texports) <> char ',')
45                         $$ (fsep (map pname dexports) <> char ',')
46                         $$ (fsep (map pname vexports)))) 
47 -}
48     $$ indent ((vcat (map ((<> char ';') . ptdef) tdefs))
49                $$ (vcat (map ((<> char ';') . pgvdef) vdefs)))
50
51 pgvdef (False,vdef) = text "%local" <+> pvdefg vdef
52 pgvdef (True,vdef) = pvdefg vdef
53
54 ptdef (Data tcon tbinds cdefs) =
55   (text "%data" <+> pname tcon <+> (hsep (map ptbind tbinds)) <+> char '=')
56   $$ indent (braces ((vcat (punctuate (char ';') (map pcdef cdefs)))))
57
58 ptdef (Newtype tcon tbinds ty ) =
59   text "%newtype" <+> pname tcon <+> (hsep (map ptbind tbinds)) <+> char '=' <+> pty ty 
60
61 pcdef (Constr dcon tbinds tys)  =
62   (pname dcon) <+> (sep [hsep (map pattbind tbinds),sep (map paty tys)])
63
64 pname id = text id
65
66 pqname ("",id) = pname id
67 pqname (m,id) = pname m <> char '.' <> pname id
68
69 ptbind (t,Klifted) = pname t
70 ptbind (t,k) = parens (pname t <> text "::" <> pkind k)
71
72 pattbind (t,k) = char '@' <> ptbind (t,k)
73
74 pakind (Klifted) = char '*'
75 pakind (Kunlifted) = char '#'
76 pakind (Kopen) = char '?'
77 pakind k = parens (pkind k)
78
79 pkind (Karrow k1 k2) = parens (pakind k1 <> text "->" <> pkind k2)
80 pkind k = pakind k
81
82 paty (Tvar n) = pname n
83 paty (Tcon c) = pqname c
84 paty t = parens (pty t)
85
86 pbty (Tapp(Tapp(Tcon tc) t1) t2) | tc == tcArrow = parens(fsep [pbty t1, text "->",pty t2])
87 pbty (Tapp t1 t2) = pappty t1 [t2] 
88 pbty t = paty t
89
90 pty (Tapp(Tapp(Tcon tc) t1) t2) | tc == tcArrow = fsep [pbty t1, text "->",pty t2]
91 pty (Tforall tb t) = text "%forall" <+> pforall [tb] t
92 pty t = pbty t
93
94 pappty (Tapp t1 t2) ts = pappty t1 (t2:ts)
95 pappty t ts = sep (map paty (t:ts))
96
97 pforall tbs (Tforall tb t) = pforall (tbs ++ [tb]) t
98 pforall tbs t = hsep (map ptbind tbs) <+> char '.' <+> pty t
99
100 pvdefg (Rec vtes) = text "%rec" $$ braces (indent (vcat (punctuate (char ';') (map pvte vtes))))
101 pvdefg (Nonrec vte) = pvte vte
102
103 pvte (v,t,e) = sep [pname v <+> text "::" <+> pty t <+> char '=',
104                     indent (pexp e)]
105
106 paexp (Var x) = pqname x
107 paexp (Dcon x) = pqname x
108 paexp (Lit l) = plit l
109 paexp e = parens(pexp e)
110
111 plamexp bs (Lam b e) = plamexp (bs ++ [b]) e
112 plamexp bs e = sep [sep (map pbind bs) <+> text "->",
113                     indent (pexp e)]
114
115 pbind (Tb tb) = char '@' <+> ptbind tb
116 pbind (Vb vb) = pvbind vb
117
118 pfexp (App e1 e2) = pappexp e1 [Left e2]
119 pfexp (Appt e t) = pappexp e [Right t]
120 pfexp e = paexp e
121
122 pappexp (App e1 e2) as = pappexp e1 (Left e2:as)
123 pappexp (Appt e t) as = pappexp e (Right t:as)
124 pappexp e as = fsep (paexp e : map pa as)
125            where pa (Left e) = paexp e
126                  pa (Right t) = char '@' <+> paty t
127
128 pexp (Lam b e) = char '\\' <+> plamexp [b] e
129 pexp (Let vd e) = (text "%let" <+> pvdefg vd) $$ (text "%in" <+> pexp e)
130 pexp (Case e vb alts) = sep [text "%case" <+> paexp e,
131                              text "%of" <+> pvbind vb]
132                         $$ (indent (braces (vcat (punctuate (char ';') (map palt alts)))))
133 pexp (Coerce t e) = (text "%coerce" <+> paty t) $$ pexp e
134 pexp (Note s e) = (text "%note" <+> pstring s) $$ pexp e
135 pexp (Ccall n t) = (text "%ccall" <+> pstring n) $$ paty t
136 pexp e = pfexp e
137
138
139 pvbind (x,t) = parens(pname x <> text "::" <> pty t)
140
141 palt (Acon c tbs vbs e) =
142         sep [pqname c, 
143              sep (map pattbind tbs),
144              sep (map pvbind vbs) <+> text "->"]
145         $$ indent (pexp e)
146 palt (Alit l e) = 
147         (plit l <+>  text "->")
148         $$ indent (pexp e)
149 palt (Adefault e) = 
150         (text "%_ ->")
151         $$ indent (pexp e)
152
153 plit (Lint i t) = parens (integer i <> text "::" <> pty t)
154 plit (Lrational r t) = parens (rational r <>  text "::" <> pty t)  -- might be better to print as two integers
155 plit (Lchar c t) = parens (text ("\'" ++ escape [c] ++ "\'") <> text "::" <> pty t)
156 plit (Lstring s t) = parens (pstring s <> text "::" <> pty t)
157
158 pstring s = doubleQuotes(text (escape s))
159
160 escape s = foldr f [] (map ord s)
161     where 
162      f cv rest | (cv < 0x20 || cv > 0x7e || cv == 0x22 || cv == 0x27 || cv == 0x5c) = 
163          '\\':'u':h3:h2:h1:h0:rest
164            where (q3,r3) = quotRem cv (16*16*16) 
165                  h3 = toUpper(intToDigit q3)
166                  (q2,r2) = quotRem r3 (16*16)
167                  h2 = toUpper(intToDigit q2)
168                  (q1,r1) = quotRem r2 16
169                  h1 = toUpper(intToDigit q1)
170                  h0 = toUpper(intToDigit r1)
171      f cv rest = (chr cv):rest
172
173 \end{code}
174
175
176
177