polysemy-0.2.0.0: Higher-order, low-boilerplate, zero-cost free monads.

Safe HaskellNone
LanguageHaskell2010

Polysemy.Internal.CustomErrors

Synopsis

Documentation

type family AmbiguousSend r e where ... Source #

Equations

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 #

Equations

Break _ T1 = ((), ()) 
Break _ c = () 

type FirstOrder m e fn = 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.

Note that the parameter m is only required to work around supporting versions of GHC without QuantifiedConstraints

type family UnhandledEffect z e where ... Source #

Equations

UnhandledEffect z e = BreakSym z e (TypeError (UnhandledEffectMsg e)) (DefiningModuleForEffect e) 

type family DefiningModule (t :: k) :: Symbol Source #

Instances
type DefiningModule Resource Source # 
Instance details

Defined in Polysemy.Resource

type DefiningModule Resource = "Polysemy.Resource"
type DefiningModule Reader Source # 
Instance details

Defined in Polysemy.Reader

type DefiningModule Reader = "Polysemy.Reader"
type DefiningModule Writer Source # 
Instance details

Defined in Polysemy.Writer

type DefiningModule Writer = "Polysemy.Writer"
type DefiningModule (Error :: Type -> (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Polysemy.Error

type DefiningModule (Error :: Type -> (k -> Type) -> k -> Type) = "Polysemy.Error"
type DefiningModule (State :: Type -> k -> Type -> Type) Source # 
Instance details

Defined in Polysemy.State

type DefiningModule (State :: Type -> k -> Type -> Type) = "Polysemy.State"
type DefiningModule (Output :: Type -> k -> Type -> Type) Source # 
Instance details

Defined in Polysemy.Output

type DefiningModule (Output :: Type -> k -> Type -> Type) = "Polysemy.Output"
type DefiningModule (Random :: k -> Type -> Type) Source # 
Instance details

Defined in Polysemy.Random

type DefiningModule (Random :: k -> Type -> Type) = "Polysemy.Random"
type DefiningModule (Trace :: k -> Type -> Type) Source # 
Instance details

Defined in Polysemy.Trace

type DefiningModule (Trace :: k -> Type -> Type) = "Polysemy.Trace"
type DefiningModule (Input :: k1 -> k2 -> k1 -> Type) Source # 
Instance details

Defined in Polysemy.Input

type DefiningModule (Input :: k1 -> k2 -> k1 -> Type) = "Polysemy.Input"