Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data SolveContext
- = FunctionDef (Set TyVar)
- | InterpreterUse Bool (Set TyVar)
- mustUnify :: SolveContext -> Bool
- unify :: SolveContext -> Type -> Type -> Maybe Subst
- tryUnifyUnivarsButNotSkolems :: Set TyVar -> Type -> Type -> Maybe Subst
- data Unification = Unification {}
- newtype OrdType = OrdType {
- getOrdType :: Type
- unzipNewWanteds :: Set Unification -> [(Unification, Ct)] -> ([Unification], [Ct])
Documentation
data SolveContext Source #
The context in which we're attempting to solve a constraint.
FunctionDef (Set TyVar) | In the context of a function definition. The |
InterpreterUse Bool (Set TyVar) | In the context of running an interpreter. The |
Instances
Outputable SolveContext Source # | |
Defined in Polysemy.Plugin.Fundep.Unification ppr :: SolveContext -> SDoc # | |
Eq SolveContext Source # | |
Defined in Polysemy.Plugin.Fundep.Unification (==) :: SolveContext -> SolveContext -> Bool # (/=) :: SolveContext -> SolveContext -> Bool # | |
Ord SolveContext Source # | |
Defined in Polysemy.Plugin.Fundep.Unification compare :: SolveContext -> SolveContext -> Ordering # (<) :: SolveContext -> SolveContext -> Bool # (<=) :: SolveContext -> SolveContext -> Bool # (>) :: SolveContext -> SolveContext -> Bool # (>=) :: SolveContext -> SolveContext -> Bool # max :: SolveContext -> SolveContext -> SolveContext # min :: SolveContext -> SolveContext -> SolveContext # |
mustUnify :: SolveContext -> Bool Source #
Depending on the context in which we're solving a constraint, we may or
may not want to force a unification of effects. For example, when defining
user code whose type is Member (State Int) r => ...
, if we see get :: Sem
r s
, we should unify s ~ Int
.
:: SolveContext | |
-> Type | wanted |
-> Type | given |
-> Maybe Subst |
Determine whether or not two effects are unifiable.
All free variables in [W] constraints are considered skolems, and thus are not allowed to unify with anything but themselves. This properly handles all cases in which we are unifying ambiguous [W] constraints (which are true type variables) against [G] constraints.
data Unification Source #
A wrapper for two types that we want to say have been unified.
Instances
Eq Unification Source # | |
Defined in Polysemy.Plugin.Fundep.Unification (==) :: Unification -> Unification -> Bool # (/=) :: Unification -> Unification -> Bool # | |
Ord Unification Source # | |
Defined in Polysemy.Plugin.Fundep.Unification compare :: Unification -> Unification -> Ordering # (<) :: Unification -> Unification -> Bool # (<=) :: Unification -> Unification -> Bool # (>) :: Unification -> Unification -> Bool # (>=) :: Unification -> Unification -> Bool # max :: Unification -> Unification -> Unification # min :: Unification -> Unification -> Unification # |
Type
s don't have Eq
or Ord
instances by default, even though there
are functions in GHC that implement these operations. This newtype gives us
those instances.
unzipNewWanteds :: Set Unification -> [(Unification, Ct)] -> ([Unification], [Ct]) Source #
Filter out the unifications we've already emitted, and then give back the
things we should put into the S.Set Unification
, and the new constraints
we should emit.