annotate C-- calls that do not return
[ghc-hetmet.git] / utils / ext-core / Printer.hs
1 module Printer where
2
3 import Pretty
4 import Core
5 import Char
6 import Numeric (fromRat)
7
8 instance Show Module where
9   showsPrec d m = shows (pmodule m)
10
11 instance Show Tdef where
12   showsPrec d t = shows (ptdef t)
13
14 instance Show Cdef where
15   showsPrec d c = shows (pcdef c)
16
17 instance Show Vdefg where
18   showsPrec d v = shows (pvdefg v)
19
20 instance Show Vdef where
21   showsPrec d v = shows (pvdef v)
22
23 instance Show Exp where
24   showsPrec d e = shows (pexp e)
25
26 instance Show Alt where
27   showsPrec d a = shows (palt a)
28
29 instance Show Ty where
30   showsPrec d t = shows (pty t)
31
32 instance Show Kind where
33   showsPrec d k = shows (pkind k)
34
35 instance Show Lit where
36   showsPrec d l = shows (plit l)
37
38
39 indent = nest 2
40
41 pmodule (Module mname tdefs vdefgs) =
42   (text "%module" <+> text mname)
43   $$ indent ((vcat (map ((<> char ';') . ptdef) tdefs))
44              $$ (vcat (map ((<> char ';') . pvdefg) vdefgs)))
45
46 ptdef (Data qtcon tbinds cdefs) =
47   (text "%data" <+> pqname qtcon <+> (hsep (map ptbind tbinds)) <+> char '=')
48   $$ indent (braces ((vcat (punctuate (char ';') (map pcdef cdefs)))))
49
50 ptdef (Newtype qtcon tbinds tyopt ) =
51   text "%newtype" <+> pqname qtcon <+> (hsep (map ptbind tbinds)) <+> 
52         (case tyopt of
53            Just ty -> char '=' <+> pty ty 
54            Nothing -> empty)
55
56 pcdef (Constr qdcon tbinds tys)  =
57   (pqname qdcon) <+> (sep [hsep (map pattbind tbinds),sep (map paty tys)])
58
59 pname id = text id
60
61 pqname ("",id) = pname id
62 pqname (m,id) = pname m <> char '.' <> pname id
63
64 ptbind (t,Klifted) = pname t
65 ptbind (t,k) = parens (pname t <> text "::" <> pkind k)
66
67 pattbind (t,k) = char '@' <> ptbind (t,k)
68
69 pakind (Klifted) = char '*'
70 pakind (Kunlifted) = char '#'
71 pakind (Kopen) = char '?'
72 pakind k = parens (pkind k)
73
74 pkind (Karrow k1 k2) = parens (pakind k1 <> text "->" <> pkind k2)
75 pkind k = pakind k
76
77 paty (Tvar n) = pname n
78 paty (Tcon c) = pqname c
79 paty t = parens (pty t)
80
81 pbty (Tapp(Tapp(Tcon tc) t1) t2) | tc == tcArrow = parens(fsep [pbty t1, text "->",pty t2])
82 pbty (Tapp t1 t2) = pappty t1 [t2] 
83 pbty t = paty t
84
85 pty (Tapp(Tapp(Tcon tc) t1) t2) | tc == tcArrow = fsep [pbty t1, text "->",pty t2]
86 pty (Tforall tb t) = text "%forall" <+> pforall [tb] t
87 pty t = pbty t
88
89 pappty (Tapp t1 t2) ts = pappty t1 (t2:ts)
90 pappty t ts = sep (map paty (t:ts))
91
92 pforall tbs (Tforall tb t) = pforall (tbs ++ [tb]) t
93 pforall tbs t = hsep (map ptbind tbs) <+> char '.' <+> pty t
94
95 pvdefg (Rec vdefs) = text "%rec" $$ braces (indent (vcat (punctuate (char ';') (map pvdef vdefs))))
96 pvdefg (Nonrec vdef) = pvdef vdef
97
98 pvdef (Vdef (qv,t,e)) = sep [pqname qv <+> text "::" <+> pty t <+> char '=',
99                      indent (pexp e)]
100
101 paexp (Var x) = pqname x
102 paexp (Dcon x) = pqname x
103 paexp (Lit l) = plit l
104 paexp e = parens(pexp e)
105
106 plamexp bs (Lam b e) = plamexp (bs ++ [b]) e
107 plamexp bs e = sep [sep (map pbind bs) <+> text "->",
108                     indent (pexp e)]
109
110 pbind (Tb tb) = char '@' <+> ptbind tb
111 pbind (Vb vb) = pvbind vb
112
113 pfexp (App e1 e2) = pappexp e1 [Left e2]
114 pfexp (Appt e t) = pappexp e [Right t]
115 pfexp e = paexp e
116
117 pappexp (App e1 e2) as = pappexp e1 (Left e2:as)
118 pappexp (Appt e t) as = pappexp e (Right t:as)
119 pappexp e as = fsep (paexp e : map pa as)
120            where pa (Left e) = paexp e
121                  pa (Right t) = char '@' <+> paty t
122
123 pexp (Lam b e) = char '\\' <+> plamexp [b] e
124 pexp (Let vd e) = (text "%let" <+> pvdefg vd) $$ (text "%in" <+> pexp e)
125 pexp (Case e vb alts) = sep [text "%case" <+> paexp e,
126                              text "%of" <+> pvbind vb]
127                         $$ (indent (braces (vcat (punctuate (char ';') (map palt alts)))))
128 pexp (Coerce t e) = (text "%coerce" <+> paty t) $$ pexp e
129 pexp (Note s e) = (text "%note" <+> pstring s) $$ pexp e
130 pexp (External n t) = (text "%extcall" <+> pstring n) $$ paty t
131 pexp e = pfexp e
132
133
134 pvbind (x,t) = parens(pname x <> text "::" <> pty t)
135
136 palt (Acon c tbs vbs e) =
137         sep [pqname c, 
138              sep (map pattbind tbs),
139              sep (map pvbind vbs) <+> text "->"]
140         $$ indent (pexp e)
141 palt (Alit l e) = 
142         (plit l <+>  text "->")
143         $$ indent (pexp e)
144 palt (Adefault e) = 
145         (text "%_ ->")
146         $$ indent (pexp e)
147
148 plit (Lint i t) = parens (integer i <> text "::" <> pty t)
149 plit (Lrational r t) = parens (text (show (fromRat r)) <>  text "::" <> pty t)
150 plit (Lchar c t) = parens (text ("\'" ++ escape [c] ++ "\'") <> text "::" <> pty t)
151 plit (Lstring s t) = parens (pstring s <> text "::" <> pty t)
152
153 pstring s = doubleQuotes(text (escape s))
154
155 escape s = foldr f [] (map ord s)
156     where 
157      f cv rest | (cv < 0x20 || cv > 0x7e || cv == 0x22 || cv == 0x27 || cv == 0x5c) = 
158          '\\':'x':h1:h0:rest
159            where (q1,r1) = quotRem cv 16
160                  h1 = intToDigit q1
161                  h0 = intToDigit r1
162      f cv rest = (chr cv):rest
163