Safe Haskell | Ignore |
---|---|
Language | GHC2021 |
The ZonkEnv
zonking environment, and the ZonkT
and ZonkBndrT
monad transformers, for the final zonking to type in GHC.Tc.Zonk.Type.
See Note [Module structure for zonking] in GHC.Tc.Zonk.Type.
Synopsis
- data ZonkEnv = ZonkEnv {}
- getZonkEnv :: Monad m => ZonkT m ZonkEnv
- data ZonkFlexi
- initZonkEnv :: MonadIO m => ZonkFlexi -> ZonkT m b -> m b
- data ZonkT m a where
- newtype ZonkBndrT m a = ZonkBndrT {
- runZonkBndrT' :: forall r. (a -> ZonkT m r) -> ZonkT m r
- runZonkBndrT :: ZonkBndrT m a -> forall r. (a -> ZonkT m r) -> ZonkT m r
- noBinders :: Monad m => ZonkT m a -> ZonkBndrT m a
- don'tBind :: Monad m => ZonkBndrT m a -> ZonkT m a
- setZonkType :: ZonkFlexi -> ZonkT m a -> ZonkT m a
- extendZonkEnv :: [Var] -> ZonkBndrT m ()
- extendIdZonkEnv :: Var -> ZonkBndrT m ()
- extendIdZonkEnvRec :: [Var] -> ZonkBndrT m ()
- extendTyZonkEnv :: TyVar -> ZonkBndrT m ()
The ZonkEnv
How should we handle unfilled unification variables in the zonker?
See Note [Un-unified unification variables]
DefaultFlexi | Default unbound unification variables to Any |
SkolemiseFlexi | Skolemise unbound unification variables See Note [Zonking the LHS of a RULE] |
RuntimeUnkFlexi | Used in the GHCi debugger |
NoFlexi | Panic on unfilled meta-variables See Note [Error on unconstrained meta-variables] in GHC.Tc.Utils.TcMType |
The ZonkT
and ZonkBndrT
zonking monad transformers
A reader monad over ZonkEnv
, for zonking computations which
don't modify the ZonkEnv
(e.g. don't bind any variables).
Use ZonkBndrT
when you need to modify the ZonkEnv
(e.g. to bind
a variable).
Instances
MonadTrans ZonkT Source # | |
Defined in GHC.Tc.Zonk.Env | |
MonadFix m => MonadFix (ZonkT m) Source # | |
Defined in GHC.Tc.Zonk.Env | |
MonadIO m => MonadIO (ZonkT m) Source # | |
Defined in GHC.Tc.Zonk.Env | |
Applicative m => Applicative (ZonkT m) Source # | |
Functor m => Functor (ZonkT m) Source # | |
Monad m => Monad (ZonkT m) Source # | |
newtype ZonkBndrT m a Source #
Zonk binders, bringing them into scope in the inner computation.
Can be thought of as a state monad transformer StateT ZonkEnv m a
,
but written in continuation-passing style.
See Note [Continuation-passing style for zonking].
ZonkBndrT | |
|
Going between ZonkT
and ZonkBndrT
runZonkBndrT :: ZonkBndrT m a -> forall r. (a -> ZonkT m r) -> ZonkT m r Source #
Zonk some binders and run the continuation.
Example:
zonk (ForAllTy (Bndr tv vis) body_ty) = runZonkBndrT (zonkTyBndrX tv) $ \ tv' -> do { body_ty' <- zonkTcTypeToTypeX body_ty ; return (ForAllTy (Bndr tv' vis) body_ty') }
See Note [Continuation-passing style for zonking].
don'tBind :: Monad m => ZonkBndrT m a -> ZonkT m a Source #
Run a nested computation that modifies the ZonkEnv
,
without affecting the outer environment.
Modifying and extending the ZonkEnv
in ZonkBndrT
extendZonkEnv :: [Var] -> ZonkBndrT m () Source #
extendIdZonkEnv :: Var -> ZonkBndrT m () Source #
extendIdZonkEnvRec :: [Var] -> ZonkBndrT m () Source #
Extend the knot-tied environment.
extendTyZonkEnv :: TyVar -> ZonkBndrT m () Source #