module Optics.TH
(
makeFieldLabels
, makeFieldLabelsNoPrefix
, makeFieldLabelsFor
, makeFieldLabelsWith
, declareFieldLabels
, declareFieldLabelsFor
, declareFieldLabelsWith
, fieldLabelsRules
, fieldLabelsRulesFor
, makeLenses
, makeLensesFor
, makeLensesWith
, declareLenses
, declareLensesFor
, declareLensesWith
, lensRules
, lensRulesFor
, makeClassy
, makeClassy_
, makeClassyFor
, declareClassy
, declareClassyFor
, classyRules
, classyRules_
, classyRulesFor
, makeFields
, makeFieldsNoPrefix
, declareFields
, defaultFieldRules
, makePrismLabels
, makePrisms
, declarePrisms
, makeClassyPrisms
, LensRules
, simpleLenses
, generateSignatures
, generateUpdateableOptics
, generateLazyPatterns
, createClass
, lensField
, lensClass
, noPrefixFieldLabels
, abbreviatedFieldLabels
, underscoreFields
, camelCaseFields
, classUnderscoreNoPrefixFields
, abbreviatedFields
, FieldNamer
, ClassyNamer
, DefName(..)
, noPrefixNamer
, underscoreNoPrefixNamer
, lookingupNamer
, mappingNamer
, underscoreNamer
, camelCaseNamer
, classUnderscoreNoPrefixNamer
, abbreviatedNamer
) where
import Control.Monad.Trans.Class
import Control.Monad.Trans.State
import Control.Monad.Trans.Writer
import Data.Char (toLower, toUpper, isUpper)
import Data.Maybe (maybeToList)
import Data.Monoid
import Data.Set (Set)
import Language.Haskell.TH.Syntax hiding (lift)
import Language.Haskell.TH
import qualified Data.List as L
import qualified Data.Set as Set
import Optics.Core hiding (cons)
import Optics.TH.Internal.Product
import Optics.TH.Internal.Sum
makeFieldLabels :: Name -> DecsQ
makeFieldLabels :: Name -> DecsQ
makeFieldLabels = LensRules -> Name -> DecsQ
makeFieldLabelsWith LensRules
fieldLabelsRules
makeFieldLabelsNoPrefix :: Name -> DecsQ
makeFieldLabelsNoPrefix :: Name -> DecsQ
makeFieldLabelsNoPrefix = LensRules -> Name -> DecsQ
makeFieldLabelsWith LensRules
noPrefixFieldLabels
makeFieldLabelsFor :: [(String, String)] -> Name -> DecsQ
makeFieldLabelsFor :: [(String, String)] -> Name -> DecsQ
makeFieldLabelsFor [(String, String)]
fields = LensRules -> Name -> DecsQ
makeFieldLabelsWith ([(String, String)] -> LensRules
fieldLabelsRulesFor [(String, String)]
fields)
declareFieldLabels :: DecsQ -> DecsQ
declareFieldLabels :: DecsQ -> DecsQ
declareFieldLabels
= LensRules -> DecsQ -> DecsQ
declareFieldLabelsWith
(LensRules -> DecsQ -> DecsQ) -> LensRules -> DecsQ -> DecsQ
forall a b. (a -> b) -> a -> b
$ LensRules
fieldLabelsRules
LensRules -> (LensRules -> LensRules) -> LensRules
forall a b. a -> (a -> b) -> b
& Lens' LensRules FieldNamer
lensField Lens' LensRules FieldNamer -> FieldNamer -> LensRules -> LensRules
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ FieldNamer
noPrefixNamer
declareFieldLabelsFor :: [(String, String)] -> DecsQ -> DecsQ
declareFieldLabelsFor :: [(String, String)] -> DecsQ -> DecsQ
declareFieldLabelsFor [(String, String)]
fields
= LensRules -> DecsQ -> DecsQ
declareFieldLabelsWith
(LensRules -> DecsQ -> DecsQ) -> LensRules -> DecsQ -> DecsQ
forall a b. (a -> b) -> a -> b
$ [(String, String)] -> LensRules
fieldLabelsRulesFor [(String, String)]
fields
LensRules -> (LensRules -> LensRules) -> LensRules
forall a b. a -> (a -> b) -> b
& Lens' LensRules FieldNamer
lensField Lens' LensRules FieldNamer -> FieldNamer -> LensRules -> LensRules
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ FieldNamer
noPrefixNamer
declareFieldLabelsWith :: LensRules -> DecsQ -> DecsQ
declareFieldLabelsWith :: LensRules -> DecsQ -> DecsQ
declareFieldLabelsWith LensRules
rules = (Dec -> Declare Dec) -> DecsQ -> DecsQ
declareWith ((Dec -> Declare Dec) -> DecsQ -> DecsQ)
-> (Dec -> Declare Dec) -> DecsQ -> DecsQ
forall a b. (a -> b) -> a -> b
$ \Dec
dec -> do
[Dec] -> Declare ()
emit ([Dec] -> Declare ())
-> WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec] -> Declare ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< DecsQ -> WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec]
forall a. Q a -> Declare a
liftDeclare (LensRules -> Dec -> DecsQ
makeFieldLabelsForDec LensRules
rules Dec
dec)
Dec -> Declare Dec
forall (m :: * -> *) a. Monad m => a -> m a
return (Dec -> Declare Dec) -> Dec -> Declare Dec
forall a b. (a -> b) -> a -> b
$ Dec -> Dec
stripFields Dec
dec
fieldLabelsRules :: LensRules
fieldLabelsRules :: LensRules
fieldLabelsRules = LensRules :: Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> FieldNamer
-> ClassyNamer
-> LensRules
LensRules
{ _simpleLenses :: Bool
_simpleLenses = Bool
False
, _generateSigs :: Bool
_generateSigs = Bool
True
, _generateClasses :: Bool
_generateClasses = Bool
False
, _allowIsos :: Bool
_allowIsos = Bool
True
, _allowUpdates :: Bool
_allowUpdates = Bool
True
, _lazyPatterns :: Bool
_lazyPatterns = Bool
False
, _classyLenses :: ClassyNamer
_classyLenses = Maybe (Name, Name) -> ClassyNamer
forall a b. a -> b -> a
const Maybe (Name, Name)
forall a. Maybe a
Nothing
, _fieldToDef :: FieldNamer
_fieldToDef = FieldNamer
camelCaseNamer
}
fieldLabelsRulesFor
:: [(String, String)]
-> LensRules
fieldLabelsRulesFor :: [(String, String)] -> LensRules
fieldLabelsRulesFor [(String, String)]
fields = LensRules
fieldLabelsRules LensRules -> (LensRules -> LensRules) -> LensRules
forall a b. a -> (a -> b) -> b
& Lens' LensRules FieldNamer
lensField Lens' LensRules FieldNamer -> FieldNamer -> LensRules -> LensRules
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ [(String, String)] -> FieldNamer
lookingupNamer [(String, String)]
fields
makeLenses :: Name -> DecsQ
makeLenses :: Name -> DecsQ
makeLenses = LensRules -> Name -> DecsQ
makeFieldOptics LensRules
lensRules
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)
makeLensesWith :: LensRules -> Name -> DecsQ
makeLensesWith :: LensRules -> Name -> DecsQ
makeLensesWith = LensRules -> Name -> DecsQ
makeFieldOptics
declareLenses :: DecsQ -> DecsQ
declareLenses :: DecsQ -> DecsQ
declareLenses
= LensRules -> DecsQ -> DecsQ
declareLensesWith
(LensRules -> DecsQ -> DecsQ) -> LensRules -> DecsQ -> DecsQ
forall a b. (a -> b) -> a -> b
$ LensRules
lensRules
LensRules -> (LensRules -> LensRules) -> LensRules
forall a b. a -> (a -> b) -> b
& Lens' LensRules FieldNamer
lensField Lens' LensRules FieldNamer -> FieldNamer -> LensRules -> LensRules
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ FieldNamer
noPrefixNamer
declareLensesFor :: [(String, String)] -> DecsQ -> DecsQ
declareLensesFor :: [(String, String)] -> DecsQ -> DecsQ
declareLensesFor [(String, String)]
fields
= LensRules -> DecsQ -> DecsQ
declareLensesWith
(LensRules -> DecsQ -> DecsQ) -> LensRules -> DecsQ -> DecsQ
forall a b. (a -> b) -> a -> b
$ [(String, String)] -> LensRules
lensRulesFor [(String, String)]
fields
LensRules -> (LensRules -> LensRules) -> LensRules
forall a b. a -> (a -> b) -> b
& Lens' LensRules FieldNamer
lensField Lens' LensRules FieldNamer -> FieldNamer -> LensRules -> LensRules
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ FieldNamer
noPrefixNamer
declareLensesWith :: LensRules -> DecsQ -> DecsQ
declareLensesWith :: LensRules -> DecsQ -> DecsQ
declareLensesWith LensRules
rules = (Dec -> Declare Dec) -> DecsQ -> DecsQ
declareWith ((Dec -> Declare Dec) -> DecsQ -> DecsQ)
-> (Dec -> Declare Dec) -> DecsQ -> DecsQ
forall a b. (a -> b) -> a -> b
$ \Dec
dec -> do
[Dec] -> Declare ()
emit ([Dec] -> Declare ())
-> WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec] -> Declare ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< StateT (Set Name) Q [Dec]
-> WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (LensRules -> Dec -> StateT (Set Name) Q [Dec]
makeFieldOpticsForDec' LensRules
rules Dec
dec)
Dec -> Declare Dec
forall (m :: * -> *) a. Monad m => a -> m a
return (Dec -> Declare Dec) -> Dec -> Declare Dec
forall a b. (a -> b) -> a -> b
$ Dec -> Dec
stripFields Dec
dec
lensRules :: LensRules
lensRules :: LensRules
lensRules = LensRules :: Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> FieldNamer
-> ClassyNamer
-> LensRules
LensRules
{ _simpleLenses :: Bool
_simpleLenses = Bool
False
, _generateSigs :: Bool
_generateSigs = Bool
True
, _generateClasses :: Bool
_generateClasses = Bool
False
, _allowIsos :: Bool
_allowIsos = Bool
True
, _allowUpdates :: Bool
_allowUpdates = Bool
True
, _lazyPatterns :: Bool
_lazyPatterns = Bool
False
, _classyLenses :: ClassyNamer
_classyLenses = Maybe (Name, Name) -> ClassyNamer
forall a b. a -> b -> a
const Maybe (Name, Name)
forall a. Maybe a
Nothing
, _fieldToDef :: FieldNamer
_fieldToDef = FieldNamer
underscoreNoPrefixNamer
}
lensRulesFor
:: [(String, String)]
-> LensRules
lensRulesFor :: [(String, String)] -> LensRules
lensRulesFor [(String, String)]
fields = LensRules
lensRules LensRules -> (LensRules -> LensRules) -> LensRules
forall a b. a -> (a -> b) -> b
& Lens' LensRules FieldNamer
lensField Lens' LensRules FieldNamer -> FieldNamer -> LensRules -> LensRules
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ [(String, String)] -> FieldNamer
lookingupNamer [(String, String)]
fields
makeClassy :: Name -> DecsQ
makeClassy :: Name -> DecsQ
makeClassy = LensRules -> Name -> DecsQ
makeFieldOptics LensRules
classyRules
makeClassy_ :: Name -> DecsQ
makeClassy_ :: Name -> DecsQ
makeClassy_ = LensRules -> Name -> DecsQ
makeFieldOptics LensRules
classyRules_
makeClassyFor :: String -> String -> [(String, String)] -> Name -> DecsQ
makeClassyFor :: String -> String -> [(String, String)] -> Name -> DecsQ
makeClassyFor String
clsName String
funName [(String, String)]
fields = LensRules -> Name -> DecsQ
makeFieldOptics (LensRules -> Name -> DecsQ) -> LensRules -> Name -> DecsQ
forall a b. (a -> b) -> a -> b
$
(String -> Maybe (String, String))
-> [(String, String)] -> LensRules
classyRulesFor (Maybe (String, String) -> String -> Maybe (String, String)
forall a b. a -> b -> a
const ((String, String) -> Maybe (String, String)
forall a. a -> Maybe a
Just (String
clsName, String
funName))) [(String, String)]
fields
declareClassy :: DecsQ -> DecsQ
declareClassy :: DecsQ -> DecsQ
declareClassy
= LensRules -> DecsQ -> DecsQ
declareLensesWith
(LensRules -> DecsQ -> DecsQ) -> LensRules -> DecsQ -> DecsQ
forall a b. (a -> b) -> a -> b
$ LensRules
classyRules
LensRules -> (LensRules -> LensRules) -> LensRules
forall a b. a -> (a -> b) -> b
& Lens' LensRules FieldNamer
lensField Lens' LensRules FieldNamer -> FieldNamer -> LensRules -> LensRules
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ FieldNamer
noPrefixNamer
declareClassyFor ::
[(String, (String, String))] -> [(String, String)] -> DecsQ -> DecsQ
declareClassyFor :: [(String, (String, String))]
-> [(String, String)] -> DecsQ -> DecsQ
declareClassyFor [(String, (String, String))]
classes [(String, String)]
fields
= LensRules -> DecsQ -> DecsQ
declareLensesWith
(LensRules -> DecsQ -> DecsQ) -> LensRules -> DecsQ -> DecsQ
forall a b. (a -> b) -> a -> b
$ (String -> Maybe (String, String))
-> [(String, String)] -> LensRules
classyRulesFor (String -> [(String, (String, String))] -> Maybe (String, String)
forall a b. Eq a => a -> [(a, b)] -> Maybe b
`Prelude.lookup`[(String, (String, String))]
classes) [(String, String)]
fields
LensRules -> (LensRules -> LensRules) -> LensRules
forall a b. a -> (a -> b) -> b
& Lens' LensRules FieldNamer
lensField Lens' LensRules FieldNamer -> FieldNamer -> LensRules -> LensRules
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ FieldNamer
noPrefixNamer
classyRules :: LensRules
classyRules :: LensRules
classyRules = LensRules :: Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> FieldNamer
-> ClassyNamer
-> LensRules
LensRules
{ _simpleLenses :: Bool
_simpleLenses = Bool
True
, _generateSigs :: Bool
_generateSigs = Bool
True
, _generateClasses :: Bool
_generateClasses = Bool
True
, _allowIsos :: Bool
_allowIsos = Bool
False
, _allowUpdates :: Bool
_allowUpdates = Bool
True
, _lazyPatterns :: Bool
_lazyPatterns = Bool
False
, _classyLenses :: ClassyNamer
_classyLenses = \Name
n ->
case Name -> String
nameBase Name
n of
Char
x:String
xs -> (Name, Name) -> Maybe (Name, Name)
forall a. a -> Maybe a
Just (String -> Name
mkName (String
"Has" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
xChar -> String -> String
forall a. a -> [a] -> [a]
:String
xs), String -> Name
mkName (Char -> Char
toLower Char
xChar -> String -> String
forall a. a -> [a] -> [a]
:String
xs))
[] -> Maybe (Name, Name)
forall a. Maybe a
Nothing
, _fieldToDef :: FieldNamer
_fieldToDef = FieldNamer
underscoreNoPrefixNamer
}
classyRules_ :: LensRules
classyRules_ :: LensRules
classyRules_
= LensRules
classyRules LensRules -> (LensRules -> LensRules) -> LensRules
forall a b. a -> (a -> b) -> b
& Lens' LensRules FieldNamer
lensField Lens' LensRules FieldNamer -> FieldNamer -> LensRules -> LensRules
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ \Name
_ [Name]
_ Name
n -> [Name -> DefName
TopName (String -> Name
mkName (Char
'_'Char -> String -> String
forall a. a -> [a] -> [a]
:Name -> String
nameBase Name
n))]
classyRulesFor
:: (String -> Maybe (String, String)) ->
[(String, String)] ->
LensRules
classyRulesFor :: (String -> Maybe (String, String))
-> [(String, String)] -> LensRules
classyRulesFor String -> Maybe (String, String)
classFun [(String, String)]
fields = LensRules
classyRules
LensRules -> (LensRules -> LensRules) -> LensRules
forall a b. a -> (a -> b) -> b
& Lens' LensRules ClassyNamer
lensClass Lens' LensRules ClassyNamer
-> ClassyNamer -> LensRules -> LensRules
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ (Optic
A_Setter
'[Int]
(Maybe (String, String))
(Maybe (Name, Name))
String
Name
-> (String -> Name) -> Maybe (String, String) -> Maybe (Name, Name)
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over (Setter
(Maybe (String, String))
(Maybe (Name, Name))
(String, String)
(Name, Name)
forall (f :: * -> *) a b. Functor f => Setter (f a) (f b) a b
mapped Setter
(Maybe (String, String))
(Maybe (Name, Name))
(String, String)
(Name, Name)
-> Optic
A_Traversal '[Int] (String, String) (Name, Name) String Name
-> Optic
A_Setter
'[Int]
(Maybe (String, String))
(Maybe (Name, Name))
String
Name
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Traversal '[Int] (String, String) (Name, Name) String Name
forall i s t a b. Each i s t a b => IxTraversal i s t a b
each) String -> Name
mkName (Maybe (String, String) -> Maybe (Name, Name))
-> (Name -> Maybe (String, String)) -> ClassyNamer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe (String, String)
classFun (String -> Maybe (String, String))
-> (Name -> String) -> Name -> Maybe (String, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> String
nameBase)
LensRules -> (LensRules -> LensRules) -> LensRules
forall a b. a -> (a -> b) -> b
& Lens' LensRules FieldNamer
lensField Lens' LensRules FieldNamer -> FieldNamer -> LensRules -> LensRules
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ [(String, String)] -> FieldNamer
lookingupNamer [(String, String)]
fields
makeFields :: Name -> DecsQ
makeFields :: Name -> DecsQ
makeFields = LensRules -> Name -> DecsQ
makeFieldOptics LensRules
camelCaseFields
makeFieldsNoPrefix :: Name -> DecsQ
makeFieldsNoPrefix :: Name -> DecsQ
makeFieldsNoPrefix = LensRules -> Name -> DecsQ
makeFieldOptics LensRules
classUnderscoreNoPrefixFields
declareFields :: DecsQ -> DecsQ
declareFields :: DecsQ -> DecsQ
declareFields = LensRules -> DecsQ -> DecsQ
declareLensesWith LensRules
defaultFieldRules
defaultFieldRules :: LensRules
defaultFieldRules :: LensRules
defaultFieldRules = LensRules :: Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> FieldNamer
-> ClassyNamer
-> LensRules
LensRules
{ _simpleLenses :: Bool
_simpleLenses = Bool
True
, _generateSigs :: Bool
_generateSigs = Bool
True
, _generateClasses :: Bool
_generateClasses = Bool
True
, _allowIsos :: Bool
_allowIsos = Bool
False
, _allowUpdates :: Bool
_allowUpdates = Bool
True
, _lazyPatterns :: Bool
_lazyPatterns = Bool
False
, _classyLenses :: ClassyNamer
_classyLenses = Maybe (Name, Name) -> ClassyNamer
forall a b. a -> b -> a
const Maybe (Name, Name)
forall a. Maybe a
Nothing
, _fieldToDef :: FieldNamer
_fieldToDef = FieldNamer
camelCaseNamer
}
declarePrisms :: DecsQ -> DecsQ
declarePrisms :: DecsQ -> DecsQ
declarePrisms = (Dec -> Declare Dec) -> DecsQ -> DecsQ
declareWith ((Dec -> Declare Dec) -> DecsQ -> DecsQ)
-> (Dec -> Declare Dec) -> DecsQ -> DecsQ
forall a b. (a -> b) -> a -> b
$ \Dec
dec -> do
[Dec] -> Declare ()
emit ([Dec] -> Declare ())
-> WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec] -> Declare ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< DecsQ -> WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec]
forall a. Q a -> Declare a
liftDeclare (Bool -> Dec -> DecsQ
makeDecPrisms Bool
True Dec
dec)
Dec -> Declare Dec
forall (m :: * -> *) a. Monad m => a -> m a
return Dec
dec
simpleLenses :: Lens' LensRules Bool
simpleLenses :: Lens' LensRules Bool
simpleLenses = LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool
forall s t a b. LensVL s t a b -> Lens s t a b
lensVL (LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool)
-> LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool
forall a b. (a -> b) -> a -> b
$ \Bool -> f Bool
f LensRules
r ->
(Bool -> LensRules) -> f Bool -> f LensRules
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))
generateSignatures :: Lens' LensRules Bool
generateSignatures :: Lens' LensRules Bool
generateSignatures = LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool
forall s t a b. LensVL s t a b -> Lens s t a b
lensVL (LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool)
-> LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool
forall a b. (a -> b) -> a -> b
$ \Bool -> f Bool
f LensRules
r ->
(Bool -> LensRules) -> f Bool -> f LensRules
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))
generateUpdateableOptics :: Lens' LensRules Bool
generateUpdateableOptics :: Lens' LensRules Bool
generateUpdateableOptics = LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool
forall s t a b. LensVL s t a b -> Lens s t a b
lensVL (LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool)
-> LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool
forall a b. (a -> b) -> a -> b
$ \Bool -> f Bool
f LensRules
r ->
(Bool -> LensRules) -> f Bool -> f LensRules
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))
generateLazyPatterns :: Lens' LensRules Bool
generateLazyPatterns :: Lens' LensRules Bool
generateLazyPatterns = LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool
forall s t a b. LensVL s t a b -> Lens s t a b
lensVL (LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool)
-> LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool
forall a b. (a -> b) -> a -> b
$ \Bool -> f Bool
f LensRules
r ->
(Bool -> LensRules) -> f Bool -> f LensRules
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))
createClass :: Lens' LensRules Bool
createClass :: Lens' LensRules Bool
createClass = LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool
forall s t a b. LensVL s t a b -> Lens s t a b
lensVL (LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool)
-> LensVL LensRules LensRules Bool Bool -> Lens' LensRules Bool
forall a b. (a -> b) -> a -> b
$ \Bool -> f Bool
f LensRules
r ->
(Bool -> LensRules) -> f Bool -> f LensRules
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))
lensField :: Lens' LensRules FieldNamer
lensField :: Lens' LensRules FieldNamer
lensField = LensVL LensRules LensRules FieldNamer FieldNamer
-> Lens' LensRules FieldNamer
forall s t a b. LensVL s t a b -> Lens s t a b
lensVL (LensVL LensRules LensRules FieldNamer FieldNamer
-> Lens' LensRules FieldNamer)
-> LensVL LensRules LensRules FieldNamer FieldNamer
-> Lens' LensRules FieldNamer
forall a b. (a -> b) -> a -> b
$ \FieldNamer -> f FieldNamer
f LensRules
r ->
(FieldNamer -> LensRules) -> f FieldNamer -> f LensRules
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\FieldNamer
x -> LensRules
r { _fieldToDef :: FieldNamer
_fieldToDef = FieldNamer
x}) (FieldNamer -> f FieldNamer
f (LensRules -> FieldNamer
_fieldToDef LensRules
r))
lensClass :: Lens' LensRules ClassyNamer
lensClass :: Lens' LensRules ClassyNamer
lensClass = LensVL LensRules LensRules ClassyNamer ClassyNamer
-> Lens' LensRules ClassyNamer
forall s t a b. LensVL s t a b -> Lens s t a b
lensVL (LensVL LensRules LensRules ClassyNamer ClassyNamer
-> Lens' LensRules ClassyNamer)
-> LensVL LensRules LensRules ClassyNamer ClassyNamer
-> Lens' LensRules ClassyNamer
forall a b. (a -> b) -> a -> b
$ \ClassyNamer -> f ClassyNamer
f LensRules
r ->
(ClassyNamer -> LensRules) -> f ClassyNamer -> f LensRules
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ClassyNamer
x -> LensRules
r { _classyLenses :: ClassyNamer
_classyLenses = ClassyNamer
x }) (ClassyNamer -> f ClassyNamer
f (LensRules -> ClassyNamer
_classyLenses LensRules
r))
noPrefixFieldLabels :: LensRules
noPrefixFieldLabels :: LensRules
noPrefixFieldLabels = LensRules
fieldLabelsRules { _fieldToDef :: FieldNamer
_fieldToDef = FieldNamer
noPrefixNamer }
abbreviatedFieldLabels :: LensRules
abbreviatedFieldLabels :: LensRules
abbreviatedFieldLabels = LensRules
fieldLabelsRules { _fieldToDef :: FieldNamer
_fieldToDef = FieldNamer
abbreviatedNamer }
underscoreFields :: LensRules
underscoreFields :: LensRules
underscoreFields = LensRules
defaultFieldRules LensRules -> (LensRules -> LensRules) -> LensRules
forall a b. a -> (a -> b) -> b
& Lens' LensRules FieldNamer
lensField Lens' LensRules FieldNamer -> FieldNamer -> LensRules -> LensRules
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ FieldNamer
underscoreNamer
camelCaseFields :: LensRules
camelCaseFields :: LensRules
camelCaseFields = LensRules
defaultFieldRules
classUnderscoreNoPrefixFields :: LensRules
classUnderscoreNoPrefixFields :: LensRules
classUnderscoreNoPrefixFields =
LensRules
defaultFieldRules LensRules -> (LensRules -> LensRules) -> LensRules
forall a b. a -> (a -> b) -> b
& Lens' LensRules FieldNamer
lensField Lens' LensRules FieldNamer -> FieldNamer -> LensRules -> LensRules
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ FieldNamer
classUnderscoreNoPrefixNamer
abbreviatedFields :: LensRules
abbreviatedFields :: LensRules
abbreviatedFields = LensRules
defaultFieldRules { _fieldToDef :: FieldNamer
_fieldToDef = FieldNamer
abbreviatedNamer }
noPrefixNamer :: FieldNamer
noPrefixNamer :: FieldNamer
noPrefixNamer Name
_ [Name]
_ Name
n = [Name -> DefName
TopName Name
n]
underscoreNoPrefixNamer :: FieldNamer
underscoreNoPrefixNamer :: FieldNamer
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
xChar -> String -> String
forall a. a -> [a] -> [a]
:String
xs))]
String
_ -> []
lookingupNamer :: [(String,String)] -> FieldNamer
lookingupNamer :: [(String, String)] -> FieldNamer
lookingupNamer [(String, String)]
kvs Name
_ [Name]
_ Name
field =
[ Name -> DefName
TopName (String -> Name
mkName String
v) | (String
k,String
v) <- [(String, String)]
kvs, String
k String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== Name -> String
nameBase Name
field]
mappingNamer :: (String -> [String])
-> FieldNamer
mappingNamer :: (String -> [String]) -> FieldNamer
mappingNamer String -> [String]
mapper Name
_ [Name]
_ = (String -> DefName) -> [String] -> [DefName]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Name -> DefName
TopName (Name -> DefName) -> (String -> Name) -> String -> DefName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Name
mkName) ([String] -> [DefName]) -> (Name -> [String]) -> Name -> [DefName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
mapper (String -> [String]) -> (Name -> String) -> Name -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> String
nameBase
underscoreNamer :: FieldNamer
underscoreNamer :: FieldNamer
underscoreNamer Name
_ [Name]
_ Name
field = Maybe DefName -> [DefName]
forall a. Maybe a -> [a]
maybeToList (Maybe DefName -> [DefName]) -> Maybe DefName -> [DefName]
forall a b. (a -> b) -> a -> b
$ do
String
_ <- String -> Maybe String
prefix String
field'
String
method <- Maybe String
niceLens
String
cls <- Maybe String
classNaming
DefName -> Maybe DefName
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> Name -> DefName
MethodName (String -> Name
mkName String
cls) (String -> Name
mkName String
method))
where
field' :: String
field' = Name -> String
nameBase Name
field
prefix :: String -> Maybe String
prefix (Char
'_':String
xs) | Char
'_' Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`L.elem` String
xs = String -> Maybe String
forall a. a -> Maybe a
Just ((Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'_') String
xs)
prefix String
_ = Maybe String
forall a. Maybe a
Nothing
niceLens :: Maybe String
niceLens = String -> Maybe String
prefix String
field' Maybe String -> (String -> String) -> Maybe String
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \String
n -> Int -> String -> String
forall a. Int -> [a] -> [a]
drop (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) String
field'
classNaming :: Maybe String
classNaming = Maybe String
niceLens Maybe String -> (String -> String) -> Maybe String
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (String
"Has_" String -> String -> String
forall a. [a] -> [a] -> [a]
++)
camelCaseNamer :: FieldNamer
camelCaseNamer :: FieldNamer
camelCaseNamer Name
tyName [Name]
fields Name
field = Maybe DefName -> [DefName]
forall a. Maybe a -> [a]
maybeToList (Maybe DefName -> [DefName]) -> Maybe DefName -> [DefName]
forall a b. (a -> b) -> a -> b
$ do
String
fieldPart <- String -> String -> Maybe String
forall a. Eq a => [a] -> [a] -> Maybe [a]
L.stripPrefix String
expectedPrefix (Name -> String
nameBase Name
field)
String
method <- String -> Maybe String
computeMethod String
fieldPart
let cls :: String
cls = String
"Has" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldPart
DefName -> Maybe DefName
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 String -> String -> String
forall a. [a] -> [a] -> [a]
++ Optic An_AffineTraversal '[] String String Char Char
-> (Char -> Char) -> String -> String
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over Optic An_AffineTraversal '[] String String Char Char
forall s a. Cons s s a a => AffineTraversal' s a
_head Char -> Char
toLower (Name -> String
nameBase Name
tyName)
optUnderscore :: String
optUnderscore = [Char
'_' | (Name -> Bool) -> [Name] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
L.isPrefixOf String
"_" (String -> Bool) -> (Name -> String) -> Name -> Bool
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 = String -> Maybe String
forall a. a -> Maybe a
Just (Char -> Char
toLower Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: String
xs)
computeMethod String
_ = Maybe String
forall a. Maybe a
Nothing
classUnderscoreNoPrefixNamer :: FieldNamer
classUnderscoreNoPrefixNamer :: FieldNamer
classUnderscoreNoPrefixNamer Name
_ [Name]
_ Name
field = Maybe DefName -> [DefName]
forall a. Maybe a -> [a]
maybeToList (Maybe DefName -> [DefName]) -> Maybe DefName -> [DefName]
forall a b. (a -> b) -> a -> b
$ do
String
fieldUnprefixed <- String -> String -> Maybe String
forall a. Eq a => [a] -> [a] -> Maybe [a]
L.stripPrefix String
"_" (Name -> String
nameBase Name
field)
let className :: String
className = String
"Has" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Optic An_AffineTraversal '[] String String Char Char
-> (Char -> Char) -> String -> String
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over Optic An_AffineTraversal '[] String String Char Char
forall s a. Cons s s a a => AffineTraversal' s a
_head Char -> Char
toUpper String
fieldUnprefixed
methodName :: String
methodName = String
fieldUnprefixed
DefName -> Maybe DefName
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> Name -> DefName
MethodName (String -> Name
mkName String
className) (String -> Name
mkName String
methodName))
abbreviatedNamer :: FieldNamer
abbreviatedNamer :: FieldNamer
abbreviatedNamer Name
_ [Name]
fields Name
field = Maybe DefName -> [DefName]
forall a. Maybe a -> [a]
maybeToList (Maybe DefName -> [DefName]) -> Maybe DefName -> [DefName]
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" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fieldPart
DefName -> Maybe DefName
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 <- String -> String -> Maybe String
forall a. Eq a => [a] -> [a] -> Maybe [a]
L.stripPrefix String
optUnderscore String
f
case (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Char -> Bool
isUpper String
x of
(String
p,String
s) | String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
L.null String
p Bool -> Bool -> Bool
|| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
L.null String
s -> Maybe String
forall a. Maybe a
Nothing
| Bool
otherwise -> String -> Maybe String
forall a. a -> Maybe a
Just String
s
optUnderscore :: String
optUnderscore = [Char
'_' | (Name -> Bool) -> [Name] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
L.isPrefixOf String
"_" (String -> Bool) -> (Name -> String) -> Name -> Bool
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 = String -> Maybe String
forall a. a -> Maybe a
Just (Char -> Char
toLower Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: String
xs)
computeMethod String
_ = Maybe String
forall a. Maybe a
Nothing
declareWith :: (Dec -> Declare Dec) -> DecsQ -> DecsQ
declareWith :: (Dec -> Declare Dec) -> DecsQ -> DecsQ
declareWith Dec -> Declare Dec
fun = (WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec] -> DecsQ
runDeclare (WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec] -> DecsQ)
-> ([Dec] -> WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec])
-> [Dec]
-> DecsQ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Dec -> Declare Dec)
-> [Dec] -> WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec]
forall (f :: * -> *).
Applicative f =>
(Dec -> f Dec) -> [Dec] -> f [Dec]
traverseDataAndNewtype Dec -> Declare Dec
fun ([Dec] -> DecsQ) -> DecsQ -> DecsQ
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<)
type Declare = WriterT (Endo [Dec]) (StateT (Set Name) Q)
liftDeclare :: Q a -> Declare a
liftDeclare :: Q a -> Declare a
liftDeclare = StateT (Set Name) Q a -> Declare a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (StateT (Set Name) Q a -> Declare a)
-> (Q a -> StateT (Set Name) Q a) -> Q a -> Declare a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Q a -> StateT (Set Name) Q a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift
runDeclare :: Declare [Dec] -> DecsQ
runDeclare :: WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec] -> DecsQ
runDeclare WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec]
dec = do
([Dec]
out, Endo [Dec]
endo) <- StateT (Set Name) Q ([Dec], Endo [Dec])
-> Set Name -> Q ([Dec], Endo [Dec])
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec]
-> StateT (Set Name) Q ([Dec], Endo [Dec])
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
runWriterT WriterT (Endo [Dec]) (StateT (Set Name) Q) [Dec]
dec) Set Name
forall a. Set a
Set.empty
[Dec] -> DecsQ
forall (m :: * -> *) a. Monad m => a -> m a
return ([Dec] -> DecsQ) -> [Dec] -> DecsQ
forall a b. (a -> b) -> a -> b
$ [Dec]
out [Dec] -> [Dec] -> [Dec]
forall a. [a] -> [a] -> [a]
++ Endo [Dec] -> [Dec] -> [Dec]
forall a. Endo a -> a -> a
appEndo Endo [Dec]
endo []
emit :: [Dec] -> Declare ()
emit :: [Dec] -> Declare ()
emit [Dec]
decs = Endo [Dec] -> Declare ()
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell (Endo [Dec] -> Declare ()) -> Endo [Dec] -> Declare ()
forall a b. (a -> b) -> a -> b
$ ([Dec] -> [Dec]) -> Endo [Dec]
forall a. (a -> a) -> Endo a
Endo ([Dec]
decs[Dec] -> [Dec] -> [Dec]
forall a. [a] -> [a] -> [a]
++)
traverseDataAndNewtype :: (Applicative f) => (Dec -> f Dec) -> [Dec] -> f [Dec]
traverseDataAndNewtype :: (Dec -> f Dec) -> [Dec] -> f [Dec]
traverseDataAndNewtype Dec -> f Dec
f [Dec]
decs = (Dec -> f Dec) -> [Dec] -> f [Dec]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Dec -> f Dec
go [Dec]
decs
where
go :: Dec -> f Dec
go Dec
dec = case Dec
dec of
DataD{} -> Dec -> f Dec
f Dec
dec
NewtypeD{} -> Dec -> f Dec
f Dec
dec
DataInstD{} -> Dec -> f Dec
f Dec
dec
NewtypeInstD{} -> Dec -> f Dec
f Dec
dec
InstanceD Maybe Overlap
moverlap Cxt
ctx Type
inst [Dec]
body -> Maybe Overlap -> Cxt -> Type -> [Dec] -> Dec
InstanceD Maybe Overlap
moverlap Cxt
ctx Type
inst ([Dec] -> Dec) -> f [Dec] -> f Dec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Dec -> f Dec) -> [Dec] -> f [Dec]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Dec -> f Dec
go [Dec]
body
Dec
_ -> Dec -> f Dec
forall (f :: * -> *) a. Applicative f => a -> f a
pure Dec
dec
stripFields :: Dec -> Dec
stripFields :: Dec -> Dec
stripFields Dec
dec = case Dec
dec of
DataD Cxt
ctx Name
tyName [TyVarBndr]
tyArgs Maybe Type
kind [Con]
cons [DerivClause]
derivings ->
Cxt
-> Name
-> [TyVarBndr]
-> Maybe Type
-> [Con]
-> [DerivClause]
-> Dec
DataD Cxt
ctx Name
tyName [TyVarBndr]
tyArgs Maybe Type
kind ((Con -> Con) -> [Con] -> [Con]
forall a b. (a -> b) -> [a] -> [b]
map Con -> Con
deRecord [Con]
cons) [DerivClause]
derivings
NewtypeD Cxt
ctx Name
tyName [TyVarBndr]
tyArgs Maybe Type
kind Con
con [DerivClause]
derivings ->
Cxt
-> Name -> [TyVarBndr] -> Maybe Type -> Con -> [DerivClause] -> Dec
NewtypeD Cxt
ctx Name
tyName [TyVarBndr]
tyArgs Maybe Type
kind (Con -> Con
deRecord Con
con) [DerivClause]
derivings
DataInstD Cxt
ctx Maybe [TyVarBndr]
tyName Type
tyArgs Maybe Type
kind [Con]
cons [DerivClause]
derivings ->
Cxt
-> Maybe [TyVarBndr]
-> Type
-> Maybe Type
-> [Con]
-> [DerivClause]
-> Dec
DataInstD Cxt
ctx Maybe [TyVarBndr]
tyName Type
tyArgs Maybe Type
kind ((Con -> Con) -> [Con] -> [Con]
forall a b. (a -> b) -> [a] -> [b]
map Con -> Con
deRecord [Con]
cons) [DerivClause]
derivings
NewtypeInstD Cxt
ctx Maybe [TyVarBndr]
tyName Type
tyArgs Maybe Type
kind Con
con [DerivClause]
derivings ->
Cxt
-> Maybe [TyVarBndr]
-> Type
-> Maybe Type
-> Con
-> [DerivClause]
-> Dec
NewtypeInstD Cxt
ctx Maybe [TyVarBndr]
tyName Type
tyArgs Maybe Type
kind (Con -> Con
deRecord Con
con) [DerivClause]
derivings
Dec
_ -> Dec
dec
deRecord :: Con -> Con
deRecord :: Con -> Con
deRecord con :: Con
con@NormalC{} = Con
con
deRecord con :: Con
con@InfixC{} = Con
con
deRecord (ForallC [TyVarBndr]
tyVars Cxt
ctx Con
con) = [TyVarBndr] -> Cxt -> Con -> Con
ForallC [TyVarBndr]
tyVars Cxt
ctx (Con -> Con) -> Con -> Con
forall a b. (a -> b) -> a -> b
$ Con -> Con
deRecord Con
con
deRecord (RecC Name
conName [VarBangType]
fields) = Name -> [BangType] -> Con
NormalC Name
conName ((VarBangType -> BangType) -> [VarBangType] -> [BangType]
forall a b. (a -> b) -> [a] -> [b]
map VarBangType -> BangType
dropFieldName [VarBangType]
fields)
deRecord con :: Con
con@GadtC{} = Con
con
deRecord (RecGadtC [Name]
ns [VarBangType]
fields Type
retTy) = [Name] -> [BangType] -> Type -> Con
GadtC [Name]
ns ((VarBangType -> BangType) -> [VarBangType] -> [BangType]
forall a b. (a -> b) -> [a] -> [b]
map VarBangType -> BangType
dropFieldName [VarBangType]
fields) Type
retTy
dropFieldName :: VarBangType -> BangType
dropFieldName :: VarBangType -> BangType
dropFieldName (Name
_, Bang
str, Type
typ) = (Bang
str, Type
typ)