lens-3.7.1.2: Lenses, Folds and Traversals

PortabilityTemplateHaskell
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Control.Lens.TH

Contents

Description

 

Synopsis

Constructing Lenses Automatically

makeLenses :: Name -> Q [Dec]Source

Build lenses (and traversals) with a sensible default configuration.

 makeLenses = makeLensesWith lensRules

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

Derive lenses and traversals, specifying explicit pairings of (fieldName, lensName).

If you map multiple names to the same label, and it is present in the same constructor then this will generate a Traversal.

e.g.

 makeLensesFor [("_foo", "fooLens"), ("baz", "lbaz")] ''Foo
 makeLensesFor [("_barX", "bar"), ("_barY", "bar)] ''Bar

makeClassy :: Name -> Q [Dec]Source

Make lenses and traversals for a type, and create a class when the type has no arguments.

e.g.

 data Foo = Foo { _fooX, _fooY :: Int }
 makeClassy ''Foo

will create

 class HasFoo t where
   foo :: Simple Lens t Foo
 instance HasFoo Foo where foo = id
 fooX, fooY :: HasFoo t => Simple Lens t Int
 makeClassy = makeLensesWith classyRules

makeClassyFor :: String -> String -> [(String, String)] -> Name -> Q [Dec]Source

Derive lenses and traversals, using a named wrapper class, and specifying explicit pairings of (fieldName, traversalName).

Example usage:

 makeClassyFor "HasFoo" "foo" [("_foo", "fooLens"), ("bar", "lbar")] ''Foo

makeIso :: Name -> Q [Dec]Source

Make a top level isomorphism injecting into the type.

The supplied name is required to be for a type with a single constructor that has a single argument

e.g.

 newtype List a = List [a]
 makeIso ''List

will create

 list :: Iso [a] [b] (List a) (List b)
 makeIso = makeLensesWith isoRules

Configuring Lenses

makeLensesWith :: LensRules -> Name -> Q [Dec]Source

Build lenses with a custom configuration.

defaultRules :: LensRulesSource

Default lens rules

data LensRules Source

This configuration describes the options we'll be using to make isomorphisms or lenses.

lensRules :: LensRulesSource

Rules for making fairly simple partial lenses, ignoring the special cases for isomorphisms and traversals, and not making any classes.

classyRules :: LensRulesSource

Rules for making lenses and traversals that precompose another lens.

isoRules :: LensRulesSource

Rules for making an isomorphism from a data type

lensIso :: Simple Lens LensRules (String -> Maybe String)Source

Lens to access the convention for naming top level isomorphisms in our lens rules.

Defaults to lowercasing the first letter of the constructor.

lensField :: Simple Lens LensRules (String -> Maybe String)Source

Lens to access the convention for naming fields in our lens rules.

Defaults to stripping the _ off of the field name, lowercasing the name, and rejecting the field if it doesn't start with an '_'.

lensClass :: Simple Lens LensRules (String -> Maybe (String, String))Source

Retrieve options such as the name of the class and method to put in it to build a class around monomorphic data types.

lensFlags :: Simple Lens LensRules (Set LensFlag)Source

Retrieve options such as the name of the class and method to put in it to build a class around monomorphic data types.

simpleLenses :: Simple Lens LensRules BoolSource

Only Generate valid Simple Lens lenses.

partialLenses :: Simple Lens LensRules BoolSource

Enables the generation of partial lenses, generating runtime errors for every constructor that does not have a valid definition for the lens. This occurs when the constructor lacks the field, or has multiple fields mapped to the same lens.

buildTraversals :: Simple Lens LensRules BoolSource

In the situations that a lens would be partial, when partialLenses is used, this flag instead causes traversals to be generated. Only one can be used, and if neither are, then compile-time errors are generated.

handleSingletons :: Simple Lens LensRules BoolSource

Handle singleton constructors specially.

singletonIso :: Simple Lens LensRules BoolSource

Use Iso for singleton constructors.

singletonRequired :: Simple Lens LensRules BoolSource

Expect a single constructor, single field newtype or data type.

createClass :: Simple Lens LensRules BoolSource

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

createInstance :: Simple Lens LensRules BoolSource

Create the instance if the constructor is simple and the lensClass rule matches.

classRequired :: Simple Lens LensRules BoolSource

Die if the lensClass fails to match.

singletonAndField :: Simple Lens LensRules BoolSource

When building a singleton Iso (or Lens) for a record constructor, build both the Iso (or Lens) for the record and the one for the field.

generateSignatures :: Simple Lens LensRules BoolSource

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.