{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Trustworthy #-}

#ifndef MIN_VERSION_template_haskell
#define MIN_VERSION_template_haskell(x,y,z) (defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 706)
#endif

#ifndef MIN_VERSION_containers
#define MIN_VERSION_containers(x,y,z) 1
#endif

#if __GLASGOW_HASKELL__ >= 800
{-# LANGUAGE TemplateHaskellQuotes #-}
#else
{-# LANGUAGE TemplateHaskell #-}
#endif


{- |
Module      :  Lens.Micro.TH
Copyright   :  (C) 2013-2016 Eric Mertens, Edward Kmett, Artyom Kazak; 2018 Monadfix
License     :  BSD-style (see the file LICENSE)
-}
module Lens.Micro.TH
(
  -- * Dealing with “not in scope” errors
  -- $errors-note

  -- * Using this module in GHCi
  -- $ghci-note

  -- * 'SimpleGetter' and 'SimpleFold'
  -- $getter-fold-note

  -- * Generating lenses
  makeLenses,
  makeLensesFor,
  makeLensesWith,
  makeFields,
  makeClassy,

  -- * Default lens rules
  LensRules,
  DefName(..),
  lensRules,
  lensRulesFor,
  classyRules,
  camelCaseFields,
  abbreviatedFields,

  -- * Configuring lens rules
  lensField,
  lensClass,
  createClass,
  simpleLenses,
  generateSignatures,
  generateUpdateableOptics,
  generateLazyPatterns,
)
where


import           Control.Monad
import           Control.Monad.Trans.State
import           Data.Char
import           Data.Data
import           Data.Either
import qualified Data.Map as Map
import           Data.Map (Map)
import qualified Data.Set as Set
import           Data.Set (Set)
import           Data.List (nub, findIndices, stripPrefix, isPrefixOf)
import           Data.Maybe
import           Lens.Micro
import           Lens.Micro.Internal (phantom)
import           Lens.Micro.TH.Internal
import           Language.Haskell.TH
import qualified Language.Haskell.TH.Datatype as D
import qualified Language.Haskell.TH.Datatype.TyVarBndr as D

#if __GLASGOW_HASKELL__ < 710
import           Control.Applicative
import           Data.Traversable (traverse, sequenceA)
#endif


{- $errors-note

When you use Template Haskell, the order of declarations suddenly starts to matter. For instance, if you try to use 'makeLenses', 'makeFields', etc before the type is defined, you'll get a “not in scope” error:

@
'makeLenses' ''Foo

data Foo = Foo {_foo :: Int}
@

@
Not in scope: type constructor or class ‘Foo’ …
    In the Template Haskell quotation ''Foo
@

You can't refer to generated lenses before you call 'makeLenses', either:

@
data Foo = Foo {_foo :: Int}

bar :: Lens' Foo Int
bar = foo

'makeLenses' ''Foo
@

@
Not in scope: ‘foo’ …
    Perhaps you meant one of these:
      data constructor ‘Foo’ (line 1), ‘_foo’ (line 1)
@
-}

{- $ghci-note

You can use 'makeLenses' and friends to define lenses right from GHCi, but it's slightly tricky.

First, enable Template Haskell:

>>> :set -XTemplateHaskell

Then define a bogus type (you can use any name in place of @M@, and you can use the same name many times), and follow the definition by the actual Template Haskell command you want to use:

>>> data M; makeLenses ''Foo

This will generate lenses for @Foo@ and you'll be able to use them from GHCi.

If you want, you can define the type and lenses for it simultaneously with @:{@ and @:}@:

@
>>> :{
data Foobar = Foobar {
  _foo :: Int,
  _bar :: Bool }
  deriving (Eq, Show)

makeLenses ''Foobar
:}
@
-}

{- $getter-fold-note

When updates are forbidden (by using 'generateUpdateableOptics'), or when a field simply can't be updated (for instance, in the presence of @forall@), instead of 'Lens' and 'Traversal' we generate 'SimpleGetter' and 'SimpleFold'. These aren't true @Getter@ and @Fold@ from lens, so beware. (Still, they're compatible, it's just that you can't do some things with them that you can do with original ones – for instance, @backwards@ and @takingWhile@ don't work on 'SimpleFold'.)

If you want to export true folds, it's recommended that you depend on <http://hackage.haskell.org/package/microlens-contra microlens-contra>, use 'makeLensesFor' to generate 'SimpleFold's with prefixes, and then export versions of those folds with @<http://hackage.haskell.org/package/microlens-contra/docs/Lens-Micro-Contra.html#v:fromSimpleFold fromSimpleFold>@ applied.
-}

-- Utilities

-- like 'rewrite' from uniplate
rewrite :: (Data a, Data b) => (a -> Maybe a) -> b -> b
rewrite :: forall a b. (Data a, Data b) => (a -> Maybe a) -> b -> b
rewrite a -> Maybe a
f b
mbA = case forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast b
mbA of
  Maybe a
Nothing -> forall a. Data a => (forall b. Data b => b -> b) -> a -> a
gmapT (forall a b. (Data a, Data b) => (a -> Maybe a) -> b -> b
rewrite a -> Maybe a
f) b
mbA
  Just a
a  -> let a' :: a
a' = forall a. Data a => (forall b. Data b => b -> b) -> a -> a
gmapT (forall a b. (Data a, Data b) => (a -> Maybe a) -> b -> b
rewrite a -> Maybe a
f) a
a
             in  forall a. HasCallStack => Maybe a -> a
fromJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe a
a' (a -> Maybe a
f a
a')

-- like 'children' from uniplate
children :: Data a => a -> [a]
children :: forall a. Data a => a -> [a]
children = forall a. [Maybe a] -> [a]
catMaybes forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a u. Data a => (forall d. Data d => d -> u) -> a -> [u]
gmapQ forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast

-- Control.Lens.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
makeLenses :: Name -> DecsQ
makeLenses = LensRules -> Name -> DecsQ
makeFieldOptics LensRules
lensRules

{- |
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
makeLensesFor :: [(String, String)] -> Name -> DecsQ
makeLensesFor [(String, String)]
fields = LensRules -> Name -> DecsQ
makeFieldOptics ([(String, String)] -> LensRules
lensRulesFor [(String, String)]
fields)

{- |
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
makeLensesWith :: LensRules -> Name -> DecsQ
makeLensesWith = LensRules -> Name -> DecsQ
makeFieldOptics

{- |
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
makeFields :: Name -> DecsQ
makeFields = LensRules -> Name -> DecsQ
makeFieldOptics LensRules
camelCaseFields

{- |
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
makeClassy :: Name -> DecsQ
makeClassy = LensRules -> Name -> DecsQ
makeFieldOptics LensRules
classyRules

{- |
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
simpleLenses :: Lens' LensRules Bool
simpleLenses Bool -> f Bool
f LensRules
r = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Bool
x -> LensRules
r { _simpleLenses :: Bool
_simpleLenses = Bool
x}) (Bool -> f Bool
f (LensRules -> Bool
_simpleLenses LensRules
r))

{- |
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
generateSignatures :: Lens' LensRules Bool
generateSignatures Bool -> f Bool
f LensRules
r =
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Bool
x -> LensRules
r { _generateSigs :: Bool
_generateSigs = Bool
x}) (Bool -> f Bool
f (LensRules -> Bool
_generateSigs LensRules
r))

{- |
Generate “updateable” optics. When turned off, 'SimpleFold's will be generated instead of 'Traversal's and 'SimpleGetter's will be generated instead of 'Lens'es.

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
generateUpdateableOptics :: Lens' LensRules Bool
generateUpdateableOptics Bool -> f Bool
f LensRules
r =
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Bool
x -> LensRules
r { _allowUpdates :: Bool
_allowUpdates = Bool
x}) (Bool -> f Bool
f (LensRules -> Bool
_allowUpdates LensRules
r))

{- |
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
generateLazyPatterns :: Lens' LensRules Bool
generateLazyPatterns Bool -> f Bool
f LensRules
r =
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Bool
x -> LensRules
r { _lazyPatterns :: Bool
_lazyPatterns = Bool
x}) (Bool -> f Bool
f (LensRules -> Bool
_lazyPatterns LensRules
r))

{- |
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])
lensField :: Lens' LensRules (Name -> [Name] -> Name -> [DefName])
lensField (Name -> [Name] -> Name -> [DefName])
-> f (Name -> [Name] -> Name -> [DefName])
f LensRules
r = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Name -> [Name] -> Name -> [DefName]
x -> LensRules
r { _fieldToDef :: Name -> [Name] -> Name -> [DefName]
_fieldToDef = Name -> [Name] -> Name -> [DefName]
x}) ((Name -> [Name] -> Name -> [DefName])
-> f (Name -> [Name] -> Name -> [DefName])
f (LensRules -> Name -> [Name] -> Name -> [DefName]
_fieldToDef LensRules
r))

{- |
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))
lensClass :: Lens' LensRules (Name -> Maybe (Name, Name))
lensClass (Name -> Maybe (Name, Name)) -> f (Name -> Maybe (Name, Name))
f LensRules
r = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Name -> Maybe (Name, Name)
x -> LensRules
r { _classyLenses :: Name -> Maybe (Name, Name)
_classyLenses = Name -> Maybe (Name, Name)
x }) ((Name -> Maybe (Name, Name)) -> f (Name -> Maybe (Name, Name))
f (LensRules -> Name -> Maybe (Name, Name)
_classyLenses LensRules
r))

{- |
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
createClass :: Lens' LensRules Bool
createClass Bool -> f Bool
f LensRules
r =
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Bool
x -> LensRules
r { _generateClasses :: Bool
_generateClasses = Bool
x}) (Bool -> f Bool
f (LensRules -> Bool
_generateClasses LensRules
r))

{- |
Lens rules used by default (i.e. in 'makeLenses'):

* 'generateSignatures' is turned on
* 'generateUpdateableOptics' is turned on
* 'generateLazyPatterns' is turned off
* 'simpleLenses' is turned off
* 'lensField' strips “_” off the field name, lowercases the next character after “_”, and skips the field entirely if it doesn't start with “_” (you can see how it's implemented in the docs for 'lensField')
* 'lensClass' isn't used (i.e. defined as @const Nothing@)
-}
lensRules :: LensRules
lensRules :: LensRules
lensRules = LensRules
  { _simpleLenses :: Bool
_simpleLenses    = Bool
False
  , _generateSigs :: Bool
_generateSigs    = Bool
True
  , _generateClasses :: Bool
_generateClasses = Bool
False
  -- , _allowIsos       = True
  , _allowUpdates :: Bool
_allowUpdates    = Bool
True
  , _lazyPatterns :: Bool
_lazyPatterns    = Bool
False
  , _classyLenses :: Name -> Maybe (Name, Name)
_classyLenses    = forall a b. a -> b -> a
const forall a. Maybe a
Nothing
  , _fieldToDef :: Name -> [Name] -> Name -> [DefName]
_fieldToDef      = \Name
_ [Name]
_ Name
n ->
       case Name -> String
nameBase Name
n of
         Char
'_':Char
x:String
xs -> [Name -> DefName
TopName (String -> Name
mkName (Char -> Char
toLower Char
xforall a. a -> [a] -> [a]
:String
xs))]
         String
_        -> []
  }

{- |
A modification of 'lensRules' used by 'makeLensesFor' (the only difference is that a simple lookup function is used for 'lensField').
-}
lensRulesFor
  :: [(String, String)] -- ^ @[(fieldName, lensName)]@
  -> LensRules
lensRulesFor :: [(String, String)] -> LensRules
lensRulesFor [(String, String)]
fields = LensRules
lensRules forall a b. a -> (a -> b) -> b
& Lens' LensRules (Name -> [Name] -> Name -> [DefName])
lensField forall s t a b. ASetter s t a b -> b -> s -> t
.~ [(String, String)] -> Name -> [Name] -> Name -> [DefName]
mkNameLookup [(String, String)]
fields

mkNameLookup :: [(String,String)] -> Name -> [Name] -> Name -> [DefName]
mkNameLookup :: [(String, String)] -> Name -> [Name] -> Name -> [DefName]
mkNameLookup [(String, String)]
kvs Name
_ [Name]
_ Name
field =
  [ Name -> DefName
TopName (String -> Name
mkName String
v) | (String
k,String
v) <- [(String, String)]
kvs, String
k forall a. Eq a => a -> a -> Bool
== Name -> String
nameBase Name
field]

{- |
Lens rules used by 'makeFields':

* 'generateSignatures' is turned on
* 'generateUpdateableOptics' is turned on
* 'generateLazyPatterns' is turned off
* 'simpleLenses' is turned on (unlike in 'lensRules')
* 'lensField' is more complicated – it takes fields which are prefixed with the name of the type they belong to (e.g. “fooFieldName” for “Foo”), strips that prefix, and generates a class called “HasFieldName” with a single method called “fieldName”. If some fields are prefixed with underscores, underscores would be stripped too, but then fields without underscores won't have any lenses generated for them. Also note that e.g. “foolish” won't have a lens called “lish” generated for it – the prefix must be followed by a capital letter (or else it wouldn't be camel case).
* 'lensClass' isn't used (i.e. defined as @const Nothing@)
-}
camelCaseFields :: LensRules
camelCaseFields :: LensRules
camelCaseFields = LensRules
defaultFieldRules

camelCaseNamer :: Name -> [Name] -> Name -> [DefName]
camelCaseNamer :: Name -> [Name] -> Name -> [DefName]
camelCaseNamer Name
tyName [Name]
fields Name
field = forall a. Maybe a -> [a]
maybeToList forall a b. (a -> b) -> a -> b
$ do

  String
fieldPart <- forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix String
expectedPrefix (Name -> String
nameBase Name
field)
  String
method    <- String -> Maybe String
computeMethod String
fieldPart
  let cls :: String
cls = String
"Has" forall a. [a] -> [a] -> [a]
++ String
fieldPart
  forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> Name -> DefName
MethodName (String -> Name
mkName String
cls) (String -> Name
mkName String
method))

  where
  expectedPrefix :: String
expectedPrefix = String
optUnderscore forall a. [a] -> [a] -> [a]
++ forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over forall s a. Cons s s a a => Traversal' s a
_head Char -> Char
toLower (Name -> String
nameBase Name
tyName)

  optUnderscore :: String
optUnderscore  = [Char
'_' | forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf String
"_" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> String
nameBase) [Name]
fields ]

  computeMethod :: String -> Maybe String
computeMethod (Char
x:String
xs) | Char -> Bool
isUpper Char
x = forall a. a -> Maybe a
Just (Char -> Char
toLower Char
x forall a. a -> [a] -> [a]
: String
xs)
  computeMethod String
_                  = forall a. Maybe a
Nothing

{- |
Like standard rules used by 'makeFields', but doesn't put any restrictions on the prefix. I.e. if you have fields called

* @_fooBarBaz@
* @_someX@
* @someY@

then the generated lenses would be called @barBaz@ and @x@.
-}
abbreviatedFields :: LensRules
abbreviatedFields :: LensRules
abbreviatedFields = LensRules
defaultFieldRules { _fieldToDef :: Name -> [Name] -> Name -> [DefName]
_fieldToDef = Name -> [Name] -> Name -> [DefName]
abbreviatedNamer }

abbreviatedNamer :: Name -> [Name] -> Name -> [DefName]
abbreviatedNamer :: Name -> [Name] -> Name -> [DefName]
abbreviatedNamer Name
_ [Name]
fields Name
field = forall a. Maybe a -> [a]
maybeToList forall a b. (a -> b) -> a -> b
$ do

  String
fieldPart <- String -> Maybe String
stripMaxLc (Name -> String
nameBase Name
field)
  String
method    <- String -> Maybe String
computeMethod String
fieldPart
  let cls :: String
cls = String
"Has" forall a. [a] -> [a] -> [a]
++ String
fieldPart
  forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> Name -> DefName
MethodName (String -> Name
mkName String
cls) (String -> Name
mkName String
method))

  where
  stripMaxLc :: String -> Maybe String
