optics-th-0.1: Optics construction using TemplateHaskell

Safe HaskellNone
LanguageHaskell2010

Optics.TH

Contents

Synopsis

Generation of field optics

Labels

makeFieldLabels :: Name -> DecsQ Source #

Build field optics as instances of LabelOptic class for use as overloaded labels.

e.g.

data Animal
  = Cat { animalAge  :: Int
        , animalName :: String
        }
  | Dog { animalAge    :: Int
        , animalAbsurd :: forall a b. a -> b
        }
makeFieldLabels ''Animal

will create

instance
  (a ~ Int, b ~ Int
  ) => LabelOptic "age" A_Lens Animal Animal a b where
  labelOptic = lensVL $ \f s -> case s of
    Cat x1 x2 -> fmap (\y -> Cat y x2) (f x1)
    Dog x1 x2 -> fmap (\y -> Dog y x2) (f x1)

instance
  (a ~ String, b ~ String
  ) => LabelOptic "name" An_AffineTraversal Animal Animal a b where
  labelOptic = atraversalVL $ \point f s -> case s of
    Cat x1 x2 -> fmap (\y -> Cat x1 y) (f x2)
    Dog x1 x2 -> point (Dog x1 x2)

which can be used as #age and #name with language extension OverloadedLabels.

Note: if you wonder about the form of instances or why there is no label for animalAbsurd, check documentation for LabelOptic.

makeFieldOptics = makeFieldLabelsWith fieldLabelsRules

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

Derive field optics as labels, specifying explicit pairings of (fieldName, labelName).

If you map multiple fields to the same label and it is present in the same constructor, Traversal (or Fold for a read only version) will be generated.

e.g.

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

makeFieldLabelsWith :: LensRules -> Name -> DecsQ Source #

Build field optics as labels with a custom configuration.

declareFieldLabels :: DecsQ -> DecsQ Source #

Make field optics as labels for all records in the given declaration quote. All record syntax in the input will be stripped off.

e.g.

declareLenses [d|
  data Dog = Dog { name :: String, age :: Int }
    deriving Show
  |]

will create

data Dog = Dog String Int
  deriving Show
instance LabelOptic "name" A_Lens Dog Dog ...
instance LabelOptic "age" A_Lens Dog Dog ...

declareFieldLabelsFor :: [(String, String)] -> DecsQ -> DecsQ Source #

Similar to makeFieldLabelsFor, but takes a declaration quote.

fieldLabelsRules :: LensRules Source #

Rules for generation of LabelOptic intances for use with OverloadedLabels. Same as lensRules, but uses camelCaseNamer.

Note: if you don't want to prefix field names with the full name of the data type, you can use abbreviatedNamer instead.

fieldLabelsRulesFor Source #

Arguments

:: [(String, String)]
(Field name, Label name)
-> LensRules 

Construct a LensRules value for generating LabelOptic instances using the given map from field names to definition names.

Functions

makeLenses :: Name -> DecsQ Source #

Build field optics as top level functions with a sensible default configuration.

e.g.

data Animal
  = Cat { _age  :: Int
        , _name :: String
        }
  | Dog { _age    :: Int
        , _absurd :: forall a b. a -> b
        }
makeLenses ''Animal

will create

absurd :: forall a b. AffineFold Animal (a -> b)
absurd = afolding $ \s -> case s of
  Cat _ _ -> Nothing
  Dog _ x -> Just x

age :: Lens' Animal Int
age = lensVL $ \f s -> case s of
  Cat x1 x2 -> fmap (\y -> Cat y x2) (f x1)
  Dog x1 x2 -> fmap (\y -> Dog y x2) (f x1)

name :: AffineTraversal' Animal String
name = atraversalVL $ \point f s -> case s of
  Cat x1 x2 -> fmap (\y -> Cat x1 y) (f x2)
  Dog x1 x2 -> point (Dog x1 x2)
makeLenses = makeLensesWith lensRules

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

Derive field optics, specifying explicit pairings of (fieldName, opticName).

If you map multiple fields to the same optic and it is present in the same constructor, Traversal (or Fold for a read only version) will be generated.

e.g.

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

makeLensesWith :: LensRules -> Name -> DecsQ Source #

Build field optics with a custom configuration.

declareLenses :: DecsQ -> DecsQ Source #

Make field optics 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 Source #

Similar to makeLensesFor, but takes a declaration quote.

lensRules :: LensRules Source #

Rules for making read-write field optics as top-level functions. It uses underscoreNoPrefixNamer.

lensRulesFor Source #

Arguments

:: [(String, String)]
(Field name, Optic name)
-> LensRules 

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

Single class per data type

makeClassy :: Name -> DecsQ 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 c where
  foo  :: Lens' c Foo
  fooX :: Lens' c Int
  fooY :: Lens' c Int
  fooX = foo % fooX
  fooY = foo % fooY

instance HasFoo Foo where
  foo  = lensVL id
  fooX = lensVL $ \f s -> case s of
    Foo x1 x2 -> fmap (\y -> Foo y x2) (f x1)
  fooY = lensVL $ \f s -> case s of
    Foo x1 x2 -> fmap (\y -> Foo x1 y) (f x2)
