[project @ 2000-05-11 07:10:11 by andy]
[ghc-hetmet.git] / ghc / compiler / javaGen / Java.lhs
1 bstract 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 \begin{code}
9 module Java where
10
11 \end{code}
12
13 %************************************************************************
14 %*                                                                      *
15 \subsection{Java type declararations}
16 %*                                                                      *
17 %************************************************************************
18
19 \begin{code}
20 data CompilationUnit
21   = Package Name [Decl]
22     deriving (Show)
23     
24 data Decl
25  = Import [Name]
26  | Field [Modifier] Type Name (Maybe Expr)   
27  | Constructor [Modifier] Name [Parameter] [Statement]
28                                 -- Add Throws (list of Names)
29                                 -- to Method
30  | Method [Modifier] Type Name [Parameter] [Statement]
31  | Comment [String]
32  | Interface [Modifier] Name [Name] [Decl]
33  | Class [Modifier] Name [Name] [Name] [Decl]
34    deriving (Show)
35    
36 data Parameter
37  = Parameter [Modifier] Type Name
38    deriving (Show)
39    
40 data Statement
41   = Skip
42   | Return Expr
43   | Block [Statement]
44   | ExprStatement Expr
45   | Declaration Decl -- variable = inner Field, Class = innerclass
46   | IfThenElse [(Expr,Statement)] (Maybe Statement)
47   | Switch Expr [(Expr, [Statement])] (Maybe [Statement])
48     deriving (Show)
49
50 data Expr 
51   = Var Name
52   | Literal Lit
53   | Cast Type Expr
54   | Access Expr Name
55   | Assign Expr Expr
56   | InstanceOf Expr Type
57   | Call Expr Name [Expr]
58   | Op Expr String Expr
59   | New Type [Expr] (Maybe [Decl]) -- anonymous innerclass
60   | NewArray Type [Expr]
61     deriving (Show)
62     
63 data Modifier 
64   = Public | Protected | Private
65   | Static
66   | Abstract | Final | Native | Synchronized | Transient | Volatile
67   deriving (Show, Eq, Ord)
68   
69 data Type 
70   = PrimType String
71   | ArrayType Type
72   | Type [Name]
73     deriving (Show)
74
75 -- If you want qualified names, use Access <expr> <name> 
76 -- Type's are already qualified.
77 type Name = String
78
79 data Lit
80   = IntLit Int          -- Boxed
81   | UIntLit Int         -- Unboxed
82   | CharLit Char        -- Boxed
83   | UCharLit Char       -- Unboxed
84   | StringLit String
85   deriving Show
86
87 data OType 
88   = ObjectType          -- Object *
89   | UnboxedIntType      -- int
90   | UnboxedCharType     -- char
91
92 data OVar = OVar Name OType
93                         -- Object x.y
94
95 addModifier :: Modifier -> Decl -> Decl
96 addModifier = \m -> \d ->
97  case d of
98    { Import n -> Import n
99    ; Field ms t n e -> Field (m:ms) t n e  
100    ; Constructor ms n as ss -> Constructor (m:ms) n as ss
101    ; Method ms t n as ss -> Method (m:ms) t n as ss
102    ; Comment ss -> Comment ss
103    ; Interface ms n xs ds -> Interface (m:ms) n xs ds
104    ; Class ms n xs is ds -> Class (m:ms) n xs is ds
105    }
106    
107 areSimple :: [Expr] -> Bool
108 areSimple = \es -> all isSimple es
109
110 isSimple :: Expr -> Bool
111 isSimple = \e ->
112   case e of
113    { Cast t e -> isSimple e
114    ; Access e n -> isSimple e
115    ; Assign l r -> isSimple l && isSimple r
116    ; InstanceOf e t -> isSimple e
117    ; Call e n es -> isSimple e && areSimple es
118    ; Op e1 o e2 -> False
119    ; New n es Nothing -> areSimple es
120    ; New n es (Just ds) -> False
121    ; otherwise -> True
122    }
123 \end{code}