diff options
author | simonpj <unknown> | 2001-06-25 08:10:03 +0000 |
---|---|---|
committer | simonpj <unknown> | 2001-06-25 08:10:03 +0000 |
commit | d069cec2bd92d4156aeab80f7eb1f222a82e4103 (patch) | |
tree | f50bd239110777d3e9effa526df25b667fdb176e /ghc/compiler/javaGen | |
parent | 3622a7de695b4cb795171c8cb59bfe41c7f4d85f (diff) | |
download | haskell-d069cec2bd92d4156aeab80f7eb1f222a82e4103.tar.gz |
[project @ 2001-06-25 08:09:57 by simonpj]
----------------
Squash newtypes
----------------
This commit squashes newtypes and their coerces, from the typechecker
onwards. The original idea was that the coerces would not get in the
way of optimising transformations, but despite much effort they continue
to do so. There's no very good reason to retain newtype information
beyond the typechecker, so now we don't.
Main points:
* The post-typechecker suite of Type-manipulating functions is in
types/Type.lhs, as before. But now there's a new suite in types/TcType.lhs.
The difference is that in the former, newtype are transparent, while in
the latter they are opaque. The typechecker should only import TcType,
not Type.
* The operations in TcType are all non-monadic, and most of them start with
"tc" (e.g. tcSplitTyConApp). All the monadic operations (used exclusively
by the typechecker) are in a new module, typecheck/TcMType.lhs
* I've grouped newtypes with predicate types, thus:
data Type = TyVarTy Tyvar | ....
| SourceTy SourceType
data SourceType = NType TyCon [Type]
| ClassP Class [Type]
| IParam Type
[SourceType was called PredType.] This is a little wierd in some ways,
because NTypes can't occur in qualified types. However, the idea is that
a SourceType is a type that is opaque to the type checker, but transparent
to the rest of the compiler, and newtypes fit that as do implicit parameters
and dictionaries.
* Recursive newtypes still retain their coreces, exactly as before. If
they were transparent we'd get a recursive type, and that would make
various bits of the compiler diverge (e.g. things which do type comparison).
* I've removed types/Unify.lhs (non-monadic type unifier and matcher),
merging it into TcType.
Ditto typecheck/TcUnify.lhs (monadic unifier), merging it into TcMType.
Diffstat (limited to 'ghc/compiler/javaGen')
-rw-r--r-- | ghc/compiler/javaGen/JavaGen.lhs | 41 |
1 files changed, 15 insertions, 26 deletions
diff --git a/ghc/compiler/javaGen/JavaGen.lhs b/ghc/compiler/javaGen/JavaGen.lhs index 716492991e..58d8808b3e 100644 --- a/ghc/compiler/javaGen/JavaGen.lhs +++ b/ghc/compiler/javaGen/JavaGen.lhs @@ -286,37 +286,34 @@ javaCase r e x [(DataAlt d,bs,rhs)] | length bs > 0 ] javaCase r e x alts - | isIfThenElse && isPrimCmp = - javaIfThenElse r (fromJust maybePrim) tExpr fExpr - | otherwise = - java_expr PushExpr e ++ + | isIfThenElse && isPrimCmp + = javaIfThenElse r (fromJust maybePrim) tExpr fExpr + | otherwise + = java_expr PushExpr e ++ [ var [Final] (javaName x) (whnf primRep (vmPOP (primRepToType primRep))) - , mkIfThenElse (map mk_alt alts) + , IfThenElse (map mk_alt con_alts) (Just default_code) ] where - isIfThenElse = CoreUtils.exprType e == boolTy + isIfThenElse = CoreUtils.exprType e `Type.eqType` boolTy -- also need to check that x is not free in -- any of the branches. maybePrim = findCmpPrim e [] isPrimCmp = isJust maybePrim - tExpr = matches trueDataCon alts - fExpr = matches falseDataCon alts - - matches con [] = error "no match for true or false branch of if/then/else" - matches con ((DataAlt d,[],rhs):rest) | con == d = rhs - matches con ((DEFAULT,[],rhs):_) = rhs - matches con (other:rest) = matches con rest + (_,_,tExpr) = CoreUtils.findAlt (DataAlt trueDataCon) alts + (_,_,fExpr) = CoreUtils.findAlt (DataAlt falseDataCon) alts primRep = idPrimRep x whnf PtrRep = vmWHNF -- needs evaluation whnf _ = id - mk_alt (DEFAULT, [], rhs) = (true, Block (javaExpr r rhs)) - mk_alt (DataAlt d, bs, rhs) = (instanceOf x d, Block (bind_args d bs ++ javaExpr r rhs)) - mk_alt alt@(LitAlt lit, [], rhs) - = (eqLit lit , Block (javaExpr r rhs)) - mk_alt alt@(LitAlt _, _, _) = pprPanic "mk_alt" (ppr alt) + (con_alts, maybe_default) = CoreUtils.findDefault alts + default_code = case maybe_default of + Nothing -> ExprStatement (Raise excName [Literal (StringLit "case failure")]) + Just rhs -> Block (javaExpr r rhs) + + mk_alt (DataAlt d, bs, rhs) = (instanceOf x d, Block (bind_args d bs ++ javaExpr r rhs)) + mk_alt (LitAlt lit, bs, rhs) = (eqLit lit , Block (javaExpr r rhs)) eqLit (MachInt n) = Op (Literal (IntLit n)) @@ -336,14 +333,6 @@ javaCase r e x alts , not (isDeadBinder b) ] - -mkIfThenElse [(Var (Name "true" _),code)] = code -mkIfThenElse other = IfThenElse other - (Just (ExprStatement - (Raise excName [Literal (StringLit "case failure")]) - ) - ) - javaIfThenElse r cmp tExpr fExpr {- - Now what we need to do is generate code for the if/then/else. |