lens-family-core-2.0.0: Haskell 2022 Lens Families

Safe HaskellSafe
LanguageHaskell98

Lens.Family.State.Lazy

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) s a -> StateT a m c -> StateT s m c Source #

zoom :: Monad m => Lens' s a -> StateT a m c -> StateT s 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 :: (Monad m, Monoid c) => Traversal' s a -> StateT a m c -> StateT s m c

Run the "subroutine" on each element of the traversal in turn and mconcat all the results together.

zoom :: Monad m => Traversal' s a -> StateT a m () -> StateT s m ()

Run the "subroutine" on each element the traversal in turn.

use :: Monad m => FoldLike a s t a b -> StateT s m a Source #

use :: Monad m => Getter s t a b -> StateT s m a

Retrieve a field of the state

use :: (Monad m, Monoid a) => Fold s t a b -> StateT s m a

Retrieve a monoidal summary of all the referenced fields from the state

uses :: Monad m => FoldLike r s t a b -> (a -> r) -> StateT s m r Source #

uses :: (Monad m, Monoid r) => Fold s t a b -> (a -> r) -> StateT s m r

Retrieve all the referenced fields from the state and foldMap the results together with f :: a -> r.

uses :: Monad m => Getter s t a b -> (a -> r) -> StateT s m r

Retrieve a field of the state and pass it through the function f :: a -> r.

uses l f = f <$> use l

(%=) :: Monad m => ASetter s s a b -> (a -> b) -> StateT s m () infix 4 Source #

Modify a field of the state.

assign :: Monad m => ASetter s s a b -> b -> StateT s m () Source #

Set a field of the state.

(.=) :: Monad m => ASetter s s a b -> b -> StateT s m () infix 4 Source #

Set a field of the state.

(%%=) :: Monad m => LensLike (Writer c) s s a b -> (a -> (c, b)) -> StateT s m c infix 4 Source #

(%%=) :: Monad m => Lens s s a b -> (a -> (c, b)) -> StateT s m c

Modify a field of the state while returning another value.

(%%=) :: (Monad m, Monoid c) => Traversal s s a b -> (a -> (c, b)) -> StateT s m c

Modify each field of the state and return the mconcat of the other values.

(<~) :: Monad m => ASetter s s a b -> StateT s m b -> StateT s m () infixr 2 Source #

Set a field of the state using the result of executing a stateful command.

Compound Assignments

(+=) :: (Monad m, Num a) => ASetter' s a -> a -> StateT s m () infixr 4 Source #

(-=) :: (Monad m, Num a) => ASetter' s a -> a -> StateT s m () infixr 4 Source #

(*=) :: (Monad m, Num a) => ASetter' s a -> a -> StateT s m () infixr 4 Source #

