[project @ 2005-12-16 16:04:03 by simonpj]
[ghc-hetmet.git] / ghc / compiler / javaGen / Java.lhs
index 5de371b..368be03 100644 (file)
@@ -1,10 +1,14 @@
-Abstract syntax for Java subset that is the target of Mondrian.
+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
 
@@ -18,28 +22,33 @@ module Java where
 
 \begin{code}
 data CompilationUnit
-  = Package Name [Decl]
+  = Package PackageName [Decl]
     deriving (Show)
     
 data Decl
- = Import Name
- | Field [Modifier] Type Name (Maybe Expr)   
- | Constructor [Modifier] Name [Parameter] [Statement]
- | Method [Modifier] Type Name [Parameter] [Statement]
+ = Import PackageName
+ | Field [Modifier] Name (Maybe Expr)
+ | Constructor [Modifier] TypeName [Parameter] [Statement]
+ | Method [Modifier] Name [Parameter] [Exception] [Statement]
  | Comment [String]
- | Interface [Modifier] Name [Name] [Decl]
- | Class [Modifier] Name [Name] [Name] [Decl]
+ | Interface [Modifier] TypeName [TypeName] [Decl]
+ | Class [Modifier] TypeName [TypeName] [TypeName] [Decl]
    deriving (Show)
-   
+
 data Parameter
- = Parameter [Modifier] Type Name
+ = Parameter [Modifier] Name
    deriving (Show)
    
 data Statement
   = Skip
-  | Return Expr
+  | 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
+  | 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])
@@ -54,13 +63,8 @@ data 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
+  | Raise TypeName [Expr]
+  | New Type [Expr] (Maybe [Decl]) -- anonymous innerclass
     deriving (Show)
     
 data Modifier 
@@ -68,28 +72,83 @@ data Modifier
   | Static
   | Abstract | Final | Native | Synchronized | Transient | Volatile
   deriving (Show, Eq, Ord)
-  
-type Name = [String]
+
+-- 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, Eq)
+
+data PrimType 
+  = PrimInt 
+  | PrimBoolean
+  | PrimChar
+  | PrimLong
+  | PrimFloat
+  | PrimDouble
+  | PrimByte
+  | PrimVoid
+    deriving (Show, Eq)
+
+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>"
+
+data Name        = Name String Type
+       deriving Show           -- A class name or method etc, 
+                               -- at defintion time,
+                               -- this generally not a qualified name.
+
+                               -- The type is shape of the box require
+                               -- to store an access to this thing.
+                               -- So variables might be Int or Object.
+
+                               --  ** method calls store the returned
+                               --  ** type, not a complete arg x result type.
+                               --
+                               -- Thinking:
+                               -- ... foo1.foo2(...).foo3 ...
+                               -- here you want to know the *result*
+                               -- after calling foo1, then foo2,
+                               -- then foo3.
+
+instance Eq Name where
+   (Name nm _) == (Name nm' _) = nm == nm'
+
+
+instance Ord Name where
+   (Name nm _) `compare` (Name nm' _) = nm `compare` nm'
+
 
 data Lit
-  = IntLit Int         -- Boxed
-  | UIntLit Int                -- Unboxed
-  | CharLit Char       -- Boxed
-  | UCharLit Char      -- Unboxed
-  | StringLit String
+  = IntLit Integer     -- unboxed
+  | CharLit Int        -- 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  
+   ; Field ms n e -> Field (m:ms) 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
+   ; Method ms n as ts ss -> Method (m:ms) 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
    }
+
+changeNameType :: Type -> Name -> Name
+changeNameType ty (Name n _) = Name n ty
    
 areSimple :: [Expr] -> Bool
 areSimple = \es -> all isSimple es