stripMaxLc String
f = do String
x <- forall a. Eq a => [a] -> [a] -> Maybe [a]
stripPrefix String
optUnderscore String
f
                    case forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isUpper String
x of
                      (String
p,String
s) | forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
p Bool -> Bool -> Bool
|| forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
s -> forall a. Maybe a
Nothing
                            | Bool
otherwise        -> forall a. a -> Maybe a
Just String
s
  optUnderscore :: String
optUnderscore  = [Char
'_' | forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf String
"_" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> String
nameBase) [Name]
fields ]

  computeMethod :: String -> Maybe String
computeMethod (Char
x:String
xs) | Char -> Bool
isUpper Char
x = forall a. a -> Maybe a
Just (Char -> Char
toLower Char
x forall a. a -> [a] -> [a]
: String
xs)
  computeMethod String
_                  = forall a. Maybe a
Nothing

defaultFieldRules :: LensRules
defaultFieldRules :: LensRules
defaultFieldRules = LensRules
  { _simpleLenses :: Bool
_simpleLenses    = Bool
True
  , _generateSigs :: Bool
_generateSigs    = Bool
True
  , _generateClasses :: Bool
_generateClasses = Bool
True  -- classes will still be skipped if they already exist
  -- , _allowIsos       = False -- generating Isos would hinder field class reuse
  , _allowUpdates :: Bool
_allowUpdates    = Bool
True
  , _lazyPatterns :: Bool
_lazyPatterns    = Bool
False
  , _classyLenses :: Name -> Maybe (Name, Name)
_classyLenses    = forall a b. a -> b -> a
const forall a. Maybe a
Nothing
  , _fieldToDef :: Name -> [Name] -> Name -> [DefName]
_fieldToDef      = Name -> [Name] -> Name -> [DefName]
camelCaseNamer
  }

underscoreNoPrefixNamer :: Name -> [Name] -> Name -> [DefName]
underscoreNoPrefixNamer :: Name -> [Name] -> Name -> [DefName]
underscoreNoPrefixNamer Name
_ [Name]
_ Name
n =
  case Name -> String
nameBase Name
n of
    Char
'_':Char
x:String
xs -> [Name -> DefName
TopName (String -> Name
mkName (Char -> Char
toLower Char
xforall a. a -> [a] -> [a]
:String
xs))]
    String
