lens-family-1.2.2: Lens Families

Safe HaskellSafe
LanguageHaskell98

Lens.Family2.State.Strict

Contents

Description

Lenses allow you to use fields of the state of a state monad as if they were variables in an imperative language. use is used to retrieve the value of a variable, and .= and %= allow you to set and modify a variable. C-style compound assignments are also provided.

Synopsis

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, Monad 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 #

(&&=) :: MonadState a m => Setter' a Bool -> Bool -> m () infixr 4 Source #

(||=) :: MonadState a m => Setter' a Bool -> Bool -> 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.

Strict Assignments

(%!=) :: MonadState a m => Setter a a b b' -> (b -> b') -> m () infix 4 Source #

Strictly modify a field of the state.

(+!=) :: (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 #

(&&!=) :: MonadState a m => Setter' a Bool -> Bool -> m () infixr 4 Source #

(||!=) :: MonadState a m => Setter' a Bool -> Bool -> m () infixr 4 Source #

(<>!=) :: (Monoid o, MonadState a m) => Setter' a o -> o -> m () infixr 4 Source #

Types

data Zooming m c a :: (* -> *) -> * -> * -> * #

Instances

Monad m => Functor (Zooming m c) 

Methods

fmap :: (a -> b) -> Zooming m c a -> Zooming m c b #

(<$) :: a -> Zooming m c b -> Zooming m c a #

(Monoid c, Monad m) => Applicative (Zooming m c) 

Methods

pure :: a -> Zooming m c a #

(<*>) :: Zooming m c (a -> b) -> Zooming m c a -> Zooming m c b #

(*>) :: Zooming m c a -> Zooming m c b -> Zooming m c b #

(<*) :: Zooming m c a -> Zooming m c b -> 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 #

type FoldLike r a a' b b' = LensLike (Constant * r) a a' b b' #

data Constant k a b :: forall k. * -> k -> * #

Constant functor.

Instances

Eq2 (Constant *) 

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Constant * a c -> Constant * b d -> Bool #

Ord2 (Constant *) 

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Constant * a c -> Constant * b d -> Ordering #

Read2 (Constant *) 

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Constant * a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Constant * a b] #

Show2 (Constant *) 

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Constant * a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Constant * a b] -> ShowS #

Bifunctor (Constant *) 

Methods

bimap :: (a -> b) -> (c -> d) -> Constant * a c -> Constant * b d #

first :: (a -> b) -> Constant * a c -> Constant * b c #

second :: (b -> c) -> Constant * a b -> Constant * a c #

Functor (Constant * a) 

Methods

fmap :: (a -> b) -> Constant * a a -> Constant * a b #

(<$) :: a -> Constant * a b -> Constant * a a #

Monoid a => Applicative (Constant * a) 

Methods

pure :: a -> Constant * a a #

(<*>) :: Constant * a (a -> b) -> Constant * a a -> Constant * a b #

(*>) :: Constant * a a -> Constant * a b -> Constant * a b #

(<*) :: Constant * a a -> Constant * a b -> Constant * a a #

Foldable (Constant * a) 

Methods

fold :: Monoid m => Constant * a m -> m #

foldMap :: Monoid m => (a -> m) -> Constant * a a -> m #

foldr :: (a -> b -> b) -> b -> Constant * a a -> b #

foldr' :: (a -> b -> b) -> b -> Constant * a a -> b #

foldl :: (b -> a -> b) -> b -> Constant * a a -> b #

foldl' :: (b -> a -> b) -> b -> Constant * a a -> b #

foldr1 :: (a -> a -> a) -> Constant * a a -> a #

foldl1 :: (a -> a -> a) -> Constant * a a -> a #

toList :: Constant * a a -> [a] #

null :: Constant * a a -> Bool #

length :: Constant * a a -> Int #

elem :: Eq a => a -> Constant * a a -> Bool #

maximum :: Ord a => Constant * a a -> a #

minimum :: Ord a => Constant * a a -> a #

sum :: Num a => Constant * a a -> a #

product :: Num a => Constant * a a -> a #

Traversable (Constant * a) 

Methods

traverse :: Applicative f => (a -> f b) -> Constant * a a -> f (Constant * a b) #

