2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
4 \section{Generate Java}
8 -- The above warning supression flag is a temporary kludge.
9 -- While working on this module you are encouraged to remove it and fix
10 -- any warnings in the module. See
11 -- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
14 module PrintJava( compilationUnit ) where
18 import Char( toLower )
22 indent :: SDoc -> SDoc
26 %************************************************************************
28 \subsection{Pretty printer}
30 %************************************************************************
33 compilationUnit :: CompilationUnit -> SDoc
34 compilationUnit (Package n ds) = package n (decls ds)
36 package = \n -> \ds ->
37 text "package" <+> packagename n <> text ";"
42 decls (d:ds) = decl d $$ decls ds
46 { Import n -> importDecl (packagename n)
47 ; Field mfs n e -> field (modifiers mfs) (nameTy n) (name n) e
48 ; Constructor mfs n as ss -> constructor (modifiers mfs) (typename n) (parameters as) (statements ss)
49 ; Method mfs n as ts ss -> method (modifiers mfs) (nameTy n) (name n) (parameters as) (throws ts) (statements ss)
50 ; Comment s -> comment s
51 ; Interface mfs n is ms -> interface (modifiers mfs) (typename n) (extends is) (decls ms)
52 ; Class mfs n x is ms -> clazz (modifiers mfs) (typename n) (extends x) (implements is) (decls ms)
55 importDecl n = text "import" <+> n <> text ";"
57 field = \mfs -> \t -> \n -> \e ->
59 { Nothing -> mfs <+> t <+> n <> text ";"
60 ; Just e -> lay [mfs <+> t <+> n <+> text "=", indent (expr e <> text ";")]
62 lay | isSimple e = hsep
66 constructor = \mfs -> \n -> \as -> \ss ->
67 mfs <+> n <+> parens (hsep (punctuate comma as)) <+> text "{"
71 method = \mfs -> \t -> \n -> \as -> \ts -> \ss ->
72 mfs <+> t <+> n <+> parens (hsep (punctuate comma as)) <+> ts <+> text "{"
78 $$ indent (vcat [ text s | s <- ss])
81 interface = \mfs -> \n -> \xs -> \ms ->
82 mfs <+> n <+> xs <+> text "{"
86 clazz = \mfs -> \n -> \x -> \is -> \ms ->
87 mfs <+> text "class" <+> n <+> x <+> is <+> text "{"
91 modifiers mfs = hsep (map modifier mfs)
93 modifier mf = text $ map toLower (show mf)
96 extends xs = text "extends" <+> hsep (punctuate comma (map typename xs))
99 implements xs = text "implements" <+> hsep (punctuate comma (map typename xs))
102 throws xs = text "throws" <+> hsep (punctuate comma (map typename xs))
104 name (Name n t) = text n
106 nameTy (Name n t) = typ t
109 packagename n = text n
111 parameters as = map parameter as
113 parameter (Parameter mfs n) = modifiers mfs <+> nameTy n <+> name n
115 typ (PrimType s) = primtype s
116 typ (Type n) = typename n
117 typ (ArrayType t) = typ t <> text "[]"
119 primtype PrimInt = text "int"
120 primtype PrimBoolean = text "boolean"
121 primtype PrimChar = text "char"
122 primtype PrimLong = text "long"
123 primtype PrimFloat = text "float"
124 primtype PrimDouble = text "double"
125 primtype PrimByte = text "byte"
126 primtype PrimVoid = text "void"
128 statements ss = vcat (map statement ss)
133 ; Return e -> returnStat (expr e)
134 ; Block ss -> vcat [statement s | s <- ss]
135 ; ExprStatement e -> exprStatement (expr e)
136 ; Declaration d -> declStatement (decl d)
137 ; IfThenElse ecs s -> ifthenelse [ (expr e, statement s) | (e,s) <- ecs ] (maybe Nothing (Just .statement) s)
138 ; Switch e as d -> switch (expr e) (arms as) (deflt d)
143 returnStat e = sep [text "return", indent e <> semi]
145 exprStatement e = e <> semi
149 ifthenelse ((e,s):ecs) ms = sep [ text "if" <+> parens e <+> text "{",
153 thenelse ((e,s):ecs) ms = sep [ text "} else if" <+> parens e <+> text "{",
157 thenelse [] Nothing = text "}"
158 thenelse [] (Just s) = sep [text "} else {", indent s, text "}"]
160 switch = \e -> \as -> \d ->
161 text "switch" <+> parens e <+> text "{"
165 deflt Nothing = empty
166 deflt (Just ss) = text "default:" $$ indent (statements ss)
169 arms ((e,ss):as) = text "case" <+> expr e <> colon
170 $$ indent (statements ss)
173 maybeExpr Nothing = Nothing
174 maybeExpr (Just e) = Just (expr e)
179 ; Literal l -> literal l
180 ; Cast t e -> cast (typ t) e
181 ; Access e n -> expr e <> text "." <> name n
182 ; Assign l r -> assign (expr l) r
183 ; New n es ds -> new (typ n) es (maybeClass ds)
184 ; Raise n es -> text "raise" <+> text n
185 <+> parens (hsep (punctuate comma (map expr es)))
186 ; Call e n es -> call (expr e) (name n) es
187 ; Op e1 o e2 -> op e1 o e2
188 ; InstanceOf e t -> expr e <+> text "instanceof" <+> typ t
191 op = \e1 -> \o -> \e2 ->
194 else parens (expr e1)
201 else parens (expr e2)
206 then l <+> text "=" <+> (expr r)
207 else l <+> text "=" $$ indent (expr r)
211 then parens (parens t <> expr e)
212 else parens (parens t $$ indent (expr e))
214 new n [] (Just ds) = sep [text "new" <+> n <+> text "()" <+> text "{",
217 new n es Nothing = text "new" <+> n <> parens (hsep (punctuate comma (map expr es)))
220 call e n es = e <> dot <> n <> parens (hsep (punctuate comma (map expr es)))
224 { IntLit i -> text (show i)
225 ; CharLit c -> text "(char)" <+> text (show c)
226 ; StringLit s -> text ("\"" ++ s ++ "\"") -- strings are already printable
229 maybeClass Nothing = Nothing
230 maybeClass (Just ds) = Just (decls ds)