X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Ftypecheck%2FTcBinds.lhs;h=a3b17a600ce1f278676154dd45b18e67ac2ad775;hp=9cc66e3951d8aeb83b329f7a44d79c7e6d3bc95d;hb=9da4639011348fb6c318e3cba4b08622f811d9c4;hpb=3e83dfb21b2f2220dce97427fff5c19459ae68d1 diff --git a/compiler/typecheck/TcBinds.lhs b/compiler/typecheck/TcBinds.lhs index 9cc66e3..a3b17a6 100644 --- a/compiler/typecheck/TcBinds.lhs +++ b/compiler/typecheck/TcBinds.lhs @@ -19,16 +19,15 @@ import DynFlags ( dopt, DynFlags, DynFlag(Opt_MonomorphismRestriction, Opt_MonoPatBinds, Opt_GlasgowExts) ) import HsSyn ( HsExpr(..), HsBind(..), LHsBinds, LHsBind, Sig(..), HsLocalBinds(..), HsValBinds(..), HsIPBinds(..), - LSig, Match(..), IPBind(..), Prag(..), - HsType(..), LHsType, HsExplicitForAll(..), hsLTyVarNames, + LSig, Match(..), IPBind(..), Prag(..), LHsType, isVanillaLSig, sigName, placeHolderNames, isPragLSig, - LPat, GRHSs, MatchGroup(..), pprLHsBinds, mkHsCoerce, + LPat, GRHSs, MatchGroup(..), pprLHsBinds, mkHsWrap, hsExplicitTvs, collectHsBindBinders, collectPatBinders, pprPatBind, isBangHsBind ) import TcHsSyn ( zonkId ) import TcRnMonad -import Inst ( newDictsAtLoc, newIPDict, instToId ) +import Inst ( newDictBndrs, newIPDict, instToId ) import TcEnv ( tcExtendIdEnv, tcExtendIdEnv2, tcExtendTyVarEnv2, pprBinders, tcLookupId, tcGetGlobalTyVars ) @@ -439,7 +438,7 @@ tcSpecPrag poly_id hs_ty inl ; (co_fn, lie) <- getLIE (tcSubExp (idType poly_id) spec_ty) ; extendLIEs lie ; let const_dicts = map instToId lie - ; return (SpecPrag (mkHsCoerce co_fn (HsVar poly_id)) spec_ty const_dicts inl) } + ; return (SpecPrag (mkHsWrap co_fn (HsVar poly_id)) spec_ty const_dicts inl) } -- Most of the work of specialisation is done by -- the desugarer, guided by the SpecPrag @@ -773,7 +772,7 @@ might not otherwise be related. This is a rather subtle issue. unifyCtxts :: [TcSigInfo] -> TcM [Inst] unifyCtxts (sig1 : sigs) -- Argument is always non-empty = do { mapM unify_ctxt sigs - ; newDictsAtLoc (sig_loc sig1) (sig_theta sig1) } + ; newDictBndrs (sig_loc sig1) (sig_theta sig1) } where theta1 = sig_theta sig1 unify_ctxt :: TcSigInfo -> TcM () @@ -973,13 +972,12 @@ mkTcSigFun :: [LSig Name] -> TcSigFun -- Precondition: no duplicates mkTcSigFun sigs = lookupNameEnv env where - env = mkNameEnv [(name, scoped_tyvars hs_ty) - | L span (TypeSig (L _ name) (L _ hs_ty)) <- sigs] - scoped_tyvars (HsForAllTy Explicit tvs _ _) = hsLTyVarNames tvs - scoped_tyvars other = [] + env = mkNameEnv [(name, hsExplicitTvs lhs_ty) + | L span (TypeSig (L _ name) lhs_ty) <- sigs] -- The scoped names are the ones explicitly mentioned -- in the HsForAll. (There may be more in sigma_ty, because -- of nested type synonyms. See Note [Scoped] with TcSigInfo.) + -- See Note [Only scoped tyvars are in the TyVarEnv] --------------- data TcSigInfo @@ -998,6 +996,19 @@ data TcSigInfo sig_loc :: InstLoc -- The location of the signature } + +-- Note [Only scoped tyvars are in the TyVarEnv] +-- We are careful to keep only the *lexically scoped* type variables in +-- the type environment. Why? After all, the renamer has ensured +-- that only legal occurrences occur, so we could put all type variables +-- into the type env. +-- +-- But we want to check that two distinct lexically scoped type variables +-- do not map to the same internal type variable. So we need to know which +-- the lexically-scoped ones are... and at the moment we do that by putting +-- only the lexically scoped ones into the environment. + + -- Note [Scoped] -- There may be more instantiated type variables than scoped -- ones. For example: @@ -1010,7 +1021,7 @@ data TcSigInfo -- and remember the names from the original HsForAllTy in sig_scoped -- Note [Instantiate sig] --- It's vital to instantiate a type signature with fresh variable. +-- It's vital to instantiate a type signature with fresh variables. -- For example: -- type S = forall a. a->a -- f,g :: S @@ -1046,7 +1057,7 @@ tcInstSig :: Bool -> Name -> [Name] -> TcM TcSigInfo -- Instantiate the signature, with either skolems or meta-type variables -- depending on the use_skols boolean. This variable is set True -- when we are typechecking a single function binding; and False for --- pattern bindigs and a group of several function bindings. +-- pattern bindings and a group of several function bindings. -- Reason: in the latter cases, the "skolems" can be unified together, -- so they aren't properly rigid in the type-refinement sense. -- NB: unless we are doing H98, each function with a sig will be done