sequenceA :: Applicative f => Constant * a (f a) -> f (Constant * a a) #

mapM :: Monad m => (a -> m b) -> Constant * a a -> m (Constant * a b) #

sequence :: Monad m => Constant * a (m a) -> m (Constant * a a) #

Eq a => Eq1 (Constant * a) 

Methods

liftEq :: (a -> b -> Bool) -> Constant * a a -> Constant * a b -> Bool #

Ord a => Ord1 (Constant * a) 

Methods

liftCompare :: (a -> b -> Ordering) -> Constant * a a -> Constant * a b -> Ordering #

Read a => Read1 (Constant * a) 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Constant * a a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Constant * a a] #

Show a => Show1 (Constant * a) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Constant * a a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Constant * a a] -> ShowS #

Phantom (Constant * a) 

Methods

coerce :: Constant * a a -> Constant * a b

Eq a => Eq (Constant k a b) 

Methods

(==) :: Constant k a b -> Constant k a b -> Bool #

(/=) :: Constant k a b -> Constant k a b -> Bool #

Ord a => Ord (Constant k a b) 

Methods

compare :: Constant k a b -> Constant k a b -> Ordering #

(<) :: Constant k a b -> Constant k a b -> Bool #

(<=) :: Constant k a b -> Constant k a b -> Bool #

(>) :: Constant k a b -> Constant k a b -> Bool #

(>=) :: Constant k a b -> Constant k a b -> Bool #

max :: Constant k a b -> Constant k a b -> Constant k a b #

min :: Constant k a b -> Constant k a b -> Constant k a b #

Read a => Read (Constant k a b) 
Show a => Show (Constant k a b) 

Methods

showsPrec :: Int -> Constant k a b -> ShowS #

show :: Constant k a b -> String #

showList :: [Constant k a b] -> ShowS #

Monoid a => Monoid (Constant k a b) 

Methods

mempty :: Constant k a b #

mappend :: Constant k a b -> Constant k a b -> Constant k a b #

mconcat :: [Constant k a b] -> Constant k a b #

type Setter a a' b b' = forall f. Identical f => LensLike f a a' b b' Source #

type Setter' a b = forall f. Identical f => LensLike' f a b Source #

class Applicative f => Identical f #

Minimal complete definition

extract

Instances

Identical Identity 

Methods

extract :: Identity a -> a

Identical f => Identical (Backwards * f) 

Methods

extract :: Backwards * f a -> a

(Identical f, Identical g) => Identical (Compose * * f g) 

Methods

extract :: Compose * * f g a -> 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) 

Methods

get :: StateT s m s #

put :: s -> StateT s m () #

state :: (s -> (a, s)) -> StateT s m a #

MonadTrans (StateT s) 

Methods

lift :: Monad m => m a -> StateT s m a #

Monad m => Monad (StateT s m) 

Methods

(>>=) :: StateT s m a -> (a -> StateT s m b) -> StateT s m b #

(>>) :: StateT s m a -> StateT s m b -> StateT s m b #

return :: a -> StateT s m a #

fail :: String -> StateT s m a #

Functor m => Functor (StateT s m) 

Methods

fmap :: (a -> b) -> StateT s m a -> StateT s m b #

(<$) :: a -> StateT s m b -> StateT s m a #

MonadFix m => MonadFix (StateT s m) 

Methods

mfix :: (a -> StateT s m a) -> StateT s m a #

MonadFail m => MonadFail (StateT s m) 

Methods

fail :: String -> StateT s m a #

(Functor m, Monad m) => Applicative (StateT s m) 

Methods

pure :: a -> StateT s m a #

(<*>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b #

(*>) :: StateT s m a -> StateT s m b -> StateT s m b #

(<*) :: StateT s m a -> StateT s m b -> StateT s m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

(Functor m, MonadPlus m) => Alternative (StateT s m) 

Methods

empty :: StateT s m a #

(<|>) :: StateT s m a -> StateT s m a -> StateT s m a #

some :: StateT s m a -> StateT s m [a] #

many :: StateT s m a -> StateT s m [a] #

MonadPlus m => MonadPlus (StateT s m) 

Methods

mzero :: StateT s m a #

mplus :: StateT s m a -> StateT s m a -> StateT s m a #

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) 

