fclabels-0.4.2: First class accessor labels.Source codeContentsIndex
Data.Record.Label
Contents
Getter, setter and modifier types.
Label type.
Bidirectional functor.
State monadic label operations.
Derive labels using Template Haskell.
Synopsis
type Getter f o = f -> o
type Setter f i = i -> f -> f
type Modifier f i o = (o -> i) -> f -> f
data Point f i o
newtype f :-> a = Label (Point f a a)
label :: Getter f a -> Setter f a -> f :-> a
get :: (f :-> a) -> f -> a
set :: (f :-> a) -> a -> f -> f
mod :: (f :-> a) -> (a -> a) -> f -> f
fmapL :: Applicative f => (a :-> b) -> f a :-> f b
data a :<->: b = Lens {
fw :: a -> b
bw :: b -> a
}
(<->) :: (a -> b) -> (b -> a) -> a :<->: b
class Iso f where
iso :: (a :<->: b) -> f a -> f b
osi :: (a :<->: b) -> f b -> f a
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 ()
mkLabels :: [Name] -> Q [Dec]
Getter, setter and modifier types.
type Getter f o = f -> oSource
type Setter f i = i -> f -> fSource
type Modifier f i o = (o -> i) -> f -> fSource
Label type.
data Point f i o Source
show/hide Instances
newtype f :-> a Source
Constructors
Label (Point f a a)
show/hide Instances
label :: Getter f a -> Setter f a -> f :-> aSource
get :: (f :-> a) -> f -> aSource
Get the getter function from a label.
set :: (f :-> a) -> a -> f -> fSource
Get the setter function from a label.
mod :: (f :-> a) -> (a -> a) -> f -> fSource
Get the modifier function from a label.
fmapL :: Applicative f => (a :-> b) -> f a :-> f bSource
Bidirectional functor.
data a :<->: b Source
The lens datatype, a function that works in two directions. To bad there is no convenient way to do application for this.
Constructors
Lens
fw :: a -> b
bw :: b -> a
show/hide Instances
(<->) :: (a -> b) -> (b -> a) -> a :<->: bSource
Constructor for lenses.
class Iso f whereSource
This isomorphism type class is like a Functor but works in two directions.
Methods
iso :: (a :<->: b) -> f a -> f bSource
osi :: (a :<->: b) -> f b -> f aSource
show/hide Instances
Iso (:<->: i)
Iso (:-> i)
lmap :: Functor f => (a :<->: b) -> f a :<->: f bSource
for :: (i -> o) -> (f :-> o) -> Point f i oSource
Combine a partial destructor with a label 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.)
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.
Derive labels using Template Haskell.
mkLabels :: [Name] -> Q [Dec]Source
Derive labels for all the record selector in a datatype.
Produced by Haddock version 2.6.0