Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype WrapC (e :: Effect) (e' :: Effect) m (a :: *) = WrapC (m a)
- wrap :: (Member e (Derivs m), Carrier m, Coercible unwrappedE e) => WrapC unwrappedE e m a -> m a
- wrapWith :: (Member e (Derivs m), Carrier m, Coercible unwrappedE e) => (unwrappedE z x -> e z x) -> WrapC unwrappedE e m a -> m a
- newtype UnwrapC (e :: Effect) m (a :: *) = UnwrapC (m a)
- unwrap :: forall e m a. (Carrier m, Member (UnwrappedEff e) (Derivs m), EffNewtype e) => UnwrapC e m a -> m a
- newtype UnwrapTopC (e :: Effect) m (a :: *) = UnwrapTopC (m a)
- unwrapTop :: forall e m a. (HeadEff (UnwrappedEff e) m, EffNewtype e, Carrier m) => UnwrapTopC e m a -> m a
- class EffNewtype (e :: Effect) where
- type UnwrappedEff e :: Effect
- unwrapped :: e z x -> UnwrappedEff e z x
- newtype WrapperOf (e :: Effect) (e' :: Effect) m a = WrapperOf (e m a)
Documentation
newtype WrapC (e :: Effect) (e' :: Effect) m (a :: *) Source #
WrapC (m a) |
Instances
wrap :: (Member e (Derivs m), Carrier m, Coercible unwrappedE e) => WrapC unwrappedE e m a -> m a Source #
wrapWith :: (Member e (Derivs m), Carrier m, Coercible unwrappedE e) => (unwrappedE z x -> e z x) -> WrapC unwrappedE e m a -> m a Source #
Wrap uses of an effect, injecting them into a newtype of that effect. The first argument is ignored.
This is useful for creating actions of effect newtypes. For example:
newtype Counter m a = Counter (State
Int m) probe :: Eff Counter m => m Int probe =wrapWith
Counter $state'
@Int (\s -> (s + 1, s))
newtype UnwrapC (e :: Effect) m (a :: *) Source #
UnwrapC (m a) |
Instances
unwrap :: forall e m a. (Carrier m, Member (UnwrappedEff e) (Derivs m), EffNewtype e) => UnwrapC e m a -> m a Source #
Unwrap uses of an effect
newtype UnwrapTopC (e :: Effect) m (a :: *) Source #
UnwrapTopC (m a) |
Instances
unwrapTop :: forall e m a. (HeadEff (UnwrappedEff e) m, EffNewtype e, Carrier m) => UnwrapTopC e m a -> m a Source #
Unwrap uses of an effect, placing its unwrapped version on top of the effect stack.
class EffNewtype (e :: Effect) where Source #
Nothing
type UnwrappedEff e :: Effect Source #
unwrapped :: e z x -> UnwrappedEff e z x Source #
default unwrapped :: Coercible e (UnwrappedEff e) => e z x -> UnwrappedEff e z x Source #
Instances
EffNewtype Conc Source # | |
Defined in Control.Effect.Internal.Conc type UnwrappedEff Conc :: Effect Source # | |
Coercible e e' => EffNewtype (WrapperOf e e') Source # | |
Defined in Control.Effect.Internal.Newtype type UnwrappedEff (WrapperOf e e') :: Effect Source # |
newtype WrapperOf (e :: Effect) (e' :: Effect) m a Source #
Useful for deriving instances of EffNewtype
.
newtype SomeWrapper m a = SomeWrapper (SomeEffect m a) derivingEffNewtype
via SomeWrapper `WrapperOf
` SomeEffect
WrapperOf (e m a) |
Instances
Coercible e e' => EffNewtype (WrapperOf e e') Source # | |
Defined in Control.Effect.Internal.Newtype type UnwrappedEff (WrapperOf e e') :: Effect Source # | |
type UnwrappedEff (WrapperOf e e') Source # | |
Defined in Control.Effect.Internal.Newtype |