Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
- zoom :: Monad m => LensLike' (Zooming m c) a b -> StateT b m c -> StateT a m c
- use :: MonadState a m => FoldLike b a a' b b' -> m b
- uses :: MonadState a m => FoldLike r a a' b b' -> (b -> r) -> m r
- (%=) :: MonadState a m => Setter a a b b' -> (b -> b') -> m ()
- assign :: MonadState a m => Setter a a b b' -> b' -> m ()
- (.=) :: MonadState a m => Setter a a b b' -> b' -> m ()
- (%%=) :: MonadState a m => LensLike (Writer c) a a b b' -> (b -> (c, b')) -> m c
- (<~) :: MonadState a m => Setter a a b b' -> m b' -> m ()
- (+=) :: (MonadState a m, Num b) => Setter' a b -> b -> m ()
- (-=) :: (MonadState a m, Num b) => Setter' a b -> b -> m ()
- (*=) :: (MonadState a m, Num b) => Setter' a b -> b -> m ()
- (//=) :: (MonadState a m, Fractional b) => Setter' a b -> b -> m ()
- (&&=) :: MonadState a m => Setter' a Bool -> Bool -> m ()
- (||=) :: MonadState a m => Setter' a Bool -> Bool -> m ()
- (<>=) :: (Monoid o, MonadState a m) => Setter' a o -> o -> m ()
- data Zooming m c a :: (* -> *) -> * -> * -> *
- type LensLike f a a' b b' = (b -> f b') -> a -> f a'
- type LensLike' f a b = (b -> f b) -> a -> f a
- type FoldLike r a a' b b' = LensLike (Constant r) a a' b b'
- data Constant a b :: * -> * -> *
- type Setter a a' b b' = forall f. Identical f => LensLike f a a' b b'
- type Setter' a b = forall f. Identical f => LensLike' f a b
- class Applicative f => Identical f
- data StateT s m a :: * -> (* -> *) -> * -> *
- class Monad m => MonadState s m | m -> s
- type Writer w = WriterT w Identity
- class Monoid a
Documentation
zoom :: Monad m => LensLike' (Zooming m c) a b -> StateT b m c -> StateT a m c
zoom :: Monad m => Lens' a b -> StateT b m c -> StateT a m c
Lift a stateful operation on a field to a stateful operation on the whole state. This is a good way to call a "subroutine" that only needs access to part of the state.
zoom :: (Monoid c, Moand m) => Traversal' a b -> StateT b m c -> StateT a m c
Run the "subroutine" on each element of the traversal in turn and mconcat
all the results together.
zoom :: Monad m => Traversal' a b -> StateT b m () -> StateT a m ()
Run the "subroutine" on each element the traversal in turn.
use :: MonadState a m => FoldLike b a a' b b' -> m b Source
use :: MonadState a m => Getter a a' b b' -> m b
Retrieve a field of the state
use :: (Monoid b, MonadState a m) => Fold a a' b b' -> m b
Retrieve a monoidal summary of all the referenced fields from the state
uses :: MonadState a m => FoldLike r a a' b b' -> (b -> r) -> m r Source
uses :: (MonadState a m, Monoid r) => Fold a a' b b' -> (b -> r) -> m r
Retrieve all the referenced fields from the state and foldMap the results together with f :: b -> r
.
uses :: MonadState a m => Getter a a' b b' -> (b -> r) -> m r
Retrieve a field of the state and pass it through the function f :: b -> r
.
uses l f = f <$> use l
(%=) :: MonadState a m => Setter a a b b' -> (b -> b') -> m () infix 4 Source
Modify a field of the state.
assign :: MonadState a m => Setter a a b b' -> b' -> m () Source
Set a field of the state.
(.=) :: MonadState a m => Setter a a b b' -> b' -> m () infix 4 Source
Set a field of the state.
(%%=) :: MonadState a m => LensLike (Writer c) a a b b' -> (b -> (c, b')) -> m c infix 4 Source
(%%=) :: MonadState a m => Lens a a b b' -> (b -> (c, b')) -> m c
Modify a field of the state while returning another value.
(%%=) :: (MonadState a m, Monoid c) => Traversal a a b b' -> (b -> (c, b')) -> m c
Modify each field of the state and return the mconcat
of the other values.
(<~) :: MonadState a m => Setter a a b b' -> m b' -> m () infixr 2 Source
Set a field of the state using the result of executing a stateful command.
Compound Assignments
(+=) :: (MonadState a m, Num b) => Setter' a b -> b -> m () infixr 4 Source
(-=) :: (MonadState a m, Num b) => Setter' a b -> b -> m () infixr 4 Source
(*=) :: (MonadState a m, Num b) => Setter' a b -> b -> m () infixr 4 Source
(//=) :: (MonadState a m, Fractional b) => Setter' a b -> b -> m () infixr 4 Source
(<>=) :: (Monoid o, MonadState a m) => Setter' a o -> o -> m () infixr 4 Source
Monoidally append a value to all referenced fields of the state.
Types
data Zooming m c a :: (* -> *) -> * -> * -> *
Re-exports
type LensLike f a a' b b' = (b -> f b') -> a -> f a'
type LensLike' f a b = (b -> f b) -> a -> f a
data Constant a b :: * -> * -> *
Constant functor.
Functor (Constant a) | |
Monoid a => Applicative (Constant a) | |
Foldable (Constant a) | |
Traversable (Constant a) | |
Phantom (Constant a) | |
Eq a => Eq1 (Constant a) | |
Ord a => Ord1 (Constant a) | |
Read a => Read1 (Constant a) | |
Show a => Show1 (Constant a) | |
Eq a => Eq (Constant a b) | |
Ord a => Ord (Constant a b) | |
Read a => Read (Constant a b) | |
Show a => Show (Constant a b) |
class Applicative f => Identical f
extract
data StateT s m a :: * -> (* -> *) -> * -> *
A state transformer monad parameterized by:
s
- The state.m
- The inner monad.
The return
function leaves the state unchanged, while >>=
uses
the final state of the first computation as the initial state of
the second.
Monad m => MonadState s (StateT s m) | |
MonadTrans (StateT s) | |
(Functor m, MonadPlus m) => Alternative (StateT s m) | |
Monad m => Monad (StateT s m) | |
Functor m => Functor (StateT s m) | |
MonadFix m => MonadFix (StateT s m) | |
MonadPlus m => MonadPlus (StateT s m) | |
(Functor m, Monad m) => Applicative (StateT s m) | |
MonadIO m => MonadIO (StateT s m) |
class Monad m => MonadState s m | m -> s
Minimal definition is either both of get
and put
or just state
MonadState s m => MonadState s (MaybeT m) | |
MonadState s m => MonadState s (ListT m) | |
MonadState s m => MonadState s (IdentityT m) | |
(Monoid w, MonadState s m) => MonadState s (WriterT w m) | |
(Monoid w, MonadState s m) => MonadState s (WriterT w m) | |
Monad m => MonadState s (StateT s m) | |
Monad m => MonadState s (StateT s m) | |
MonadState s m => MonadState s (ReaderT r m) | |
MonadState s m => MonadState s (ExceptT e m) | |
(Error e, MonadState s m) => MonadState s (ErrorT e m) | |
MonadState s m => MonadState s (ContT r m) | |
(Monad m, Monoid w) => MonadState s (RWST r w s m) | |
(Monad m, Monoid w) => MonadState s (RWST r w s m) |
class Monoid a
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:
mappend mempty x = x
mappend x mempty = x
mappend x (mappend y z) = mappend (mappend x y) z
mconcat =
foldr
mappend mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Minimal complete definition: mempty
and mappend
.
Some types can be viewed as a monoid in more than one way,
e.g. both addition and multiplication on numbers.
In such cases we often define newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
Monoid Ordering | |
Monoid () | |
Monoid All | |
Monoid Any | |
Monoid IntSet | |
Monoid [a] | |
Monoid a => Monoid (Dual a) | |
Monoid (Endo a) | |
Num a => Monoid (Sum a) | |
Num a => Monoid (Product a) | |
Monoid (First a) | |
Monoid (Last a) | |
Monoid a => Monoid (Maybe a) | Lift a semigroup into |
Monoid (IntMap a) | |
Ord a => Monoid (Set a) | |
Monoid b => Monoid (a -> b) | |
(Monoid a, Monoid b) => Monoid (a, b) | |
Monoid a => Monoid (Const a b) | |
Monoid (Proxy * s) | |
Ord k => Monoid (Map k v) | |
Typeable (* -> Constraint) Monoid | |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) |