X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Ftypecheck%2FTcHsSyn.lhs;h=6e174661ceea4a0db1bbbb5ddb5b74200947f26b;hb=2423c249f5ca7785d0ec89eb33e72662da7561c1;hp=026893c86cd7b23363ad4bdbe09eb654f644650d;hpb=bf40e268d916947786c56ec38db86190854a2d2c;p=ghc-hetmet.git diff --git a/compiler/typecheck/TcHsSyn.lhs b/compiler/typecheck/TcHsSyn.lhs index 026893c..6e17466 100644 --- a/compiler/typecheck/TcHsSyn.lhs +++ b/compiler/typecheck/TcHsSyn.lhs @@ -1,7 +1,9 @@ - % +% +% (c) The University of Glasgow 2006 % (c) The AQUA Project, Glasgow University, 1996-1998 % -\section[TcHsSyn]{Specialisations of the @HsSyn@ syntax for the typechecker} + +TcHsSyn: Specialisations of the @HsSyn@ syntax for the typechecker This module is an extension of @HsSyn@ syntax, for use in the type checker. @@ -13,6 +15,7 @@ module TcHsSyn ( mkHsAppTy, mkSimpleHsAlt, nlHsIntLit, mkVanillaTuplePat, + mkArbitraryType, -- Put this elsewhere? -- re-exported from TcMonad TcId, TcIdSet, TcDictBinds, @@ -27,30 +30,26 @@ module TcHsSyn ( import HsSyn -- oodles of it -- others: -import Id ( idType, setIdType, Id ) +import Id import TcRnMonad -import Type ( Type, isLiftedTypeKind, liftedTypeKind, isSubKind, eqKind ) -import TcType ( TcType, TcTyVar, mkTyVarTy, mkTyConApp, isImmutableTyVar ) +import Type +import TcType import qualified Type -import TcMType ( zonkQuantifiedTyVar, zonkType, zonkTcType, writeMetaTyVar ) -import TysPrim ( charPrimTy, intPrimTy, floatPrimTy, - doublePrimTy, addrPrimTy - ) -import TysWiredIn ( charTy, stringTy, intTy, - mkListTy, mkPArrTy, mkTupleTy, unitTy, - voidTy, listTyCon, tupleTyCon ) -import TyCon ( mkPrimTyCon, tyConKind, PrimRep(..) ) -import {- Kind parts of -} Type ( splitKindFunTys ) -import Name ( Name, getOccName, mkInternalName, mkDerivedTyConOcc ) -import Var ( Var, isId, isLocalVar, tyVarKind ) +import TcMType +import TysPrim +import TysWiredIn +import TyCon +import {- Kind parts of -} Type +import Name +import Var import VarSet import VarEnv -import BasicTypes ( Boxity(..), IPName(..), ipNameName, mapIPName ) -import Maybes ( orElse ) -import Unique ( Uniquable(..) ) -import SrcLoc ( noSrcLoc, noLoc, Located(..), unLoc ) -import Util ( mapSnd ) +import BasicTypes +import Maybes +import Unique +import SrcLoc +import Util import Bag import Outputable \end{code} @@ -120,7 +119,7 @@ hsLitType (HsDoublePrim d) = doublePrimTy zonkId :: TcId -> TcM TcId zonkId id = zonkTcType (idType id) `thenM` \ ty' -> - returnM (setIdType id ty') + returnM (Id.setIdType id ty') \end{code} The rest of the zonking is done *after* typechecking. @@ -189,7 +188,7 @@ zonkIdOccs env ids = map (zonkIdOcc env) ids zonkIdBndr :: ZonkEnv -> TcId -> TcM Id zonkIdBndr env id = zonkTcTypeToType env (idType id) `thenM` \ ty' -> - returnM (setIdType id ty') + returnM (Id.setIdType id ty') zonkIdBndrs :: ZonkEnv -> [TcId] -> TcM [Id] zonkIdBndrs env ids = mappM (zonkIdBndr env) ids @@ -771,16 +770,16 @@ zonkConStuff env (InfixCon p1 p2) ; return (env', InfixCon p1' p2') } zonkConStuff env (RecCon rpats) - = do { (env', pats') <- zonkPats env pats - ; returnM (env', RecCon (fields `zip` pats')) } - where - (fields, pats) = unzip rpats + = do { let (fields, pats) = unzip [ (f, p) | HsRecField f p _ <- rpats ] + ; (env', pats') <- zonkPats env pats + ; let recCon = RecCon [ mkRecField f p | (f, p) <- zip fields pats' ] + ; returnM (env', recCon) } --------------------------- zonkPats env [] = return (env, []) zonkPats env (pat:pats) = do { (env1, pat') <- zonkPat env pat - ; (env', pats') <- zonkPats env1 pats - ; return (env', pat':pats') } + ; (env', pats') <- zonkPats env1 pats + ; return (env', pat':pats') } \end{code} %************************************************************************ @@ -922,24 +921,22 @@ mkArbitraryType :: TcTyVar -> Type -- Make up an arbitrary type whose kind is the same as the tyvar. -- We'll use this to instantiate the (unbound) tyvar. mkArbitraryType tv - | liftedTypeKind `isSubKind` kind = voidTy -- The vastly common case + | liftedTypeKind `isSubKind` kind = anyPrimTy -- The vastly common case | otherwise = mkTyConApp tycon [] where kind = tyVarKind tv (args,res) = splitKindFunTys kind - tycon | eqKind kind (tyConKind listTyCon) -- *->* - = listTyCon -- No tuples this size + tycon | eqKind kind (tyConKind anyPrimTyCon1) -- *->* + = anyPrimTyCon1 -- No tuples this size | all isLiftedTypeKind args && isLiftedTypeKind res = tupleTyCon Boxed (length args) -- *-> ... ->*->* + -- Horrible hack to make less use of mkAnyPrimTyCon | otherwise - = pprTrace "Urk! Inventing strangely-kinded void TyCon:" (ppr tc_name $$ ppr kind) $ - mkPrimTyCon tc_name kind 0 VoidRep + = mkAnyPrimTyCon (getUnique tv) kind -- Same name as the tyvar, apart from making it start with a colon (sigh) -- I dread to think what will happen if this gets out into an -- interface file. Catastrophe likely. Major sigh. - - tc_name = mkInternalName (getUnique tv) (mkDerivedTyConOcc (getOccName tv)) noSrcLoc \end{code}