lens-4.7.0.1: Lenses, Folds and Traversals

Copyright(C) 2012-14 Edward Kmett, Michael Sloan
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell98

Control.Lens.TH

Contents

Description

 

Synopsis

Constructing Lenses Automatically

makeLenses :: Name -> DecsQ

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

e.g.

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

will create

x :: Lens' FooBar Int
x f (Foo a b) = (\a' -> Foo a' b) <$> f a
x f (Bar a)   = Bar <$> f a
y :: Traversal' FooBar Int
y f (Foo a b) = (\b' -> Foo a  b') <$> f b
y _ c@(Bar _) = pure c
makeLenses = makeLensesWith lensRules

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

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

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 :: Lens' t Foo
  fooX :: Lens' t Int
  fooX = foo . go where go f (Foo x y) = (\x' -> Foo x' y) <$> f x
  fooY :: Lens' t Int
  fooY = foo . go where go f (Foo x y) = (\y' -> Foo x y') <$> f y
instance HasFoo Foo where
  foo = id
makeClassy = makeLensesWith classyRules

makeClassyFor :: String -> String -> [(String, String)] -> Name -> DecsQ

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

makeClassy_ :: Name -> DecsQ

Make lenses and traversals for a type, and create a class when the type has no arguments. Works the same as makeClassy except that (a) it expects that record field names do not begin with an underscore, (b) all record fields are made into lenses, and (c) the resulting lens is prefixed with an underscore.

makePrisms

Arguments

:: Name

Type constructor name

-> DecsQ 

Generate a Prism for each constructor of a data type. Isos generated when possible. Reviews are created for constructors with existentially quantified constructors and GADTs.

e.g.

data FooBarBaz a
  = Foo Int
  | Bar a
  | Baz Int Char
makePrisms ''FooBarBaz

will create

_Foo :: Prism' (FooBarBaz a) Int
_Bar :: Prism (FooBarBaz a) (FooBarBaz b) a b
_Baz :: Prism' (FooBarBaz a) (Int, Char)

makeClassyPrisms

Arguments

:: Name

Type constructor name

-> DecsQ 

Generate a Prism for each constructor of a data type and combine them into a single class. No Isos are created. Reviews are created for constructors with existentially quantified constructors and GADTs.

e.g.

data FooBarBaz a
  = Foo Int
  | Bar a
  | Baz Int Char
makeClassyPrisms ''FooBarBaz

will create

class AsFooBarBaz s a | s -> a where
  _FooBarBaz :: Prism' s (FooBarBaz a)
  _Foo :: Prism' s Int
  _Bar :: Prism' s a
  _Baz :: Prism' s (Int,Char)

  _Foo = _FooBarBaz . _Foo
  _Bar = _FooBarBaz . _Bar
  _Baz = _FooBarBaz . _Baz

instance AsFooBarBaz (FooBarBaz a) a

Generate an As class of prisms. Names are selected by prefixing the constructor name with an underscore. Constructors with multiple fields will construct Prisms to tuples of those fields.

makeWrapped :: Name -> DecsQ

Build Wrapped instance for a given newtype

makeFields :: Name -> DecsQ

Generate overloaded field accessors.

e.g

data Foo a = Foo { _fooX :: Int, _fooY : a }
newtype Bar = Bar { _barX :: Char }
makeFields ''Foo
makeFields ''Bar

will create

_fooXLens :: Lens' (Foo a) Int
_fooYLens :: Lens (Foo a) (Foo b) a b
class HasX s a | s -> a where
  x :: Lens' s a
instance HasX (Foo a) Int where
  x = _fooXLens
class HasY s a | s -> a where
  y :: Lens' s a
instance HasY (Foo a) a where
  y = _fooYLens
_barXLens :: Iso' Bar Char
instance HasX Bar Char where
  x = _barXLens

For details, see camelCaseFields.

makeFields = makeLensesWith defaultFieldRules

makeFieldsWith :: LensRules -> Name -> DecsQ

