lens-family-th-0.3.0.0: Generate lens-family style lenses

Safe HaskellNone

Lens.Family.TH

Description

Derive lenses for Lens.Family.

Example usage:

 {-# LANGUAGE TemplateHaskell #-}
 
 import Lens.Family
 import Lens.Family.TH
 
 data Foo a = Foo { _bar :: Int, _baz :: a }
            deriving (Show, Read, Eq, Ord)
 $(makeLenses ''Foo)

Synopsis

Documentation

makeLenses :: Name -> Q [Dec]Source

Derive lenses for the record selectors in a single-constructor data declaration, or for the record selector in a newtype declaration. Lenses will only be generated for record fields which are prefixed with an underscore.

Example usage:

$(makeLenses ''Foo)

makeLensesBy :: (String -> Maybe String) -> Name -> Q [Dec]Source

Derive lenses with the provided name transformation and filtering function. Produce Just lensName to generate a lens of the resultant name, or Nothing to not generate a lens for the input record name.

Example usage:

 $(makeLensesBy (\n -> Just (n ++ "L")) ''Foo)

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

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

Example usage:

 $(makeLensesFor [("_foo", "fooLens"), ("bar", "lbar")] ''Foo)

mkLenses :: Name -> Q [Dec]Source

Deprecated: Use makeLenses instead.

mkLensesBy :: (String -> Maybe String) -> Name -> Q [Dec]Source

Deprecated: Use makeLensesBy instead.

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

Deprecated: Use makeLensesFor instead.