makeClassy = makeLensesWith classyRules

makeClassy_ :: Name -> DecsQ Source #

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.

makeClassyFor :: String -> String -> [(String, String)] -> Name -> DecsQ 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

declareClassy :: DecsQ -> DecsQ Source #

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 Source #

Similar to makeClassyFor, but takes a declaration quote.

classyRules :: LensRules Source #

Rules for making lenses and traversals that precompose another Lens.

classyRulesFor Source #

Arguments

:: (String -> Maybe (String, String))

Type Name -> Maybe (Class Name, Method Name)

-> [(String, String)]
(Field Name, Method Name)
-> LensRules 

Rules for making lenses and traversals that precompose another Lens using a custom function for naming the class, main class method, and a mapping from field names to definition names.

Multiple classes per data type

makeFields :: Name -> DecsQ Source #

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

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

instance HasX (Foo a) Int where
  x = lensVL $ \f s -> case s of
    Foo x1 x2 -> fmap (\y -> Foo y x2) (f x1)

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

instance HasY (Foo a) a where
  y = lensVL $ \f s -> case s of
    Foo x1 x2 -> fmap (\y -> Foo x1 y) (f x2)

instance HasX Bar Char where
  x = lensVL $ \f s -> case s of
    Bar x1 -> fmap (\y -> Bar y) (f x1)

For details, see camelCaseFields.

makeFields = makeLensesWith defaultFieldRules

makeFieldsNoPrefix :: Name -> DecsQ Source #

Generate overloaded field accessors based on field names which are only prefixed with an underscore (e.g. _name), not additionally with the type name (e.g. _fooName).

This might be the desired behaviour in case the DuplicateRecordFields language extension is used in order to get rid of the necessity to prefix each field name with the type name.

As an example:

data Foo a  = Foo { _x :: Int, _y :: a }
newtype Bar = Bar { _x :: Char }
makeFieldsNoPrefix ''Foo
makeFieldsNoPrefix ''Bar

will create classes

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

together with instances

instance HasX (Foo a) Int
instance HasY (Foo a) a where
instance HasX Bar Char where

For details, see classUnderscoreNoPrefixFields.

makeFieldsNoPrefix = makeLensesWith classUnderscoreNoPrefixFields

Generation of constructor optics

Labels

Functions

makePrisms Source #

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)

declarePrisms :: DecsQ -> DecsQ Source #

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)

Single class per data type

makeClassyPrisms Source #

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.

Generation rules for field optics

data LensRules Source #

Rules to construct lenses for data fields.

simpleLenses :: Lens' LensRules Bool Source #

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

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, (affine) folds will be generated instead of (affine) 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}

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 using lazy optics the strict optic can be recovered by composing with equality':

strictOptic = equality' % lazyOptic

createClass :: Lens' LensRules Bool Source #

Create the class if the constructor if generated lenses would be type-preserving and the lensClass rule matches.

lensField :: Lens' LensRules FieldNamer Source #

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

lensClass :: Lens' LensRules ClassyNamer Source #

Lens' to access the option for naming "classy" lenses.

Common rules

underscoreFields :: LensRules Source #

Field rules for fields in the form _prefix_fieldname

camelCaseFields :: LensRules Source #

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

classUnderscoreNoPrefixFields :: LensRules Source #

Field rules for fields in the form _fieldname (the leading underscore is mandatory).

Note: The primary difference to camelCaseFields is that for classUnderscoreNoPrefixFields the field names are not expected to be prefixed with the type name. This might be the desired behaviour when the DuplicateRecordFields extension is enabled.

abbreviatedFields :: LensRules Source #

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.

Field namers

type FieldNamer Source #

Arguments

 = Name

Name of the data type that lenses are being generated for.

-> [Name]

Names of all fields (including the field being named) in the data type.

-> Name

Name of the field being named.

-> [DefName]

Name(s) of the lens functions. If empty, no lens is created for that field.

The rule to create function names of lenses for data fields.

Although it's sometimes useful, you won't need the first two arguments most of the time.

type ClassyNamer Source #

Arguments

 = Name

Name of the data type that lenses are being generated for.

-> Maybe (Name, Name)

Names of the class and the main method it generates, respectively.

The optional rule to create a class and method around a monomorphic data type. If this naming convention is provided, it generates a "classy" lens.

data DefName Source #

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

Instances
Eq DefName Source # 
Instance details

Defined in Optics.TH.Internal.Product

Methods

(==) :: DefName -> DefName -> Bool #

(/=) :: DefName -> DefName -> Bool #

Ord DefName Source # 
Instance details

Defined in Optics.TH.Internal.Product

Show DefName Source # 
Instance details

Defined in Optics.TH.Internal.Product

underscoreNoPrefixNamer :: FieldNamer Source #

A FieldNamer that strips the _ off of the field name, lowercases the name, and skips the field if it doesn't start with an '_'.

lookingupNamer :: [(String, String)] -> FieldNamer Source #

Create a FieldNamer from explicit pairings of (fieldName, lensName).

mappingNamer Source #

Arguments

:: (String -> [String])

A function that maps a fieldName to lensNames.

-> FieldNamer 

Create a FieldNamer from a mapping function. If the function returns [], it creates no lens for the field.