X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;ds=sidebyside;f=ghc%2Fcompiler%2Ftypecheck%2FTcIfaceSig.lhs;h=eceff0e733966163132f8214edee502bb03c289b;hb=cae34044d89a87bd3da83b0e867b4a5d6994079a;hp=57ff4c03190b941b9af6645cb798dadd9ce20227;hpb=111cee3f1ad93816cb828e38b38521d85c3bcebb;p=ghc-hetmet.git diff --git a/ghc/compiler/typecheck/TcIfaceSig.lhs b/ghc/compiler/typecheck/TcIfaceSig.lhs index 57ff4c0..eceff0e 100644 --- a/ghc/compiler/typecheck/TcIfaceSig.lhs +++ b/ghc/compiler/typecheck/TcIfaceSig.lhs @@ -8,20 +8,18 @@ module TcIfaceSig ( tcInterfaceSigs, tcVar, tcCoreExpr, tcCoreLamBndrs ) where #include "HsVersions.h" -import HsSyn ( HsDecl(..), IfaceSig(..) ) +import HsSyn ( HsDecl(..), IfaceSig(..), HsTupCon(..) ) import TcMonad -import TcMonoType ( tcHsType, tcHsTypeKind, +import TcMonoType ( tcHsType ) -- NB: all the tyars in interface files are kinded, -- so tcHsType will do the Right Thing without -- having to mess about with zonking - tcExtendTyVarScope - ) + import TcEnv ( ValueEnv, tcExtendTyVarEnv, tcExtendGlobalValEnv, tcSetValueEnv, tcLookupValueMaybe, explicitLookupValue, badCon, badPrimOp, valueEnvIds ) -import TcType ( TcKind, kindToTcKind ) import RnHsSyn ( RenamedHsDecl ) import HsCore @@ -31,7 +29,6 @@ import CoreUtils ( exprType ) import CoreUnfold import CoreLint ( lintUnfolding ) import WorkWrap ( mkWrapper ) -import PrimOp ( PrimOp(..), CCall(..), CCallTarget(..) ) import Id ( Id, mkId, mkVanillaId, isDataConWrapId_maybe @@ -39,15 +36,11 @@ import Id ( Id, mkId, mkVanillaId, import MkId ( mkCCallOpId ) import IdInfo import DataCon ( dataConSig, dataConArgTys ) -import Type ( mkSynTy, mkTyVarTys, splitAlgTyConApp, splitFunTys, unUsgTy ) +import Type ( mkSynTy, mkTyVarTys, splitAlgTyConApp, splitAlgTyConApp_maybe, splitFunTys, unUsgTy ) import Var ( mkTyVar, tyVarKind ) -import VarEnv import Name ( Name, NamedThing(..), isLocallyDefined ) -import Unique ( rationalTyConKey ) -import TysWiredIn ( integerTy, stringTy ) import Demand ( wwLazy ) import ErrUtils ( pprBagOfErrors ) -import Maybes ( maybeToBool, MaybeErr(..) ) import Outputable import Util ( zipWithEqual ) \end{code} @@ -85,7 +78,6 @@ tcIdInfo unf_env in_scope_vars name ty info info_ins = foldlTc tcPrag vanillaIdInfo info_ins where tcPrag info (HsArity arity) = returnTc (info `setArityInfo` arity) - tcPrag info (HsUpdate upd) = returnTc (info `setUpdateInfo` upd) tcPrag info (HsNoCafRefs) = returnTc (info `setCafInfo` NoCafRefs) tcPrag info HsCprInfo = returnTc (info `setCprInfo` ReturnsCPR) @@ -96,14 +88,14 @@ tcIdInfo unf_env in_scope_vars name ty info info_ins -- is never inspected; so the typecheck doesn't even happen unfold_info = case maybe_expr' of Nothing -> noUnfolding - Just expr' -> mkTopUnfolding (cprInfo info) expr' + Just expr' -> mkTopUnfolding expr' info1 = info `setUnfoldingInfo` unfold_info info2 = info1 `setInlinePragInfo` inline_prag in returnTc info2 - tcPrag info (HsStrictness (HsStrictnessInfo (demands,bot_result))) - = returnTc (info `setStrictnessInfo` StrictnessInfo demands bot_result) + tcPrag info (HsStrictness strict_info) + = returnTc (info `setStrictnessInfo` strict_info) tcPrag info (HsWorker nm) = tcWorkerInfo unf_env ty info nm @@ -119,7 +111,7 @@ tcWorkerInfo unf_env ty info worker_name let -- Watch out! We can't pull on unf_env too eagerly! info' = case explicitLookupValue unf_env worker_name of - Just worker_id -> info `setUnfoldingInfo` mkTopUnfolding cpr_info (wrap_fn worker_id) + Just worker_id -> info `setUnfoldingInfo` mkTopUnfolding (wrap_fn worker_id) `setWorkerInfo` HasWorker worker_id arity Nothing -> pprTrace "tcWorkerInfo failed:" (ppr worker_name) info @@ -147,8 +139,8 @@ tcPragExpr unf_env name in_scope_vars expr -- Check for type consistency in the unfolding tcGetSrcLoc `thenNF_Tc` \ src_loc -> case lintUnfolding src_loc in_scope_vars core_expr' of - Nothing -> returnTc core_expr' - Just fail_msg -> failWithTc ((doc <+> text "failed Lint") $$ fail_msg) + (Nothing,_) -> returnTc core_expr' -- ignore warnings + (Just fail_msg,_) -> failWithTc ((doc <+> text "failed Lint") $$ fail_msg) where doc = text "unfolding of" <+> ppr name @@ -192,7 +184,7 @@ UfCore expressions. tcCoreExpr :: UfExpr Name -> TcM s CoreExpr tcCoreExpr (UfType ty) - = tcHsTypeKind ty `thenTc` \ (_, ty') -> + = tcHsType ty `thenTc` \ ty' -> -- It might not be of kind type returnTc (Type ty') @@ -214,7 +206,7 @@ tcCoreExpr (UfCCall cc ty) tcGetUnique `thenNF_Tc` \ u -> returnTc (Var (mkCCallOpId u cc ty')) -tcCoreExpr (UfTuple name args) +tcCoreExpr (UfTuple (HsTupCon name _) args) = tcVar name `thenTc` \ con_id -> mapTc tcCoreExpr args `thenTc` \ args' -> let @@ -332,20 +324,22 @@ tcCoreAlt scrut_ty (UfLitLitAlt str ty, names, rhs) -- A case alternative is made quite a bit more complicated -- by the fact that we omit type annotations because we can -- work them out. True enough, but its not that easy! -tcCoreAlt scrut_ty (UfDataAlt con_name, names, rhs) +tcCoreAlt scrut_ty alt@(UfDataAlt con_name, names, rhs) = tcVar con_name `thenTc` \ con_id -> let - con = case isDataConWrapId_maybe con_id of - Just con -> con - Nothing -> pprPanic "tcCoreAlt" (ppr con_id) + con = case isDataConWrapId_maybe con_id of + Just con -> con + Nothing -> pprPanic "tcCoreAlt" (ppr con_id) (main_tyvars, _, ex_tyvars, _, _, _) = dataConSig con - (tycon, inst_tys, cons) = splitAlgTyConApp scrut_ty - ex_tyvars' = [mkTyVar name (tyVarKind tv) | (name,tv) <- names `zip` ex_tyvars] - ex_tys' = mkTyVarTys ex_tyvars' - arg_tys = dataConArgTys con (inst_tys ++ ex_tys') - id_names = drop (length ex_tyvars) names + (_, inst_tys, cons) = case splitAlgTyConApp_maybe scrut_ty of + Just stuff -> stuff + Nothing -> pprPanic "tcCoreAlt" (ppr alt) + ex_tyvars' = [mkTyVar name (tyVarKind tv) | (name,tv) <- names `zip` ex_tyvars] + ex_tys' = mkTyVarTys ex_tyvars' + arg_tys = dataConArgTys con (inst_tys ++ ex_tys') + id_names = drop (length ex_tyvars) names arg_ids #ifdef DEBUG | length id_names /= length arg_tys