simple-effects-0.10.0.0: A simple effect system that integrates with MTL

Safe HaskellSafe
LanguageHaskell2010

Control.Effects.Generic

Documentation

data M a Source #

Instances

((~) * b (m x), Monad m) => MonadicMethod * a b (M * x) m Source # 

Methods

mergeMethod :: Proxy a m -> (b m -> M * x) -> m (b m) -> M * x Source #

(MonadTrans t, Monad m, (~) * a (m x)) => SimpleMethod * a (M * x) m t Source # 

Associated Types

type LiftedMethod a (M * x) (m :: a) (t :: * -> *) (t :: (* -> *) -> * -> *) :: * Source #

Methods

liftMethod :: Proxy (* -> *) t -> Proxy ((* -> *) -> * -> *) t -> Proxy a m -> M * x -> LiftedMethod a (M * x) m t t Source #

TypeError Constraint ((:<>:) ((:<>:) (Text "Parameters of methods can't depend on the monadic context (") (ShowType (* -> *) m)) (Text ")")) => IndependentOfM (k -> *) (M k) m Source # 
type LiftedMethod * a (M * x) m t Source # 
type LiftedMethod * a (M * x) m t = t m x

class (Generic (a m), Generic (a (t m)), Generic (a M)) => SimpleMethods a m t where Source #

Minimal complete definition

liftSimple

Methods

liftSimple :: a m -> a (t m) Source #

Instances

((~) (* -> *) (Rep (a m)) (D1 * m1 (C1 * m2 p)), (~) (* -> *) (Rep (a (M k))) (D1 * m1 (C1 * m2 pM)), (~) (* -> *) (Rep (a (t m))) (D1 * m1 (C1 * m2 (LiftedProducts (* -> *) (k -> *) ((k -> *) -> k -> *) p pM m t))), ProductOfSimpleMethods (* -> *) (k -> *) ((k -> *) -> k -> *) p pM m t, Generic (a m), Generic (a (t m)), Generic (a (M k))) => SimpleMethods k a m t Source # 

Methods

liftSimple :: m t -> m (t t) Source #

class ProductOfSimpleMethods p pM m t where Source #

Minimal complete definition

liftProducts

Associated Types

type LiftedProducts p pM m t :: * -> * Source #

Methods

liftProducts :: Proxy m -> Proxy t -> Proxy pM -> p x -> LiftedProducts p pM m t x Source #

Instances

(ProductOfSimpleMethods (k3 -> *) k2 k1 f1 f1M m t, ProductOfSimpleMethods (k3 -> *) k2 k1 f2 f2M m t) => ProductOfSimpleMethods (k3 -> *) k2 k1 ((:*:) * f1 f2) ((:*:) k3 f1M f2M) m t Source # 

Associated Types

type LiftedProducts ((* :*: f1) f2) ((k3 :*: f1M) f2M) m (t :: * -> *) (pM :: (* :*: f1) f2) (m :: (k3 :*: f1M) f2M) (t :: m) :: * -> * Source #

Methods

liftProducts :: Proxy ((k3 :*: f1M) f2M) m -> Proxy m t -> Proxy ((* :*: f1) f2) pM -> t x -> LiftedProducts ((* :*: f1) f2) ((k3 :*: f1M) f2M) m t pM m t x Source #

SimpleMethod * f fM m t => ProductOfSimpleMethods (k -> *) (* -> *) ((* -> *) -> * -> *) (S1 * m1 (Rec0 * f)) (S1 k m1 (Rec0 k fM)) m t Source # 

Associated Types

type LiftedProducts (S1 * m1 (Rec0 * f)) (S1 k m1 (Rec0 k fM)) m (t :: * -> *) (pM :: S1 * m1 (Rec0 * f)) (m :: S1 k m1 (Rec0 k fM)) (t :: m) :: * -> * Source #

Methods

liftProducts :: Proxy (S1 k m1 (Rec0 k fM)) m -> Proxy m t -> Proxy (S1 * m1 (Rec0 * f)) pM -> t x -> LiftedProducts (S1 * m1 (Rec0 * f)) (S1 k m1 (Rec0 k fM)) m t pM m t x Source #

class (MonadTrans t, Monad m) => SimpleMethod f fM (m :: * -> *) (t :: (* -> *) -> * -> *) where Source #

Minimal complete definition

liftMethod

Associated Types

type LiftedMethod f fM m t Source #

Methods

liftMethod :: Proxy m -> Proxy t -> Proxy fM -> f -> LiftedMethod f fM m t Source #

Instances

(TypeError Constraint (Text "Effect methods must be monadic actions or functions resulting in monadic actions"), Monad m, MonadTrans t) => SimpleMethod k a b m t Source # 

Associated Types

type LiftedMethod a b (m :: a) (t :: * -> *) (t :: (* -> *) -> * -> *) :: * Source #

