Add HsCoreTy to HsType
[ghc-hetmet.git] / compiler / typecheck / TcEnv.lhs
index f9a9179..67e65af 100644 (file)
@@ -55,12 +55,12 @@ import TcRnMonad
 import TcMType
 import TcType
 -- import TcSuspension
-import qualified Type
+-- import qualified Type
 import Id
 import Coercion
 import Var
 import VarSet
-import VarEnv
+-- import VarEnv
 import RdrName
 import InstEnv
 import FamInstEnv
@@ -115,10 +115,10 @@ tcLookupGlobal name
 
                -- Should it have been in the local envt?
        { case nameModule_maybe name of
-               Nothing -> notFound name env -- Internal names can happen in GHCi
+               Nothing -> notFound name -- Internal names can happen in GHCi
 
                Just mod | mod == tcg_mod env   -- Names from this module 
-                        -> notFound name env -- should be in tcg_type_env
+                        -> notFound name -- should be in tcg_type_env
                         | otherwise
                         -> tcImportDecl name   -- Go find it in an interface
        }}}}}
@@ -319,13 +319,10 @@ tcExtendKindEnv things thing_inside
     upd lcl_env = lcl_env { tcl_env = extend (tcl_env lcl_env) }
     extend env  = extendNameEnvList env [(n, AThing k) | (n,k) <- things]
 
-tcExtendKindEnvTvs :: [LHsTyVarBndr Name] -> TcM r -> TcM r
+tcExtendKindEnvTvs :: [LHsTyVarBndr Name] -> ([LHsTyVarBndr Name] -> TcM r) -> TcM r
 tcExtendKindEnvTvs bndrs thing_inside
-  = updLclEnv upd thing_inside
-  where
-    upd lcl_env = lcl_env { tcl_env = extend (tcl_env lcl_env) }
-    extend env  = extendNameEnvList env pairs
-    pairs       = [(n, AThing k) | L _ (KindedTyVar n k) <- bndrs]
+  = tcExtendKindEnv (map (hsTyVarNameKind . unLoc) bndrs)
+                    (thing_inside bndrs)
 
 tcExtendTyVarEnv :: [TyVar] -> TcM r -> TcM r
 tcExtendTyVarEnv tvs thing_inside
@@ -538,7 +535,7 @@ checkWellStaged pp_thing bind_lvl use_lvl
   = failWithTc $ 
     sep [ptext (sLit "GHC stage restriction:") <+>  pp_thing,
         nest 2 (vcat [ ptext (sLit "is used in a top-level splice or annotation,")
-                      , ptext (sLit ", and must be imported, not defined locally")])]
+                      , ptext (sLit "and must be imported, not defined locally")])]
 
   | otherwise                  -- Badly staged
   = failWithTc $               -- E.g.  \x -> $(f x)
@@ -616,13 +613,20 @@ data InstBindings a
                                -- specialised instances
        Bool                    -- True <=> This code came from a standalone deriving clause
 
-  | NewTypeDerived              -- Used for deriving instances of newtypes, where the
-       CoercionI               -- witness dictionary is identical to the argument 
-                               -- dictionary.  Hence no bindings, no pragmas.
-               -- The coercion maps from newtype to the representation type
-               -- (mentioning type variables bound by the forall'd iSpec variables)
-               -- E.g.   newtype instance N [a] = N1 (Tree a)
-               --        co : N [a] ~ Tree a
+  | NewTypeDerived      -- Used for deriving instances of newtypes, where the
+                       -- witness dictionary is identical to the argument 
+                       -- dictionary.  Hence no bindings, no pragmas.
+
+       CoercionI       -- The coercion maps from newtype to the representation type
+                       -- (mentioning type variables bound by the forall'd iSpec variables)
+                       -- E.g.   newtype instance N [a] = N1 (Tree a)
+                       --        co : N [a] ~ Tree a
+
+       TyCon           -- The TyCon is the newtype N.  If it's indexed, then it's the 
+                       -- representation TyCon, so that tyConDataCons returns [N1], 
+                       -- the "data constructor".
+                       -- See Note [Newtype deriving and unused constructors]
+                        -- in TcDeriv
 
 pprInstInfo :: InstInfo a -> SDoc
 pprInstInfo info = vcat [ptext (sLit "InstInfo:") <+> ppr (idType (iDFunId info))]
@@ -631,7 +635,7 @@ pprInstInfoDetails :: OutputableBndr a => InstInfo a -> SDoc
 pprInstInfoDetails info = pprInstInfo info $$ nest 2 (details (iBinds info))
   where
     details (VanillaInst b _ _) = pprLHsBinds b
-    details (NewTypeDerived _)  = text "Derived from the representation type"
+    details (NewTypeDerived {}) = text "Derived from the representation type"
 
 simpleInstInfoClsTy :: InstInfo a -> (Class, Type)
 simpleInstInfoClsTy info = case instanceHead (iSpec info) of
@@ -710,12 +714,14 @@ pprBinders :: [Name] -> SDoc
 pprBinders [bndr] = quotes (ppr bndr)
 pprBinders bndrs  = pprWithCommas ppr bndrs
 
-notFound :: Name -> TcGblEnv -> TcM TyThing
-notFound name env
-  = failWithTc (vcat[ptext (sLit "GHC internal error:") <+> quotes (ppr name) <+> 
+notFound :: Name -> TcM TyThing
+notFound name 
+  = do { (gbl,lcl) <- getEnvs
+       ; failWithTc (vcat[ptext (sLit "GHC internal error:") <+> quotes (ppr name) <+> 
                      ptext (sLit "is not in scope during type checking, but it passed the renamer"),
-                     ptext (sLit "tcg_type_env of environment:") <+> ppr (tcg_type_env env)]
-                    )
+                     ptext (sLit "tcg_type_env of environment:") <+> ppr (tcg_type_env gbl),
+                     ptext (sLit "tcl_env of environment:") <+> ppr (tcl_env lcl)]
+                    ) }
 
 wrongThingErr :: String -> TcTyThing -> Name -> TcM a
 wrongThingErr expected thing name