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