in-other-words-0.1.0.0: A higher-order effect system where the sky's the limit
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Type.Optional

Synopsis

Effects

data Optional s m a where Source #

A helper primitive effect for manipulating a region, with the option to execute it in full or in part. s is expected to be a functor.

Helper primitive effects are effects that allow you to avoid interpreting one of your own effects as a primitive if the power needed from direct access to the underlying monad can instead be provided by the relevant helper primitive effect. The reason why you'd want to do this is that helper primitive effects already have ThreadsEff instances defined for them, so you don't have to define any for your own effect.

The helper primitive effects offered in this library are -- in order of ascending power -- Regional, Optional, BaseControl and Unlift.

The typical use-case of Optional is to lift a natural transformation of a base monad equipped with the power to recover from an exception. HoistOption and accompanying interpreters is provided as a specialization of Optional for this purpose.

Optional in its most general form lacks a pre-defined interpreter: when not using HoistOption, you're expected to define your own interpreter for Optional (treating it as a primitive effect).

Optional is typically used as a primitive effect. If you define a Carrier that relies on a novel non-trivial monad transformer t, then you need to make a Functor s => ThreadsEff t (Optional s) instance (if possible). threadOptionalViaBaseControl can help you with that.

The following threading constraints accept Optional:

Constructors

Optionally :: s a -> m a -> Optional s m a 

Instances

Instances details
Carrier m => PrimHandler HoistOptionH (HoistOption m) m Source # 
Instance details

Defined in Control.Effect.Internal.Optional

Functor s => ThreadsEff ListT (Optional s) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (ListT m) a -> ListT m a Source #

Functor s => ThreadsEff (ExceptT e) (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (ExceptT e m) a -> ExceptT e m a Source #

(Functor s, Monoid w) => ThreadsEff (WriterT w) (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (WriterT w m) a -> WriterT w m a Source #

Functor s => ThreadsEff (StateT s') (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (StateT s' m) a -> StateT s' m a Source #

ThreadsEff (ReaderT i) (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (ReaderT i m) a -> ReaderT i m a Source #

Functor s => ThreadsEff (StateT s') (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (StateT s' m) a -> StateT s' m a Source #

(Functor s, Monoid w) => ThreadsEff (WriterT w) (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (WriterT w m) a -> WriterT w m a Source #

(Functor s, Monoid w) => ThreadsEff (WriterT w) (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (WriterT w m) a -> WriterT w m a Source #

Functor s => ThreadsEff (FreeT f) (Optional s) Source # 
Instance details

Defined in Control.Monad.Trans.Free.Church.Alternate

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (FreeT f m) a -> FreeT f m a Source #

Threading utilities

threadRegionalViaOptional :: (ThreadsEff t (Optional (Const s)), Monad m) => (forall x. Regional s m x -> m x) -> Regional s (t m) a -> t m a Source #

A valid definition of threadEff for a ThreadsEff (Regional s) t instance, given that t threads Optional f for any functor f.