| Copyright | (C) Koz Ross 2022 | 
|---|---|
| License | BSD-3-Clause (see the LICENSE file) | 
| Maintainer | koz.ross@retro-freedom.nz | 
| Stability | Experimental | 
| Portability | GHC only | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Control.Monad.Select
Contents
Description
- Computation type:
- Backtracking search, with ras 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:
- Selectr 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) ar -> ; if we instead have
 State s a ~ r -> s -> (a, s)StateT s (Reader r) as -> . Since we
 can always reorder function arguments (for example, using Reader r (a, s) ~ s -> r -> (a, s)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) aState s (Maybe a) ~ s -> (Maybe a, s)StateT s Maybe as -> : here,
 if we error, we lose both the state and the result! Thus, error and state effects
 do not commute with each other.Maybe (a, s)
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)
 aStateT s Maybe a
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
- class Monad m => MonadSelect r (m :: Type -> Type) | m -> r where- select :: ((a -> r) -> a) -> m a
 
- newtype LiftingSelect (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) a = LiftingSelect (t m a)
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
Instances
| MonadSelect r m => MonadSelect r (MaybeT m) Source # | 'Extends' the possibilities considered by  Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
| (MonadTrans t, MonadSelect r m, Monad (t m)) => MonadSelect r (LiftingSelect t m) Source # | Since: mtl-2.3 | 
| 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  Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
| MonadSelect r m => MonadSelect r (ExceptT e m) Source # | 'Extends' the possibilities considered by  Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
| MonadSelect r m => MonadSelect r (IdentityT m) Source # | Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
| MonadSelect r (SelectT r Identity) Source # | Since: mtl-2.3 | 
| MonadSelect r' m => MonadSelect r' (ReaderT r m) Source # | Provides a read-only environment of type  Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
| MonadSelect w m => MonadSelect w (StateT s m) Source # | 'Readerizes' the state: the 'ranking' function can see a value of
 type  Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
| MonadSelect w m => MonadSelect w (StateT s m) Source # | 'Readerizes' the state: the 'ranking' function can see a value of
 type  Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
| 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  Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
| (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  Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
| (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  Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
| MonadSelect r' m => MonadSelect r' (ContT r m) Source # | The continuation describes a way of choosing a 'search' or 'ranking'
 strategy for  Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
| MonadSelect w' m => MonadSelect w' (RWST r w s m) Source # | A combination of an 'outer'  Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
| (MonadSelect w' m, Monoid w) => MonadSelect w' (RWST r w s m) Source # | A combination of an 'outer'  Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
| (MonadSelect w' m, Monoid w) => MonadSelect w' (RWST r w s m) Source # | A combination of an 'outer'  Since: mtl-2.3 | 
| Defined in Control.Monad.Select | |
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) |