Methods

get :: MaybeT m s #

put :: s -> MaybeT m () #

state :: (s -> (a, s)) -> MaybeT m a #

MonadState s m => MonadState s (ListT m) 

Methods

get :: ListT m s #

put :: s -> ListT m () #

state :: (s -> (a, s)) -> ListT m a #

(Monoid w, MonadState s m) => MonadState s (WriterT w m) 

Methods

get :: WriterT w m s #

put :: s -> WriterT w m () #

state :: (s -> (a, s)) -> WriterT w m a #

(Monoid w, MonadState s m) => MonadState s (WriterT w m) 

Methods

get :: WriterT w m s #

put :: s -> WriterT w m () #

state :: (s -> (a, s)) -> WriterT w m a #

Monad m => MonadState s (StateT s m) 

Methods

get :: StateT s m s #

put :: s -> StateT s m () #

state :: (s -> (a, s)) -> StateT s m a #

Monad m => MonadState s (StateT s m) 

Methods

get :: StateT s m s #

put :: s -> StateT s m () #

state :: (s -> (a, s)) -> StateT s m a #

MonadState s m => MonadState s (IdentityT * m) 

Methods

get :: IdentityT * m s #

put :: s -> IdentityT * m () #

state :: (s -> (a, s)) -> IdentityT * m a #

MonadState s m => MonadState s (ExceptT e m) 

Methods

get :: ExceptT e m s #

put :: s -> ExceptT e m () #

state :: (s -> (a, s)) -> ExceptT e m a #

(Error e, MonadState s m) => MonadState s (ErrorT e m) 

Methods

get :: ErrorT e m s #

put :: s -> ErrorT e m () #

state :: (s -> (a, s)) -> ErrorT e m a #

MonadState s m => MonadState s (ReaderT * r m) 

Methods

get :: ReaderT * r m s #

put :: s -> ReaderT * r m () #

state :: (s -> (a, s)) -> ReaderT * r m a #

MonadState s m => MonadState s (ContT * r m) 

Methods

get :: ContT * r m s #

put :: s -> ContT * r m () #

state :: (s -> (a, s)) -> ContT * r m a #

(Monad m, Monoid w) => MonadState s (RWST r w s m) 

Methods

get :: RWST r w s m s #

put :: s -> RWST r w s m () #

state :: (s -> (a, s)) -> RWST r w s m a #

(Monad m, Monoid w) => MonadState s (RWST r w s m) 

Methods

get :: RWST r w s m s #

put :: s -> RWST r w s m () #

state :: (s -> (a, s)) -> RWST r w s m a #

type Writer w = WriterT w Identity #

A writer monad parameterized by the type w of output to accumulate.

The return function produces the output mempty, while >>= combines the outputs of the subcomputations using mappend.

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.

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 newtypes and make those instances of Monoid, e.g. Sum and Product.

Minimal complete definition

mempty, mappend

Instances

Monoid Ordering 
Monoid () 

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid All 

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any 

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid IntSet 
Monoid [a] 

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [a] #

Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (IO a) 

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

Ord a => Monoid (Max a) 

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Ord a => Monoid (Min a) 

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Monoid a => Monoid (Dual a) 

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a) 

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Sum a) 

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Num a => Monoid (Product a) 

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Monoid (First a) 

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a) 

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid (IntMap a) 

Methods

mempty :: IntMap a #

mappend :: IntMap a -> IntMap a -> IntMap a #

mconcat :: [IntMap a] -> IntMap a #

Ord a => Monoid (Set a) 

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

mconcat :: [Set a] -> Set a #

Monoid b => Monoid (a -> b) 

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

(Monoid a, Monoid b) => Monoid (a, b) 

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

Ord k => Monoid (Map k v) 

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

Alternative f => Monoid (Alt * f a) 

Methods

mempty :: Alt * f a #

mappend :: Alt * f a -> Alt * f a -> Alt * f a #

mconcat :: [Alt * f a] -> Alt * f a #

Monoid a => Monoid (Constant k a b) 

Methods

mempty :: Constant k a b #

mappend :: Constant k a b -> Constant k a b -> Constant k a b #

mconcat :: [Constant k a b] -> Constant k a b #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) 

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) 

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #