A brief tutorial-introduction to 'fclabels' 1.0
Sebastiaan Visser et al. last week announced the release of v1.0 of fclabels. This is a short introduction to the changes for people who are already somewhat familiar with the package.
Que? The fclabels package is a haskell library providing “first class labels” for haskell data types and some Template Haskell code for automatically generating said labels. This makes for a more composable and much more powerful alternative to haskell’s built-in record syntactic sugar. Here is a good introductory tutorial.
The new version features (besides some better names) a type for lenses that can fail. S.V. et al. added this functionality in a brilliant and mostly (except for the name changes) backwards compatible way. We’ll see how it all works now.
We’ll prepare a module for fclabels in the usual way:
{-# LANGUAGE TemplateHaskell, TypeOperators #-}
import Control.Category
import Data.Label
import qualified Data.Label.Maybe as M
import Prelude hiding ((.), id)
The only odd thing above is our qualified import of Data.Label.Maybe
which
provides getters, setters etc. that can fail.
We want to generate lenses for the following type, so we do the underdash thing:
data Example = X { _int :: Int , _char :: Char}
| Y { _int :: Int , _example :: Example }
Notice how _int
is a valid record for both constructors X
and Y
, where
the other two are partial functions.
Lastly, the usual splice for generating labels:
$(mkLabels[''Example])
Let’s load our file into GHCi and play a little:
Prelude> :l test.hs
[1 of 1] Compiling Main ( test.hs, interpreted )
Ok, modules loaded: Main.
*Main> get int $ X 1 'a'
1
*Main> M.get int $ X 1 'a'
Just 1
*Main> M.get char $ X 1 'a'
Just 'a'
*Main> M.get example $ X 1 'a'
Nothing
*Main> get example $ X 1 'a'
:1:5:
No instance for (Control.Arrow.ArrowZero (->))
arising from a use of `example'
Possible fix:
add an instance declaration for (Control.Arrow.ArrowZero (->))
In the first argument of `get', namely `example'
In the expression: get example
In the expression: get example $ X 1 'a'
Above we saw that:
-
the total
int
label could be used in bothget
andData.Label.Maybe.get
-
M.get on our “partial lenses” (
example
andchar
) safely returned a Maybe value. -
pure
get
used with partial lenses doesn’t type check
We need to look at some types (note I’ve cleaned up some of these type signatures, yours may look uglier):
*Main> :t get
get :: (f :-> a) -> f -> a
*Main> :t M.get
M.get :: (f M.:~> a) -> f -> Maybe a
*Main> :info (:->)
type (:->) f a = Data.Label.Pure.PureLens f a
-- Defined in Data.Label.Pure
*Main> :info (M.:~>)
type (M.:~>) f a = Data.Label.Maybe.MaybeLens f a
-- Defined in Data.Label.Maybe
You can see above that setters and getters are monomorphic. But how then were
we able to use int
in both get
and M.get
? Time to look at the types of
our TH-generated lenses:
*Main> :t int
int
:: Control.Arrow.Arrow (~>) => Lens (~>) Example Int
*Main> :t char
char
:: (Control.Arrow.ArrowZero (~>),
Control.Arrow.ArrowChoice (~>)) =>
Lens (~>) Example Char
*Main> :t example
example
:: (Control.Arrow.ArrowZero (~>),
Control.Arrow.ArrowChoice (~>)) =>
Lens (~>) Example Example
Whoah! Lenses themselves are polymorphic in the Arrow class; partial lenses
have additional restrictions of ArrowZero
and ArrowChoice
allowing for
failure and
choice.
This is wizardry of the highest order.
Notice how we can still compose lenses freely, whether partial or total:
*Main> :t (.) (.) :: Category cat => cat b c -> cat a b -> cat a c
*Main> M.get (int . example) (Y 1 (X 2 'a')) Just 2
A note on mkLabelsNoTypes
I had been using the noTypes variation to generate lenses that I was exporting in a module, because the TH-assigned type sigs looked pretty nasty. If you do this with >1.0 you will run into the monomorphism restriction and ambiguous type variables.
Instead I would suggest defining exported lables by hand and giving them a nicer looking (or monomorphic if you prefer) type sig.
You can even let fclabels generate the code and just paste it in, e.g.:
Prelude> :set -ddump-splices
Prelude> :l test.hs
[1 of 1] Compiling Main ( test.hs, interpreted )
test.hs:1:1: Splicing declarations
mkLabels ['Example]
======>
test.hs:40:3-21
char ::
forall ~>[a1kk]. (Control.Arrow.ArrowChoice ~>[a1kk],
Control.Arrow.ArrowZero ~>[a1kk]) =>
Lens ~>[a1kk] Example Char
{-# INLINE[0] CONLIKE char #-}
char
= let
c[a1kl]
= (Control.Arrow.zeroArrow Control.Arrow.||| Control.Arrow.returnA)
in
Data.Label.Abstract.lens
(c[a1kl]
. Control.Arrow.arr
(\ p[a1km]
-> case p[a1km] of {
X {} -> Right (_char p[a1km])
_ -> Left GHC.Unit.() }))
(c[a1kl]
. Control.Arrow.arr
(\ (v[a1kn], p[a1ko])
-> case p[a1ko] of {
X {} -> Right (p[a1ko] {_char = v[a1kn]})
_ -> Left GHC.Unit.() }))