_        -> []

{- |
Lens rules used by 'makeClassy':

* 'generateSignatures' is turned on
* 'generateUpdateableOptics' is turned on
* 'generateLazyPatterns' is turned off
* 'simpleLenses' is turned on (unlike in 'lensRules')
* 'lensField' is the same as in 'lensRules'
* 'lensClass' just adds “Has” to the name of the type (so for “Person” the generated class would be called “HasPerson” and the type-specific lens in that class would be called “person”)
-}
classyRules :: LensRules
classyRules :: LensRules
classyRules = LensRules
  { _simpleLenses :: Bool
_simpleLenses    = Bool
True
  , _generateSigs :: Bool
_generateSigs    = Bool
True
  , _generateClasses :: Bool
_generateClasses = Bool
True
  -- , _allowIsos       = False -- generating Isos would hinder "subtyping"
  , _allowUpdates :: Bool
_allowUpdates    = Bool
True
  , _lazyPatterns :: Bool
_lazyPatterns    = Bool
False
  , _classyLenses :: Name -> Maybe (Name, Name)
_classyLenses    = \Name
n ->
        case Name -> String
nameBase Name
n of
          Char
x:String
xs -> forall a. a -> Maybe a
Just (String -> Name
mkName (String
"Has" forall a. [a] -> [a] -> [a]
++ Char
xforall a. a -> [a] -> [a]
:String
xs), String -> Name
mkName (Char -> Char
toLower Char
xforall a. a -> [a] -> [a]
:String
xs))
          []   -> forall a. Maybe a
Nothing
  , _fieldToDef :: Name -> [Name] -> Name -> [DefName]
_fieldToDef      = Name -> [Name] -> Name -> [DefName]
underscoreNoPrefixNamer
  }

-- FieldTH.hs

------------------------------------------------------------------------
-- Field generation entry point
------------------------------------------------------------------------


-- Compute the field optics for the type identified by the given type name.
-- Lenses will be computed when possible, Traversals otherwise.
makeFieldOptics :: LensRules -> Name -> DecsQ
makeFieldOptics :: LensRules -> Name -> DecsQ
makeFieldOptics LensRules
rules = (forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
`evalStateT` forall a. Set a
Set.empty) forall b c a. (b -> c) -> (a -> b) -> a -> c
. LensRules -> DatatypeInfo -> StateT (Set Name) Q [Dec]
makeFieldOpticsForDatatype LensRules
rules forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Name -> Q DatatypeInfo
D.reifyDatatype

type HasFieldClasses = StateT (Set Name) Q

addFieldClassName :: Name -> HasFieldClasses ()
addFieldClassName :: Name -> HasFieldClasses ()
addFieldClassName Name
n = forall (m :: * -> *) s. Monad m => (s -> s) -> StateT s m ()
modify forall a b. (a -> b) -> a -> b
$ forall a. Ord a => a -> Set a -> Set a
Set.insert Name
n

-- | Compute the field optics for a deconstructed datatype Dec
-- When possible build an Iso otherwise build one optic per field.
makeFieldOpticsForDatatype :: LensRules -> D.DatatypeInfo -> HasFieldClasses [Dec]
makeFieldOpticsForDatatype :: LensRules -> DatatypeInfo -> StateT (Set Name) Q [Dec]
makeFieldOpticsForDatatype LensRules
rules DatatypeInfo
info =
  do Map DefName (OpticType, OpticStab, [(Name, Int, [Int])])
perDef <- forall (m :: * -> *) a s. Monad m => m a -> StateT s m a
liftState forall a b. (a -> b) -> a -> b
$ do
       [(Name, [(Maybe Name, Type)])]
fieldCons <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ConstructorInfo -> Q (Name, [(Maybe Name, Type)])
normalizeConstructor [ConstructorInfo]
cons
       let allFields :: [Name]
allFields  = forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf (forall (f :: * -> *) a. Foldable f => SimpleFold (f a) a
folded forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s t a b. Field2 s t a b => Lens s t a b
_2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Foldable f => SimpleFold (f a) a
folded forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s t a b. Field1 s t a b => Lens s t a b
_1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Foldable f => SimpleFold (f a) a
folded) [(Name, [(Maybe Name, Type)])]
fieldCons
       let defCons :: [(Name, [([DefName], Type)])]
defCons    = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over forall a b.
Traversal [(Name, [(a, Type)])] [(Name, [(b, Type)])] a b
normFieldLabels ([Name] -> Maybe Name -> [DefName]
expandName [Name]
allFields) [(Name, [(Maybe Name, Type)])]
fieldCons
           allDefs :: Set DefName
allDefs    = forall a s. Ord a => Getting (Endo [a]) s a -> s -> Set a
setOf (forall a b.
Traversal [(Name, [(a, Type)])] [(Name, [(b, Type)])] a b
normFieldLabels forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Foldable f => SimpleFold (f a) a
folded) [(Name, [([DefName], Type)])]
defCons
       forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (forall k a. (k -> a) -> Set k -> Map k a
Map.fromSet (LensRules
-> Type
-> [(Name, [([DefName], Type)])]
-> DefName
-> Q (OpticType, OpticStab, [(Name, Int, [Int])])
buildScaffold LensRules
rules Type
s [(Name, [([DefName], Type)])]
defCons) Set DefName
allDefs)

     let defs :: [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
defs = forall k a. Map k a -> [(k, a)]
Map.toList Map DefName (OpticType, OpticStab, [(Name, Int, [Int])])
perDef
     case LensRules -> Name -> Maybe (Name, Name)
_classyLenses LensRules
rules Name
tyName of
       Just (Name
className, Name
methodName) ->
         LensRules
-> Name
-> Name
-> Type
-> [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
-> StateT (Set Name) Q [Dec]
makeClassyDriver LensRules
rules Name
className Name
methodName Type
s [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
defs
       Maybe (Name, Name)
Nothing -> do [[Dec]]
decss <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (LensRules
-> (DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))
-> StateT (Set Name) Q [Dec]
makeFieldOptic LensRules
rules) [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
defs
                     forall (m :: * -> *) a. Monad m => a -> m a
return (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Dec]]
decss)

  where
  tyName :: Name
tyName = DatatypeInfo -> Name
D.datatypeName     DatatypeInfo
info
  s :: Type
s      = DatatypeInfo -> Type
datatypeTypeKinded DatatypeInfo
info
  cons :: [ConstructorInfo]
cons   = DatatypeInfo -> [ConstructorInfo]
D.datatypeCons     DatatypeInfo
info

  -- Traverse the field labels of a normalized constructor
  normFieldLabels :: Traversal [(Name,[(a,Type)])] [(Name,[(b,Type)])] a b
  normFieldLabels :: forall a b.
Traversal [(Name, [(a, Type)])] [(Name, [(b, Type)])] a b
normFieldLabels = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s t a b. Field2 s t a b => Lens s t a b
_2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s t a b. Field1 s t a b => Lens s t a b
_1

  -- Map a (possibly missing) field's name to zero-to-many optic definitions
  expandName :: [Name] -> Maybe Name -> [DefName]
  expandName :: [Name] -> Maybe Name -> [DefName]
expandName [Name]
allFields = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (LensRules -> Name -> [Name] -> Name -> [DefName]
_fieldToDef LensRules
rules Name
tyName [Name]
allFields) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Maybe a -> [a]
maybeToList

normalizeConstructor ::
  D.ConstructorInfo ->
  Q (Name, [(Maybe Name, Type)]) -- ^ constructor name, field name, field type

normalizeConstructor :: ConstructorInfo -> Q (Name, [(Maybe Name, Type)])
normalizeConstructor ConstructorInfo
con =
  forall (m :: * -> *) a. Monad m => a -> m a
return (ConstructorInfo -> Name
D.constructorName ConstructorInfo
con,
          forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall {b} {a}. HasTypeVars b => Maybe a -> b -> (Maybe a, b)
checkForExistentials [Maybe Name]
fieldNames (ConstructorInfo -> [Type]
D.constructorFields ConstructorInfo
con))
  where
    fieldNames :: [Maybe Name]
fieldNames =
      case ConstructorInfo -> ConstructorVariant
D.constructorVariant ConstructorInfo
con of
        D.RecordConstructor [Name]
xs -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just [Name]
xs
        ConstructorVariant
D.NormalConstructor    -> forall a. a -> [a]
repeat forall a. Maybe a
Nothing
        ConstructorVariant
D.InfixConstructor     -> forall a. a -> [a]
repeat forall a. Maybe a
Nothing

    -- Fields mentioning existentially quantified types are not
    -- elligible for TH generated optics.
    checkForExistentials :: Maybe a -> b -> (Maybe a, b)
checkForExistentials Maybe a
_ b
fieldtype
      | forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\TyVarBndr_ ()
tv -> forall flag. TyVarBndr_ flag -> Name
D.tvName TyVarBndr_ ()
tv forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Name
used) [TyVarBndr_ ()]
unallowable
      = (forall a. Maybe a
Nothing, b
fieldtype)
      where
        used :: Set Name
