summaryrefslogtreecommitdiff
path: root/ghc/compiler/javaGen/Java.lhs
blob: 5de371b6189347fb50101148a1ac5774dfb29afe (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
Abstract syntax for Java subset that is the target of Mondrian.
The syntax has been taken from "The Java Language Specification".

(c) Erik Meijer & Arjan van IJzendoorn

November 1999

\begin{code}
module Java where

\end{code}

%************************************************************************
%*									*
\subsection{Java type declararations}
%*									*
%************************************************************************

\begin{code}
data CompilationUnit
  = Package Name [Decl]
    deriving (Show)
    
data Decl
 = Import Name
 | Field [Modifier] Type Name (Maybe Expr)   
 | Constructor [Modifier] Name [Parameter] [Statement]
 | Method [Modifier] Type Name [Parameter] [Statement]
 | Comment [String]
 | Interface [Modifier] Name [Name] [Decl]
 | Class [Modifier] Name [Name] [Name] [Decl]
   deriving (Show)
   
data Parameter
 = Parameter [Modifier] Type Name
   deriving (Show)
   
data Statement
  = Skip
  | Return Expr
  | Block [Statement]
  | ExprStatement Expr
  | Declaration Decl -- variable = inner Field, Class = innerclass
  | IfThenElse [(Expr,Statement)] (Maybe Statement)
  | Switch Expr [(Expr, [Statement])] (Maybe [Statement])
    deriving (Show)

data Expr 
  = Var Name
  | Literal Lit
  | Cast Type Expr
  | Access Expr Name
  | Assign Expr Expr
  | InstanceOf Expr Type
  | Call Expr Name [Expr]
  | Op Expr String Expr
  | New Name [Expr] (Maybe [Decl]) -- anonymous innerclass
  | NewArray Name [Expr]
    deriving (Show)
    
data Type 
  = Type Name
  | Array Type
    deriving (Show)
    
data Modifier 
  = Public | Protected | Private
  | Static
  | Abstract | Final | Native | Synchronized | Transient | Volatile
  deriving (Show, Eq, Ord)
  
type Name = [String]

data Lit
  = IntLit Int		-- Boxed
  | UIntLit Int		-- Unboxed
  | CharLit Char	-- Boxed
  | UCharLit Char	-- Unboxed
  | StringLit String
  deriving Show

addModifier :: Modifier -> Decl -> Decl
addModifier = \m -> \d ->
 case d of
   { Import n -> Import n
   ; Field ms t n e -> Field (m:ms) t n e  
   ; Constructor ms n as ss -> Constructor (m:ms) n as ss
   ; Method ms t n as ss -> Method (m:ms) t n as ss
   ; Comment ss -> Comment ss
   ; Interface ms n xs ds -> Interface (m:ms) n xs ds
   ; Class ms n xs is ds -> Class (m:ms) n xs is ds
   }
   
areSimple :: [Expr] -> Bool
areSimple = \es -> all isSimple es

isSimple :: Expr -> Bool
isSimple = \e ->
  case e of
   { Cast t e -> isSimple e
   ; Access e n -> isSimple e
   ; Assign l r -> isSimple l && isSimple r
   ; InstanceOf e t -> isSimple e
   ; Call e n es -> isSimple e && areSimple es
   ; Op e1 o e2 -> False
   ; New n es Nothing -> areSimple es
   ; New n es (Just ds) -> False
   ; otherwise -> True
   }
\end{code}