remove empty dir
[ghc-hetmet.git] / compiler / javaGen / Java.lhs
1 Anbstract syntax for Java subset that is the target of Mondrian.
2 The syntax has been taken from "The Java Language Specification".
3
4 (c) Erik Meijer & Arjan van IJzendoorn
5
6 November 1999
7
8 Major reworking to be usable for the intermeduate (GOO) language
9 for the backend of GHC and to target languauges like Java sucessfully.
10 -- Andy Gill
11
12 \begin{code}
13 module Java where
14
15 \end{code}
16
17 %************************************************************************
18 %*                                                                      *
19 \subsection{Java type declararations}
20 %*                                                                      *
21 %************************************************************************
22
23 \begin{code}
24 data CompilationUnit
25   = Package PackageName [Decl]
26     deriving (Show)
27     
28 data Decl
29  = Import PackageName
30  | Field [Modifier] Name (Maybe Expr)
31  | Constructor [Modifier] TypeName [Parameter] [Statement]
32  | Method [Modifier] Name [Parameter] [Exception] [Statement]
33  | Comment [String]
34  | Interface [Modifier] TypeName [TypeName] [Decl]
35  | Class [Modifier] TypeName [TypeName] [TypeName] [Decl]
36    deriving (Show)
37
38 data Parameter
39  = Parameter [Modifier] Name
40    deriving (Show)
41    
42 data Statement
43   = Skip
44   | Return Expr         -- This always comes last in a list
45                         -- of statements, and it is understood
46                         -- you might change this to something
47                         -- else (like a variable assignment)
48                         -- if this is not top level statements.
49   | Block [Statement]
50   | ExprStatement Expr  -- You are never interested in the result
51                         -- of an ExprStatement
52   | Declaration Decl -- variable = inner Field, Class = innerclass
53   | IfThenElse [(Expr,Statement)] (Maybe Statement)
54   | Switch Expr [(Expr, [Statement])] (Maybe [Statement])
55     deriving (Show)
56
57 data Expr 
58   = Var Name
59   | Literal Lit
60   | Cast Type Expr
61   | Access Expr Name
62   | Assign Expr Expr
63   | InstanceOf Expr Type
64   | Call Expr Name [Expr]
65   | Op Expr String Expr
66   | Raise TypeName [Expr]
67   | New Type [Expr] (Maybe [Decl]) -- anonymous innerclass
68     deriving (Show)
69     
70 data Modifier 
71   = Public | Protected | Private
72   | Static
73   | Abstract | Final | Native | Synchronized | Transient | Volatile
74   deriving (Show, Eq, Ord)
75
76 -- A type is used to refer in general to the shape of things,
77 -- or a specific class. Never use a name to refer to a class,
78 -- always use a type.
79
80 data Type 
81   = PrimType  PrimType
82   | ArrayType Type
83   | Type      TypeName
84     deriving (Show, Eq)
85
86 data PrimType 
87   = PrimInt 
88   | PrimBoolean
89   | PrimChar
90   | PrimLong
91   | PrimFloat
92   | PrimDouble
93   | PrimByte
94   | PrimVoid
95     deriving (Show, Eq)
96
97 type PackageName = String       -- A package name
98                                 -- like "java.awt.Button"
99
100 type Exception   = TypeName     -- A class name that must be an exception.
101
102 type TypeName    = String       -- a fully qualified type name
103                                 -- like "java.lang.Object".
104                                 -- has type "Type <the name>"
105
106 data Name        = Name String Type
107         deriving Show           -- A class name or method etc, 
108                                 -- at defintion time,
109                                 -- this generally not a qualified name.
110
111                                 -- The type is shape of the box require
112                                 -- to store an access to this thing.
113                                 -- So variables might be Int or Object.
114
115                                 --  ** method calls store the returned
116                                 --  ** type, not a complete arg x result type.
117                                 --
118                                 -- Thinking:
119                                 -- ... foo1.foo2(...).foo3 ...
120                                 -- here you want to know the *result*
121                                 -- after calling foo1, then foo2,
122                                 -- then foo3.
123
124 instance Eq Name where
125    (Name nm _) == (Name nm' _) = nm == nm'
126
127
128 instance Ord Name where
129    (Name nm _) `compare` (Name nm' _) = nm `compare` nm'
130
131
132 data Lit
133   = IntLit Integer      -- unboxed
134   | CharLit Int         -- unboxed
135   | StringLit String    -- java string
136   deriving Show
137
138 addModifier :: Modifier -> Decl -> Decl
139 addModifier = \m -> \d ->
140  case d of
141    { Import n -> Import n
142    ; Field ms n e -> Field (m:ms) n e  
143    ; Constructor ms n as ss -> Constructor (m:ms) n as ss
144    ; Method ms n as ts ss -> Method (m:ms) n as ts ss
145    ; Comment ss -> Comment ss
146    ; Interface ms n xs ds -> Interface (m:ms) n xs ds
147    ; Class ms n xs is ds -> Class (m:ms) n xs is ds
148    }
149
150 changeNameType :: Type -> Name -> Name
151 changeNameType ty (Name n _) = Name n ty
152    
153 areSimple :: [Expr] -> Bool
154 areSimple = \es -> all isSimple es
155
156 isSimple :: Expr -> Bool
157 isSimple = \e ->
158   case e of
159    { Cast t e -> isSimple e
160    ; Access e n -> isSimple e
161    ; Assign l r -> isSimple l && isSimple r
162    ; InstanceOf e t -> isSimple e
163    ; Call e n es -> isSimple e && areSimple es
164    ; Op e1 o e2 -> False
165    ; New n es Nothing -> areSimple es
166    ; New n es (Just ds) -> False
167    ; otherwise -> True
168    }
169 \end{code}