used        = forall a s. Ord a => Getting (Endo [a]) s a -> s -> Set a
setOf forall t. HasTypeVars t => Traversal' t Name
typeVars b
fieldtype
        unallowable :: [TyVarBndr_ ()]
unallowable = ConstructorInfo -> [TyVarBndr_ ()]
D.constructorVars ConstructorInfo
con
    checkForExistentials Maybe a
fieldname b
fieldtype = (Maybe a
fieldname, b
fieldtype)

makeClassyDriver ::
  LensRules ->
  Name ->
  Name ->
  Type {- ^ Outer 's' type -} ->
  [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))] ->
  HasFieldClasses [Dec]
makeClassyDriver :: LensRules
-> Name
-> Name
-> Type
-> [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
-> StateT (Set Name) Q [Dec]
makeClassyDriver LensRules
rules Name
className Name
methodName Type
s [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
defs = forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (forall {s}. [StateT s Q Dec]
cls forall a. [a] -> [a] -> [a]
++ [StateT (Set Name) Q Dec]
inst)

  where
  cls :: [StateT s Q Dec]
cls | LensRules -> Bool
_generateClasses LensRules
rules = [forall (m :: * -> *) a s. Monad m => m a -> StateT s m a
liftState forall a b. (a -> b) -> a -> b
$ Name
-> Name
-> Type
-> [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
-> DecQ
makeClassyClass Name
className Name
methodName Type
s [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
defs]
      | Bool
otherwise = []

  inst :: [StateT (Set Name) Q Dec]
inst = [LensRules
-> Name
-> Name
-> Type
-> [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
-> StateT (Set Name) Q Dec
makeClassyInstance LensRules
rules Name
className Name
methodName Type
s [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
defs]

makeClassyClass ::
  Name ->
  Name ->
  Type {- ^ Outer 's' type -} ->
  [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))] ->
  DecQ
makeClassyClass :: Name
-> Name
-> Type
-> [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
-> DecQ
makeClassyClass Name
className Name
methodName Type
s [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
defs = do
  let ss :: [Type]
ss   = forall a b. (a -> b) -> [a] -> [b]
map (OpticStab -> Type
stabToS forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall s a. s -> Getting a s a -> a
^. forall s t a b. Field2 s t a b => Lens s t a b
_2forall b c a. (b -> c) -> (a -> b) -> a -> c
.forall s t a b. Field2 s t a b => Lens s t a b
_2)) [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
defs
  (Map Name Type
sub,Type
s') <- [Type] -> Q (Map Name Type, Type)
unifyTypes (Type
s forall a. a -> [a] -> [a]
: [Type]
ss)
  Name
c <- forall (m :: * -> *). Quote m => String -> m Name
newName String
"c"
  let vars :: [TyVarBndr_ ()]
vars     = [Type] -> [TyVarBndr_ ()]
D.freeVariablesWellScoped [Type
s']
      varNames :: [Name]
varNames = forall a b. (a -> b) -> [a] -> [b]
map forall flag. TyVarBndr_ flag -> Name
D.tvName [TyVarBndr_ ()]
vars
      fd :: [FunDep]
fd   | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TyVarBndr_ ()]
vars = []
           | Bool
otherwise = [[Name] -> [Name] -> FunDep
FunDep [Name
c] [Name]
varNames]


  forall (m :: * -> *).
Quote m =>
m [Type] -> Name -> [TyVarBndr_ ()] -> [FunDep] -> [m Dec] -> m Dec
classD (forall (m :: * -> *). Quote m => [m Type] -> m [Type]
cxt[]) Name
className (Name -> TyVarBndr_ ()
D.plainTV Name
cforall a. a -> [a] -> [a]
:[TyVarBndr_ ()]
vars) [FunDep]
fd
    forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). Quote m => Name -> m Type -> m Dec
sigD Name
methodName (forall (m :: * -> *) a. Monad m => a -> m a
return (''Lens' Name -> [Type] -> Type
`conAppsT` [Name -> Type
VarT Name
c, Type
s']))
    forall a. a -> [a] -> [a]
: forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
      [ [forall (m :: * -> *). Quote m => Name -> m Type -> m Dec
sigD Name
defName (forall (m :: * -> *) a. Monad m => a -> m a
return Type
ty)
        ,forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Dec
valD (forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
defName) (forall (m :: * -> *). Quote m => m Exp -> m Body
normalB Q Exp
body) []
        ] forall a. [a] -> [a] -> [a]
++
        Name -> [DecQ]
inlinePragma Name
defName
      | (TopName Name
defName, (OpticType
_, OpticStab
stab, [(Name, Int, [Int])]
_)) <- [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
defs
      , let body :: Q Exp
body = forall (m :: * -> *). Quote m => [m Exp] -> m Exp
appsE [forall (m :: * -> *). Quote m => Name -> m Exp
varE '(.), forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
methodName, forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
defName]
      , let ty :: Type
ty   = Set Name -> [Type] -> Type -> Type
quantifyType' (forall a. Ord a => [a] -> Set a
Set.fromList (Name
cforall a. a -> [a] -> [a]
:[Name]
varNames))
                                 (OpticStab -> [Type]
stabToContext OpticStab
stab)
                 forall a b. (a -> b) -> a -> b
$ OpticStab -> Name
stabToOptic OpticStab
stab Name -> [Type] -> Type
`conAppsT`
                       [Name -> Type
VarT Name
c, Map Name Type -> Type -> Type
applyTypeSubst Map Name Type
sub (OpticStab -> Type
stabToA OpticStab
stab)]
      ]

makeClassyInstance ::
  LensRules ->
  Name ->
  Name ->
  Type {- ^ Outer 's' type -} ->
  [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))] ->
  HasFieldClasses Dec
makeClassyInstance :: LensRules
-> Name
-> Name
-> Type
-> [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
-> StateT (Set Name) Q Dec
makeClassyInstance LensRules
rules Name
className Name
methodName Type
s [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
defs = do
  [[Dec]]
methodss <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (LensRules
-> (DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))
-> StateT (Set Name) Q [Dec]
makeFieldOptic LensRules
rules') [(DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))]
defs

  forall (m :: * -> *) a s. Monad m => m a -> StateT s m a
liftState forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *).
Quote m =>
m [Type] -> m Type -> [m Dec] -> m Dec
instanceD (forall (m :: * -> *). Quote m => [m Type] -> m [Type]
cxt[]) (forall (m :: * -> *) a. Monad m => a -> m a
return Type
instanceHead)
    forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Dec
valD (forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
methodName) (forall (m :: * -> *). Quote m => m Exp -> m Body
normalB (forall (m :: * -> *). Quote m => Name -> m Exp
varE 'id)) []
    forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall (m :: * -> *) a. Monad m => a -> m a
return (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Dec]]
methodss)

  where
  instanceHead :: Type
instanceHead = Name
className Name -> [Type] -> Type
`conAppsT` (Type
s forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall flag. TyVarBndr_ flag -> Type
tvbToType [TyVarBndr_ ()]
vars)
  vars :: [TyVarBndr_ ()]
vars         = [Type] -> [TyVarBndr_ ()]
D.freeVariablesWellScoped [Type
s]
  rules' :: LensRules
rules'       = LensRules
rules { _generateSigs :: Bool
_generateSigs    = Bool
False
                       , _generateClasses :: Bool
_generateClasses = Bool
False
                       }

data OpticType = GetterType | LensType -- or IsoType


-- Compute the positional location of the fields involved in
-- each constructor for a given optic definition as well as the
-- type of clauses to generate and the type to annotate the declaration
-- with.
buildScaffold ::
  LensRules                                                                ->
  Type                              {- outer type                       -} ->
  [(Name, [([DefName], Type)])]     {- normalized constructors          -} ->
  DefName                           {- target definition                -} ->
  Q (OpticType, OpticStab, [(Name, Int, [Int])])
              {- ^ optic type, definition type, field count, target fields -}
buildScaffold :: LensRules
-> Type
-> [(Name, [([DefName], Type)])]
-> DefName
-> Q (OpticType, OpticStab, [(Name, Int, [Int])])
buildScaffold LensRules
rules Type
s [(Name, [([DefName], Type)])]
cons DefName
defName =

  do (Type
s',Type
t,Type
a,Type
b) <- Type -> [Either Type Type] -> Q (Type, Type, Type, Type)
buildStab Type
s (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a b. (a, b) -> b
snd [(Name, [Either Type Type])]
consForDef)

     let defType :: OpticStab
defType
           | Just ([TyVarBndrSpec]
_,[Type]
cx,Type
a') <- Type
a forall s a. s -> Getting (First a) s a -> Maybe a
^? Traversal' Type ([TyVarBndrSpec], [Type], Type)
_ForallT =
               let optic :: Name
optic | Bool
lensCase  = ''SimpleGetter
                         | Bool
otherwise = ''SimpleFold
               in [Type] -> Name -> Type -> Type -> OpticStab
OpticSa [Type]
cx Name
optic Type
s' Type
a'

           -- Getter and Fold are always simple
           | Bool -> Bool
not (LensRules -> Bool
_allowUpdates LensRules
rules) =
               let optic :: Name
optic | Bool
lensCase  = ''SimpleGetter
                         | Bool
otherwise = ''SimpleFold
               in [Type] -> Name -> Type -> Type -> OpticStab
OpticSa [] Name
optic Type
s' Type
a

           -- Generate simple Lens and Traversal where possible
           | LensRules -> Bool
_simpleLenses LensRules
rules Bool -> Bool -> Bool
|| Type
s' forall a. Eq a => a -> a -> Bool
== Type
t Bool -> Bool -> Bool
&& Type
a forall a. Eq a => a -> a -> Bool
== Type
b =
               let optic :: Name
optic -- isoCase && _allowIsos rules = ''Iso'
                         | Bool
lensCase                    = ''Lens'
                         | Bool
otherwise                   = ''Traversal'
               in [Type] -> Name -> Type -> Type -> OpticStab
OpticSa [] Name
optic Type
s' Type
a

           -- Generate type-changing Lens and Traversal otherwise
           | Bool
otherwise =
               let optic :: Name
optic -- isoCase && _allowIsos rules = ''Iso
                         | Bool
lensCase                    = ''Lens
                         | Bool
otherwise                   = ''Traversal
               in Name -> Type -> Type -> Type -> Type -> OpticStab
OpticStab Name
optic Type
s' Type
t Type
a Type
b

         opticType :: OpticType
opticType | forall s a. Getting Any s a -> s -> Bool
has Traversal' Type ([TyVarBndrSpec], [Type], Type)
_ForallT Type
a            = OpticType
GetterType
                   | Bool -> Bool
not (LensRules -> Bool
_allowUpdates LensRules
rules) = OpticType
GetterType
                   -- isoCase                   = IsoType
                   | Bool
otherwise                 = OpticType
LensType

     forall (m :: * -> *) a. Monad m => a -> m a
return (OpticType
opticType, OpticStab
defType, [(Name, Int, [Int])]
scaffolds)
  where
  consForDef :: [(Name, [Either Type Type])]
  consForDef :: [(Name, [Either Type Type])]
consForDef = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over (forall (f :: * -> *) a b. Functor f => ASetter (f a) (f b) a b
mapped forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s t a b. Field2 s t a b => Lens s t a b
_2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => ASetter (f a) (f b) a b
mapped) ([DefName], Type) -> Either Type Type
categorize [(Name, [([DefName], Type)])]
cons

  scaffolds :: [(Name, Int, [Int])]
  scaffolds :: [(Name, Int, [Int])]
scaffolds = [ (Name
n, forall (t :: * -> *) a. Foldable t => t a -> Int
length [Either Type Type]
ts, [Either Type Type] -> [Int]
rightIndices [Either Type Type]
ts) | (Name
n,[Either Type Type]
ts) <- [(Name, [Either Type Type])]
consForDef ]

  rightIndices :: [Either Type Type] -> [Int]
  rightIndices :: [Either Type Type] -> [Int]
rightIndices = forall a. (a -> Bool) -> [a] -> [Int]
findIndices (forall s a. Getting Any s a -> s -> Bool
has forall a b b'. Traversal (Either a b) (Either a b') b b'
_Right)

  -- Right: types for this definition
  -- Left : other types
  categorize :: ([DefName], Type) -> Either Type Type
  categorize :: ([DefName], Type) -> Either Type Type
categorize ([DefName]
defNames, Type
t)
    | DefName
defName forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [DefName]
defNames = forall a b. b -> Either a b
Right Type
t
    | Bool
otherwise               = forall a b. a -> Either a b
Left  Type
t

  lensCase :: Bool
  lensCase :: Bool
lensCase = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\(Name, [Either Type Type])
x -> forall a s. Getting (Endo [a]) s a -> s -> Int
lengthOf (forall s t a b. Field2 s t a b => Lens s t a b
_2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Foldable f => SimpleFold (f a) a
folded forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b b'. Traversal (Either a b) (Either a b') b b'
_Right) (Name, [Either Type Type])
x forall a. Eq a => a -> a -> Bool
== Int
1) [(Name, [Either Type Type])]
consForDef

  -- isoCase :: Bool
  -- isoCase = case scaffolds of
  --             [(_,1,[0])] -> True
  --             _           -> False

data OpticStab = OpticStab     Name Type Type Type Type
               | OpticSa   Cxt Name Type Type


stabToType :: OpticStab -> Type
stabToType :: OpticStab -> Type
stabToType (OpticStab  Name
c Type
s Type
t Type
a Type
b) = [Type] -> Type -> Type
quantifyType [] (Name
c Name -> [Type] -> Type
`conAppsT` [Type
s,Type
t,Type
a,Type
b])
stabToType (OpticSa [Type]
cx Name
c Type
s   Type
a  ) = [Type] -> Type -> Type
quantifyType [Type]
cx (Name
c Name -> [Type] -> Type
`conAppsT` [Type
s,Type
a])

stabToContext :: OpticStab -> Cxt
stabToContext :: OpticStab -> [Type]
stabToContext OpticStab{}        = []
stabToContext (OpticSa [Type]
cx Name
_ Type
_ Type
_) = [Type]
cx

stabToOptic :: OpticStab -> Name
stabToOptic :: OpticStab -> Name
stabToOptic (OpticStab Name
c Type
_ Type
_ Type
_ Type
_) = Name
c
stabToOptic (OpticSa [Type]
_ Name
c Type
_ Type
_) = Name
c

stabToS :: OpticStab -> Type
stabToS :: OpticStab -> Type
stabToS (OpticStab Name
_ Type
s Type
_ Type
_ Type
_) = Type
s
stabToS (OpticSa [Type]
_ Name
_ Type
s Type
_) = Type
s

stabToA :: OpticStab -> Type
stabToA :: OpticStab -> Type
stabToA (OpticStab Name
_ Type
_ Type
_ Type
a Type
_) = Type
a
stabToA (OpticSa [Type]
_ Name
_ Type
_ Type
a) = Type
a

-- Compute the s t a b types given the outer type 's' and the
-- categorized field types. Left for fixed and Right for visited.
-- These types are "raw" and will be packaged into an 'OpticStab'
-- shortly after creation.
buildStab :: Type -> [Either Type Type] -> Q (Type,Type,Type,Type)
buildStab :: Type -> [Either Type Type] -> Q (Type, Type, Type, Type)
buildStab Type
s [Either Type Type]
categorizedFields =
  do (Map Name Type
subA,Type
a) <- [Type] -> Q (Map Name Type, Type)
unifyTypes [Type]
targetFields
     let s' :: Type
s' = Map Name Type -> Type -> Type
applyTypeSubst Map Name Type
subA Type
s

     -- compute possible type changes
     Map Name Name
sub <- forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (forall k a. (k -> a) -> Set k -> Map k a
Map.fromSet (forall (m :: * -> *). Quote m => String -> m Name
newName forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> String
nameBase) Set Name
unfixedTypeVars)
     let (Type
t,Type
b) = forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over forall a b. Traversal (a, a) (b, b) a b
both (forall t. HasTypeVars t => Map Name Name -> t -> t
substTypeVars Map Name Name
sub) (Type
s',Type
a)

     forall (m :: * -> *) a. Monad m => a -> m a
return (Type
s',Type
t,Type
a,Type
b)

  where
  ([Type]
fixedFields, [Type]
targetFields) = forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either Type Type]
categorizedFields

  fixedTypeVars, unfixedTypeVars :: Set Name
  fixedTypeVars :: Set Name
fixedTypeVars   = Set Name -> Set Name
closeOverKinds forall a b. (a -> b) -> a -> b
$ forall a s. Ord a => Getting (Endo [a]) s a -> s -> Set a
setOf forall t. HasTypeVars t => Traversal' t Name
typeVars [Type]
fixedFields
  unfixedTypeVars :: Set Name
unfixedTypeVars = forall a s. Ord a => Getting (Endo [a]) s a -> s -> Set a
setOf forall t. HasTypeVars t => Traversal' t Name
typeVars Type
s forall a. Ord a => Set a -> Set a -> Set a
Set.\\ Set Name
fixedTypeVars

  -- Compute the kind variables that appear in the kind of a type variable
  -- binder. For example, @kindVarsOfTvb (x :: (a, b)) = (x, {a, b})@. If a
  -- type variable binder lacks an explicit kind annotation, this
  -- conservatively assumes that there are no kind variables. For example,
  -- @kindVarsOfTvb (y) = (y, {})@.
  kindVarsOfTvb :: D.TyVarBndr_ flag -> (Name, Set Name)
  kindVarsOfTvb :: forall flag. TyVarBndr_ flag -> (Name, Set Name)
kindVarsOfTvb = forall r flag.
(Name -> r) -> (Name -> Type -> r) -> TyVarBndr_ flag -> r
D.elimTV (\Name
n   -> (Name
n, forall a. Set a
Set.empty))
                           (\Name
n Type
k -> (Name
n, forall a s. Ord a => Getting (Endo [a]) s a -> s -> Set a
setOf forall t. HasTypeVars t => Traversal' t Name
typeVars Type
k))

  -- For each type variable name that appears in @s@, map to the kind variables
  -- that appear in that type variable's kind.
  sKindVarMap :: Map Name (Set Name)
  sKindVarMap :: Map Name (Set Name)
sKindVarMap = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall flag. TyVarBndr_ flag -> (Name, Set Name)
kindVarsOfTvb forall a b. (a -> b) -> a -> b
$ [Type] -> [TyVarBndr_ ()]
D.freeVariablesWellScoped [Type
s]

  lookupSKindVars :: Name -> Set Name
  lookupSKindVars :: Name -> Set Name
lookupSKindVars Name
n = forall a. a -> Maybe a -> a
fromMaybe forall a. Set a
Set.empty forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
n Map Name (Set Name)
sKindVarMap

  -- Consider this example (adapted from #972):
  --
  --   data Dart (s :: k) = Dart { _arc :: Proxy s, _direction :: Int }
  --   $(makeLenses ''Dart)
  --
  -- When generating a Lens for `direction`, the type variable `s` should be
  -- fixed. But note that (s :: k), and as a result, the kind variable `k`
  -- needs to be fixed as well. This is because a type like this would be
  -- ill kinded:
  --
  --   direction :: Lens (Dart (s :: k1)) (Dart (s :: k2)) Direction Direction
  --
  -- However, only `s` is mentioned syntactically in the type of `_arc`, so we
  -- have to infer that `k` is mentioned in the kind of `s`. We accomplish this
  -- with `closeOverKinds`, which does the following:
  --
  -- 1. Use freeVariablesWellScoped to compute the free type variables of
  --    `Dart (s :: k)`, which gives us `(s :: k)`.
  -- 2. For each type variable name in `Proxy s`, the type of `_arc`, look up
  --    the kind variables in the type variable's kind. In the case of `s`,
  --    the only kind variable is `k`.
  -- 3. Add these kind variables to the set of fixed type variables.
  closeOverKinds :: Set Name -> Set Name
  closeOverKinds :: Set Name -> Set Name
closeOverKinds Set Name
st = forall a b. (a -> b -> a) -> a -> Set b -> a
Set.foldl' forall a. Ord a => Set a -> Set a -> Set a
Set.union forall a. Set a
Set.empty (forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map Name -> Set Name
lookupSKindVars Set Name
st) forall a. Ord a => Set a -> Set a -> Set a
`Set.union` Set Name
st

-- Build the signature and definition for a single field optic.
-- In the case of a singleton constructor irrefutable matches are
-- used to enable the resulting lenses to be used on a bottom value.
makeFieldOptic ::
  LensRules ->
  (DefName, (OpticType, OpticStab, [(Name, Int, [Int])])) ->
  HasFieldClasses [Dec]
makeFieldOptic :: LensRules
-> (DefName, (OpticType, OpticStab, [(Name, Int, [Int])]))
-> StateT (Set Name) Q [Dec]
makeFieldOptic LensRules
rules (DefName
defName, (OpticType
opticType, OpticStab
defType, [(Name, Int, [Int])]
cons)) = do
  Set Name
locals <- forall (m :: * -> *) s. Monad m => StateT s m s
get
  HasFieldClasses ()
addName
  forall (m :: * -> *) a s. Monad m => m a -> StateT s m a
liftState forall a b. (a -> b) -> a -> b
$ do
    [DecQ]
cls <- Set Name -> Q [DecQ]
mkCls Set Name
locals
    forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA ([DecQ]
cls forall a. [a] -> [a] -> [a]
++ [DecQ]
sig forall a. [a] -> [a] -> [a]
++ [DecQ]
def)
  where
  mkCls :: Set Name -> Q [DecQ]
mkCls Set Name
locals = case DefName
defName of
                 MethodName Name
c Name
n | LensRules -> Bool
_generateClasses LensRules
rules ->
                  do Bool
classExists <- forall a. Maybe a -> Bool
isJust forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Q (Maybe Name)
lookupTypeName (forall a. Show a => a -> String
show Name
c)
                     forall (m :: * -> *) a. Monad m => a -> m a
return (if Bool
classExists Bool -> Bool -> Bool
|| forall a. Ord a => a -> Set a -> Bool
Set.member Name
c Set Name
locals then [] else [OpticStab -> Name -> Name -> DecQ
makeFieldClass OpticStab
defType Name
c Name
n])
                 DefName
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return []

  addName :: HasFieldClasses ()
addName = case DefName
defName of
            MethodName Name
c Name
_ -> Name -> HasFieldClasses ()
addFieldClassName Name
c
            DefName
_              -> forall (m :: * -> *) a. Monad m => a -> m a
return ()

  sig :: [DecQ]
sig = case DefName
defName of
          DefName
_ | Bool -> Bool
not (LensRules -> Bool
_generateSigs LensRules
rules) -> []
          TopName Name
n -> [forall (m :: * -> *). Quote m => Name -> m Type -> m Dec
sigD Name
n (forall (m :: * -> *) a. Monad m => a -> m a
return (OpticStab -> Type
stabToType OpticStab
defType))]
          MethodName{} -> []

  fun :: Name -> [DecQ]
fun Name
n = forall (m :: * -> *). Quote m => Name -> [m Clause] -> m Dec
funD Name
n [ClauseQ]
clauses forall a. a -> [a] -> [a]
: Name -> [DecQ]
inlinePragma Name
n

  def :: [DecQ]
def = case DefName
defName of
          TopName Name
n      -> Name -> [DecQ]
fun Name
n
          MethodName Name
c Name
n -> [OpticStab -> Name -> [DecQ] -> DecQ
makeFieldInstance OpticStab
defType Name
c (Name -> [DecQ]
fun Name
n)]

  clauses :: [ClauseQ]
clauses = LensRules -> OpticType -> [(Name, Int, [Int])] -> [ClauseQ]
makeFieldClauses LensRules
rules OpticType
opticType [(Name, Int, [Int])]
cons

------------------------------------------------------------------------
-- Field class generation
------------------------------------------------------------------------

makeFieldClass :: OpticStab -> Name -> Name -> DecQ
makeFieldClass :: OpticStab -> Name -> Name -> DecQ
makeFieldClass OpticStab
defType Name
className Name
methodName =
  forall (m :: * -> *).
Quote m =>
m [Type] -> Name -> [TyVarBndr_ ()] -> [FunDep] -> [m Dec] -> m Dec
classD (forall (m :: * -> *). Quote m => [m Type] -> m [Type]
cxt []) Name
className [Name -> TyVarBndr_ ()
D.plainTV Name
s, Name -> TyVarBndr_ ()
D.plainTV Name
a] [[Name] -> [Name] -> FunDep
FunDep [Name
s] [Name
a]]
         [forall (m :: * -> *). Quote m => Name -> m Type -> m Dec
sigD Name
methodName (forall (m :: * -> *) a. Monad m => a -> m a
return Type
methodType)]
  where
  methodType :: Type
methodType = Set Name -> [Type] -> Type -> Type
quantifyType' (forall a. Ord a => [a] -> Set a
Set.fromList [Name
s,Name
a])
                             (OpticStab -> [Type]
stabToContext OpticStab
defType)
             forall a b. (a -> b) -> a -> b
$ OpticStab -> Name
stabToOptic OpticStab
defType Name -> [Type] -> Type
`conAppsT` [Name -> Type
VarT Name
s,Name -> Type
VarT Name
a]
  s :: Name
s = String -> Name
mkName String
"s"
  a :: Name
a = String -> Name
mkName String
"a"

-- | Build an instance for a field. If the field’s type contains any type
-- families, will produce an equality constraint to avoid a type family
-- application in the instance head.
makeFieldInstance :: OpticStab -> Name -> [DecQ] -> DecQ
makeFieldInstance :: OpticStab -> Name -> [DecQ] -> DecQ
makeFieldInstance OpticStab
defType Name
className [DecQ]
decs =
  Type -> Q Bool
containsTypeFamilies Type
a forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> DecQ
pickInstanceDec
  where
  s :: Type
s = OpticStab -> Type
stabToS OpticStab
defType
  a :: Type
a = OpticStab -> Type
stabToA OpticStab
defType

  containsTypeFamilies :: Type -> Q Bool
containsTypeFamilies = Type -> Q Bool
go forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Type -> Q Type
D.resolveTypeSynonyms
    where
    go :: Type -> Q Bool
go (ConT Name
nm) = (\Info
i -> case Info
i of FamilyI Dec
d [Dec]
_ -> Dec -> Bool
isTypeFamily Dec
d; Info
_ -> Bool
False)
                   forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> Q Info
reify Name
nm
    go Type
ty = forall (t :: * -> *). Foldable t => t Bool -> Bool
or forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Type -> Q Bool
go (forall a. Data a => a -> [a]
children Type
ty)

#if MIN_VERSION_template_haskell(2,11,0)
  isTypeFamily :: Dec -> Bool
isTypeFamily OpenTypeFamilyD{}       = Bool
True
  isTypeFamily ClosedTypeFamilyD{}     = Bool
True
#elif MIN_VERSION_template_haskell(2,9,0)
  isTypeFamily (FamilyD TypeFam _ _ _) = True
  isTypeFamily ClosedTypeFamilyD{}     = True
#else
  isTypeFamily (FamilyD TypeFam _ _ _) = True
#endif
  isTypeFamily Dec
_ = Bool
False

  pickInstanceDec :: Bool -> DecQ
pickInstanceDec Bool
hasFamilies
    | Bool
hasFamilies = do
        Type
placeholder <- Name -> Type
VarT forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). Quote m => String -> m Name
newName String
"a"
        [Q Type] -> [Type] -> DecQ
mkInstanceDec
          [forall (m :: * -> *) a. Monad m => a -> m a
return (Type -> Type -> Type
D.equalPred Type
placeholder Type
a)]
          [Type
s, Type
placeholder]
    | Bool
otherwise = [Q Type] -> [Type] -> DecQ
mkInstanceDec [] [Type
s, Type
a]

  mkInstanceDec :: [Q Type] -> [Type] -> DecQ
mkInstanceDec [Q Type]
context [Type]
headTys =
    forall (m :: * -> *).
Quote m =>
m [Type] -> m Type -> [m Dec] -> m Dec
instanceD (forall (m :: * -> *). Quote m => [m Type] -> m [Type]
cxt [Q Type]
context) (forall (m :: * -> *) a. Monad m => a -> m a
return (Name
className Name -> [Type] -> Type
`conAppsT` [Type]
headTys)) [DecQ]
decs

------------------------------------------------------------------------
-- Optic clause generators
------------------------------------------------------------------------

makeFieldClauses :: LensRules -> OpticType -> [(Name, Int, [Int])] -> [ClauseQ]
makeFieldClauses :: LensRules -> OpticType -> [(Name, Int, [Int])] -> [ClauseQ]
makeFieldClauses LensRules
rules OpticType
opticType [(Name, Int, [Int])]
cons =
  case OpticType
opticType of

    -- IsoType    -> [ makeIsoClause conName | (conName, _, _) <- cons ]

    OpticType
GetterType -> [ Name -> Int -> [Int] -> ClauseQ
makeGetterClause Name
conName Int
fieldCount [Int]
fields
                    | (Name
conName, Int
fieldCount, [Int]
fields) <- [(Name, Int, [Int])]
cons ]

    OpticType
LensType   -> [ Name -> Int -> [Int] -> Bool -> ClauseQ
makeFieldOpticClause Name
conName Int
fieldCount [Int]
fields Bool
irref
                    | (Name
conName, Int
fieldCount, [Int]
fields) <- [(Name, Int, [Int])]
cons ]
      where
      irref :: Bool
irref = LensRules -> Bool
_lazyPatterns LensRules
rules
           Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Name, Int, [Int])]
cons forall a. Eq a => a -> a -> Bool
== Int
1

-- Construct an optic clause that returns an unmodified value
-- given a constructor name and the number of fields on that
-- constructor.
makePureClause :: Name -> Int -> ClauseQ
makePureClause :: Name -> Int -> ClauseQ
makePureClause Name
conName Int
fieldCount =
  do [Name]
xs <- String -> Int -> Q [Name]
newNames String
"x" Int
fieldCount
     -- clause: _ (Con x1..xn) = pure (Con x1..xn)
     forall (m :: * -> *).
Quote m =>
[m Pat] -> m Body -> [m Dec] -> m Clause
clause [forall (m :: * -> *). Quote m => m Pat
wildP, forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
conName (forall a b. (a -> b) -> [a] -> [b]
map forall (m :: * -> *). Quote m => Name -> m Pat
varP [Name]
xs)]
            (forall (m :: * -> *). Quote m => m Exp -> m Body
normalB (forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
varE 'pure) (forall (m :: * -> *). Quote m => [m Exp] -> m Exp
appsE (forall (m :: * -> *). Quote m => Name -> m Exp
conE Name
conName forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall (m :: * -> *). Quote m => Name -> m Exp
varE [Name]
xs))))
            []

-- Construct an optic clause suitable for a Getter or Fold
-- by visited the fields identified by their 0 indexed positions
makeGetterClause :: Name -> Int -> [Int] -> ClauseQ
makeGetterClause :: Name -> Int -> [Int] -> ClauseQ
makeGetterClause Name
conName Int
fieldCount []     = Name -> Int -> ClauseQ
makePureClause Name
conName Int
fieldCount
makeGetterClause Name
conName Int
fieldCount [Int]
fields =
  do Name
f  <- forall (m :: * -> *). Quote m => String -> m Name
newName String
"f"
     [Name]
xs <- String -> Int -> Q [Name]
newNames String
"x" (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
fields)

     let pats :: [Int] -> [Name] -> [m Pat]
pats (Int
i:[Int]
is) (Name
y:[Name]
ys)
           | Int
i forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Int]
fields = forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
y forall a. a -> [a] -> [a]
: [Int] -> [Name] -> [m Pat]
pats [Int]
is [Name]
ys
           | Bool