Methods

liftMethod :: Proxy (* -> *) t -> Proxy ((* -> *) -> * -> *) t -> Proxy a m -> b -> LiftedMethod a b m t t Source #

((~) * f (a -> b), SimpleMethod * b bM m t, IndependentOfM * a m) => SimpleMethod * f (a -> bM) m t Source # 

Associated Types

type LiftedMethod f (a -> bM) (m :: f) (t :: * -> *) (t :: (* -> *) -> * -> *) :: * Source #

Methods

liftMethod :: Proxy (* -> *) t -> Proxy ((* -> *) -> * -> *) t -> Proxy f m -> (a -> bM) -> LiftedMethod f (a -> bM) m t t Source #

(MonadTrans t, Monad m, (~) * a (m x)) => SimpleMethod * a (M * x) m t Source # 

Associated Types

type LiftedMethod a (M * x) (m :: a) (t :: * -> *) (t :: (* -> *) -> * -> *) :: * Source #

Methods

liftMethod :: Proxy (* -> *) t -> Proxy ((* -> *) -> * -> *) t -> Proxy a m -> M * x -> LiftedMethod a (M * x) m t t Source #

type family FuncRes f where ... Source #

Equations

FuncRes (a -> b) = b 

class IndependentOfM (a :: k) (m :: * -> *) Source #

Instances

IndependentOfM k a m Source # 
(IndependentOfM (k1 -> k2) a m, IndependentOfM k1 b m) => IndependentOfM k2 (a b) m Source # 
TypeError Constraint ((:<>:) ((:<>:) (Text "Parameters of methods can't depend on the monadic context (") (ShowType (* -> *) m)) (Text ")")) => IndependentOfM (k -> *) (M k) m Source # 

genericLiftThrough :: forall t e em m. (MonadTrans t, Monad m, Monad (t m), SimpleMethods (em e) m t) => em e m -> em e (t m) Source #

class MonadicMethods a m where Source #

Minimal complete definition

mergeMonadicMethods

Methods

mergeMonadicMethods :: m (a m) -> a m Source #

Instances

((~) (* -> *) (Rep (a m)) (D1 * m1 (C1 * m2 p)), (~) (* -> *) (Rep (a (M *))) (D1 * m1 (C1 * m2 pM)), ProductOfMonadicMethods * (* -> *) p pM a m, Generic (a m), Generic (a (M *))) => MonadicMethods a m Source # 

Methods

mergeMonadicMethods :: m (a m) -> a m Source #

class ProductOfMonadicMethods p pM a m where Source #

Minimal complete definition

mergeMonadicProducts

Methods

mergeMonadicProducts :: Proxy p -> Proxy pM -> m (a m) -> (a m -> p x) -> p x Source #

Instances

(ProductOfMonadicMethods k2 (k1 -> *) f1 f1M a m, ProductOfMonadicMethods k2 (k1 -> *) f2 f2M a m) => ProductOfMonadicMethods k2 (k1 -> *) ((:*:) k2 f1 f2) ((:*:) k1 f1M f2M) a m Source # 

Methods

mergeMonadicProducts :: Proxy ((k2 :*: f1) f2 -> *) a -> Proxy ((k1 :*: f1M) f2M) m -> m (a m) -> (a m -> a x) -> a x Source #

MonadicMethod * a f fM m => ProductOfMonadicMethods k1 (k2 -> *) (S1 k1 m1 (Rec0 k1 f)) (S1 k2 m1 (Rec0 k2 fM)) a m Source # 

Methods

mergeMonadicProducts :: Proxy (S1 k1 m1 (Rec0 k1 f) -> *) a -> Proxy (S1 k2 m1 (Rec0 k2 fM)) m -> m (a m) -> (a m -> a x) -> a x Source #

class Monad m => MonadicMethod a f fM m where Source #

Minimal complete definition

mergeMethod

Methods

mergeMethod :: Proxy fM -> (a m -> f) -> m (a m) -> f Source #

Instances

(TypeError Constraint (Text "Effect methods must be monadic actions or functions resulting in monadic actions"), Monad m) => MonadicMethod k a f fM m Source # 

Methods

mergeMethod :: Proxy a m -> (f m -> fM) -> m (f m) -> fM Source #

((~) * f (b -> c), Monad m, MonadicMethod * a c cM m) => MonadicMethod * a f (bM -> cM) m Source # 

Methods

mergeMethod :: Proxy a m -> (f m -> bM -> cM) -> m (f m) -> bM -> cM Source #

((~) * b (m x), Monad m) => MonadicMethod * a b (M * x) m Source # 

Methods

mergeMethod :: Proxy a m -> (b m -> M * x) -> m (b m) -> M * x Source #

genericMergeContext :: MonadicMethods a m => m (a m) -> a m Source #