Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Lens a b = Lens {
- runLens :: a -> (b -> a, b)
- lens :: (a -> b) -> (b -> a -> a) -> Lens a b
- iso :: (a -> b) -> (b -> a) -> Lens a b
- getL :: Lens a b -> a -> b
- setL :: Lens a b -> b -> a -> a
- modL :: Lens a b -> (b -> b) -> a -> a
- modL' :: Lens a b -> (b -> b) -> a -> a
- (^.) :: b -> Lens b c -> c
- vanLaarhoven :: Functor f => Lens a b -> (b -> f b) -> a -> f a
- nameMakeLens :: Name -> (String -> Maybe String) -> Q [Dec]
- makeLenses :: [Name] -> Q [Dec]
- makeLens :: Name -> Q [Dec]
- access :: MonadState a m => Lens a b -> m b
- (~=) :: MonadState a m => Lens a b -> b -> m ()
- (!=) :: MonadState a m => Lens a b -> b -> m ()
- (%=) :: MonadState a m => Lens a b -> (b -> b) -> m ()
- (!%=) :: MonadState a m => Lens a b -> (b -> b) -> m ()
- zoom :: (MonadStateT stateT, MonadState s (stateT s m), MonadTrans (stateT s), Monad m) => Lens s s' -> stateT s' m a -> stateT s m a
- class MonadStateT t
Lenses and basic operations
Simple lens data type
modL' :: Lens a b -> (b -> b) -> a -> a Source #
Get the modifier function from a lens. Forces function application.
(^.) :: b -> Lens b c -> c infixl 9 Source #
Infix version of getL
(with the reverse order of the arguments)
vanLaarhoven :: Functor f => Lens a b -> (b -> f b) -> a -> f a Source #
Convert a lens to its van Laarhoven representation
Generate lenses using TH
nameMakeLens :: Name -> (String -> Maybe String) -> Q [Dec] Source #
nameMakeLens n f
where n
is the name of a data type
declared with data
and f
is a function from names of fields
in that data type to the name of the corresponding accessor. If
f
returns Nothing
, then no accessor is generated for that
field.
makeLenses :: [Name] -> Q [Dec] Source #
makeLenses n
where n
is the name of a data type
declared with data
looks through all the declared fields
of the data type, and for each field beginning with an underscore
generates an accessor of the same name without the underscore.
It is "nameMakeLens" n f where f
satisfies
f ('_' : s) = Just s f x = Nothing -- otherwise
For example, given the data type:
data Score = Score { _p1Score :: Int , _p2Score :: Int , rounds :: Int }
makeLenses
will generate the following objects:
p1Score :: Lens Score Int p1Score = lens _p1Score (\x s -> s { _p1Score = x }) p2Score :: Lens Score Int p2Score = lens _p2Score (\x s -> s { _p2Score = x })
It is used with Template Haskell syntax like:
$( makeLenses [''TypeName] )
And will generate accessors when TypeName was declared
using data
or newtype
.
MonadState operators
access :: MonadState a m => Lens a b -> m b Source #
Get the value of a lens into state
(~=) :: MonadState a m => Lens a b -> b -> m () infixr 4 Source #
Set a value using a lens into state
(!=) :: MonadState a m => Lens a b -> b -> m () infixr 4 Source #
Set a value using a lens into state. Forces both the value and the whole state.
(%=) :: MonadState a m => Lens a b -> (b -> b) -> m () infixr 4 Source #
Infix modification of a value through a lens into state
(!%=) :: MonadState a m => Lens a b -> (b -> b) -> m () infixr 4 Source #
Infix modification of a value through a lens into state. Forces both the function application and the whole state.
zoom :: (MonadStateT stateT, MonadState s (stateT s m), MonadTrans (stateT s), Monad m) => Lens s s' -> stateT s' m a -> stateT s m a Source #
Run a stateful computation with a smaller state inside another computation with a bigger state.
class MonadStateT t Source #
The purpose of this class is to abstract the difference between the
lazy and strict state monads, so that zoom
can work with either of
them.
runStateT
Instances
MonadStateT StateT Source # | |
Defined in Data.Lens.Light.State | |
MonadStateT StateT Source # | |
Defined in Data.Lens.Light.State |