Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
- makeLenses :: Name -> DecsQ
- makeLensesFor :: [(String, String)] -> Name -> DecsQ
- makeClassy :: Name -> DecsQ
- makeClassyFor :: String -> String -> [(String, String)] -> Name -> DecsQ
- makeClassy_ :: Name -> DecsQ
- makePrisms :: Name -> DecsQ
- makeClassyPrisms :: Name -> DecsQ
- makeWrapped :: Name -> DecsQ
- makeFields :: Name -> DecsQ
- makeFieldsWith :: LensRules -> Name -> DecsQ
- declareLenses :: DecsQ -> DecsQ
- declareLensesFor :: [(String, String)] -> DecsQ -> DecsQ
- declareClassy :: DecsQ -> DecsQ
- declareClassyFor :: [(String, (String, String))] -> [(String, String)] -> DecsQ -> DecsQ
- declarePrisms :: DecsQ -> DecsQ
- declareWrapped :: DecsQ -> DecsQ
- declareFields :: DecsQ -> DecsQ
- makeLensesWith :: LensRules -> Name -> DecsQ
- declareLensesWith :: LensRules -> DecsQ -> DecsQ
- defaultFieldRules :: LensRules
- camelCaseFields :: LensRules
- underscoreFields :: LensRules
- data LensRules
- data DefName
- = TopName Name
- | MethodName Name Name
- lensRules :: LensRules
- lensRulesFor :: [(String, String)] -> LensRules
- classyRules :: LensRules
- classyRules_ :: LensRules
- lensField :: Lens' LensRules ([Name] -> Name -> [DefName])
- lensClass :: Lens' LensRules (Name -> Maybe (Name, Name))
- simpleLenses :: Lens' LensRules Bool
- createClass :: Lens' LensRules Bool
- generateSignatures :: Lens' LensRules Bool
Constructing Lenses Automatically
makeLenses :: Name -> DecsQSource
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'
FooBarInt
x f (Foo a b) = (\a' -> Foo a' b) <$> f a x f (Bar a) = Bar <$> f a y ::Traversal'
FooBarInt
y f (Foo a b) = (\b' -> Foo a b') <$> f b y _ c@(Bar _) = pure c
makeLenses
=makeLensesWith
lensRules
makeLensesFor :: [(String, String)] -> Name -> DecsQSource
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")] ''FoomakeLensesFor
[("_barX", "bar"), ("_barY", "bar")] ''Bar
makeClassy :: Name -> DecsQSource
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'
tInt
fooX = foo . go where go f (Foo x y) = (\x' -> Foo x' y) <$> f x fooY ::Lens'
tInt
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 -> DecsQSource
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 -> DecsQSource
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.
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)
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 -> DecsQSource
Build Wrapped
instance for a given newtype
makeFields :: Name -> DecsQSource
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
makeFields =makeLensesWith
defaultFieldRules
makeFieldsWith :: LensRules -> Name -> DecsQSource
Deprecated: Use makeLensesWith
, functionality merged
Deprecated alias for makeLensesWith
Constructing Lenses Given a Declaration Quote
declareLenses :: DecsQ -> DecsQSource
declareLensesFor :: [(String, String)] -> DecsQ -> DecsQSource
Similar to makeLensesFor
, but takes a declaration quote.
declareClassy :: DecsQ -> DecsQSource
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
} derivingShow
|]
will create
data Foo = FooInt
Int
derivingShow
class HasFoo t where foo ::Lens'
t Foo instance HasFoo Foo where foo =id
fooX, fooY :: HasFoo t =>Lens'
tInt
declareClassyFor :: [(String, (String, String))] -> [(String, String)] -> DecsQ -> DecsQSource
Similar to makeClassyFor
, but takes a declaration quote.
declarePrisms :: DecsQ -> DecsQSource
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 -> DecsQSource
Build Wrapped
instance for each newtype.
declareFields :: DecsQ -> DecsQSource
declareFields =declareFieldsWith
defaultFieldRules
Configuring Lenses
makeLensesWith :: LensRules -> Name -> DecsQSource
Build lenses with a custom configuration.
declareLensesWith :: LensRules -> DecsQ -> DecsQSource
Declare lenses for each records in the given declarations, using the
specified LensRules
. Any record syntax in the input will be stripped
off.
camelCaseFields :: LensRulesSource
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.
underscoreFields :: LensRulesSource
Field rules for fields in the form _prefix_fieldname
Name to give to generated field optics.
TopName Name | Simple top-level definiton name |
MethodName Name Name | makeFields-style class name and method name |
Rules for making fairly simple partial lenses, ignoring the special cases for isomorphisms and traversals, and not making any classes.
Construct a LensRules
value for generating top-level definitions
using the given map from field names to definition names.
classyRules :: LensRulesSource
Rules for making lenses and traversals that precompose another Lens
.
lensField :: Lens' LensRules ([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.
lensClass :: Lens' LensRules (Name -> Maybe (Name, Name))Source
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)
generateSignatures :: 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.