fclabels-0.11.1: First class accessor labels implemented as lenses.

Data.Record.Label

Contents

Synopsis

Lens types.

data Point f i o Source

Constructors

Point (f -> o) (i -> f -> f) 

Instances

newtype f :-> a Source

Constructors

Lens (Point f a a) 

Instances

lens :: (f -> a) -> (a -> f -> f) -> f :-> aSource

Create a lens out of a getter and setter.

getL :: (f :-> a) -> f -> aSource

Get the getter function from a lens.

setL :: (f :-> a) -> a -> f -> fSource

Get the setter function from a lens.

modL :: (f :-> a) -> (a -> a) -> f -> fSource

Get the modifier function from a lens.

fmapL :: Applicative f => (a :-> b) -> f a :-> f bSource

Bidirectional functor.

data a :<->: b Source

The bijections datatype, a function that works in two directions.

Constructors

:<->: 

Fields

fw :: a -> b
 
bw :: b -> a
 

Instances

Category :<->:

Constructor for bijections.

Iso (:<->: i) 

class Iso f whereSource

This isomorphism type class is like a Functor but works in two directions.

Methods

(%) :: (a :<->: b) -> f a -> f bSource

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 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.

(=:) :: MonadState s m => (s :-> b) -> b -> m ()Source

Alias for setM that reads like an assignment.

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.