diff options
author | simonpj <unknown> | 2000-04-20 16:45:16 +0000 |
---|---|---|
committer | simonpj <unknown> | 2000-04-20 16:45:16 +0000 |
commit | 1abb301c708c5265c15b3f52fadb57d58299c0b4 (patch) | |
tree | 88a317b5851cbc981c02d802abf1845c7d3683d1 /ghc/compiler/javaGen/Java.lhs | |
parent | 8f674b1c9bc152363650adb609f07b695eb9ecf2 (diff) | |
download | haskell-1abb301c708c5265c15b3f52fadb57d58299c0b4.tar.gz |
[project @ 2000-04-20 16:45:16 by simonpj]
Add support for Java generation, written in
a lightning day with Erik Meijer
ghc -J Foo.hs
will do the business, generating Foo.java
The code is in a new directory, javaGen/, so
you'll need to cvs update -d.
I've reorganised main/CodeOutput quite a bit; it
is now much much tidier, and will accommodate new
languages quite easily.
I've also fiddled with the flags that communicate
between the driver and hsc.
GONE: -S= -C=
NEW: -olang=xxx output language xxx
xxx can be: C, asm, java
-ofile=xxx put the output code in file xxx
BEWARE that I might have broken some of the more
cryptic stuff in ghc.lprl.
Simon
Diffstat (limited to 'ghc/compiler/javaGen/Java.lhs')
-rw-r--r-- | ghc/compiler/javaGen/Java.lhs | 110 |
1 files changed, 110 insertions, 0 deletions
diff --git a/ghc/compiler/javaGen/Java.lhs b/ghc/compiler/javaGen/Java.lhs new file mode 100644 index 0000000000..5de371b618 --- /dev/null +++ b/ghc/compiler/javaGen/Java.lhs @@ -0,0 +1,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} |