microlens-th-0.1.1.0: Automatic generation of record lenses for microlens

Safe HaskellNone
LanguageHaskell2010

Lens.Micro.TH

Contents

Synopsis

Documentation

When updates aren't allowed, or when a field simply can't be updated (for instance, in the presence of forall), instead of Lens and Traversal we generate Getter and Fold. These aren't true Getter and Fold from lens – they're not sufficiently polymorphic. Beware. (Still, they're compatible, it's just that you can't do some things with them that you can do with original ones.)

type Getter s a = forall r. Getting r s a Source

type Fold s a = forall r. Applicative (Const r) => Getting r s a Source

Making lenses

makeLenses :: Name -> DecsQ Source

Generate lenses for a data type or a newtype.

To use, you have to enable Template Haskell:

Then, after declaring the datatype (let's say Foo), add makeLenses ''Foo on a separate line:

data Foo = Foo {
  _x :: Int,
  _y :: Bool }

makeLenses ''Foo

This would generate the following lenses, which can be used to access the fields of Foo:

x :: Lens' Foo Int
x f foo = (\x' -> f {_x = x'}) <$> f (_x foo)

y :: Lens' Foo Bool
y f foo = (\y' -> f {_y = y'}) <$> f (_y foo)

If you don't want a lens to be generated for some field, don't prefix it with an _.

When the data type has type parameters, it's possible for a lens to do a polymorphic update – i.e. change the type of the thing along with changing the type of the field. For instance, with this type:

data Foo a = Foo {
  _x :: a,
  _y :: Bool }

the following lenses would be generated:

x :: Lens (Foo a) (Foo b) a b
y :: Lens' (Foo a) Bool

However, when there are several fields using the same type parameter, type-changing updates are no longer possible:

data Foo a = Foo {
  _x :: a,
  _y :: a }

generates

x :: Lens' (Foo a) a
y :: Lens' (Foo a) a

Next thing. When the type has several constructors, some of fields may not be always present – for those, a Traversal is generated instead. For instance, in this example y can be present or absent:

data FooBar
  = Foo { _x :: Int, _y :: Bool }
  | Bar { _x :: Int }

and the following accessors would be generated:

x :: Lens' FooBar Int
y :: Traversal' FooBar Bool

So, to get _y, you'd have to either use (^?) if you're not sure it's there, or (^?!) if you're absolutely sure (and if you're wrong, you'll get an exception). Setting and updating _y can be done as usual.

makeLensesFor :: [(String, String)] -> Name -> DecsQ Source

Like makeLenses, but lets you choose your own names for lenses:

data Foo = Foo {foo :: Int, bar :: Bool}

makeLensesFor [("foo", "fooLens"), ("bar", "_bar")] ''Foo

would create lenses called fooLens and _bar. This is useful, for instance, when you don't want to prefix your fields with underscores and want to prefix lenses with underscores instead.

If you give the same name to different fields, it will generate a Traversal instead:

data Foo = Foo {slot1, slot2, slot3 :: Int}

makeLensesFor [("slot1", "slots"),
                 ("slot2", "slots"),
                 ("slot3", "slots")] ''Foo

makeLensesWith :: LensRules -> Name -> DecsQ Source

Generate lenses with custom parameters.

This function lets you customise generated lenses; to see what exactly can be changed, look at LensRules. makeLenses is implemented with makeLensesWith – it uses the lensRules configuration (which you can build upon – see the “Configuring lens rules” section).

Here's an example of generating lenses that would use lazy patterns:

data Foo = Foo {_x, _y :: Int}

makeLensesWith (lensRules & generateLazyPatterns .~ True) ''Foo

When there are several modifications to the rules, the code looks nicer when you use flip:

flip makeLensesWith ''Foo $
  lensRules
    & generateLazyPatterns .~ True
    & generateSignatures   .~ False

makeFields :: Name -> DecsQ Source

Generate overloaded lenses.

This lets you deal with several data types having same fields. For instance, let's say you have Foo and Bar, and both have a field named x. To avoid those fields clashing, you would have to use prefixes:

