- data Point f i o = Point (f -> o) (i -> f -> f)
- newtype f :-> a = Lens (Point f a a)
- lens :: (f -> a) -> (a -> f -> f) -> f :-> a
- getL :: (f :-> a) -> f -> a
- setL :: (f :-> a) -> a -> f -> f
- modL :: (f :-> a) -> (a -> a) -> f -> f
- fmapL :: Applicative f => (a :-> b) -> f a :-> f b
- data a :<->: b = :<->: {}
- class Iso f where
- lmap :: Functor f => (a :<->: b) -> f a :<->: f b
- for :: (i -> o) -> (f :-> o) -> Point f i o
- getM :: MonadState s m => (s :-> b) -> m b
- setM :: MonadState s m => (s :-> b) -> b -> m ()
- modM :: MonadState s m => (s :-> b) -> (b -> b) -> m ()
- (=:) :: MonadState s m => (s :-> b) -> b -> m ()
- askM :: MonadReader r m => (r :-> b) -> m b
- localM :: MonadReader r m => (r :-> b) -> (b -> b) -> m a -> m a
- mkLabels :: [Name] -> Q [Dec]
- mkLabelsNoTypes :: [Name] -> Q [Dec]
Lens types.
fmapL :: Applicative f => (a :-> b) -> f a :-> f bSource
Bidirectional functor.
The bijections datatype, a function that works in two directions.
This isomorphism type class is like a Functor
but works in two directions.
for :: (i -> o) -> (f :-> o) -> Point f i oSource
Combine a partial destructor with a lens into something easily used in the
applicative instance for the hidden Point
datatype. Internally uses the
covariant in getter, contravariant in setter bi-functioral-map function.
(Please refer to the example because this function is just not explainable
on its own.)
Monadic lens operations.
getM :: MonadState s m => (s :-> b) -> m bSource
Get a value out of state pointed to by the specified lens.
setM :: MonadState s m => (s :-> b) -> b -> m ()Source
Set a value somewhere in state pointed to by the specified lens.
modM :: MonadState s m => (s :-> b) -> (b -> b) -> m ()Source
Modify a value with a function somewhere in state pointed to by the specified lens.
askM :: MonadReader r m => (r :-> b) -> m bSource
Fetch a value pointed to by a lens out of a reader environment.
localM :: MonadReader r m => (r :-> b) -> (b -> b) -> m a -> m aSource
Execute a computation in a modified environment. The lens is used to point out the part to modify.
Derive labels using Template Haskell.
mkLabels :: [Name] -> Q [Dec]Source
Derive lenses including type signatures for all the record selectors in a datatype.
mkLabelsNoTypes :: [Name] -> Q [Dec]Source
Derive lenses without type signatures for all the record selectors in a datatype.