mtl-2.3.1: Monad classes for transformers, using functional dependencies
Copyright(C) Koz Ross 2022
LicenseBSD-3-Clause (see the LICENSE file)
Maintainerkoz.ross@retro-freedom.nz
StabilityExperimental
PortabilityGHC only
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Monad.Select

Description

Computation type:
Backtracking search, with r as a 'ranking' or 'evaluation' type.
Binding strategy:
Binding a function to a monadic value 'chains together' strategies; having seen the result of one search, decide which policy to use to continue.
Useful for:
Search problems.
Zero and plus:
None.
Example type:
Select r a

A note on commutativity

Some effects are commutative: it doesn't matter which you resolve first, as all possible orderings of commutative effects are isomorphic. Consider, for example, the reader and state effects, as exemplified by ReaderT and StateT respectively. If we have ReaderT r (State s) a, this is effectively r -> State s a ~ r -> s -> (a, s); if we instead have StateT s (Reader r) a, this is effectively s -> Reader r (a, s) ~ s -> r -> (a, s). Since we can always reorder function arguments (for example, using flip, as in this case) without changing the result, these are isomorphic, showing that reader and state are commutative, or, more precisely, commute with each other.

However, this isn't generally the case. Consider instead the error and state effects, as exemplified by MaybeT and StateT respectively. If we have MaybeT (State s) a, this is effectively State s (Maybe a) ~ s -> (Maybe a, s): put simply, the error can occur only in the result, but not the state, which always 'survives'. On the other hand, if we have StateT s Maybe a, this is instead s -> Maybe (a, s): here, if we error, we lose both the state and the result! Thus, error and state effects do not commute with each other.

As the MTL is capability-based, we support any ordering of non-commutative effects on an equal footing. Indeed, if you wish to use MonadState, for example, whether your final monadic stack ends up being MaybeT (State s) a, StateT s Maybe a, or anything else, you will be able to write your desired code without having to consider such differences. However, the way we implement these capabilities for any given transformer (or rather, any given transformed stack) is affected by this ordering unless the effects in question are commutative.

We note in this module which effects the accumulation effect does and doesn't commute with; we also note on implementations with non-commutative transformers what the outcome will be. Note that, depending on how the 'inner monad' is structured, this may be more complex than we note: we describe only what impact the 'outer effect' has, not what else might be in the stack.

Commutativity of selection

The selection effect commutes with the identity effect (IdentityT), but nothing else.

Synopsis

Type class

class Monad m => MonadSelect r (m :: Type -> Type) | m -> r where Source #

The capability to search with backtracking. Essentially describes a 'policy function': given the state of the search (and a 'ranking' or 'evaluation' of each possible result so far), pick the result that's currently best.

Laws

Any instance of MonadSelect must follow these laws:

Since: mtl-2.3

Methods

select :: ((a -> r) -> a) -> m a Source #

Instances

Instances details
MonadSelect r m => MonadSelect r (MaybeT m) Source #

'Extends' the possibilities considered by m to include Nothing; this means that Nothing gains a 'rank' (namely, a value of r), and the potential result could also be Nothing.

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> r) -> a) -> MaybeT m a Source #

(MonadTrans t, MonadSelect r m, Monad (t m)) => MonadSelect r (LiftingSelect t m) Source #

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> r) -> a) -> LiftingSelect t m a Source #

(MonadSelect r m, Monoid w) => MonadSelect r (AccumT w m) Source #

'Readerizes' the accumulator: the 'ranking' function can see the value that has been accumulated (of type w), but can't add anything to it. Effectively, can be thought of as 'extending' the 'ranking' by all values of w, but which w gets given to any rank calls is predetermined by the 'outer accumulation' (and cannot change).

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> r) -> a) -> AccumT w m a Source #

MonadSelect r m => MonadSelect r (ExceptT e m) Source #

'Extends' the possibilities considered by m to include every value of e; this means that the potential result could be either a Left (making it a choice of type e) or a Right (making it a choice of type a).

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> r) -> a) -> ExceptT e m a Source #

MonadSelect r m => MonadSelect r (IdentityT m) Source #

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> r) -> a) -> IdentityT m a Source #

MonadSelect r (SelectT r Identity) Source #

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> r) -> a) -> SelectT r Identity a Source #

MonadSelect r' m => MonadSelect r' (ReaderT r m) Source #

Provides a read-only environment of type r to the 'strategy' function. However, the 'ranking' function (or more accurately, representation) has no access to r. Put another way, you can influence what values get chosen by changing r, but not how solutions are ranked.

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> r') -> a) -> ReaderT r m a Source #

MonadSelect w m => MonadSelect w (StateT s m) Source #

'Readerizes' the state: the 'ranking' function can see a value of type s, but not modify it. Effectively, can be thought of as 'extending' the 'ranking' by all values in s, but which s gets given to any rank calls is predetermined by the 'outer state' (and cannot change).

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> w) -> a) -> StateT s m a Source #