otherwise = forall (m :: * -> *). Quote m => m Pat
wildP forall a. a -> [a] -> [a]
: [Int] -> [Name] -> [m Pat]
pats [Int]
is (Name
yforall a. a -> [a] -> [a]
:[Name]
ys)
         pats [Int]
is     [Name]
_  = forall a b. (a -> b) -> [a] -> [b]
map (forall a b. a -> b -> a
const forall (m :: * -> *). Quote m => m Pat
wildP) [Int]
is

         fxs :: [Q Exp]
fxs   = [ forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
f) (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
x) | Name
x <- [Name]
xs ]
         body :: Q Exp
body  = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\Q Exp
a Q Exp
b -> forall (m :: * -> *). Quote m => [m Exp] -> m Exp
appsE [forall (m :: * -> *). Quote m => Name -> m Exp
varE '(<*>), Q Exp
a, Q Exp
b])
                       (forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
varE 'phantom) (forall a. [a] -> a
head [Q Exp]
fxs))
                       (forall a. [a] -> [a]
tail [Q Exp]
fxs)

     -- clause f (Con x1..xn) = coerce (f x1) <*> ... <*> f xn
     forall (m :: * -> *).
Quote m =>
[m Pat] -> m Body -> [m Dec] -> m Clause
clause [forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
f, forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
conName (forall {m :: * -> *}. Quote m => [Int] -> [Name] -> [m Pat]
pats [Int
0..Int
fieldCount forall a. Num a => a -> a -> a
- Int
1] [Name]
xs)]
            (forall (m :: * -> *). Quote m => m Exp -> m Body
normalB Q Exp
body)
            []