data Foo a = Foo {
  fooX :: Int,
  fooY :: a }

data Bar = Bar {
  barX :: Char }

However, if you use makeFields on both Foo and Bar now, it would generate lenses called x and y – and x would be able to access both fooX and barX! This is done by generating a separate class for each field, and making relevant types instances of that class:

class HasX s a | s -> a where
  x :: Lens' s a

instance HasX (Foo a) Int where
  x :: Lens' (Foo a) Int
  x = ...

instance HasX Bar Char where
  x :: Lens' Bar Char
  x = ...


class HasY s a | s -> a where
  y :: Lens' s a

instance HasY (Foo a) a where
  y :: Lens' (Foo a) a
  y = ...

(There's a minor drawback, tho: you can't perform type-changing updates with these lenses.)

If you only want to make lenses for some fields, you can prefix them with underscores – the rest would be untouched. If no fields are prefixed with underscores, lenses would be created for all fields.

The prefix must be the same as the name of the name of the data type (not the constructor).

If you want to use makeFields on types declared in different modules, you can do it, but then you would have to export the Has* classes from one of the modules – makeFields creates a class if it's not in scope yet, so the class must be in scope or else there would be duplicate classes and you would get an “Ambiguous occurrence” error.

Finally, makeFields is implemented as makeLenses camelCaseFields, so you can build on camelCaseFields if you want to customise behavior of makeFields.

Default lens rules

data LensRules Source

Rules used to generate lenses. You can't create them from scratch, but you can customise already existing ones with lenses in the “Configuring lens rules” section.

For an example, see makeLensesWith.

data DefName Source

Name to give to a generated lens.

Constructors

TopName Name

Simple top-level definiton name

MethodName Name Name

makeFields-style class name and method name

lensRulesFor Source

Arguments

:: [(String, String)]
(Field Name, Lens Name)
-> LensRules 

Used in makeLensesFor.

Configuring lens rules

lensField :: Lens' LensRules (Name -> [Name] -> Name -> [DefName]) Source

Lens' to access the convention for naming fields in our LensRules.

Defaults to stripping the _ off of the field name, lowercasing the name, and skipping the field if it doesn't start with an '_'. The field naming rule provides the names of all fields in the type as well as the current field. This extra generality enables field naming conventions that depend on the full set of names in a type.

The field naming rule has access to the type name, the names of all the field of that type (including the field being named), and the name of the field being named.

TypeName -> FieldNames -> FieldName -> DefinitionNames

simpleLenses :: Lens' LensRules Bool Source

Generate "simple" optics even when type-changing optics are possible. (e.g. Lens' instead of Lens)

createClass :: Lens' LensRules Bool Source

Create the class if the constructor is Simple and the lensClass rule matches.

generateSignatures :: Lens' LensRules Bool Source

Indicate whether or not to supply the signatures for the generated lenses.

Disabling this can be useful if you want to provide a more restricted type signature or if you want to supply hand-written haddocks.

generateUpdateableOptics :: Lens' LensRules Bool Source

Generate "updateable" optics when True. When False, Folds will be generated instead of Traversals and Getters will be generated instead of Lenses. This mode is intended to be used for types with invariants which must be maintained by "smart" constructors.

generateLazyPatterns :: Lens' LensRules Bool Source

Generate optics using lazy pattern matches. This can allow fields of an undefined value to be initialized with lenses:

data Foo = Foo {_x :: Int, _y :: Bool}
  deriving Show

makeLensesWith (lensRules & generateLazyPatterns .~ True) ''Foo
> undefined & x .~ 8 & y .~ True
Foo {_x = 8, _y = True}

(Without generateLazyPatterns, the result would be just undefined.)

The downside of this flag is that it can lead to space-leaks and code-size/compile-time increases when generated for large records. By default this flag is turned off, and strict optics are generated.

When you have a lazy optic, you can get a strict optic from it by composing with ($!):

strictOptic = ($!) . lazyOptic