MonadSelect w m => MonadSelect w (StateT s m) Source #

'Readerizes' the state: the 'ranking' function can see a value of type s, but not modify it. Effectively, can be thought of as 'extending' the 'ranking' by all values in s, but which s gets given to any rank calls is predetermined by the 'outer state' (and cannot change).

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> w) -> a) -> StateT s m a Source #

MonadSelect w' m => MonadSelect w' (WriterT w m) Source #

'Readerizes' the writer: the 'ranking' function can see the value that's been accumulated (of type w), but can't add anything to the log. Effectively, can be thought of as 'extending' the 'ranking' by all values of w, but which w gets given to any rank calls is predetermined by the 'outer writer' (and cannot change).

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> w') -> a) -> WriterT w m a Source #

(MonadSelect w' m, Monoid w) => MonadSelect w' (WriterT w m) Source #

'Readerizes' the writer: the 'ranking' function can see the value that's been accumulated (of type w), but can't add anything to the log. Effectively, can be thought of as 'extending' the 'ranking' by all values of w, but which w gets given to any rank calls is predetermined by the 'outer writer' (and cannot change).

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> w') -> a) -> WriterT w m a Source #

(MonadSelect w' m, Monoid w) => MonadSelect w' (WriterT w m) Source #

'Readerizes' the writer: the 'ranking' function can see the value that's been accumulated (of type w), but can't add anything to the log. Effectively, can be thought of as 'extending' the 'ranking' by all values of w, but which w gets given to any rank calls is predetermined by the 'outer writer' (and cannot change).

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> w') -> a) -> WriterT w m a Source #

MonadSelect r' m => MonadSelect r' (ContT r m) Source #

The continuation describes a way of choosing a 'search' or 'ranking' strategy for r, based on a 'ranking' using r', given any a. We then get a 'search' strategy for r.

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> r') -> a) -> ContT r m a Source #

MonadSelect w' m => MonadSelect w' (RWST r w s m) Source #

A combination of an 'outer' ReaderT, WriterT and StateT. In short, you get a value of type r which can influence what gets picked, but not how anything is ranked, and the 'ranking' function gets access to an s and a w, but can modify neither.

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> w') -> a) -> RWST r w s m a Source #

(MonadSelect w' m, Monoid w) => MonadSelect w' (RWST r w s m) Source #

A combination of an 'outer' ReaderT, WriterT and StateT. In short, you get a value of type r which can influence what gets picked, but not how anything is ranked, and the 'ranking' function gets access to an s and a w, but can modify neither.

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> w') -> a) -> RWST r w s m a Source #

(MonadSelect w' m, Monoid w) => MonadSelect w' (RWST r w s m) Source #

A combination of an 'outer' ReaderT, WriterT and StateT. In short, you get a value of type r which can influence what gets picked, but not how anything is ranked, and the 'ranking' function gets access to an s and a w, but can modify neither.

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> w') -> a) -> RWST r w s m a Source #

Lifting helper type

newtype LiftingSelect (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) a Source #

A helper type to decrease boilerplate when defining new transformer instances of MonadSelect.

Most of the instances in this module are derived using this method; for example, our instance of ExceptT is derived as follows:

deriving via (LiftingSelect (ExceptT e) m) instance (MonadSelect r m) =>
 MonadSelect r (ExceptT e m)

Since: mtl-2.3

Constructors

LiftingSelect (t m a) 

Instances

Instances details
(MonadTrans t, MonadSelect r m, Monad (t m)) => MonadSelect r (LiftingSelect t m) Source #

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

select :: ((a -> r) -> a) -> LiftingSelect t m a Source #

Applicative (t m) => Applicative (LiftingSelect t m) Source #

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

pure :: a -> LiftingSelect t m a #

(<*>) :: LiftingSelect t m (a -> b) -> LiftingSelect t m a -> LiftingSelect t m b #

liftA2 :: (a -> b -> c) -> LiftingSelect t m a -> LiftingSelect t m b -> LiftingSelect t m c #

(*>) :: LiftingSelect t m a -> LiftingSelect t m b -> LiftingSelect t m b #

(<*) :: LiftingSelect t m a -> LiftingSelect t m b -> LiftingSelect t m a #

Functor (t m) => Functor (LiftingSelect t m) Source #

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

fmap :: (a -> b) -> LiftingSelect t m a -> LiftingSelect t m b #

(<$) :: a -> LiftingSelect t m b -> LiftingSelect t m a #

Monad (t m) => Monad (LiftingSelect t m) Source #

Since: mtl-2.3

Instance details

Defined in Control.Monad.Select

Methods

(>>=) :: LiftingSelect t m a -> (a -> LiftingSelect t m b) -> LiftingSelect t m b #

(>>) :: LiftingSelect t m a -> LiftingSelect t m b -> LiftingSelect t m b #

return :: a -> LiftingSelect t m a #