monad-levels-0.1.0.0: Specific levels of monad transformers

Copyright(c) Ivan Lazar Miljenovic
License3-Clause BSD-style
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Levels

Contents

Description

 

Synopsis

Monadic stacks

class (Applicative m, Monad m) => MonadTower_ m Source

Monads in a monadic stack.

For monads that are not instances of MonadicLevel_ then it suffices to say instance MonadTower_ MyMonad; for levels it is required to define BaseMonad (typically recursively).

You should use MonadTower in any constraints rather than this class. This includes when writing instances of MonadTower_ for monadic transformers.

Associated Types

type BaseMonad m :: * -> * Source

type MonadTower m = (MonadTower_ m, MonadTower_ (BaseMonad m), BaseMonad (BaseMonad m) ~ BaseMonad m, BaseMonad m ~ BaseMonad (BaseMonad m)) Source

This is MonadTower_ with additional sanity constraints to ensure that applying BaseMonad is idempotent.

class (MonadTower m, MonadTower (LowerMonad m), BaseMonad m ~ BaseMonad (LowerMonad m), BaseMonad (LowerMonad m) ~ BaseMonad m, CanAddInternalM m) => MonadLevel_ m where Source

How to handle wrappers around existing MonadTower instances.

For newtype wrappers (e.g. IdentityT), it is sufficient to only define LowerMonad.

You should use MonadLevel rather than this class in constraints.

Minimal complete definition

Nothing

Associated Types

type LowerMonad m :: * -> * Source

type InnerValue m a :: * Source

How the value is represented internally; defaults to a.

type WithLower_ m :: (* -> *) -> * -> * Source

An instance of AddInternalM; this is defined so as to be able to make it easier to add constraints rather than solely relying upon its value within Unwrapper.

type AllowOtherValues m :: Bool Source

Within the continuation for wrap for m a, we can unwrap any m b if AllowOtherValues m ~ True; otherwise, we can only unwrap m a. Defaults to True.

type DefaultAllowConstraints m :: Bool Source

By default, should all constraints be allowed through this level? Defaults to True.

Methods

wrap :: CanUnwrap m a b => Proxy a -> Unwrapper m a (LowerMonadValue m b) -> m b Source

A continuation-based approach to create a value of this level.

A default is provided for newtype wrappers around existing MonadTower instances, provided that - with the exception of LowerMonad - all associated types are left as their defaults.

type MonadLevel m = (MonadLevel_ m, (Forall (CanUnwrapSelf m), WithLowerC m)) Source

This is MonadLevel_ with some additional sanity constraints.

Helper types/aliases

type Unwrapper m a t = (forall b. CanUnwrap m a b => m b -> LowerMonadValue m b) -> WithLower m a -> t Source

A continuation function to produce a value of type t.

type LowerMonadValue m a = LowerMonad m (InnerValue m a) Source

The value contained within the actual level (e.g. for StateT s m a, this is equivalent to m (a,s)).

class (MonadLevel_ m, CanUnwrap_ m a b) => CanUnwrap m a b Source

If we're dealing overall with m a, then this allows us to specify those b values for which we can also manipulate m b.

If AllowOtherValues m ~ False then we require that a ~ b; otherwise, any b is accepted.

Instances

(MonadLevel_ m, CanUnwrap_ m a b) => CanUnwrap m a b 
MonadLevel_ m => Class (MonadLevel_ m, CanUnwrap m a a) (CanUnwrapSelf m a) 

class (MonadLevel_ m, CanUnwrap m a a) => CanUnwrapSelf m a Source

Used to ensure that for all monad levels, CanUnwrap m a a is satisfied.

Instances

Manipulating internal values

class AddInternalM ai where Source

Associated Types

type AddConstraint ai m :: Constraint Source

Methods

addInternalM :: (MonadLevel m, WithLower_ m ~ ai, CanUnwrap m a b) => ai m a -> LowerMonad m b -> LowerMonadValue m b Source

newtype AddIM m a Source

Used for monad transformers like ContT where it is not possible to manipulate the internal value without considering the monad that it is within.

Constructors

AddIM 

Fields

addIMFunc :: forall b. CanUnwrap m a b => LowerMonad m b -> LowerMonadValue m b
 

Instances

class AddInternalM ai => AddInternal ai where Source

Methods

addInternal :: (MonadLevel m, WithLower_ m ~ ai, CanUnwrap m a b) => ai m a -> b -> InnerValue m b Source

mapInternal :: (MonadLevel m, WithLower_ m ~ ai, CanUnwrap m a b, CanUnwrap m a c) => ai m a -> (b -> c) -> InnerValue m b -> InnerValue m c Source

data AddI m a Source

In most cases you will want to use AddIG instead of this; this is defined for cases like ListT where it may not be possible to obtain either zero or one value for use with getInternal.

Constructors

AddI 

Fields

setIFunc :: forall b. CanUnwrap m a b => b -> InnerValue m b
 
mapIFunc :: forall b c. (CanUnwrap m a b, CanUnwrap m a c) => (b -> c) -> InnerValue m b -> InnerValue m c
 

data AddIdent m a Source

Used for monad transformers where InnerValue m a ~ a.

Constructors

AddIdent 

class AddInternal ai => GetInternal ai where Source

Methods

getInternal :: (MonadLevel m, WithLower_ m ~ ai, CanUnwrap m a b) => ai m a -> c -> (b -> c) -> InnerValue m b -> c Source

This is like a lifted maybe function that applies to InnerValue values rather than just Maybes.

data AddIG m a Source

Used for monad transformers where it is possible to consider the InnerValue in isolation. If InnerValue m a ~ a then use AddIdent instead.

Constructors

AddIG 

Fields

setIUFunc :: forall b. CanUnwrap m a b => b -> InnerValue m b
 
mapIUFunc :: forall b c. (CanUnwrap m a b, CanUnwrap m a c) => (b -> c) -> InnerValue m b -> InnerValue m c
 
getIUFunc :: forall b c. CanUnwrap m a b => c -> (b -> c) -> InnerValue m b -> c
 

Basic level manipulation

lift :: forall m a. MonadLevel m => LowerMonad m a -> m a Source

Lifting from the base

type HasBaseMonad m = SatisfyConstraint IsBaseMonad m Source

Ideally, this alias would not be needed as every instance of MonadTower should satisfy the required constraint. However, this is needed for technical reasons.

type BaseMonadOf b m = (HasBaseMonad m, BaseMonad m ~ b, b ~ BaseMonad m) Source

liftIO :: BaseMonadOf IO m => IO a -> m a Source

An alias defined for convenience with existing code.

Lifting from a specific transformer

type HasTransformer t m = (SatisfyConstraint (IsTransformer t) m, MonadLevel (TransformedMonad t m), TransformedMonad t m ~ t (LowerMonad (TransformedMonad t m))) Source

Unlike HasBaseMonad, this is not a universal constraint applicable to all MonadLevel instances, as otherwise it can be used to bypass the lack of an allowed constraint.

type TransformedMonad t m = SatMonad (IsTransformer t) m Source

The sub-part of the monadic stack where the requested transformer is on top.