[project @ 2000-06-12 06:01:03 by andy]
[ghc-hetmet.git] / ghc / compiler / javaGen / PrintJava.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
3 %
4 \section{Generate Java}
5
6 \begin{code}
7 module PrintJava( compilationUnit ) where
8
9 import Java
10 import Outputable
11 import Char( toLower )
12 \end{code}
13
14 \begin{code}
15 indent :: SDoc -> SDoc
16 indent = nest 2
17 \end{code}
18   
19 %************************************************************************
20 %*                                                                      *
21 \subsection{Pretty printer}
22 %*                                                                      *
23 %************************************************************************
24
25 \begin{code}
26 compilationUnit :: CompilationUnit -> SDoc
27 compilationUnit (Package n ds) = package n (decls ds)
28
29 package = \n -> \ds ->
30   text "package" <+> packagename n <> text ";"
31   $$
32   ds
33   
34 decls []     = empty
35 decls (d:ds) = decl d $$ decls ds
36     
37 decl = \d ->
38   case d of
39     { Import n -> importDecl (packagename n)
40     ; Field mfs n e -> field (modifiers mfs) (nameTy n) (name n) e  
41     ; Constructor mfs n as ss -> constructor (modifiers mfs) (typename n) (parameters as) (statements ss)
42     ; Method mfs n as ts ss -> method (modifiers mfs) (nameTy n) (name n) (parameters as) (throws ts) (statements ss)
43     ; Comment s -> comment s
44     ; Interface mfs n is ms -> interface (modifiers mfs) (typename n) (extends is) (decls ms)
45     ; Class mfs n x is ms -> clazz (modifiers mfs) (typename n) (extends x) (implements is) (decls ms)
46     }
47
48 importDecl n = text "import" <+> n <> text ";"
49   
50 field = \mfs -> \t -> \n -> \e ->
51   case e of
52     { Nothing -> mfs <+> t <+> n <> text ";" 
53     ; Just e  -> lay [mfs <+> t <+> n <+> text "=", indent (expr e <> text ";")]
54              where
55                 lay | isSimple e = hsep
56                     | otherwise  = sep
57     }
58
59 constructor = \mfs -> \n -> \as -> \ss ->
60   mfs <+> n <+> parens (hsep (punctuate comma as)) <+> text "{"
61   $$ indent ss 
62   $$ text "}"
63
64 method = \mfs -> \t -> \n -> \as -> \ts -> \ss -> 
65   mfs <+> t <+> n <+> parens (hsep (punctuate comma as)) <+> ts <+> text "{" 
66   $$ indent ss 
67   $$ text "}"
68
69 comment = \ss ->
70   text "/**"
71   $$ indent (vcat [ text s | s <- ss])
72   $$ text "**/"
73
74 interface = \mfs -> \n -> \xs -> \ms -> 
75   mfs <+> n <+> xs <+> text "{"
76   $$ indent ms
77   $$ text "}"
78      
79 clazz = \mfs -> \n -> \x -> \is -> \ms ->
80   mfs <+> text "class" <+> n <+> x <+> is <+> text "{" 
81   $$ indent ms 
82   $$ text "}"
83
84 staticblock = \ss ->
85   text "static" <+> text "{"
86   $$ indent ss
87   $$ text "}"
88     
89 modifiers mfs = hsep (map modifier mfs)
90     
91 modifier mf = text $ map toLower (show mf)
92   
93 extends [] = empty
94 extends xs = text "extends" <+> hsep (punctuate comma (map typename xs))
95
96 implements [] = empty
97 implements xs = text "implements" <+> hsep (punctuate comma (map typename xs))
98
99 throws [] = empty
100 throws xs = text "throws" <+> hsep (punctuate comma (map typename xs))
101
102 name (Name n t)   = text n
103
104 nameTy (Name n t) = typ t
105
106 typename n        = text n
107 packagename n     = text n
108
109 parameters as = map parameter as
110
111 parameter (Parameter mfs n) = modifiers mfs <+> nameTy n <+> name n
112
113 typ (PrimType s)  = primtype s
114 typ (Type n)      = typename n
115 typ (ArrayType t) = typ t <> text "[]"
116
117 primtype PrimInt     = text "int"
118 primtype PrimBoolean = text "boolean"
119 primtype PrimChar    = text "char"
120 primtype PrimLong    = text "long"
121 primtype PrimFloat   = text "float"
122 primtype PrimDouble  = text "double"
123 primtype PrimByte    = text "byte"
124 primtype PrimVoid    = text "void"
125
126 statements ss = vcat (map statement ss)
127   
128 statement = \s ->
129   case s of
130     { Skip -> skip
131     ; Return e -> returnStat (expr e)
132     ; Block ss -> vcat [statement s | s <- ss]
133     ; ExprStatement e -> exprStatement (expr e)
134     ; Declaration d -> declStatement (decl d)
135     ; IfThenElse ecs s -> ifthenelse [ (expr e, statement s) | (e,s) <- ecs ] (maybe Nothing (Just .statement) s)
136     ; Switch e as d -> switch (expr e) (arms as) (deflt d)
137     } 
138
139 skip = empty
140   
141 returnStat e = sep [text "return", indent e <> semi]
142
143 exprStatement e = e <> semi
144
145 declStatement d = d
146
147 ifthenelse ((e,s):ecs) ms = sep [ text "if" <+> parens e <+> text "{", 
148                                   indent s, 
149                                   thenelse ecs ms]
150
151 thenelse ((e,s):ecs) ms = sep [ text "} else if" <+> parens e <+> text "{", 
152                                 indent s,
153                                 thenelse ecs ms]
154
155 thenelse [] Nothing  = text "}"
156 thenelse [] (Just s) = sep [text "} else {", indent s, text "}"]
157     
158 switch = \e -> \as -> \d ->
159   text "switch" <+> parens e <+> text "{" 
160   $$ indent (as $$ d)
161   $$ text "}"
162   
163 deflt Nothing   = empty
164 deflt (Just ss) = text "default:" $$ indent (statements ss)  
165     
166 arms [] = empty
167 arms ((e,ss):as) = text "case" <+> expr e <> colon
168                    $$ indent (statements ss)
169                    $$ arms as
170
171 maybeExpr Nothing  = Nothing
172 maybeExpr (Just e) = Just (expr e)
173            
174 expr = \e ->
175  case e of
176    { Var n -> name n
177    ; Literal l -> literal l
178    ; Cast t e -> cast (typ t) e
179    ; Access e n -> expr e <> text "." <> name n
180    ; Assign l r -> assign (expr l) r
181    ; New n es ds -> new (typ n) es (maybeClass ds)
182    ; Raise n es  -> text "raise" <+> text n
183                         <+> parens (hsep (punctuate comma (map expr es)))
184    ; Call e n es -> call (expr e) (name n) es
185    ; Op e1 o e2 -> op e1 o e2
186    ; InstanceOf e t -> expr e <+> text "instanceof" <+> typ t
187    }
188    
189 op = \e1 -> \o -> \e2 ->
190   ( if isSimple e1 
191     then expr e1 
192     else parens (expr e1)
193   ) 
194   <+> 
195   text o
196   <+>
197   ( if isSimple e2
198     then expr e2 
199     else parens (expr e2)
200   )
201   
202 assign = \l -> \r ->
203   if isSimple r
204   then l <+> text "=" <+> (expr r)
205   else l <+> text "=" $$ indent (expr r)
206
207 cast = \t -> \e ->
208   if isSimple e
209   then parens (parens t <> expr e)
210   else parens (parens t $$ indent (expr e))
211
212 new n [] (Just ds) = sep [text "new" <+> n <+> text "()" <+> text "{",
213                              indent ds,
214                              text "}"]
215 new n es Nothing = text "new" <+> n <> parens (hsep (punctuate comma (map expr es)))
216
217       
218 call e n es = e <> dot <> n <> parens (hsep (punctuate comma (map expr es)))
219
220 literal = \l ->
221   case l of
222     { IntLit i    -> text (show i)
223     ; CharLit c   -> text (show c)
224     ; StringLit s -> text ("\"" ++ s ++ "\"")   -- strings are already printable
225     }
226
227 maybeClass Nothing   = Nothing
228 maybeClass (Just ds) = Just (decls ds)
229 \end{code}