Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type family AmbiguousSend r e where ...
- type family Break (c :: Constraint) (rep :: (* -> *) -> * -> *) :: Constraint where ...
- type FirstOrder e fn = forall m. Coercible (e m) (e (FirstOrderError e fn))
- type family UnhandledEffect z e where ...
- type family DefiningModule (t :: k) :: Symbol
- type family DefiningModuleForEffect (e :: k) :: Symbol where ...
Documentation
type family AmbiguousSend r e where ... Source #
AmbiguousSend r (e a b c d f) = TypeError (AmbigousEffectMessage r e (e a b c d f) '[a, b c d f]) | |
AmbiguousSend r (e a b c d) = TypeError (AmbigousEffectMessage r e (e a b c d) '[a, b c d]) | |
AmbiguousSend r (e a b c) = TypeError (AmbigousEffectMessage r e (e a b c) '[a, b c]) | |
AmbiguousSend r (e a b) = TypeError (AmbigousEffectMessage r e (e a b) '[a, b]) | |
AmbiguousSend r (e a) = TypeError (AmbigousEffectMessage r e (e a) '[a]) | |
AmbiguousSend r e = TypeError (((((((Text "Could not deduce: (Member " :<>: ShowType e) :<>: Text " ") :<>: ShowType r) :<>: Text ") ") :$$: Text "Fix:") :$$: ((((Text " add (Member " :<>: ShowType e) :<>: Text " ") :<>: ShowType r) :<>: Text ") to the context of")) :$$: Text " the type signature") |
type family Break (c :: Constraint) (rep :: (* -> *) -> * -> *) :: Constraint where ... Source #
type FirstOrder e fn = forall m. Coercible (e m) (e (FirstOrderError e fn)) Source #
This constraint gives helpful error messages if you attempt to use a first-order combinator with a higher-order type.
type family UnhandledEffect z e where ... Source #
UnhandledEffect z e = BreakSym z e (TypeError (UnhandledEffectMsg e)) (DefiningModuleForEffect e) |
type family DefiningModule (t :: k) :: Symbol Source #
Instances
type DefiningModule Resource Source # | |
Defined in Polysemy.Resource | |
type DefiningModule Reader Source # | |
Defined in Polysemy.Reader | |
type DefiningModule Writer Source # | |
Defined in Polysemy.Writer | |
type DefiningModule (Error :: Type -> (k -> Type) -> k -> Type) Source # | |
Defined in Polysemy.Error | |
type DefiningModule (State :: Type -> k -> Type -> Type) Source # | |
Defined in Polysemy.State | |
type DefiningModule (Output :: Type -> k -> Type -> Type) Source # | |
Defined in Polysemy.Output | |
type DefiningModule (Random :: k -> Type -> Type) Source # | |
Defined in Polysemy.Random | |
type DefiningModule (Trace :: k -> Type -> Type) Source # | |
Defined in Polysemy.Trace | |
type DefiningModule (Input :: k1 -> k2 -> k1 -> Type) Source # | |
Defined in Polysemy.Input |
type family DefiningModuleForEffect (e :: k) :: Symbol where ... Source #