-- Build a clause that updates the field at the given indexes
-- When irref is 'True' the value with me matched with an irrefutable
-- pattern. This is suitable for Lens and Traversal construction
makeFieldOpticClause :: Name -> Int -> [Int] -> Bool -> ClauseQ
makeFieldOpticClause :: Name -> Int -> [Int] -> Bool -> ClauseQ
makeFieldOpticClause Name
conName Int
fieldCount [] Bool
_ =
  Name -> Int -> ClauseQ
makePureClause Name
conName Int
fieldCount
makeFieldOpticClause Name
conName Int
fieldCount (Int
field:[Int]
fields) Bool
irref =
  do Name
f  <- forall (m :: * -> *). Quote m => String -> m Name
newName String
"f"
     [Name]
xs <- String -> Int -> Q [Name]
newNames String
"x" Int
fieldCount
     [Name]
ys <- String -> Int -> Q [Name]
newNames String
"y" (Int
1 forall a. Num a => a -> a -> a
+ forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
fields)

     let xs' :: [Name]
xs' = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\(Int
i,Name
x) -> forall s t a b. ASetter s t a b -> b -> s -> t
set (forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Int
i) Name
x) [Name]
xs (forall a b. [a] -> [b] -> [(a, b)]
zip (Int
fieldforall a. a -> [a] -> [a]
:[Int]
fields) [Name]
ys)

         mkFx :: Int -> m Exp
