summaryrefslogtreecommitdiff
path: root/ghc/compiler/deSugar/Check.lhs
diff options
context:
space:
mode:
authorsimonpj <unknown>2001-06-25 08:10:03 +0000
committersimonpj <unknown>2001-06-25 08:10:03 +0000
commitd069cec2bd92d4156aeab80f7eb1f222a82e4103 (patch)
treef50bd239110777d3e9effa526df25b667fdb176e /ghc/compiler/deSugar/Check.lhs
parent3622a7de695b4cb795171c8cb59bfe41c7f4d85f (diff)
downloadhaskell-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/deSugar/Check.lhs')
-rw-r--r--ghc/compiler/deSugar/Check.lhs16
1 files changed, 6 insertions, 10 deletions
diff --git a/ghc/compiler/deSugar/Check.lhs b/ghc/compiler/deSugar/Check.lhs
index dd4c9ae97d..c777de51ff 100644
--- a/ghc/compiler/deSugar/Check.lhs
+++ b/ghc/compiler/deSugar/Check.lhs
@@ -12,6 +12,7 @@ module Check ( check , ExhaustivePat ) where
import HsSyn
import TcHsSyn ( TypecheckedPat )
+import TcType ( tcTyConAppTyCon, tcTyConAppArgs )
import DsHsSyn ( outPatType )
import DsUtils ( EquationInfo(..), MatchResult(..), EqnSet,
CanItFail(..), tidyLitPat, tidyNPat,
@@ -20,7 +21,7 @@ import Id ( idType )
import DataCon ( DataCon, dataConTyCon, dataConArgTys,
dataConSourceArity, dataConFieldLabels )
import Name ( Name, mkLocalName, getOccName, isDataSymOcc, getName, mkVarOcc )
-import Type ( splitAlgTyConApp, mkTyVarTys, splitTyConApp_maybe )
+import TcType ( mkTyVarTys )
import TysPrim ( charPrimTy )
import TysWiredIn
import PrelNames ( unboundKey )
@@ -413,17 +414,12 @@ get_unused_cons :: [TypecheckedPat] -> [DataCon]
get_unused_cons used_cons = unused_cons
where
(ConPat _ ty _ _ _) = head used_cons
- Just (ty_con,_) = sTyConApp_maybe used_cons ty
+ ty_con = tcTyConAppTyCon ty -- Newtype observable
all_cons = tyConDataCons ty_con
used_cons_as_id = map (\ (ConPat d _ _ _ _) -> d) used_cons
unused_cons = uniqSetToList
(mkUniqSet all_cons `minusUniqSet` mkUniqSet used_cons_as_id)
-sTyConApp_maybe used_cons ty =
- case splitTyConApp_maybe ty of
- Just x -> Just x
- Nothing -> pprTrace "splitTyConApp_maybe" (ppr (used_cons, ty)) $ Nothing
-
all_vars :: [TypecheckedPat] -> Bool
all_vars [] = True
all_vars (WildPat _:ps) = all_vars ps
@@ -592,9 +588,9 @@ simplify_pat (RecPat dc ty ex_tvs dicts [])
where
all_wild_pats = map WildPat con_arg_tys
- -- identical to machinations in Match.tidy1:
- (_, inst_tys, _) = splitAlgTyConApp ty
- con_arg_tys = dataConArgTys dc (inst_tys ++ mkTyVarTys ex_tvs)
+ -- Identical to machinations in Match.tidy1:
+ inst_tys = tcTyConAppArgs ty -- Newtype is observable
+ con_arg_tys = dataConArgTys dc (inst_tys ++ mkTyVarTys ex_tvs)
simplify_pat (RecPat dc ty ex_tvs dicts idps)
= ConPat dc ty ex_tvs dicts pats