mezzolens-0.0.0: Pure Profunctor Functional Lenses

Safe HaskellSafe
LanguageHaskell2010

Mezzolens.State.Strict

Synopsis

Documentation

zoom :: Optical' (SubStar (Compose m ((,) c))) ta a -> StateT a m c -> StateT ta m c Source

zoom :: Functor m => Lens' ta a -> StateT a m c -> StateT ta m c
zoom :: (Monoid c, Applicative m) => Traversal' ta a -> StateT a m c -> StateT ta m c

use :: MonadState ta m => Optical (SubStar (Constant a)) ta tb a b -> m a Source

uses :: MonadState ta m => Optical (SubStar (Constant r)) ta tb a b -> (a -> r) -> m r Source

assign :: MonadState ta m => Optical (->) ta ta a b -> b -> m () Source

update :: MonadState ta m => Optical (->) ta ta a b -> (a -> b) -> m () Source

(%=) :: MonadState ta m => Optical (->) ta ta a b -> (a -> b) -> m () infix 4 Source

(.=) :: MonadState ta m => Optical (->) ta ta b1 b -> b -> m () infix 4 Source

(+=) :: (Num b, MonadState ta m) => Optical (->) ta ta b b -> b -> m () infix 4 Source

(-=) :: (Num b, MonadState ta m) => Optical (->) ta ta b b -> b -> m () infix 4 Source

(*=) :: (Num b, MonadState ta m) => Optical (->) ta ta b b -> b -> m () infix 4 Source

(//=) :: (Fractional b, MonadState ta m) => Optical (->) ta ta b b -> b -> m () infix 4 Source

(&&=) :: MonadState ta m => Optical (->) ta ta Bool Bool -> Bool -> m () infix 4 Source

(||=) :: MonadState ta m => Optical (->) ta ta Bool Bool -> Bool -> m () infix 4 Source

(<>=) :: (Monoid b, MonadState ta m) => Optical (->) ta ta b b -> b -> m () infix 4 Source

(%%=) :: MonadState ta m => Optical (SubStar ((,) c)) ta ta a b -> (a -> (c, b)) -> m c infix 4 Source

(%%=) :: MonadState ta m => Lens' ta a -> (a -> (c,a))  -> m c
(%%=) :: (Monoid c, MonadState ta m) => Traversal' ta a -> (a -> (c,a)) -> m c

(<~) :: MonadState ta m => Optical (->) ta ta a b -> m b -> m () infixr 2 Source

type Optical p ta tb a b = p a b -> p ta tb Source

type Optical' p ta a = p a a -> p ta ta Source

data Constant a b :: * -> * -> *

Constant functor.

Instances

Functor (Constant a) 
Monoid a => Applicative (Constant a) 
Foldable (Constant a) 
Traversable (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) 

data Compose f g a :: (* -> *) -> (* -> *) -> * -> * infixr 9

Right-to-left composition of functors. The composition of applicative functors is always applicative, but the composition of monads is not always a monad.

Instances

(Functor f, Functor g) => Functor (Compose f g) 
(Applicative f, Applicative g) => Applicative (Compose f g) 
(Foldable f, Foldable g) => Foldable (Compose f g) 
(Traversable f, Traversable g) => Traversable (Compose f g) 
(Alternative f, Applicative g) => Alternative (Compose f g) 
(Functor f, Eq1 f, Eq1 g) => Eq1 (Compose f g) 
(Functor f, Ord1 f, Ord1 g) => Ord1 (Compose f g) 
(Functor f, Read1 f, Read1 g) => Read1 (Compose f g) 
(Functor f, Show1 f, Show1 g) => Show1 (Compose f g) 
(Functor f, Eq1 f, Eq1 g, Eq a) => Eq (Compose f g a) 
(Functor f, Ord1 f, Ord1 g, Ord a) => Ord (Compose f g a) 
(Functor f, Read1 f, Read1 g, Read a) => Read (Compose f g a) 
(Functor f, Show1 f, Show1 g, Show a) => Show (Compose f g a) 

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.

Instances

Monad m => MonadState s (StateT s m) 
MonadTrans (StateT s) 
Monad m => Monad (StateT s m) 
Functor m => Functor (StateT s m) 
MonadFix m => MonadFix (StateT s m) 
(Functor m, Monad m) => Applicative (StateT s m) 
(Functor m, MonadPlus m) => Alternative (StateT s m) 
MonadPlus m => MonadPlus (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

Minimal complete definition

state | get, put

Instances

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)