fclabels-0.3.0: First class accessor labels.Source codeContentsIndex
Data.Record.Label
Contents
Getter, setter and modifier types.
Label type.
Identity and composition.
Bidirectional functor.
State monadic label operations.
Useful example labels.
Derive labels using Template Haskell.
Synopsis
type Getter a b = a -> b
type Setter a b = b -> a -> a
type Modifier a b = (b -> b) -> a -> a
data a :-> b = Label {
lget :: Getter a b
lset :: Setter a b
lmod :: Modifier a b
}
mkModifier :: Getter a b -> Setter a b -> Modifier a b
mkLabel :: Getter a b -> Setter a b -> a :-> b
idL :: a :-> a
(%) :: (g :-> a) -> (f :-> g) -> f :-> a
class Lens f where
lmap :: (a -> b, b -> a) -> f a -> f b
(%%) :: Functor f => (a :-> b) -> (g :-> f a) -> g :-> f b
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 ()
list :: Int -> [a] :-> a
maybeNull :: [a] :-> Maybe [a]
mkLabels :: [Name] -> Q [Dec]
Getter, setter and modifier types.
type Getter a b = a -> bSource
type Setter a b = b -> a -> aSource
type Modifier a b = (b -> b) -> a -> aSource
Label type.
data a :-> b Source
Constructors
Label
lget :: Getter a b
lset :: Setter a b
lmod :: Modifier a b
show/hide Instances
mkModifier :: Getter a b -> Setter a b -> Modifier a bSource
Create a modifier function out of a getter and a setter.
mkLabel :: Getter a b -> Setter a b -> a :-> bSource
Smart constructor for Labels, the modifier will be computed based on getter and setter.
Identity and composition.
idL :: a :-> aSource
(%) :: (g :-> a) -> (f :-> g) -> f :-> aSource
Bidirectional functor.
class Lens f whereSource
Methods
lmap :: (a -> b, b -> a) -> f a -> f bSource
show/hide Instances
Lens (:-> f)
(%%) :: Functor f => (a :-> b) -> (g :-> f a) -> g :-> f bSource
Apply label to lifted value and join afterwards.
State monadic label operations.
getM :: MonadState s m => (s :-> b) -> m bSource
Get a value out of state pointed to by the specified label.
setM :: MonadState s m => (s :-> b) -> b -> m ()Source
Set a value somewhere in state pointed to by the specified label.
modM :: MonadState s m => (s :-> b) -> (b -> b) -> m ()Source
Modify a value with a function somewhere in state pointed to by the specified label.
(=:) :: MonadState s m => (s :-> b) -> b -> m ()Source
Alias for setM that reads like an assignment.
Useful example labels.
list :: Int -> [a] :-> aSource
maybeNull :: [a] :-> Maybe [a]Source
Derive labels using Template Haskell.
mkLabels :: [Name] -> Q [Dec]Source
Produced by Haddock version 2.4.2