1ad2cbcd342757fef4d510ec3413400207645dca
[ghc-hetmet.git] / ghc / 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 Name [Decl]
26     deriving (Show)
27     
28 data Decl
29  = Import PackageName
30  | Field [Modifier] Type Name (Maybe Expr)
31  | Constructor [Modifier] Name [Parameter] [Statement]
32  | Method [Modifier] Type Name [Parameter] [Exception] [Statement]
33  | Comment [String]
34  | Interface [Modifier] Name [TypeName] [Decl]
35  | Class [Modifier] Name [TypeName] [TypeName] [Decl]
36    deriving (Show)
37
38 data Parameter
39  = Parameter [Modifier] Type 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 Type
59   | Literal Lit Type
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   | New Type [Expr] (Maybe [Decl]) -- anonymous innerclass
67     deriving (Show)
68     
69 data Modifier 
70   = Public | Protected | Private
71   | Static
72   | Abstract | Final | Native | Synchronized | Transient | Volatile
73   deriving (Show, Eq, Ord)
74
75 -- A type is used to refer in general to the shape of things,
76 -- or a specific class. Never use a name to refer to a class,
77 -- always use a type.
78
79 data Type 
80   = PrimType  PrimType
81   | ArrayType Type
82   | Type      TypeName
83     deriving (Show)
84
85 data PrimType 
86   = PrimInt 
87   | PrimBoolean
88   | PrimChar
89   | PrimLong
90   | PrimFloat
91   | PrimDouble
92   | PrimByte
93     deriving (Show)
94
95 type PackageName = String       -- A package name
96                                 -- like "java.awt.Button"
97
98 type Exception   = TypeName     -- A class name that must be an exception.
99
100 type TypeName    = String       -- a fully qualified type name
101                                 -- like "java.lang.Object".
102
103 type Name        = String       -- A class name or method etc, 
104                                 -- at defintion time,
105                                 -- this generally not a qualified name.
106
107 data Lit
108   = IntLit Int          -- Boxed
109   | UIntLit Int         -- Unboxed
110   | CharLit Char        -- Boxed
111   | UCharLit Char       -- Unboxed
112   | StringLit String
113   deriving Show
114
115 addModifier :: Modifier -> Decl -> Decl
116 addModifier = \m -> \d ->
117  case d of
118    { Import n -> Import n
119    ; Field ms t n e -> Field (m:ms) t n e  
120    ; Constructor ms n as ss -> Constructor (m:ms) n as ss
121    ; Method ms t n as ts ss -> Method (m:ms) t n as ts ss
122    ; Comment ss -> Comment ss
123    ; Interface ms n xs ds -> Interface (m:ms) n xs ds
124    ; Class ms n xs is ds -> Class (m:ms) n xs is ds
125    }
126    
127 areSimple :: [Expr] -> Bool
128 areSimple = \es -> all isSimple es
129
130 isSimple :: Expr -> Bool
131 isSimple = \e ->
132   case e of
133    { Cast t e -> isSimple e
134    ; Access e n -> isSimple e
135    ; Assign l r -> isSimple l && isSimple r
136    ; InstanceOf e t -> isSimple e
137    ; Call e n es -> isSimple e && areSimple es
138    ; Op e1 o e2 -> False
139    ; New n es Nothing -> areSimple es
140    ; New n es (Just ds) -> False
141    ; otherwise -> True
142    }
143 \end{code}