Safe Haskell | None |
---|---|
Language | Haskell98 |
This package provides first class labels that can act as bidirectional record fields. The labels can be derived automatically using Template Haskell which means you don't have to write any boilerplate yourself. The labels are implemented as lenses and are fully composable. Labels can be used to get, set and modify parts of a datatype in a consistent way.
Synopsis
- type (:->) f o = Lens Total f o
- lens :: (f -> a) -> ((a -> a) -> f -> f) -> f :-> a
- get :: (f :-> a) -> f -> a
- set :: (f :-> a) -> a -> f -> f
- modify :: (f :-> a) -> (a -> a) -> f -> f
- point :: Point cat g i f o -> Lens cat (f -> g) (o -> i)
- (>-) :: Arrow arr => Lens arr (j -> a) (i -> b) -> Lens arr (f -> g) (o -> i) -> Point arr g j f o
- for :: Arrow arr => Lens arr (j -> a) (i -> b) -> Lens arr (f -> g) (o -> i) -> Point arr g j f o
- data Iso cat i o = Iso {}
- inv :: Iso cat i o -> Iso cat o i
- iso :: ArrowApply cat => Iso cat f o -> Lens cat f o
- mkLabel :: Name -> Q [Dec]
- mkLabels :: [Name] -> Q [Dec]
- getLabel :: Name -> Q Exp
- fclabels :: Q [Dec] -> Q [Dec]
Working with fclabels
.
The lens datatype, conveniently called :->
, is an instance of the
Control.Category type class: meaning it has a proper identity and
composition. The library has support for automatically deriving labels from
record selectors that start with an underscore.
To illustrate this package, let's take the following two example datatypes.
{-# LANGUAGE TemplateHaskell, TypeOperators #-} import Control.Category import Data.Label import Prelude hiding ((.), id) data Person = Person { _name :: String , _age :: Int , _place :: Place } deriving Show data Place = Place { _city , _country , _continent :: String } deriving Show
Both datatypes are record types with all the labels prefixed with an underscore. This underscore is an indication for our Template Haskell code to derive lenses for these fields. Deriving lenses can be done with this simple one-liner:
mkLabels [''Person, ''Place]
For all labels a lens will created.
Now let's look at this example. This 71 year old fellow, my neighbour called Jan, didn't mind using him as an example:
jan :: Person jan = Person "Jan" 71 (Place "Utrecht" "The Netherlands" "Europe")
When we want to be sure Jan is really as old as he claims we can use the get
function to get the age out as an integer:
hisAge :: Int hisAge = get age jan
Consider he now wants to move to Amsterdam: what better place to spend your old days. Using composition we can change the city value deep inside the structure:
moveToAmsterdam :: Person -> Person moveToAmsterdam = set (city . place) "Amsterdam"
And now:
ghci> moveToAmsterdam jan Person "Jan" 71 (Place "Amsterdam" "The Netherlands" "Europe")
Composition is done using the (
operator which is part of the
Control.Category module. Make sure to import this module and hide the default
.
)(
, .
)id
function from the Haskell Prelude.
Total monomorphic lenses.
:: (f -> a) | Getter. |
-> ((a -> a) -> f -> f) | Modifier. |
-> f :-> a |
Create a total lens from a getter and a modifier.
We expect the following law to hold:
get l (modify l m f) == m (get l f)
Vertical composition using Applicative
.
Now, because Jan is an old guy, moving to another city is not a very easy task,
this really takes a while. It will probably take no less than two years before
he will actually be settled. To reflect this change it might be useful to have
a first class view on the Person
datatype that only reveals the age and
city. This can be done by using a neat Applicative
functor instance:
import Control.Applicative
(fstL, sndL) = $(getLabel ''(,))
ageAndCity :: Person :-> (Int, String) ageAndCity = point $ (,) <$> fstL >- age <*> sndL >- city . place
Because the applicative type class on its own is not capable of expressing
bidirectional relations, which we need for our lenses, the actual instance is
defined for an internal helper structure called Point
. Points are a more
general than lenses. As you can see above, the point
function has to be
used to convert a Point
back into a Lens
. The (>-
) operator is used to
indicate which partial destructor to use per arm of the applicative
composition.
Now that we have an appropriate age+city view on the Person
datatype (which
is itself a lens again), we can use the modify
function to make Jan move to
Amsterdam over exactly two years:
moveToAmsterdamOverTwoYears :: Person -> Person moveToAmsterdamOverTwoYears = modify ageAndCity (\(a, _) -> (a+2, "Amsterdam"))
ghci> moveToAmsterdamOverTwoYears jan Person "Jan" 73 True (Place "Amsterdam" "The Netherlands" "Europe")
(>-) :: Arrow arr => Lens arr (j -> a) (i -> b) -> Lens arr (f -> g) (o -> i) -> Point arr g j f o infix 7 Source #
Make a Lens output diverge by changing the input of the modifier. The operator can be read as points-to.
for :: Arrow arr => Lens arr (j -> a) (i -> b) -> Lens arr (f -> g) (o -> i) -> Point arr g j f o infix 7 Source #
Non-operator version of >-
, since it clashes with an operator
when the Arrows language extension is used.
Working with isomorphisms.
This package contains an isomorphisms datatype that encodes bidirectional
functions, or better bidirectional categories. Just like lenses,
isomorphisms can be composed using the Category
type class. Isomorphisms
can be used to change the type of a lens. Every isomorphism can be lifted
into a lens.
For example, when we want to treat the age of a person as a string we can do the following:
ageAsString :: Person :-> String ageAsString = iso (Iso show read) . age
Derive labels using Template Haskell.
Template Haskell functions for automatically generating labels for
algebraic datatypes, newtypes and GADTs. There are two basic modes of label
generation, the mkLabels
family of functions create labels (and optionally
type signatures) in scope as top level funtions, the getLabel
family of
funtions create labels as expressions that can be named and typed manually.
In the case of multi-constructor datatypes some fields might not always be
available and the derived labels will be partial. Partial labels are
provided with an additional type context that forces them to be only usable
in the Partial
or Failing
context.
More derivation functions can be found in Data.Label.Derive.
mkLabel :: Name -> Q [Dec] Source #
Derive labels including type signatures for all the record selectors in a single datatype. The types will be polymorphic and can be used in an arbitrary context.
mkLabels :: [Name] -> Q [Dec] Source #
Derive labels including type signatures for all the record selectors for a collection of datatypes. The types will be polymorphic and can be used in an arbitrary context.
getLabel :: Name -> Q Exp Source #
Derive unnamed labels as n-tuples that can be named manually. The types will be polymorphic and can be used in an arbitrary context.
Example:
(left, right) = $(getLabel ''Either)
The lenses can now also be typed manually:
left :: (Either a b -> Either c b) :~> (a -> c) right :: (Either a b -> Either a c) :~> (b -> c)
Note: Because of the abstract nature of the generated lenses and the top
level pattern match, it might be required to use NoMonomorphismRestriction
in some cases.
fclabels :: Q [Dec] -> Q [Dec] Source #
Derive labels for all the record types in the supplied declaration. The record fields don't need an underscore prefix. Multiple data types / newtypes are allowed at once.
The advantage of this approach is that you don't need to explicitly hide the
original record accessors from being exported and they won't show up in the
derived Show
instance.
Example:
fclabels [d| data Record = Record { int :: Int , bool :: Bool } deriving Show |]
ghci> modify int (+2) (Record 1 False) Record 3 False