Deprecated: Use makeLensesWith, functionality merged

Deprecated alias for makeLensesWith

Constructing Lenses Given a Declaration Quote

declareLenses :: DecsQ -> DecsQ

Make lenses for all records in the given declaration quote. All record syntax in the input will be stripped off.

e.g.

declareLenses [d|
  data Foo = Foo { fooX, fooY :: Int }
    deriving Show
  |]

will create

data Foo = Foo Int Int deriving Show
fooX, fooY :: Lens' Foo Int

declareLensesFor :: [(String, String)] -> DecsQ -> DecsQ

Similar to makeLensesFor, but takes a declaration quote.

declareClassy :: DecsQ -> DecsQ

For each record in the declaration quote, make lenses and traversals for it, and create a class when the type has no arguments. All record syntax in the input will be stripped off.

e.g.

declareClassy [d|
  data Foo = Foo { fooX, fooY :: Int }
    deriving Show
  |]

will create

data Foo = Foo Int Int deriving Show
class HasFoo t where
  foo :: Lens' t Foo
instance HasFoo Foo where foo = id
fooX, fooY :: HasFoo t => Lens' t Int

declareClassyFor :: [(String, (String, String))] -> [(String, String)] -> DecsQ -> DecsQ

Similar to makeClassyFor, but takes a declaration quote.

declarePrisms :: DecsQ -> DecsQ

Generate a Prism for each constructor of each data type.

e.g.

declarePrisms [d|
  data Exp = Lit Int | Var String | Lambda{ bound::String, body::Exp }
  |]

will create

data Exp = Lit Int | Var String | Lambda { bound::String, body::Exp }
_Lit :: Prism' Exp Int
_Var :: Prism' Exp String
_Lambda :: Prism' Exp (String, Exp)

declareWrapped :: DecsQ -> DecsQ

Build Wrapped instance for each newtype.

Configuring Lenses

makeLensesWith :: LensRules -> Name -> DecsQ

Build lenses with a custom configuration.

declareLensesWith :: LensRules -> DecsQ -> DecsQ

Declare lenses for each records in the given declarations, using the specified LensRules. Any record syntax in the input will be stripped off.

camelCaseFields :: LensRules

Field rules for fields in the form prefixFieldname or _prefixFieldname If you want all fields to be lensed, then there is no reason to use an _ before the prefix. If any of the record fields leads with an _ then it is assume a field without an _ should not have a lens created.

Note: The prefix must be the same as the typename (with the first letter lowercased). This is a change from lens versions before lens 4.5. If you want the old behaviour, use makeLensesWith abbreviatedFields

underscoreFields :: LensRules

Field rules for fields in the form _prefix_fieldname

abbreviatedFields :: LensRules

Field rules fields in the form prefixFieldname or _prefixFieldname If you want all fields to be lensed, then there is no reason to use an _ before the prefix. If any of the record fields leads with an _ then it is assume a field without an _ should not have a lens created.

Note that prefix may be any string of characters that are not uppercase letters. (In particular, it may be arbitrary string of lowercase letters and numbers) This is the behavior that defaultFieldRules had in lens 4.4 and earlier.

data DefName

Name to give to generated field optics.

Constructors

TopName Name

Simple top-level definiton name

MethodName Name Name

makeFields-style class name and method name

lensRules :: LensRules

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

lensRulesFor

Arguments

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

Construct a LensRules value for generating top-level definitions using the given map from field names to definition names.

classyRules :: LensRules

Rules for making lenses and traversals that precompose another Lens.

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

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

lensClass :: Lens' LensRules (Name -> Maybe (Name, Name))

Retrieve options such as the name of the class and method to put in it to build a class around monomorphic data types. Classy lenses are generated when this naming convention is provided. TypeName -> Maybe (ClassName, MainMethodName)

simpleLenses :: Lens' LensRules Bool

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

createClass :: Lens' LensRules Bool

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

generateSignatures :: Lens' LensRules Bool

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

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.