2 % (c) The University of Glasgow 2001
6 module PprExternalCore () where
11 import Encoding ( zEncodeString )
13 instance Show Module where
14 showsPrec d m = shows (pmodule m)
16 instance Show Tdef where
17 showsPrec d t = shows (ptdef t)
19 instance Show Cdef where
20 showsPrec d c = shows (pcdef c)
22 instance Show Vdefg where
23 showsPrec d v = shows (pvdefg v)
25 instance Show Exp where
26 showsPrec d e = shows (pexp e)
28 instance Show Alt where
29 showsPrec d a = shows (palt a)
31 instance Show Ty where
32 showsPrec d t = shows (pty t)
34 instance Show Kind where
35 showsPrec d k = shows (pkind k)
37 instance Show Lit where
38 showsPrec d l = shows (plit l)
43 pmodule (Module mname tdefs vdefgs) =
44 (text "%module" <+> text (zEncodeString mname))
45 $$ indent ((vcat (map ((<> char ';') . ptdef) tdefs))
46 $$ (vcat (map ((<> char ';') . pvdefg) vdefgs)))
48 ptdef (Data tcon tbinds cdefs) =
49 (text "%data" <+> pqname tcon <+> (hsep (map ptbind tbinds)) <+> char '=')
50 $$ indent (braces ((vcat (punctuate (char ';') (map pcdef cdefs)))))
52 ptdef (Newtype tcon tbinds rep ) =
53 text "%newtype" <+> pqname tcon <+> (hsep (map ptbind tbinds)) <+> repclause
54 where repclause = case rep of
55 Just ty -> char '=' <+> pty ty
58 pcdef (Constr dcon tbinds tys) =
59 (pname dcon) <+> (sep [hsep (map pattbind tbinds),sep (map paty tys)])
60 pcdef (GadtConstr dcon ty) =
61 (pname dcon) <+> text "::" <+> pty ty
63 pname id = text (zEncodeString id)
65 pqname ("",id) = pname id
66 pqname (m,id) = pname m <> char '.' <> pname id
68 ptbind (t,Klifted) = pname t
69 ptbind (t,k) = parens (pname t <> text "::" <> pkind k)
71 pattbind (t,k) = char '@' <> ptbind (t,k)
73 pakind (Klifted) = char '*'
74 pakind (Kunlifted) = char '#'
75 pakind (Kopen) = char '?'
76 pakind k = parens (pkind k)
78 pkind (Karrow k1 k2) = parens (pakind k1 <> text "->" <> pkind k2)
81 paty (Tvar n) = pname n
82 paty (Tcon c) = pqname c
83 paty t = parens (pty t)
85 pbty (Tapp(Tapp(Tcon tc) t1) t2) | tc == tcArrow = parens(fsep [pbty t1, text "->",pty t2])
86 pbty (Tapp t1 t2) = pappty t1 [t2]
89 pty (Tapp(Tapp(Tcon tc) t1) t2) | tc == tcArrow = fsep [pbty t1, text "->",pty t2]
90 pty (Tforall tb t) = text "%forall" <+> pforall [tb] t
93 pappty (Tapp t1 t2) ts = pappty t1 (t2:ts)
94 pappty t ts = sep (map paty (t:ts))
96 pforall tbs (Tforall tb t) = pforall (tbs ++ [tb]) t
97 pforall tbs t = hsep (map ptbind tbs) <+> char '.' <+> pty t
99 pvdefg (Rec vdefs) = text "%rec" $$ braces (indent (vcat (punctuate (char ';') (map pvdef vdefs))))
100 pvdefg (Nonrec vdef) = pvdef vdef
102 pvdef (l,v,t,e) = sep [plocal l <+> pname v <+> text "::" <+> pty t <+> char '=',
105 plocal True = text "%local"
108 paexp (Var x) = pqname x
109 paexp (Dcon x) = pqname x
110 paexp (Lit l) = plit l
111 paexp e = parens(pexp e)
113 plamexp bs (Lam b e) = plamexp (bs ++ [b]) e
114 plamexp bs e = sep [sep (map pbind bs) <+> text "->",
117 pbind (Tb tb) = char '@' <+> ptbind tb
118 pbind (Vb vb) = pvbind vb
120 pfexp (App e1 e2) = pappexp e1 [Left e2]
121 pfexp (Appt e t) = pappexp e [Right t]
124 pappexp (App e1 e2) as = pappexp e1 (Left e2:as)
125 pappexp (Appt e t) as = pappexp e (Right t:as)
126 pappexp e as = fsep (paexp e : map pa as)
127 where pa (Left e) = paexp e
128 pa (Right t) = char '@' <+> paty t
130 pexp (Lam b e) = char '\\' <+> plamexp [b] e
131 pexp (Let vd e) = (text "%let" <+> pvdefg vd) $$ (text "%in" <+> pexp e)
132 pexp (Case e vb ty alts) = sep [text "%case" <+> parens (paty ty) <+> paexp e,
133 text "%of" <+> pvbind vb]
134 $$ (indent (braces (vcat (punctuate (char ';') (map palt alts)))))
135 pexp (Coerce t e) = (text "%coerce" <+> paty t) $$ pexp e
136 pexp (Note s e) = (text "%note" <+> pstring s) $$ pexp e
137 pexp (External n t) = (text "%external" <+> pstring n) $$ paty t
141 pvbind (x,t) = parens(pname x <> text "::" <> pty t)
143 palt (Acon c tbs vbs e) =
145 sep (map pattbind tbs),
146 sep (map pvbind vbs) <+> text "->"]
149 (plit l <+> text "->")
155 plit (Lint i t) = parens (integer i <> text "::" <> pty t)
156 plit (Lrational r t) = parens (rational r <> text "::" <> pty t) -- might be better to print as two integers
157 plit (Lchar c t) = parens (text ("\'" ++ escape [c] ++ "\'") <> text "::" <> pty t)
158 plit (Lstring s t) = parens (pstring s <> text "::" <> pty t)
160 pstring s = doubleQuotes(text (escape s))
162 escape s = foldr f [] (map ord s)
165 | cv > 0xFF = '\\':'x':hs ++ rest
166 | (cv < 0x20 || cv > 0x7e || cv == 0x22 || cv == 0x27 || cv == 0x5c) =
168 where (q1,r1) = quotRem cv 16
171 hs = dropWhile (=='0') $ reverse $ mkHex cv
173 mkHex cv = intToDigit r : mkHex q
174 where (q,r) = quotRem cv 16
175 f cv rest = (chr cv):rest