mkFx Int
i = forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
f) (forall (m :: * -> *). Quote m => Name -> m Exp
varE ([Name]
xs forall a. [a] -> Int -> a
!! Int
i))

         body0 :: Q Exp
body0 = forall (m :: * -> *). Quote m => [m Exp] -> m Exp
appsE [ forall (m :: * -> *). Quote m => Name -> m Exp
varE 'fmap
                       , forall (m :: * -> *). Quote m => [m Pat] -> m Exp -> m Exp
lamE (forall a b. (a -> b) -> [a] -> [b]
map forall (m :: * -> *). Quote m => Name -> m Pat
varP [Name]
ys) (forall (m :: * -> *). Quote m => [m Exp] -> m Exp
appsE (forall (m :: * -> *). Quote m => Name -> m Exp
conE Name
conName forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall (m :: * -> *). Quote m => Name -> m Exp
varE [Name]
xs'))
                       , forall {m :: * -> *}. Quote m => Int -> m Exp
mkFx Int
field
                       ]

         body :: Q Exp
body = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\Q Exp
a Int
b -> forall (m :: * -> *). Quote m => [m Exp] -> m Exp
appsE [forall (m :: * -> *). Quote m => Name -> m Exp
varE '(<*>), Q Exp
a, forall {m :: * -> *}. Quote m => Int -> m Exp
mkFx Int
b]) Q Exp
body0 [Int]
fields

     let wrap :: Q Pat -> Q Pat
wrap = if Bool
irref then forall (m :: * -> *). Quote m => m Pat -> m Pat
tildeP else forall a. a -> a
id

     forall (m :: * -> *).
Quote m =>
[m Pat] -> m Body -> [m Dec] -> m Clause
clause [forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
f, Q Pat -> Q Pat
wrap (forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
conName (forall a b. (a -> b) -> [a] -> [b]
map forall (m :: * -> *). Quote m => Name -> m Pat
varP [Name]
xs))]
            (forall (m :: * -> *). Quote m => m Exp -> m Body
normalB Q Exp
body)
            []

------------------------------------------------------------------------
-- Unification logic
------------------------------------------------------------------------

-- The field-oriented optic generation supports incorporating fields
-- with distinct but unifiable types into a single definition.

-- Unify the given list of types, if possible, and return the
-- substitution used to unify the types for unifying the outer
-- type when building a definition's type signature.
unifyTypes :: [Type] -> Q (Map Name Type, Type)
unifyTypes :: [Type] -> Q (Map Name Type, Type)
unifyTypes (Type
x:[Type]
xs) = forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Map Name Type -> Type -> Type -> Q (Map Name Type, Type)
unify1) (forall k a. Map k a
Map.empty, Type
x) [Type]
xs
unifyTypes []     = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"unifyTypes: Bug: Unexpected empty list"


