blob: 578be9a89b0905cee28d7ab0e41fbacef7ab6b63 (
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
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
|
Anbstract 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
Major reworking to be usable for the intermeduate (GOO) language
for the backend of GHC and to target languauges like Java sucessfully.
-- Andy Gill
\begin{code}
module Java where
\end{code}
%************************************************************************
%* *
\subsection{Java type declararations}
%* *
%************************************************************************
\begin{code}
data CompilationUnit
= Package Name [Decl]
deriving (Show)
data Decl
= Import PackageName
| Field [Modifier] Type Name (Maybe Expr)
| Constructor [Modifier] Name [Parameter] [Statement]
| Method [Modifier] Type Name [Parameter] [Exception] [Statement]
| Comment [String]
| Interface [Modifier] Name [TypeName] [Decl]
| Class [Modifier] Name [TypeName] [TypeName] [Decl]
deriving (Show)
data Parameter
= Parameter [Modifier] Type Name
deriving (Show)
data Statement
= Skip
| Return Expr -- This always comes last in a list
-- of statements, and it is understood
-- you might change this to something
-- else (like a variable assignment)
-- if this is not top level statements.
| Block [Statement]
| ExprStatement Expr -- You are never interested in the result
-- of an ExprStatement
| Declaration Decl -- variable = inner Field, Class = innerclass
| IfThenElse [(Expr,Statement)] (Maybe Statement)
| Switch Expr [(Expr, [Statement])] (Maybe [Statement])
deriving (Show)
data Expr
= Var Name Type
| Literal Lit Type
| Cast Type Expr
| Access Expr Name -- perhaps: Access Expr Var?
| Assign Expr Expr
| InstanceOf Expr Type
| Call Expr Name [Expr]
| Op Expr String Expr
| New Type [Expr] (Maybe [Decl]) -- anonymous innerclass
deriving (Show)
data Modifier
= Public | Protected | Private
| Static
| Abstract | Final | Native | Synchronized | Transient | Volatile
deriving (Show, Eq, Ord)
-- A type is used to refer in general to the shape of things,
-- or a specific class. Never use a name to refer to a class,
-- always use a type.
data Type
= PrimType PrimType
| ArrayType Type
| Type TypeName
deriving (Show)
data PrimType
= PrimInt
| PrimBoolean
| PrimChar
| PrimLong
| PrimFloat
| PrimDouble
| PrimByte
deriving (Show)
type PackageName = String -- A package name
-- like "java.awt.Button"
type Exception = TypeName -- A class name that must be an exception.
type TypeName = String -- a fully qualified type name
-- like "java.lang.Object".
-- has type "Type <the name>"
type Name = String -- A class name or method etc,
-- at defintion time,
-- this generally not a qualified name.
data Lit
= IntLit Integer -- unboxed
| CharLit Char -- unboxed
| StringLit String -- java 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 ts ss -> Method (m:ms) t n as ts 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}
|