-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Automatic generation of record lenses for microlens -- -- This package lets you automatically generate lenses for data types; -- code was extracted from the lens package, and therefore generated -- lenses are fully compatible with ones generated by lens (and can be -- used both from lens and microlens). -- -- This package is a part of the microlens family; see the readme -- on Github. @package microlens-th @version 0.4.3.14 -- | Functions used by Lens.Micro.TH. This is an internal module and -- it may go away or change at any time; do not depend on it. module Lens.Micro.TH.Internal -- | Has a Name class HasName t -- | Extract (or modify) the Name of something name :: HasName t => Lens' t Name -- | Generate many new names from a given base name. newNames :: String -> Int -> Q [Name] -- | Provides for the extraction of free type variables, and alpha -- renaming. class HasTypeVars t typeVarsEx :: HasTypeVars t => Set Name -> Traversal' t Name typeVars :: HasTypeVars t => Traversal' t Name substTypeVars :: HasTypeVars t => Map Name Name -> t -> t datatypeTypeKinded :: DatatypeInfo -> Type -- | Generate an INLINE pragma. inlinePragma :: Name -> [DecQ] -- | Apply arguments to a type constructor. conAppsT :: Name -> [Type] -> Type -- | Template Haskell wants type variables declared in a forall, so we find -- all free type variables in a given type and declare them. quantifyType :: Cxt -> Type -> Type -- | This function works like quantifyType except that it takes a -- list of variables to exclude from quantification. quantifyType' :: Set Name -> Cxt -> Type -> Type -- | Convert a TyVarBndr into its corresponding Type. tvbToType :: TyVarBndr_ flag -> Type -- | Peel off a kind signature from a Type (if it has one). unSigT :: Type -> Type elemOf :: Eq a => Getting (Endo [a]) s a -> a -> s -> Bool lengthOf :: Getting (Endo [a]) s a -> s -> Int setOf :: Ord a => Getting (Endo [a]) s a -> s -> Set a _ForallT :: Traversal' Type ([TyVarBndrSpec], Cxt, Type) instance Lens.Micro.TH.Internal.HasTypeVars (Language.Haskell.TH.Datatype.TyVarBndr.TyVarBndr_ flag) instance Lens.Micro.TH.Internal.HasTypeVars Language.Haskell.TH.Syntax.Name instance Lens.Micro.TH.Internal.HasTypeVars Language.Haskell.TH.Syntax.Type instance Lens.Micro.TH.Internal.HasTypeVars Language.Haskell.TH.Syntax.Con instance Lens.Micro.TH.Internal.HasTypeVars t => Lens.Micro.TH.Internal.HasTypeVars [t] instance Lens.Micro.TH.Internal.HasTypeVars t => Lens.Micro.TH.Internal.HasTypeVars (GHC.Maybe.Maybe t) instance Lens.Micro.TH.Internal.HasName (Language.Haskell.TH.Datatype.TyVarBndr.TyVarBndr_ flag) instance Lens.Micro.TH.Internal.HasName Language.Haskell.TH.Syntax.Name instance Lens.Micro.TH.Internal.HasName Language.Haskell.TH.Syntax.Con module Lens.Micro.TH -- | Generate lenses for a data type or a newtype. -- -- To use it, you have to enable Template Haskell first: -- --
--   {-# LANGUAGE TemplateHaskell #-}
--   
-- -- Then, after declaring the datatype (let's say Foo), add -- makeLenses ''Foo on a separate line (if you do it before the -- type is declared, you'll get a “not in scope” error – see the section -- at the top of this page): -- --
--   data Foo = Foo {
--     _x :: Int,
--     _y :: Bool }
--   
--   makeLenses ''Foo
--   
-- -- This would generate the following lenses, which can be used to access -- the fields of Foo: -- --
--   x :: Lens' Foo Int
--   x f foo = (\x' -> foo {_x = x'}) <$> f (_x foo)
--   
--   y :: Lens' Foo Bool
--   y f foo = (\y' -> foo {_y = y'}) <$> f (_y foo)
--   
-- -- (If you don't want a lens to be generated for some field, don't prefix -- it with “_”.) -- -- If you want to create lenses for many types, you can do it all in one -- place like this (of course, instead you just can use makeLenses -- several times if you feel it would be more readable): -- --
--   data Foo = ...
--   data Bar = ...
--   data Quux = ...
--   
--   concat <$> mapM makeLenses [''Foo, ''Bar, ''Quux]
--   
-- -- When the data type has type parameters, it's possible for a lens to do -- a polymorphic update – i.e. change the type of the thing along with -- changing the type of the field. For instance, with this type -- --
--   data Foo a = Foo {
--     _x :: a,
--     _y :: Bool }
--   
-- -- the following lenses would be generated: -- --
--   x :: Lens (Foo a) (Foo b) a b
--   y :: Lens' (Foo a) Bool
--   
-- -- However, when there are several fields using the same type parameter, -- type-changing updates are no longer possible: -- --
--   data Foo a = Foo {
--     _x :: a,
--     _y :: a }
--   
-- -- generates -- --
--   x :: Lens' (Foo a) a
--   y :: Lens' (Foo a) a
--   
-- -- Finally, when the type has several constructors, some of fields may -- not be always present – for those, a Traversal is -- generated instead. For instance, in this example y can be -- present or absent: -- --
--   data FooBar
--     = Foo { _x :: Int, _y :: Bool }
--     | Bar { _x :: Int }
--   
-- -- and the following accessors would be generated: -- --
--   x :: Lens' FooBar Int
--   y :: Traversal' FooBar Bool
--   
-- -- So, to get _y, you'd have to either use (^?) if you're -- not sure it's there, or (^?!) if you're absolutely sure (and if -- you're wrong, you'll get an exception). Setting and updating -- _y can be done as usual. makeLenses :: Name -> DecsQ -- | Like makeLenses, but lets you choose your own names for lenses: -- --
--   data Foo = Foo {foo :: Int, bar :: Bool}
--   
--   makeLensesFor [("foo", "fooLens"), ("bar", "_bar")] ''Foo
--   
-- -- would create lenses called fooLens and _bar. This is -- useful, for instance, when you don't want to prefix your fields with -- underscores and want to prefix lenses with underscores instead. -- -- If you give the same name to different fields, it will generate a -- Traversal instead: -- --
--   data Foo = Foo {slot1, slot2, slot3 :: Int}
--   
--   makeLensesFor [("slot1", "slots"),
--                  ("slot2", "slots"),
--                  ("slot3", "slots")] ''Foo
--   
-- -- would generate -- --
--   slots :: Traversal' Foo Int
--   slots f foo = Foo <$> f (slot1 foo)
--                     <*> f (slot2 foo)
--                     <*> f (slot3 foo)
--   
makeLensesFor :: [(String, String)] -> Name -> DecsQ -- | Generate lenses with custom parameters. -- -- To see what exactly you can customise, look at the “Configuring lens -- rules” section. Usually you would build upon the lensRules -- configuration, which is used by makeLenses: -- --
--   makeLenses = makeLensesWith lensRules
--   
-- -- Here's an example of generating lenses that would use lazy patterns: -- --
--   data Foo = Foo {_x, _y :: Int}
--   
--   makeLensesWith (lensRules & generateLazyPatterns .~ True) ''Foo
--   
-- -- When there are several modifications to the rules, the code looks -- nicer when you use flip: -- --
--   flip makeLensesWith ''Foo $
--     lensRules
--       & generateLazyPatterns .~ True
--       & generateSignatures   .~ False
--   
makeLensesWith :: LensRules -> Name -> DecsQ -- | Generate overloaded lenses. -- -- This lets you deal with several data types having same fields. For -- instance, let's say you have Foo and Bar, and both -- have a field named x. To avoid those fields clashing, you -- would have to use prefixes: -- --
--   data Foo a = Foo {
--     fooX :: Int,
--     fooY :: a }
--   
--   data Bar = Bar {
--     barX :: Char }
--   
-- -- However, if you use makeFields on both Foo and -- Bar now, it would generate lenses called x and -- y – and x would be able to access both fooX -- and barX! This is done by generating a separate class for -- each field, and making relevant types instances of that class: -- --
--   class HasX s a | s -> a where
--     x :: Lens' s a
--   
--   instance HasX (Foo a) Int where
--     x :: Lens' (Foo a) Int
--     x = ...
--   
--   instance HasX Bar Char where
--     x :: Lens' Bar Char
--     x = ...
--   
--   
--   class HasY s a | s -> a where
--     y :: Lens' s a
--   
--   instance HasY (Foo a) a where
--     y :: Lens' (Foo a) a
--     y = ...
--   
-- -- (There's a minor drawback, though: you can't perform type-changing -- updates with these lenses.) -- -- If you only want to make lenses for some fields, you can prefix them -- with underscores – the rest would be untouched. If no fields are -- prefixed with underscores, lenses would be created for all fields. -- -- The prefix must be the same as the name of the name of the data type -- (not the constructor). If you don't like this behavior, use -- makeLensesWith abbreviatedFields – it allows -- any prefix (and even different prefixes). -- -- If you want to use makeFields on types declared in different -- modules, you can do it, but then you would have to export the -- Has* classes from one of the modules – makeFields -- creates a class if it's not in scope yet, so the class must be in -- scope or else there would be duplicate classes and you would get an -- “Ambiguous occurrence” error. -- -- Finally, makeFields is implemented as makeLensesWith -- camelCaseFields, so you can build on -- camelCaseFields if you want to customise behavior of -- makeFields. makeFields :: Name -> DecsQ -- | Generate overloaded lenses without ad-hoc classes; useful when there's -- a collection of fields that you want to make common for several types. -- -- Like makeFields, each lens is a member of a class. However, the -- classes are per-type and not per-field. Let's take the following type: -- --
--   data Person = Person {
--     _name :: String,
--     _age :: Double }
--   
-- -- makeClassy would generate a single class with 3 methods: -- --
--   class HasPerson c where
--     person :: Lens' c Person
--   
--     age :: Lens' c Double
--     age = person.age
--   
--     name :: Lens' c String
--     name = person.name
--   
-- -- And an instance: -- --
--   instance HasPerson Person where
--     person = id
--   
--     name = ...
--     age = ...
--   
-- -- So, you can use name and age to refer to the -- _name and _age fields, as usual. However, the extra -- lens – person – allows you to do a kind of subtyping. Let's -- say that there's a type called Worker and every worker has -- the same fields that a person has, but also a job. If you -- were using makeFields, you'd do the following: -- --
--   data Worker = Worker {
--     _workerName :: String,
--     _workerAge :: Double,
--     _workerJob :: String }
--   
-- -- However, with makeClassy you can say “every worker is a person” -- in a more principled way: -- --
--   data Worker = Worker {
--     _workerPerson :: Person,
--     _job :: String }
--   
--   makeClassy ''Worker
--   
--   instance HasPerson Worker where person = workerPerson
--   
-- -- Now you can use age and name to access name/age of a -- Worker, but you also can use person to “downgrade” a -- Worker to a Person (and e.g. apply some -- Person-specific function to it). -- -- Unlike makeFields, makeClassy doesn't make use of -- prefixes. _workerPerson could've just as well been named -- _foobar. -- -- makeClassy is implemented as makeLensesWith -- classyRules, so you can build on classyRules if you -- want to customise behavior of makeClassy. makeClassy :: Name -> DecsQ -- | Rules used to generate lenses. The fields are intentionally not -- exported; to create your own rules, see lenses in the “Configuring -- lens rules” section. You'd have to customise one of the existing -- rulesets; for an example of doing that, see makeLensesWith. data LensRules -- | Name to give to a generated lens (used in lensField). data DefName -- | Simple top-level definiton name TopName :: Name -> DefName -- | makeFields-style class name and method name MethodName :: Name -> Name -> DefName -- | Lens rules used by default (i.e. in makeLenses): -- -- lensRules :: LensRules -- | A modification of lensRules used by makeLensesFor (the -- only difference is that a simple lookup function is used for -- lensField). lensRulesFor :: [(String, String)] -> LensRules -- | Lens rules used by makeClassy: -- -- classyRules :: LensRules -- | Lens rules used by makeFields: -- -- camelCaseFields :: LensRules -- | Like standard rules used by makeFields, but doesn't put any -- restrictions on the prefix. I.e. if you have fields called -- -- -- -- then the generated lenses would be called barBaz and -- x. abbreviatedFields :: LensRules -- | This lets you choose which fields would have lenses generated for them -- and how would those lenses be called. To do that, you provide a -- function that would take a field name and output a list (possibly -- empty) of lenses that should be generated for that field. -- -- Here's the full type of the function you have to provide: -- --
--   Name ->     -- The datatype lenses are being generated for
--   [Name] ->   -- A list of all fields of the datatype
--   Name ->     -- The current field
--   [DefName]   -- A list of lens names
--   
-- -- Most of the time you won't need the first 2 parameters, but sometimes -- they are useful – for instance, the list of all fields would be useful -- if you wanted to implement a slightly more complicated rule like “if -- some fields are prefixed with underscores, generate lenses for them, -- but if no fields are prefixed with underscores, generate lenses for -- all fields”. -- -- As an example, here's a function used by default. It strips “_” off -- the field name, lowercases the next character after “_”, and skips the -- field entirely if it doesn't start with “_”: -- --
--   \_ _ n ->
--     case nameBase n of
--       '_':x:xs -> [TopName (mkName (toLower x : xs))]
--       _        -> []
--   
-- -- You can also generate classes (i.e. what makeFields does) by -- using MethodName className lensName instead of -- TopName lensName. lensField :: Lens' LensRules (Name -> [Name] -> Name -> [DefName]) -- | This lets you choose whether a class would be generated for the type -- itself (like makeClassy does). If so, you can choose the name -- of the class and the name of the type-specific lens. -- -- For makeLenses and makeFields this is just const -- Nothing. For makeClassy this function is defined like -- this: -- --
--   \n ->
--     case nameBase n of
--       x:xs -> Just (mkName (Has ++ x:xs), mkName (toLower x : xs))
--       []   -> Nothing
--   
lensClass :: Lens' LensRules (Name -> Maybe (Name, Name)) -- | Decide whether generation of classes is allowed at all. -- -- If this is disabled, neither makeFields nor makeClassy -- would work, regardless of values of lensField or -- lensClass. On the other hand, if lensField and -- lensClass don't generate any classes, enabling this won't have -- any effect. createClass :: Lens' LensRules Bool -- | Generate simple (monomorphic) lenses even when type-changing lenses -- are possible – i.e. Lens' instead of Lens and -- Traversal' instead of Traversal. Just in case, here's an -- example of a situation when type-changing lenses would be normally -- generated: -- --
--   data Foo a = Foo { _foo :: a }
--   
-- -- Generated lens: -- --
--   foo :: Lens (Foo a) (Foo b) a b
--   
-- -- Generated lens with simpleLenses turned on: -- --
--   foo :: Lens' (Foo a) a
--   
-- -- This option is disabled by default. simpleLenses :: Lens' LensRules Bool -- | Supply type signatures for the generated lenses. -- -- This option is enabled by default. Disable it if you want to write the -- signature by yourself – for instance, if the signature should be more -- restricted, or if you want to write haddocks for the lens (as haddocks -- are attached to the signature and not to the definition). generateSignatures :: Lens' LensRules Bool -- | Generate “updateable” optics. When turned off, SimpleFolds will -- be generated instead of Traversals and SimpleGetters -- will be generated instead of Lenses. -- -- This option is enabled by default. Disabling it can be useful for -- types with invariants (also known as “types with smart constructors”) -- – if you generate updateable optics, anyone would be able to use them -- to break your invariants. generateUpdateableOptics :: Lens' LensRules Bool -- | Generate lenses 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}
--   
-- -- (Without generateLazyPatterns, the result would be just -- undefined.) -- -- This option is disabled by default. The downside of enabling it is -- that it can lead to space-leaks and code-size/compile-time increases -- when lenses are generated for large records. -- -- When you have a lazy lens, you can get a strict lens from it by -- composing with ($!): -- --
--   strictLens = ($!) . lazyLens
--   
generateLazyPatterns :: Lens' LensRules Bool instance GHC.Classes.Ord Lens.Micro.TH.DefName instance GHC.Classes.Eq Lens.Micro.TH.DefName instance GHC.Show.Show Lens.Micro.TH.DefName