Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
- makeLenses :: Name -> Q [Dec]
- makeLensesFor :: [(String, String)] -> Name -> Q [Dec]
- makeClassy :: Name -> Q [Dec]
- makeClassyFor :: String -> String -> [(String, String)] -> Name -> Q [Dec]
- makeClassy_ :: Name -> Q [Dec]
- makeIso :: Name -> Q [Dec]
- makePrisms :: Name -> Q [Dec]
- makeWrapped :: Name -> DecsQ
- makeFields :: Name -> Q [Dec]
- declareLenses :: Q [Dec] -> Q [Dec]
- declareLensesFor :: [(String, String)] -> Q [Dec] -> Q [Dec]
- declareClassy :: Q [Dec] -> Q [Dec]
- declareClassyFor :: [(String, (String, String))] -> [(String, String)] -> Q [Dec] -> Q [Dec]
- declareIso :: Q [Dec] -> Q [Dec]
- declarePrisms :: Q [Dec] -> Q [Dec]
- declareWrapped :: Q [Dec] -> Q [Dec]
- declareFields :: Q [Dec] -> Q [Dec]
- makeLensesWith :: LensRules -> Name -> Q [Dec]
- makeFieldsWith :: FieldRules -> Name -> Q [Dec]
- declareLensesWith :: LensRules -> Q [Dec] -> Q [Dec]
- declareFieldsWith :: FieldRules -> Q [Dec] -> Q [Dec]
- defaultRules :: LensRules
- defaultFieldRules :: FieldRules
- camelCaseFields :: FieldRules
- underscoreFields :: FieldRules
- data LensRules = LensRules (String -> Maybe String) (String -> Maybe String) (String -> Maybe (String, String)) (Set LensFlag)
- data FieldRules = FieldRules ([String] -> String -> Maybe String) (String -> String) (String -> Maybe String) (String -> Maybe String)
- lensRules :: LensRules
- classyRules :: LensRules
- classyRules_ :: LensRules
- isoRules :: LensRules
- lensIso :: Lens' LensRules (String -> Maybe String)
- lensField :: Lens' LensRules (String -> Maybe String)
- lensClass :: Lens' LensRules (String -> Maybe (String, String))
- lensFlags :: Lens' LensRules (Set LensFlag)
- data LensFlag
- simpleLenses :: Lens' LensRules Bool
- partialLenses :: Lens' LensRules Bool
- buildTraversals :: Lens' LensRules Bool
- handleSingletons :: Lens' LensRules Bool
- singletonIso :: Lens' LensRules Bool
- singletonRequired :: Lens' LensRules Bool
- createClass :: Lens' LensRules Bool
- createInstance :: Lens' LensRules Bool
- classRequired :: Lens' LensRules Bool
- singletonAndField :: Lens' LensRules Bool
- generateSignatures :: Lens' LensRules Bool
Constructing Lenses Automatically
makeLenses :: Name -> Q [Dec]Source
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 -> 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")] ''FoomakeLensesFor
[("_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
tInt
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
makeClassy_ :: Name -> Q [Dec]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.
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.
newtypeList
a =List
[a]makeIso
''List
will create
list
::Iso
[a] [b] (List
a) (List
b)
makeIso
=makeLensesWith
isoRules
makePrisms :: Name -> Q [Dec]Source
Generate a Prism
for each constructor of a data type.
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)
makeWrapped :: Name -> DecsQSource
Build Wrapped
instance for a given newtype
makeFields :: Name -> Q [Dec]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
_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 =makeFieldsWith
defaultFieldRules
Constructing Lenses Given a Declaretion Quote
declareLenses :: Q [Dec] -> Q [Dec]Source
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
} derivingShow
|]
will create
data Foo = FooInt
Int
derivingShow
fooX, fooY ::Lens'
Foo Int
declareLenses =declareLensesWith
(lensRules
&
lensField
.~
Just
)
declareLensesFor :: [(String, String)] -> Q [Dec] -> Q [Dec]Source
Similar to makeLensesFor
, but takes a declaration quote.
declareClassy :: Q [Dec] -> Q [Dec]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
} 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
declareClassy =declareLensesWith
(classyRules
&
lensField
.~
Just
)
declareClassyFor :: [(String, (String, String))] -> [(String, String)] -> Q [Dec] -> Q [Dec]Source
Similar to makeClassyFor
, but takes a declaration quote.
declareIso :: Q [Dec] -> Q [Dec]Source
For each datatype declaration, make a top level isomorphism injecting into the type. The types are required to be for a type with a single constructor that has a single argument.
All record syntax in the input will be stripped off.
e.g.
declareIso [d| newtype WrappedInt = Wrap { unrwap ::Int
} newtypeList
a =List
[a] |]
will create
newtype WrappedList = WrapInt
newtype List a = List [a]wrap
::Iso'
Int WrappedIntunwrap
::Iso'
WrappedInt Intlist
::Iso
[a] [b] (List
a) (List
b)
declareIso =declareLensesWith
(isoRules
&
lensField
.~
Just
)
declarePrisms :: Q [Dec] -> Q [Dec]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)
declareFields :: Q [Dec] -> Q [Dec]Source
declareFields =declareFieldsWith
defaultFieldRules
Configuring Lenses
makeFieldsWith :: FieldRules -> Name -> Q [Dec]Source
Make fields with the specified FieldRules
.
declareLensesWith :: LensRules -> Q [Dec] -> Q [Dec]Source
Declare lenses for each records in the given declarations, using the
specified LensRules
. Any record syntax in the input will be stripped
off.
declareFieldsWith :: FieldRules -> Q [Dec] -> Q [Dec]Source
Declare fields for each records in the given declarations, using the
specified FieldRules
. Any record syntax in the input will be stripped
off.
defaultRules :: LensRulesSource
Default LensRules
.
defaultFieldRules :: FieldRulesSource
defaultFieldRules = camelCaseFields
camelCaseFields :: FieldRulesSource
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 :: FieldRulesSource
Field rules for fields in the form _prefix_fieldname
This configuration describes the options we'll be using to make isomorphisms or lenses.
data FieldRules Source
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
.
lensClass :: 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 :: 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.
Flags for Lens
construction
buildTraversals :: 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 :: Lens' LensRules BoolSource
Handle singleton constructors specially.
singletonRequired :: Lens' LensRules BoolSource
Expect a single constructor, single field newtype or data type.
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.