(//=) :: (Monad m, Fractional a) => ASetter' s a -> a -> StateT s m () infixr 4 Source #

(&&=) :: Monad m => ASetter' s Bool -> Bool -> StateT s m () infixr 4 Source #

(||=) :: Monad m => ASetter' s Bool -> Bool -> StateT s m () infixr 4 Source #

(<>=) :: (Monad m, Monoid a) => ASetter' s a -> a -> StateT s m () infixr 4 Source #

Monoidally append a value to all referenced fields of the state.

Strict Assignments

(%!=) :: Monad m => ASetter s s a b -> (a -> b) -> StateT s m () infix 4 Source #

Strictly modify a field of the state.

(+!=) :: (Monad m, Num a) => ASetter' s a -> a -> StateT s m () infixr 4 Source #

(-!=) :: (Monad m, Num a) => ASetter' s a -> a -> StateT s m () infixr 4 Source #

(*!=) :: (Monad m, Num a) => ASetter' s a -> a -> StateT s m () infixr 4 Source #

(//!=) :: (Monad m, Fractional a) => ASetter' s a -> a -> StateT s m () infixr 4 Source #

(&&!=) :: Monad m => ASetter' s Bool -> Bool -> StateT s m () infixr 4 Source #

(||!=) :: Monad m => ASetter' s Bool -> Bool -> StateT s m () infixr 4 Source #

(<>!=) :: (Monad m, Monoid a) => ASetter' s a -> a -> StateT s m () infixr 4 Source #

Types

data Zooming m c a Source #

Instances
Monad m => Functor (Zooming m c) Source # 
Instance details

Defined in Lens.Family.State.Zoom

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) Source # 
Instance details

Defined in Lens.Family.State.Zoom

Methods

pure :: a -> Zooming m c a #

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

liftA2 :: (a -> b -> c0) -> Zooming m c a -> Zooming m c b -> Zooming m c c0 #

(*>) :: 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 s t a b = (a -> f b) -> s -> f t Source #

type LensLike' f s a = (a -> f a) -> s -> f s Source #

type FoldLike r s t a b = LensLike (Constant r) s t a b Source #

data Constant a (b :: k) :: forall k. Type -> k -> Type #

Constant functor.

Instances
Bitraversable (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Constant a b -> f (Constant c d) #

Bifoldable (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

bifold :: Monoid m => Constant m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Constant a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Constant a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Constant a b -> c #

Bifunctor (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.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 #

Eq2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

Ord2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

Read2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.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] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Constant a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Constant a b] #

Show2 (Constant :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.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 #

Functor (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

Monoid a => Applicative (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

pure :: a0 -> Constant a a0 #

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

liftA2 :: (a0 -> b -> c) -> Constant a a0 -> Constant a b -> Constant a c #

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

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

Foldable (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

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

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

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

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

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

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

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

null :: Constant a a0 -> Bool #

length :: Constant a a0 -> Int #

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

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

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

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

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

Traversable (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

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

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

Contravariant (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

contramap :: (a0 -> b) -> Constant a b -> Constant a a0 #

(>$) :: b -> Constant a b -> Constant a a0 #

Eq a => Eq1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

Ord a => Ord1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

Read a => Read1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Constant a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Constant a a0] #

Show a => Show1 (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

Phantom (Constant a :: Type -> Type) Source # 
Instance details

Defined in Lens.Family.Phantom

Methods

coerce :: Constant a a0 -> Constant a b

Eq a => Eq (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

Ord a => Ord (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

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

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

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

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

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

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

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

Read a => Read (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Show a => Show (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

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

show :: Constant a b -> String #

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

Semigroup a => Semigroup (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

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

sconcat :: NonEmpty (Constant a b) -> Constant a b #

stimes :: Integral b0 => b0 -> Constant a b -> Constant a b #

Monoid a => Monoid (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Methods

mempty :: Constant a b #

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

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

type ASetter s t a b = LensLike Identity s t a b Source #

data Identity a #

Identity functor and monad. (a non-strict monad)

Since: base-4.8.0.0

Instances
Monad Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(>>=) :: Identity a -> (a -> Identity b) -> Identity b #

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

return :: a -> Identity a #

fail :: String -> Identity a #

Functor Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

fmap :: (a -> b) -> Identity a -> Identity b #

(<$) :: a -> Identity b -> Identity a #

MonadFix Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mfix :: (a -> Identity a) -> Identity a #

Applicative Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

pure :: a -> Identity a #

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

liftA2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

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

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

Foldable Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

fold :: Monoid m => Identity m -> m #

foldMap :: Monoid m => (a -> m) -> Identity a -> m #

foldr :: (a -> b -> b) -> b -> Identity a -> b #

foldr' :: (a -> b -> b) -> b -> Identity a -> b #

foldl :: (b -> a -> b) -> b -> Identity a -> b #

foldl' :: (b -> a -> b) -> b -> Identity a -> b #

foldr1 :: (a -> a -> a) -> Identity a -> a #

foldl1 :: (a -> a -> a) -> Identity a -> a #

toList :: Identity a -> [a] #

null :: Identity a -> Bool #

length :: Identity a -> Int #

elem :: Eq a => a -> Identity a -> Bool #

maximum :: Ord a => Identity a -> a #

minimum :: Ord a => Identity a -> a #

sum :: Num a => Identity a -> a #

product :: Num a => Identity a -> a #

Traversable Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f => Identity (f a) -> f (Identity a) #

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

sequence :: Monad m => Identity (m a) -> m (Identity a) #

Eq1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Identity a -> Identity b -> Bool #

Ord1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Identity a -> Identity b -> Ordering #

Read1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Identity a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Identity a] #

Show1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

Identical Identity Source # 
Instance details

Defined in Lens.Family.Identical

Methods

extract :: Identity a -> a

Bounded a => Bounded (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Enum a => Enum (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Eq a => Eq (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(==) :: Identity a -> Identity a -> Bool #

(/=) :: Identity a -> Identity a -> Bool #

Floating a => Floating (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Fractional a => Fractional (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Integral a => Integral (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Num a => Num (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Ord a => Ord (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

compare :: Identity a -> Identity a -> Ordering #

(<) :: Identity a -> Identity a -> Bool #

(<=) :: Identity a -> Identity a -> Bool #

(>) :: Identity a -> Identity a -> Bool #

(>=) :: Identity a -> Identity a -> Bool #

max :: Identity a -> Identity a -> Identity a #

min :: Identity a -> Identity a -> Identity a #

Read a => Read (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Real a => Real (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

toRational :: Identity a -> Rational #

RealFloat a => RealFloat (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

RealFrac a => RealFrac (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

properFraction :: Integral b => Identity a -> (b, Identity a) #

truncate :: Integral b => Identity a -> b #

round :: Integral b => Identity a -> b #

ceiling :: Integral b => Identity a -> b #

floor :: Integral b => Identity a -> b #

Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Ix a => Ix (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Generic (Identity a) 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a) :: Type -> Type #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Semigroup a => Semigroup (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(<>) :: Identity a -> Identity a -> Identity a #

sconcat :: NonEmpty (Identity a) -> Identity a #

stimes :: Integral b => b -> Identity a -> Identity a #

Monoid a => Monoid (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mempty :: Identity a #

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

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

Storable a => Storable (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

peekElemOff :: Ptr (Identity a) -> Int -> IO (Identity a) #

pokeElemOff :: Ptr (Identity a) -> Int -> Identity a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Identity a) #

pokeByteOff :: Ptr b -> Int -> Identity a -> IO () #

peek :: Ptr (Identity a) -> IO (Identity a) #

poke :: Ptr (Identity a) -> Identity a -> IO () #

Bits a => Bits (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

FiniteBits a => FiniteBits (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Generic1 Identity 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep1 Identity :: k -> Type #

Methods

from1 :: Identity a -> Rep1 Identity a #

to1 :: Rep1 Identity a -> Identity a #

type Rep (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

type Rep (Identity a) = D1 (MetaData "Identity" "Data.Functor.Identity" "base" True) (C1 (MetaCons "Identity" PrefixI True) (S1 (MetaSel (Just "runIdentity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

type Rep1 Identity = D1 (MetaData "Identity" "Data.Functor.Identity" "base" True) (C1 (MetaCons "Identity" PrefixI True) (S1 (MetaSel (Just "runIdentity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

data StateT s (m :: Type -> Type) 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
MonadTrans (StateT s) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

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

Monad m => Monad (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

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) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

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) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

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

MonadFail m => MonadFail (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

fail :: String -> StateT s m a #

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

Defined in Control.Monad.Trans.State.Lazy

Methods

pure :: a -> StateT s m a #

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

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

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

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

Contravariant m => Contravariant (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

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

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

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

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

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

Defined in Control.Monad.Trans.State.Lazy

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) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

mzero :: StateT s m a #

mplus :: StateT s m a -> StateT s m a -> StateT 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.