-- Attempt to unify two given types using a running substitution
unify1 :: Map Name Type -> Type -> Type -> Q (Map Name Type, Type)
unify1 :: Map Name Type -> Type -> Type -> Q (Map Name Type, Type)
unify1 Map Name Type
sub (VarT Name
x) Type
y
  | Just Type
r <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
x Map Name Type
sub = Map Name Type -> Type -> Type -> Q (Map Name Type, Type)
unify1 Map Name Type
sub Type
r Type
y
unify1 Map Name Type
sub Type
x (VarT Name
y)
  | Just Type
r <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
y Map Name Type
sub = Map Name Type -> Type -> Type -> Q (Map Name Type, Type)
unify1 Map Name Type
sub Type
x Type
r
unify1 Map Name Type
sub Type
x Type
y
  | Type
x forall a. Eq a => a -> a -> Bool
== Type
y = forall (m :: * -> *) a. Monad m => a -> m a
return (Map Name Type
sub, Type
x)
unify1 Map Name Type
sub (AppT Type
f1 Type
x1) (AppT Type
f2 Type
x2) =
  do (Map Name Type
sub1, Type
f) <- Map Name Type -> Type -> Type -> Q (Map Name Type, Type)
unify1 Map Name Type
sub  Type
f1 Type
f2
     (Map Name Type
sub2, Type
x) <- Map Name Type -> Type -> Type -> Q (Map Name Type, Type)
unify1 Map Name Type
sub1 Type
x1 Type
x2
     forall (m :: * -> *) a. Monad m => a -> m a
return (Map Name Type
sub2, Type -> Type -> Type
AppT (Map Name Type -> Type -> Type
applyTypeSubst Map Name Type
sub2 Type
f) Type
x)
unify1 Map Name Type
sub Type
x (VarT Name
y)
  | forall a s. Eq a => Getting (Endo [a]) s a -> a -> s -> Bool
elemOf forall t. HasTypeVars t => Traversal' t Name
typeVars Name
y (Map Name Type -> Type -> Type
applyTypeSubst Map Name Type
sub Type
x) =
      forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Failed to unify types: occurs check"
  | Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return (forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Name
y Type
x Map Name Type
sub, Type
x)
unify1 Map Name Type
sub (VarT Name
x) Type
y = Map Name Type -> Type -> Type -> Q (Map Name Type, Type)
unify1 Map Name Type
sub Type
y (Name -> Type
VarT Name
x)

-- TODO: Unify contexts
unify1 Map Name Type
sub (ForallT [TyVarBndrSpec]
v1 [] Type
t1) (ForallT [TyVarBndrSpec]
v2 [] Type
t2) =
     -- This approach works out because by the time this code runs
     -- all of the type variables have been renamed. No risk of shadowing.
  do (Map Name Type
sub1,Type
t) <- Map Name Type -> Type -> Type -> Q (Map Name Type, Type)
unify1 Map Name Type
sub Type
t1 Type
t2
     [TyVarBndrSpec]
v <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Eq a => [a] -> [a]
nub (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Map Name Type -> TyVarBndrSpec -> Q TyVarBndrSpec
limitedSubst Map Name Type
sub1) ([TyVarBndrSpec]
v1forall a. [a] -> [a] -> [a]
++[TyVarBndrSpec]
v2))
     forall (m :: * -> *) a. Monad m => a -> m a
return (Map Name Type
sub1, [TyVarBndrSpec] -> [Type] -> Type -> Type
ForallT [TyVarBndrSpec]
v [] Type
t)

unify1 Map Name Type
_ Type
x Type
y = forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Failed to unify types: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Type
x,Type
y))

-- Perform a limited substitution on type variables. This is used
-- when unifying rank-2 fields when trying to achieve a Getter or Fold.
limitedSubst :: Map Name Type -> D.TyVarBndrSpec -> Q D.TyVarBndrSpec
limitedSubst :: Map Name Type -> TyVarBndrSpec -> Q TyVarBndrSpec
limitedSubst Map Name Type
sub TyVarBndrSpec
tv
  | Just Type
r <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall flag. TyVarBndr_ flag -> Name
D.tvName TyVarBndrSpec
tv) Map Name Type
sub =
       case Type
r of
         VarT Name
m -> Map Name Type -> TyVarBndrSpec -> Q TyVarBndrSpec
limitedSubst Map Name Type
sub (forall flag. (Name -> Name) -> TyVarBndr_ flag -> TyVarBndr_ flag
D.mapTVName (forall a b. a -> b -> a
const Name
m) TyVarBndrSpec
tv)
         Type
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Unable to unify exotic higher-rank type"
  | Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return TyVarBndrSpec
tv

-- Apply a substitution to a type. This is used after unifying
-- the types of the fields in unifyTypes.
applyTypeSubst :: Map Name Type -> Type -> Type
applyTypeSubst :: Map Name Type -> Type -> Type
applyTypeSubst Map Name Type
sub = forall a b. (Data a, Data b) => (a -> Maybe a) -> b -> b
rewrite Type -> Maybe Type
aux
  where
  aux :: Type -> Maybe Type
aux (VarT Name
n) = forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
n Map Name Type
sub
  aux Type
_        = forall a. Maybe a
Nothing

------------------------------------------------------------------------
-- Field generation parameters
------------------------------------------------------------------------

{- |
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 = LensRules
  { LensRules -> Bool
_simpleLenses    :: Bool
  , LensRules -> Bool
_generateSigs    :: Bool
  , LensRules -> Bool
_generateClasses :: Bool
  -- , _allowIsos       :: Bool
  , LensRules -> Bool
_allowUpdates    :: Bool -- Allow Lens/Traversal (otherwise Getter/Fold)
  , LensRules -> Bool
_lazyPatterns    :: Bool
  -- Type Name -> Field Names -> Target Field Name -> Definition Names
  , LensRules -> Name -> [Name] -> Name -> [DefName]
_fieldToDef      :: Name -> [Name] -> Name -> [DefName]
  -- Type Name -> (Class Name, Top Method)
  , LensRules -> Name -> Maybe (Name, Name)
_classyLenses    :: Name -> Maybe (Name, Name)
  }

{- |
Name to give to a generated lens (used in 'lensField').
-}
data DefName
  = TopName Name          -- ^ Simple top-level definiton name
  | MethodName Name Name  -- ^ 'makeFields'-style class name and method name
  deriving (Int -> DefName -> ShowS
[DefName] -> ShowS
DefName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DefName] -> ShowS
$cshowList :: [DefName] -> ShowS
show :: DefName -> String
$cshow :: DefName -> String
showsPrec :: Int -> DefName -> ShowS
$cshowsPrec :: Int -> DefName -> ShowS
Show, DefName -> DefName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefName -> DefName -> Bool
$c/= :: DefName -> DefName -> Bool
== :: DefName -> DefName -> Bool
$c== :: DefName -> DefName -> Bool
Eq, Eq DefName
DefName -> DefName -> Bool
DefName -> DefName -> Ordering
DefName -> DefName -> DefName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DefName -> DefName -> DefName
$cmin :: DefName -> DefName -> DefName
max :: DefName -> DefName -> DefName
$cmax :: DefName -> DefName -> DefName
>= :: DefName -> DefName -> Bool
$c>= :: DefName -> DefName -> Bool
> :: DefName -> DefName -> Bool
$c> :: DefName -> DefName -> Bool
<= :: DefName -> DefName -> Bool
$c<= :: DefName -> DefName -> Bool
< :: DefName -> DefName -> Bool
$c< :: DefName -> DefName -> Bool
compare :: DefName -> DefName -> Ordering
$ccompare :: DefName -> DefName -> Ordering
Ord)


------------------------------------------------------------------------
-- Miscellaneous utility functions
------------------------------------------------------------------------

liftState :: Monad m => m a -> StateT s m a
liftState :: forall (m :: * -> *) a s. Monad m => m a -> StateT s m a
liftState m a
act = forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT (\s
s -> forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (forall a b c. (a -> b -> c) -> b -> a -> c
flip (,) s
s) m a
act)