{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ViewPatterns #-}
module Generics.Deriving.TH (
deriveMeta
, deriveData
, deriveConstructors
, deriveSelectors
, deriveAll
, deriveAll0
, deriveAll1
, deriveAll0And1
, deriveRepresentable0
, deriveRepresentable1
, deriveRep0
, deriveRep1
, makeRep0Inline
, makeRep0
, makeRep0FromType
, makeFrom
, makeFrom0
, makeTo
, makeTo0
, makeRep1Inline
, makeRep1
, makeRep1FromType
, makeFrom1
, makeTo1
, Options(..)
, defaultOptions
, RepOptions(..)
, defaultRepOptions
, KindSigOptions
, defaultKindSigOptions
, EmptyCaseOptions
, defaultEmptyCaseOptions
, deriveAll0Options
, deriveAll1Options
, deriveAll0And1Options
, deriveRepresentable0Options
, deriveRepresentable1Options
, deriveRep0Options
, deriveRep1Options
, makeFrom0Options
, makeTo0Options
, makeFrom1Options
, makeTo1Options
) where
import Control.Monad ((>=>), unless, when)
import qualified Data.Map as Map (empty, fromList)
import Generics.Deriving.TH.Internal
#if MIN_VERSION_base(4,9,0)
import Generics.Deriving.TH.Post4_9
#else
import Generics.Deriving.TH.Pre4_9
#endif
import Language.Haskell.TH.Datatype
import Language.Haskell.TH.Datatype.TyVarBndr
import Language.Haskell.TH.Lib
import Language.Haskell.TH
data Options = Options
{ Options -> RepOptions
repOptions :: RepOptions
, Options -> KindSigOptions
kindSigOptions :: KindSigOptions
, Options -> KindSigOptions
emptyCaseOptions :: EmptyCaseOptions
} deriving (Options -> Options -> KindSigOptions
(Options -> Options -> KindSigOptions)
-> (Options -> Options -> KindSigOptions) -> Eq Options
forall a.
(a -> a -> KindSigOptions) -> (a -> a -> KindSigOptions) -> Eq a
$c== :: Options -> Options -> KindSigOptions
== :: Options -> Options -> KindSigOptions
$c/= :: Options -> Options -> KindSigOptions
/= :: Options -> Options -> KindSigOptions
Eq, Eq Options
Eq Options =>
(Options -> Options -> Ordering)
-> (Options -> Options -> KindSigOptions)
-> (Options -> Options -> KindSigOptions)
-> (Options -> Options -> KindSigOptions)
-> (Options -> Options -> KindSigOptions)
-> (Options -> Options -> Options)
-> (Options -> Options -> Options)
-> Ord Options
Options -> Options -> KindSigOptions
Options -> Options -> Ordering
Options -> Options -> Options
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> KindSigOptions)
-> (a -> a -> KindSigOptions)
-> (a -> a -> KindSigOptions)
-> (a -> a -> KindSigOptions)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Options -> Options -> Ordering
compare :: Options -> Options -> Ordering
$c< :: Options -> Options -> KindSigOptions
< :: Options -> Options -> KindSigOptions
$c<= :: Options -> Options -> KindSigOptions
<= :: Options -> Options -> KindSigOptions
$c> :: Options -> Options -> KindSigOptions
> :: Options -> Options -> KindSigOptions
$c>= :: Options -> Options -> KindSigOptions
>= :: Options -> Options -> KindSigOptions
$cmax :: Options -> Options -> Options
max :: Options -> Options -> Options
$cmin :: Options -> Options -> Options
min :: Options -> Options -> Options
Ord, ReadPrec [Options]
ReadPrec Options
Int -> ReadS Options
ReadS [Options]
(Int -> ReadS Options)
-> ReadS [Options]
-> ReadPrec Options
-> ReadPrec [Options]
-> Read Options
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Options
readsPrec :: Int -> ReadS Options
$creadList :: ReadS [Options]
readList :: ReadS [Options]
$creadPrec :: ReadPrec Options
readPrec :: ReadPrec Options
$creadListPrec :: ReadPrec [Options]
readListPrec :: ReadPrec [Options]
Read, Int -> Options -> ShowS
[Options] -> ShowS
Options -> String
(Int -> Options -> ShowS)
-> (Options -> String) -> ([Options] -> ShowS) -> Show Options
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Options -> ShowS
showsPrec :: Int -> Options -> ShowS
$cshow :: Options -> String
show :: Options -> String
$cshowList :: [Options] -> ShowS
showList :: [Options] -> ShowS
Show)
defaultOptions :: Options
defaultOptions :: Options
defaultOptions = Options
{ repOptions :: RepOptions
repOptions = RepOptions
defaultRepOptions
, kindSigOptions :: KindSigOptions
kindSigOptions = KindSigOptions
defaultKindSigOptions
, emptyCaseOptions :: KindSigOptions
emptyCaseOptions = KindSigOptions
defaultEmptyCaseOptions
}
data RepOptions = InlineRep
| TypeSynonymRep
deriving (RepOptions -> RepOptions -> KindSigOptions
(RepOptions -> RepOptions -> KindSigOptions)
-> (RepOptions -> RepOptions -> KindSigOptions) -> Eq RepOptions
forall a.
(a -> a -> KindSigOptions) -> (a -> a -> KindSigOptions) -> Eq a
$c== :: RepOptions -> RepOptions -> KindSigOptions
== :: RepOptions -> RepOptions -> KindSigOptions
$c/= :: RepOptions -> RepOptions -> KindSigOptions
/= :: RepOptions -> RepOptions -> KindSigOptions
Eq, Eq RepOptions
Eq RepOptions =>
(RepOptions -> RepOptions -> Ordering)
-> (RepOptions -> RepOptions -> KindSigOptions)
-> (RepOptions -> RepOptions -> KindSigOptions)
-> (RepOptions -> RepOptions -> KindSigOptions)
-> (RepOptions -> RepOptions -> KindSigOptions)
-> (RepOptions -> RepOptions -> RepOptions)
-> (RepOptions -> RepOptions -> RepOptions)
-> Ord RepOptions
RepOptions -> RepOptions -> KindSigOptions
RepOptions -> RepOptions -> Ordering
RepOptions -> RepOptions -> RepOptions
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> KindSigOptions)
-> (a -> a -> KindSigOptions)
-> (a -> a -> KindSigOptions)
-> (a -> a -> KindSigOptions)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RepOptions -> RepOptions -> Ordering
compare :: RepOptions -> RepOptions -> Ordering
$c< :: RepOptions -> RepOptions -> KindSigOptions
< :: RepOptions -> RepOptions -> KindSigOptions
$c<= :: RepOptions -> RepOptions -> KindSigOptions
<= :: RepOptions -> RepOptions -> KindSigOptions
$c> :: RepOptions -> RepOptions -> KindSigOptions
> :: RepOptions -> RepOptions -> KindSigOptions
$c>= :: RepOptions -> RepOptions -> KindSigOptions
>= :: RepOptions -> RepOptions -> KindSigOptions
$cmax :: RepOptions -> RepOptions -> RepOptions
max :: RepOptions -> RepOptions -> RepOptions
$cmin :: RepOptions -> RepOptions -> RepOptions
min :: RepOptions -> RepOptions -> RepOptions
Ord, ReadPrec [RepOptions]
ReadPrec RepOptions
Int -> ReadS RepOptions
ReadS [RepOptions]
(Int -> ReadS RepOptions)
-> ReadS [RepOptions]
-> ReadPrec RepOptions
-> ReadPrec [RepOptions]
-> Read RepOptions
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RepOptions
readsPrec :: Int -> ReadS RepOptions
$creadList :: ReadS [RepOptions]
readList :: ReadS [RepOptions]
$creadPrec :: ReadPrec RepOptions
readPrec :: ReadPrec RepOptions
$creadListPrec :: ReadPrec [RepOptions]
readListPrec :: ReadPrec [RepOptions]
Read, Int -> RepOptions -> ShowS
[RepOptions] -> ShowS
RepOptions -> String
(Int -> RepOptions -> ShowS)
-> (RepOptions -> String)
-> ([RepOptions] -> ShowS)
-> Show RepOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RepOptions -> ShowS
showsPrec :: Int -> RepOptions -> ShowS
$cshow :: RepOptions -> String
show :: RepOptions -> String
$cshowList :: [RepOptions] -> ShowS
showList :: [RepOptions] -> ShowS
Show)
defaultRepOptions :: RepOptions
defaultRepOptions :: RepOptions
defaultRepOptions = RepOptions
InlineRep
type KindSigOptions = Bool
defaultKindSigOptions :: KindSigOptions
defaultKindSigOptions :: KindSigOptions
defaultKindSigOptions = KindSigOptions
True
type EmptyCaseOptions = Bool
defaultEmptyCaseOptions :: EmptyCaseOptions
defaultEmptyCaseOptions :: KindSigOptions
defaultEmptyCaseOptions = KindSigOptions
False
deriveAll :: Name -> Q [Dec]
deriveAll :: Name -> Q [Dec]
deriveAll = Name -> Q [Dec]
deriveAll0
deriveAll0 :: Name -> Q [Dec]
deriveAll0 :: Name -> Q [Dec]
deriveAll0 = Options -> Name -> Q [Dec]
deriveAll0Options Options
defaultOptions
deriveAll0Options :: Options -> Name -> Q [Dec]
deriveAll0Options :: Options -> Name -> Q [Dec]
deriveAll0Options = KindSigOptions -> KindSigOptions -> Options -> Name -> Q [Dec]
deriveAllCommon KindSigOptions
True KindSigOptions
False
deriveAll1 :: Name -> Q [Dec]
deriveAll1 :: Name -> Q [Dec]
deriveAll1 = Options -> Name -> Q [Dec]
deriveAll1Options Options
defaultOptions
deriveAll1Options :: Options -> Name -> Q [Dec]
deriveAll1Options :: Options -> Name -> Q [Dec]
deriveAll1Options = KindSigOptions -> KindSigOptions -> Options -> Name -> Q [Dec]
deriveAllCommon KindSigOptions
False KindSigOptions
True
deriveAll0And1 :: Name -> Q [Dec]
deriveAll0And1 :: Name -> Q [Dec]
deriveAll0And1 = Options -> Name -> Q [Dec]
deriveAll0And1Options Options
defaultOptions
deriveAll0And1Options :: Options -> Name -> Q [Dec]
deriveAll0And1Options :: Options -> Name -> Q [Dec]
deriveAll0And1Options = KindSigOptions -> KindSigOptions -> Options -> Name -> Q [Dec]
deriveAllCommon KindSigOptions
True KindSigOptions
True
deriveAllCommon :: Bool -> Bool -> Options -> Name -> Q [Dec]
deriveAllCommon :: KindSigOptions -> KindSigOptions -> Options -> Name -> Q [Dec]
deriveAllCommon KindSigOptions
generic KindSigOptions
generic1 Options
opts Name
n = do
[Dec]
a <- Name -> Q [Dec]
deriveMeta Name
n
[Dec]
b <- if KindSigOptions
generic
then GenericClass -> Options -> Name -> Q [Dec]
deriveRepresentableCommon GenericClass
Generic Options
opts Name
n
else [Dec] -> Q [Dec]
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return []
[Dec]
c <- if KindSigOptions
generic1
then GenericClass -> Options -> Name -> Q [Dec]
deriveRepresentableCommon GenericClass
Generic1 Options
opts Name
n
else [Dec] -> Q [Dec]
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return []
[Dec] -> Q [Dec]
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Dec]
a [Dec] -> [Dec] -> [Dec]
forall a. [a] -> [a] -> [a]
++ [Dec]
b [Dec] -> [Dec] -> [Dec]
forall a. [a] -> [a] -> [a]
++ [Dec]
c)
deriveRepresentable0 :: Name -> Q [Dec]
deriveRepresentable0 :: Name -> Q [Dec]
deriveRepresentable0 = Options -> Name -> Q [Dec]
deriveRepresentable0Options Options
defaultOptions
deriveRepresentable0Options :: Options -> Name -> Q [Dec]
deriveRepresentable0Options :: Options -> Name -> Q [Dec]
deriveRepresentable0Options = GenericClass -> Options -> Name -> Q [Dec]
deriveRepresentableCommon GenericClass
Generic
deriveRepresentable1 :: Name -> Q [Dec]
deriveRepresentable1 :: Name -> Q [Dec]
deriveRepresentable1 = Options -> Name -> Q [Dec]
deriveRepresentable1Options Options
defaultOptions
deriveRepresentable1Options :: Options -> Name -> Q [Dec]
deriveRepresentable1Options :: Options -> Name -> Q [Dec]
deriveRepresentable1Options = GenericClass -> Options -> Name -> Q [Dec]
deriveRepresentableCommon GenericClass
Generic1
deriveRepresentableCommon :: GenericClass -> Options -> Name -> Q [Dec]
deriveRepresentableCommon :: GenericClass -> Options -> Name -> Q [Dec]
deriveRepresentableCommon GenericClass
gClass Options
opts Name
n = do
[Dec]
rep <- if Options -> RepOptions
repOptions Options
opts RepOptions -> RepOptions -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== RepOptions
InlineRep
then [Dec] -> Q [Dec]
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return []
else GenericClass -> KindSigOptions -> Name -> Q [Dec]
deriveRepCommon GenericClass
gClass (Options -> KindSigOptions
kindSigOptions Options
opts) Name
n
[Dec]
inst <- GenericClass -> Options -> Name -> Q [Dec]
deriveInst GenericClass
gClass Options
opts Name
n
[Dec] -> Q [Dec]
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Dec]
rep [Dec] -> [Dec] -> [Dec]
forall a. [a] -> [a] -> [a]
++ [Dec]
inst)
deriveRep0 :: Name -> Q [Dec]
deriveRep0 :: Name -> Q [Dec]
deriveRep0 = KindSigOptions -> Name -> Q [Dec]
deriveRep0Options KindSigOptions
defaultKindSigOptions
deriveRep0Options :: KindSigOptions -> Name -> Q [Dec]
deriveRep0Options :: KindSigOptions -> Name -> Q [Dec]
deriveRep0Options = GenericClass -> KindSigOptions -> Name -> Q [Dec]
deriveRepCommon GenericClass
Generic
deriveRep1 :: Name -> Q [Dec]
deriveRep1 :: Name -> Q [Dec]
deriveRep1 = KindSigOptions -> Name -> Q [Dec]
deriveRep1Options KindSigOptions
defaultKindSigOptions
deriveRep1Options :: KindSigOptions -> Name -> Q [Dec]
deriveRep1Options :: KindSigOptions -> Name -> Q [Dec]
deriveRep1Options = GenericClass -> KindSigOptions -> Name -> Q [Dec]
deriveRepCommon GenericClass
Generic1
deriveRepCommon :: GenericClass -> KindSigOptions -> Name -> Q [Dec]
deriveRepCommon :: GenericClass -> KindSigOptions -> Name -> Q [Dec]
deriveRepCommon GenericClass
gClass KindSigOptions
useKindSigs Name
n = do
Either String (Name, [Type], [ConstructorInfo], DatatypeVariant_)
i <- Name
-> Q (Either
String (Name, [Type], [ConstructorInfo], DatatypeVariant_))
reifyDataInfo Name
n
let (Name
name, [Type]
instTys, [ConstructorInfo]
cons, DatatypeVariant_
dv) = (String -> (Name, [Type], [ConstructorInfo], DatatypeVariant_))
-> ((Name, [Type], [ConstructorInfo], DatatypeVariant_)
-> (Name, [Type], [ConstructorInfo], DatatypeVariant_))
-> Either
String (Name, [Type], [ConstructorInfo], DatatypeVariant_)
-> (Name, [Type], [ConstructorInfo], DatatypeVariant_)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> (Name, [Type], [ConstructorInfo], DatatypeVariant_)
forall a. HasCallStack => String -> a
error (Name, [Type], [ConstructorInfo], DatatypeVariant_)
-> (Name, [Type], [ConstructorInfo], DatatypeVariant_)
forall a. a -> a
id Either String (Name, [Type], [ConstructorInfo], DatatypeVariant_)
i
gt :: GenericTvbs
gt = GenericClass -> [Type] -> GenericTvbs
mkGenericTvbs GenericClass
gClass [Type]
instTys
!(Type, Type)
_ <- GenericClass -> KindSigOptions -> Name -> [Type] -> Q (Type, Type)
buildTypeInstance GenericClass
gClass KindSigOptions
useKindSigs Name
name [Type]
instTys
let tySynVars :: [TyVarBndrUnit]
tySynVars = GenericTvbs -> [TyVarBndrUnit]
genericInitTvbs GenericTvbs
gt
tySynVars' :: [TyVarBndrUnit]
tySynVars' = if KindSigOptions
useKindSigs
then [TyVarBndrUnit]
tySynVars
else (TyVarBndrUnit -> TyVarBndrUnit)
-> [TyVarBndrUnit] -> [TyVarBndrUnit]
forall a b. (a -> b) -> [a] -> [b]
map TyVarBndrUnit -> TyVarBndrUnit
unKindedTV [TyVarBndrUnit]
tySynVars
(Dec -> [Dec]) -> Q Dec -> Q [Dec]
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Dec -> [Dec] -> [Dec]
forall a. a -> [a] -> [a]
:[]) (Q Dec -> Q [Dec]) -> Q Dec -> Q [Dec]
forall a b. (a -> b) -> a -> b
$ Name -> [TyVarBndrUnit] -> Q Type -> Q Dec
forall (m :: * -> *).
Quote m =>
Name -> [TyVarBndrUnit] -> m Type -> m Dec
tySynD (GenericClass -> DatatypeVariant_ -> Name -> Name
genRepName GenericClass
gClass DatatypeVariant_
dv Name
name)
(() -> [TyVarBndrUnit] -> [TyVarBndrUnit]
forall newFlag oldFlag.
newFlag -> [TyVarBndr_ oldFlag] -> [TyVarBndr_ newFlag]
changeTVFlags ()
bndrReq [TyVarBndrUnit]
tySynVars')
(GenericTvbs
-> DatatypeVariant_
-> Name
-> TypeSubst
-> [ConstructorInfo]
-> Q Type
repType GenericTvbs
gt DatatypeVariant_
dv Name
name TypeSubst
forall k a. Map k a
Map.empty [ConstructorInfo]
cons)
deriveInst :: GenericClass -> Options -> Name -> Q [Dec]
deriveInst :: GenericClass -> Options -> Name -> Q [Dec]
deriveInst GenericClass
Generic = Name
-> Name
-> GenericClass
-> Name
-> Name
-> Options
-> Name
-> Q [Dec]
deriveInstCommon Name
genericTypeName Name
repTypeName GenericClass
Generic Name
fromValName Name
toValName
deriveInst GenericClass
Generic1 = Name
-> Name
-> GenericClass
-> Name
-> Name
-> Options
-> Name
-> Q [Dec]
deriveInstCommon Name
generic1TypeName Name
rep1TypeName GenericClass
Generic1 Name
from1ValName Name
to1ValName
deriveInstCommon :: Name
-> Name
-> GenericClass
-> Name
-> Name
-> Options
-> Name
-> Q [Dec]
deriveInstCommon :: Name
-> Name
-> GenericClass
-> Name
-> Name
-> Options
-> Name
-> Q [Dec]
deriveInstCommon Name
genericName Name
repName GenericClass
gClass Name
fromName Name
toName Options
opts Name
n = do
Either String (Name, [Type], [ConstructorInfo], DatatypeVariant_)
i <- Name
-> Q (Either
String (Name, [Type], [ConstructorInfo], DatatypeVariant_))
reifyDataInfo Name
n
let (Name
name, [Type]
instTys, [ConstructorInfo]
cons, DatatypeVariant_
dv) = (String -> (Name, [Type], [ConstructorInfo], DatatypeVariant_))
-> ((Name, [Type], [ConstructorInfo], DatatypeVariant_)
-> (Name, [Type], [ConstructorInfo], DatatypeVariant_))
-> Either
String (Name, [Type], [ConstructorInfo], DatatypeVariant_)
-> (Name, [Type], [ConstructorInfo], DatatypeVariant_)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> (Name, [Type], [ConstructorInfo], DatatypeVariant_)
forall a. HasCallStack => String -> a
error (Name, [Type], [ConstructorInfo], DatatypeVariant_)
-> (Name, [Type], [ConstructorInfo], DatatypeVariant_)
forall a. a -> a
id Either String (Name, [Type], [ConstructorInfo], DatatypeVariant_)
i
gt :: GenericTvbs
gt = GenericClass -> [Type] -> GenericTvbs
mkGenericTvbs GenericClass
gClass [Type]
instTys
useKindSigs :: KindSigOptions
useKindSigs = Options -> KindSigOptions
kindSigOptions Options
opts
!(Type
origTy, Type
origKind) <- GenericClass -> KindSigOptions -> Name -> [Type] -> Q (Type, Type)
buildTypeInstance GenericClass
gClass KindSigOptions
useKindSigs Name
name [Type]
instTys
Type
tyInsRHS <- if Options -> RepOptions
repOptions Options
opts RepOptions -> RepOptions -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== RepOptions
InlineRep
then GenericTvbs
-> DatatypeVariant_
-> Name
-> TypeSubst
-> [ConstructorInfo]
-> Q Type
repType GenericTvbs
gt DatatypeVariant_
dv Name
name TypeSubst
forall k a. Map k a
Map.empty [ConstructorInfo]
cons
else GenericClass -> DatatypeVariant_ -> Name -> Type -> Q Type
makeRepTySynApp GenericClass
gClass DatatypeVariant_
dv Name
name Type
origTy
let origSigTy :: Type
origSigTy = if KindSigOptions
useKindSigs
then Type -> Type -> Type
SigT Type
origTy Type
origKind
else Type
origTy
Dec
tyIns <- Name -> Maybe [Q TyVarBndrUnit] -> [Q Type] -> Q Type -> Q Dec
tySynInstDCompat Name
repName Maybe [Q TyVarBndrUnit]
forall a. Maybe a
Nothing [Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
origSigTy] (Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
tyInsRHS)
let ecOptions :: KindSigOptions
ecOptions = Options -> KindSigOptions
emptyCaseOptions Options
opts
mkBody :: (GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match)
-> [Q Clause]
mkBody GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match
maker = [[Q Pat] -> Q Body -> [Q Dec] -> Q Clause
forall (m :: * -> *).
Quote m =>
[m Pat] -> m Body -> [m Dec] -> m Clause
clause []
(Q Exp -> Q Body
forall (m :: * -> *). Quote m => m Exp -> m Body
normalB (Q Exp -> Q Body) -> Q Exp -> Q Body
forall a b. (a -> b) -> a -> b
$
Q Match -> Q Exp
mkCaseExp (Q Match -> Q Exp) -> Q Match -> Q Exp
forall a b. (a -> b) -> a -> b
$
GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match
maker GenericTvbs
gt KindSigOptions
ecOptions Name
name [ConstructorInfo]
cons)
[]]
fcs :: [Q Clause]
fcs = (GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match)
-> [Q Clause]
mkBody GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match
mkFrom
tcs :: [Q Clause]
tcs = (GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match)
-> [Q Clause]
mkBody GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match
mkTo
inline_pragmas :: [Q Dec]
inline_pragmas
| [ConstructorInfo] -> KindSigOptions
inlining_useful [ConstructorInfo]
cons
#if MIN_VERSION_template_haskell(2,7,0)
= (Name -> Q Dec) -> [Name] -> [Q Dec]
forall a b. (a -> b) -> [a] -> [b]
map (\Name
fun_name ->
Name -> Inline -> RuleMatch -> Phases -> Q Dec
forall (m :: * -> *).
Quote m =>
Name -> Inline -> RuleMatch -> Phases -> m Dec
pragInlD Name
fun_name
# if MIN_VERSION_template_haskell(2,8,0)
Inline
Inline RuleMatch
FunLike (Int -> Phases
FromPhase Int
1)
# else
(inlineSpecPhase True False True 1)
# endif
) [Name
fromName, Name
toName]
#else
= []
#endif
| KindSigOptions
otherwise
= []
(Dec -> [Dec]) -> Q Dec -> Q [Dec]
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Dec -> [Dec] -> [Dec]
forall a. a -> [a] -> [a]
:[]) (Q Dec -> Q [Dec]) -> Q Dec -> Q [Dec]
forall a b. (a -> b) -> a -> b
$
Q [Type] -> Q Type -> [Q Dec] -> Q Dec
forall (m :: * -> *).
Quote m =>
m [Type] -> m Type -> [m Dec] -> m Dec
instanceD ([Q Type] -> Q [Type]
forall (m :: * -> *). Quote m => [m Type] -> m [Type]
cxt []) (Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT Name
genericName Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
origSigTy)
([Q Dec]
inline_pragmas [Q Dec] -> [Q Dec] -> [Q Dec]
forall a. [a] -> [a] -> [a]
++ [Dec -> Q Dec
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Dec
tyIns, Name -> [Q Clause] -> Q Dec
forall (m :: * -> *). Quote m => Name -> [m Clause] -> m Dec
funD Name
fromName [Q Clause]
fcs, Name -> [Q Clause] -> Q Dec
forall (m :: * -> *). Quote m => Name -> [m Clause] -> m Dec
funD Name
toName [Q Clause]
tcs])
where
inlining_useful :: [ConstructorInfo] -> KindSigOptions
inlining_useful [ConstructorInfo]
cons
| Int
ncons Int -> Int -> KindSigOptions
forall a. Ord a => a -> a -> KindSigOptions
<= Int
1 = KindSigOptions
True
| Int
ncons Int -> Int -> KindSigOptions
forall a. Ord a => a -> a -> KindSigOptions
<= Int
4 = Int
max_fields Int -> Int -> KindSigOptions
forall a. Ord a => a -> a -> KindSigOptions
<= Int
5
| Int
ncons Int -> Int -> KindSigOptions
forall a. Ord a => a -> a -> KindSigOptions
<= Int
8 = Int
max_fields Int -> Int -> KindSigOptions
forall a. Ord a => a -> a -> KindSigOptions
<= Int
2
| Int
ncons Int -> Int -> KindSigOptions
forall a. Ord a => a -> a -> KindSigOptions
<= Int
16 = Int
max_fields Int -> Int -> KindSigOptions
forall a. Ord a => a -> a -> KindSigOptions
<= Int
1
| Int
ncons Int -> Int -> KindSigOptions
forall a. Ord a => a -> a -> KindSigOptions
<= Int
24 = Int
max_fields Int -> Int -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Int
0
| KindSigOptions
otherwise = KindSigOptions
False
where
ncons :: Int
ncons = [ConstructorInfo] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ConstructorInfo]
cons
max_fields :: Int
max_fields = [Int] -> Int
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (ConstructorInfo -> Int) -> [ConstructorInfo] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ([Type] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Type] -> Int)
-> (ConstructorInfo -> [Type]) -> ConstructorInfo -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstructorInfo -> [Type]
constructorFields) [ConstructorInfo]
cons
makeRep0Inline :: Name -> Q Type -> Q Type
makeRep0Inline :: Name -> Q Type -> Q Type
makeRep0Inline Name
n = GenericClass -> RepOptions -> Name -> Maybe (Q Type) -> Q Type
makeRepCommon GenericClass
Generic RepOptions
InlineRep Name
n (Maybe (Q Type) -> Q Type)
-> (Q Type -> Maybe (Q Type)) -> Q Type -> Q Type
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Q Type -> Maybe (Q Type)
forall a. a -> Maybe a
Just
makeRep1Inline :: Name -> Q Type -> Q Type
makeRep1Inline :: Name -> Q Type -> Q Type
makeRep1Inline Name
n = GenericClass -> RepOptions -> Name -> Maybe (Q Type) -> Q Type
makeRepCommon GenericClass
Generic1 RepOptions
InlineRep Name
n (Maybe (Q Type) -> Q Type)
-> (Q Type -> Maybe (Q Type)) -> Q Type -> Q Type
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Q Type -> Maybe (Q Type)
forall a. a -> Maybe a
Just
makeRep0 :: Name -> Q Type
makeRep0 :: Name -> Q Type
makeRep0 Name
n = GenericClass -> RepOptions -> Name -> Maybe (Q Type) -> Q Type
makeRepCommon GenericClass
Generic RepOptions
TypeSynonymRep Name
n Maybe (Q Type)
forall a. Maybe a
Nothing
makeRep1 :: Name -> Q Type
makeRep1 :: Name -> Q Type
makeRep1 Name
n = GenericClass -> RepOptions -> Name -> Maybe (Q Type) -> Q Type
makeRepCommon GenericClass
Generic1 RepOptions
TypeSynonymRep Name
n Maybe (Q Type)
forall a. Maybe a
Nothing
makeRep0FromType :: Name -> Q Type -> Q Type
makeRep0FromType :: Name -> Q Type -> Q Type
makeRep0FromType Name
n = GenericClass -> RepOptions -> Name -> Maybe (Q Type) -> Q Type
makeRepCommon GenericClass
Generic RepOptions
TypeSynonymRep Name
n (Maybe (Q Type) -> Q Type)
-> (Q Type -> Maybe (Q Type)) -> Q Type -> Q Type
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Q Type -> Maybe (Q Type)
forall a. a -> Maybe a
Just
makeRep1FromType :: Name -> Q Type -> Q Type
makeRep1FromType :: Name -> Q Type -> Q Type
makeRep1FromType Name
n = GenericClass -> RepOptions -> Name -> Maybe (Q Type) -> Q Type
makeRepCommon GenericClass
Generic1 RepOptions
TypeSynonymRep Name
n (Maybe (Q Type) -> Q Type)
-> (Q Type -> Maybe (Q Type)) -> Q Type -> Q Type
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Q Type -> Maybe (Q Type)
forall a. a -> Maybe a
Just
makeRepCommon :: GenericClass
-> RepOptions
-> Name
-> Maybe (Q Type)
-> Q Type
makeRepCommon :: GenericClass -> RepOptions -> Name -> Maybe (Q Type) -> Q Type
makeRepCommon GenericClass
gClass RepOptions
repOpts Name
n Maybe (Q Type)
mbQTy = do
Either String (Name, [Type], [ConstructorInfo], DatatypeVariant_)
i <- Name
-> Q (Either
String (Name, [Type], [ConstructorInfo], DatatypeVariant_))
reifyDataInfo Name
n
let (Name
name, [Type]
instTys, [ConstructorInfo]
cons, DatatypeVariant_
dv) = (String -> (Name, [Type], [ConstructorInfo], DatatypeVariant_))
-> ((Name, [Type], [ConstructorInfo], DatatypeVariant_)
-> (Name, [Type], [ConstructorInfo], DatatypeVariant_))
-> Either
String (Name, [Type], [ConstructorInfo], DatatypeVariant_)
-> (Name, [Type], [ConstructorInfo], DatatypeVariant_)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> (Name, [Type], [ConstructorInfo], DatatypeVariant_)
forall a. HasCallStack => String -> a
error (Name, [Type], [ConstructorInfo], DatatypeVariant_)
-> (Name, [Type], [ConstructorInfo], DatatypeVariant_)
forall a. a -> a
id Either String (Name, [Type], [ConstructorInfo], DatatypeVariant_)
i
gt :: GenericTvbs
gt = GenericClass -> [Type] -> GenericTvbs
mkGenericTvbs GenericClass
gClass [Type]
instTys
!(Type, Type)
_ <- GenericClass -> KindSigOptions -> Name -> [Type] -> Q (Type, Type)
buildTypeInstance GenericClass
gClass KindSigOptions
False Name
name [Type]
instTys
case (Maybe (Q Type)
mbQTy, RepOptions
repOpts) of
(Just Q Type
qTy, RepOptions
TypeSynonymRep) -> Q Type
qTy Q Type -> (Type -> Q Type) -> Q Type
forall a b. Q a -> (a -> Q b) -> Q b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= GenericClass -> DatatypeVariant_ -> Name -> Type -> Q Type
makeRepTySynApp GenericClass
gClass DatatypeVariant_
dv Name
name
(Just Q Type
qTy, RepOptions
InlineRep) -> Q Type
qTy Q Type -> (Type -> Q Type) -> Q Type
forall a b. Q a -> (a -> Q b) -> Q b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= GenericTvbs
-> DatatypeVariant_ -> Name -> [ConstructorInfo] -> Type -> Q Type
makeRepInline GenericTvbs
gt DatatypeVariant_
dv Name
name [ConstructorInfo]
cons
(Maybe (Q Type)
Nothing, RepOptions
TypeSynonymRep) -> Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT (Name -> Q Type) -> Name -> Q Type
forall a b. (a -> b) -> a -> b
$ GenericClass -> DatatypeVariant_ -> Name -> Name
genRepName GenericClass
gClass DatatypeVariant_
dv Name
name
(Maybe (Q Type)
Nothing, RepOptions
InlineRep) -> String -> Q Type
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"makeRepCommon"
makeRepInline :: GenericTvbs
-> DatatypeVariant_
-> Name
-> [ConstructorInfo]
-> Type
-> Q Type
makeRepInline :: GenericTvbs
-> DatatypeVariant_ -> Name -> [ConstructorInfo] -> Type -> Q Type
makeRepInline GenericTvbs
gt DatatypeVariant_
dv Name
name [ConstructorInfo]
cons Type
ty = do
let instVars :: [TyVarBndrUnit]
instVars = [Type] -> [TyVarBndrUnit]
freeVariablesWellScoped [Type
ty]
tySynVars :: [TyVarBndrUnit]
tySynVars = GenericTvbs -> [TyVarBndrUnit]
genericInitTvbs GenericTvbs
gt
typeSubst :: TypeSubst
typeSubst :: TypeSubst
typeSubst = [(Name, Type)] -> TypeSubst
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Name, Type)] -> TypeSubst) -> [(Name, Type)] -> TypeSubst
forall a b. (a -> b) -> a -> b
$
[Name] -> [Type] -> [(Name, Type)]
forall a b. [a] -> [b] -> [(a, b)]
zip ((TyVarBndrUnit -> Name) -> [TyVarBndrUnit] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map TyVarBndrUnit -> Name
forall flag. TyVarBndr_ flag -> Name
tvName [TyVarBndrUnit]
tySynVars)
((TyVarBndrUnit -> Type) -> [TyVarBndrUnit] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map (Name -> Type
VarT (Name -> Type) -> (TyVarBndrUnit -> Name) -> TyVarBndrUnit -> Type
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyVarBndrUnit -> Name
forall flag. TyVarBndr_ flag -> Name
tvName) [TyVarBndrUnit]
instVars)
GenericTvbs
-> DatatypeVariant_
-> Name
-> TypeSubst
-> [ConstructorInfo]
-> Q Type
repType GenericTvbs
gt DatatypeVariant_
dv Name
name TypeSubst
typeSubst [ConstructorInfo]
cons
makeRepTySynApp :: GenericClass -> DatatypeVariant_ -> Name
-> Type -> Q Type
makeRepTySynApp :: GenericClass -> DatatypeVariant_ -> Name -> Type -> Q Type
makeRepTySynApp GenericClass
gClass DatatypeVariant_
dv Name
name Type
ty =
let instTvbs :: [TyVarBndrUnit]
instTvbs = (TyVarBndrUnit -> TyVarBndrUnit)
-> [TyVarBndrUnit] -> [TyVarBndrUnit]
forall a b. (a -> b) -> [a] -> [b]
map TyVarBndrUnit -> TyVarBndrUnit
unKindedTV ([TyVarBndrUnit] -> [TyVarBndrUnit])
-> [TyVarBndrUnit] -> [TyVarBndrUnit]
forall a b. (a -> b) -> a -> b
$ [Type] -> [TyVarBndrUnit]
freeVariablesWellScoped [Type
ty]
in Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return (Type -> Q Type) -> Type -> Q Type
forall a b. (a -> b) -> a -> b
$ Name -> [TyVarBndrUnit] -> Type
forall flag. Name -> [TyVarBndr_ flag] -> Type
applyTyToTvbs (GenericClass -> DatatypeVariant_ -> Name -> Name
genRepName GenericClass
gClass DatatypeVariant_
dv Name
name) [TyVarBndrUnit]
instTvbs
makeFrom :: Name -> Q Exp
makeFrom :: Name -> Q Exp
makeFrom = Name -> Q Exp
makeFrom0
makeFrom0 :: Name -> Q Exp
makeFrom0 :: Name -> Q Exp
makeFrom0 = KindSigOptions -> Name -> Q Exp
makeFrom0Options KindSigOptions
defaultEmptyCaseOptions
makeFrom0Options :: EmptyCaseOptions -> Name -> Q Exp
makeFrom0Options :: KindSigOptions -> Name -> Q Exp
makeFrom0Options = (GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match)
-> GenericClass -> KindSigOptions -> Name -> Q Exp
makeFunCommon GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match
mkFrom GenericClass
Generic
makeTo :: Name -> Q Exp
makeTo :: Name -> Q Exp
makeTo = Name -> Q Exp
makeTo0
makeTo0 :: Name -> Q Exp
makeTo0 :: Name -> Q Exp
makeTo0 = KindSigOptions -> Name -> Q Exp
makeTo0Options KindSigOptions
defaultEmptyCaseOptions
makeTo0Options :: EmptyCaseOptions -> Name -> Q Exp
makeTo0Options :: KindSigOptions -> Name -> Q Exp
makeTo0Options = (GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match)
-> GenericClass -> KindSigOptions -> Name -> Q Exp
makeFunCommon GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match
mkTo GenericClass
Generic
makeFrom1 :: Name -> Q Exp
makeFrom1 :: Name -> Q Exp
makeFrom1 = KindSigOptions -> Name -> Q Exp
makeFrom1Options KindSigOptions
defaultEmptyCaseOptions
makeFrom1Options :: EmptyCaseOptions -> Name -> Q Exp
makeFrom1Options :: KindSigOptions -> Name -> Q Exp
makeFrom1Options = (GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match)
-> GenericClass -> KindSigOptions -> Name -> Q Exp
makeFunCommon GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match
mkFrom GenericClass
Generic1
makeTo1 :: Name -> Q Exp
makeTo1 :: Name -> Q Exp
makeTo1 = KindSigOptions -> Name -> Q Exp
makeTo1Options KindSigOptions
defaultEmptyCaseOptions
makeTo1Options :: EmptyCaseOptions -> Name -> Q Exp
makeTo1Options :: KindSigOptions -> Name -> Q Exp
makeTo1Options = (GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match)
-> GenericClass -> KindSigOptions -> Name -> Q Exp
makeFunCommon GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match
mkTo GenericClass
Generic1
makeFunCommon
:: (GenericTvbs -> EmptyCaseOptions -> Name -> [ConstructorInfo] -> Q Match)
-> GenericClass -> EmptyCaseOptions -> Name -> Q Exp
makeFunCommon :: (GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match)
-> GenericClass -> KindSigOptions -> Name -> Q Exp
makeFunCommon GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match
maker GenericClass
gClass KindSigOptions
ecOptions Name
n = do
Either String (Name, [Type], [ConstructorInfo], DatatypeVariant_)
i <- Name
-> Q (Either
String (Name, [Type], [ConstructorInfo], DatatypeVariant_))
reifyDataInfo Name
n
let (Name
name, [Type]
instTys, [ConstructorInfo]
cons, DatatypeVariant_
_) = (String -> (Name, [Type], [ConstructorInfo], DatatypeVariant_))
-> ((Name, [Type], [ConstructorInfo], DatatypeVariant_)
-> (Name, [Type], [ConstructorInfo], DatatypeVariant_))
-> Either
String (Name, [Type], [ConstructorInfo], DatatypeVariant_)
-> (Name, [Type], [ConstructorInfo], DatatypeVariant_)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> (Name, [Type], [ConstructorInfo], DatatypeVariant_)
forall a. HasCallStack => String -> a
error (Name, [Type], [ConstructorInfo], DatatypeVariant_)
-> (Name, [Type], [ConstructorInfo], DatatypeVariant_)
forall a. a -> a
id Either String (Name, [Type], [ConstructorInfo], DatatypeVariant_)
i
gt :: GenericTvbs
gt = GenericClass -> [Type] -> GenericTvbs
mkGenericTvbs GenericClass
gClass [Type]
instTys
GenericClass -> KindSigOptions -> Name -> [Type] -> Q (Type, Type)
buildTypeInstance GenericClass
gClass KindSigOptions
False Name
name [Type]
instTys
Q (Type, Type) -> Q Exp -> Q Exp
forall a b. a -> b -> b
`seq` Q Match -> Q Exp
mkCaseExp (GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match
maker GenericTvbs
gt KindSigOptions
ecOptions Name
name [ConstructorInfo]
cons)
genRepName :: GenericClass -> DatatypeVariant_
-> Name -> Name
genRepName :: GenericClass -> DatatypeVariant_ -> Name -> Name
genRepName GenericClass
gClass DatatypeVariant_
dv Name
n
= String -> Name
mkName
(String -> Name) -> ShowS -> String -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DatatypeVariant_ -> ShowS
showsDatatypeVariant DatatypeVariant_
dv
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String
"Rep" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (GenericClass -> Int
forall a. Enum a => a -> Int
fromEnum GenericClass
gClass)) String -> ShowS
forall a. [a] -> [a] -> [a]
++)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Name -> String
showNameQual Name
n String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"_") String -> ShowS
forall a. [a] -> [a] -> [a]
++)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
sanitizeName
(String -> Name) -> String -> Name
forall a b. (a -> b) -> a -> b
$ Name -> String
nameBase Name
n
repType :: GenericTvbs
-> DatatypeVariant_
-> Name
-> TypeSubst
-> [ConstructorInfo]
-> Q Type
repType :: GenericTvbs
-> DatatypeVariant_
-> Name
-> TypeSubst
-> [ConstructorInfo]
-> Q Type
repType GenericTvbs
gt DatatypeVariant_
dv Name
dt TypeSubst
typeSubst [ConstructorInfo]
cs =
Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT Name
d1TypeName Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` DatatypeVariant_ -> Name -> Q Type
mkMetaDataType DatatypeVariant_
dv Name
dt Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT`
(Q Type -> Q Type -> Q Type) -> Q Type -> [Q Type] -> Q Type
forall a. (a -> a -> a) -> a -> [a] -> a
foldBal Q Type -> Q Type -> Q Type
sum' (Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT Name
v1TypeName) ((ConstructorInfo -> Q Type) -> [ConstructorInfo] -> [Q Type]
forall a b. (a -> b) -> [a] -> [b]
map (GenericTvbs
-> DatatypeVariant_
-> Name
-> TypeSubst
-> ConstructorInfo
-> Q Type
repCon GenericTvbs
gt DatatypeVariant_
dv Name
dt TypeSubst
typeSubst) [ConstructorInfo]
cs)
where
sum' :: Q Type -> Q Type -> Q Type
sum' :: Q Type -> Q Type -> Q Type
sum' Q Type
a Q Type
b = Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT Name
sumTypeName Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Q Type
a Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Q Type
b
repCon :: GenericTvbs
-> DatatypeVariant_
-> Name
-> TypeSubst
-> ConstructorInfo
-> Q Type
repCon :: GenericTvbs
-> DatatypeVariant_
-> Name
-> TypeSubst
-> ConstructorInfo
-> Q Type
repCon GenericTvbs
gt DatatypeVariant_
dv Name
dt TypeSubst
typeSubst
(ConstructorInfo { constructorName :: ConstructorInfo -> Name
constructorName = Name
n
, constructorVars :: ConstructorInfo -> [TyVarBndrUnit]
constructorVars = [TyVarBndrUnit]
vars
, constructorContext :: ConstructorInfo -> [Type]
constructorContext = [Type]
ctxt
, constructorStrictness :: ConstructorInfo -> [FieldStrictness]
constructorStrictness = [FieldStrictness]
bangs
, constructorFields :: ConstructorInfo -> [Type]
constructorFields = [Type]
ts
, constructorVariant :: ConstructorInfo -> ConstructorVariant
constructorVariant = ConstructorVariant
cv
}) = do
Name -> [TyVarBndrUnit] -> [Type] -> Q ()
checkExistentialContext Name
n [TyVarBndrUnit]
vars [Type]
ctxt
let mbSelNames :: Maybe [Name]
mbSelNames = case ConstructorVariant
cv of
ConstructorVariant
NormalConstructor -> Maybe [Name]
forall a. Maybe a
Nothing
ConstructorVariant
InfixConstructor -> Maybe [Name]
forall a. Maybe a
Nothing
RecordConstructor [Name]
selNames -> [Name] -> Maybe [Name]
forall a. a -> Maybe a
Just [Name]
selNames
isRecord :: KindSigOptions
isRecord = case ConstructorVariant
cv of
ConstructorVariant
NormalConstructor -> KindSigOptions
False
ConstructorVariant
InfixConstructor -> KindSigOptions
False
RecordConstructor [Name]
_ -> KindSigOptions
True
isInfix :: KindSigOptions
isInfix = case ConstructorVariant
cv of
ConstructorVariant
NormalConstructor -> KindSigOptions
False
ConstructorVariant
InfixConstructor -> KindSigOptions
True
RecordConstructor [Name]
_ -> KindSigOptions
False
[SelStrictInfo]
ssis <- Name -> [FieldStrictness] -> Q [SelStrictInfo]
reifySelStrictInfo Name
n [FieldStrictness]
bangs
GenericTvbs
-> DatatypeVariant_
-> Name
-> Name
-> TypeSubst
-> Maybe [Name]
-> [SelStrictInfo]
-> [Type]
-> KindSigOptions
-> KindSigOptions
-> Q Type
repConWith GenericTvbs
gt DatatypeVariant_
dv Name
dt Name
n TypeSubst
typeSubst Maybe [Name]
mbSelNames [SelStrictInfo]
ssis [Type]
ts KindSigOptions
isRecord KindSigOptions
isInfix
repConWith :: GenericTvbs
-> DatatypeVariant_
-> Name
-> Name
-> TypeSubst
-> Maybe [Name]
-> [SelStrictInfo]
-> [Type]
-> Bool
-> Bool
-> Q Type
repConWith :: GenericTvbs
-> DatatypeVariant_
-> Name
-> Name
-> TypeSubst
-> Maybe [Name]
-> [SelStrictInfo]
-> [Type]
-> KindSigOptions
-> KindSigOptions
-> Q Type
repConWith GenericTvbs
gt DatatypeVariant_
dv Name
dt Name
n TypeSubst
typeSubst Maybe [Name]
mbSelNames [SelStrictInfo]
ssis [Type]
ts KindSigOptions
isRecord KindSigOptions
isInfix = do
let structureType :: Q Type
structureType :: Q Type
structureType = (Q Type -> Q Type -> Q Type) -> Q Type -> [Q Type] -> Q Type
forall a. (a -> a -> a) -> a -> [a] -> a
foldBal Q Type -> Q Type -> Q Type
prodT (Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT Name
u1TypeName) [Q Type]
f
f :: [Q Type]
f :: [Q Type]
f = case Maybe [Name]
mbSelNames of
Just [Name]
selNames -> (Name -> SelStrictInfo -> Type -> Q Type)
-> [Name] -> [SelStrictInfo] -> [Type] -> [Q Type]
forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 (GenericTvbs
-> DatatypeVariant_
-> Name
-> Name
-> TypeSubst
-> Maybe Name
-> SelStrictInfo
-> Type
-> Q Type
repField GenericTvbs
gt DatatypeVariant_
dv Name
dt Name
n TypeSubst
typeSubst (Maybe Name -> SelStrictInfo -> Type -> Q Type)
-> (Name -> Maybe Name) -> Name -> SelStrictInfo -> Type -> Q Type
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Maybe Name
forall a. a -> Maybe a
Just)
[Name]
selNames [SelStrictInfo]
ssis [Type]
ts
Maybe [Name]
Nothing -> (SelStrictInfo -> Type -> Q Type)
-> [SelStrictInfo] -> [Type] -> [Q Type]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (GenericTvbs
-> DatatypeVariant_
-> Name
-> Name
-> TypeSubst
-> Maybe Name
-> SelStrictInfo
-> Type
-> Q Type
repField GenericTvbs
gt DatatypeVariant_
dv Name
dt Name
n TypeSubst
typeSubst Maybe Name
forall a. Maybe a
Nothing)
[SelStrictInfo]
ssis [Type]
ts
Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT Name
c1TypeName
Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` DatatypeVariant_
-> Name -> Name -> KindSigOptions -> KindSigOptions -> Q Type
mkMetaConsType DatatypeVariant_
dv Name
dt Name
n KindSigOptions
isRecord KindSigOptions
isInfix
Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Q Type
structureType
prodT :: Q Type -> Q Type -> Q Type
prodT :: Q Type -> Q Type -> Q Type
prodT Q Type
a Q Type
b = Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT Name
productTypeName Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Q Type
a Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Q Type
b
repField :: GenericTvbs
-> DatatypeVariant_
-> Name
-> Name
-> TypeSubst
-> Maybe Name
-> SelStrictInfo
-> Type
-> Q Type
repField :: GenericTvbs
-> DatatypeVariant_
-> Name
-> Name
-> TypeSubst
-> Maybe Name
-> SelStrictInfo
-> Type
-> Q Type
repField GenericTvbs
gt DatatypeVariant_
dv Name
dt Name
ns TypeSubst
typeSubst Maybe Name
mbF SelStrictInfo
ssi Type
t =
Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT Name
s1TypeName
Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` DatatypeVariant_
-> Name -> Name -> Maybe Name -> SelStrictInfo -> Q Type
mkMetaSelType DatatypeVariant_
dv Name
dt Name
ns Maybe Name
mbF SelStrictInfo
ssi
Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` (GenericTvbs -> Type -> Q Type
repFieldArg GenericTvbs
gt (Type -> Q Type) -> Q Type -> Q Type
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Type -> Q Type
resolveTypeSynonyms Type
t'')
where
t', t'' :: Type
t' :: Type
t' = case GenericTvbs
gt of
Gen1{gen1LastTvbKindVar :: GenericTvbs -> Maybe Name
gen1LastTvbKindVar = Just Name
_kvName} ->
#if MIN_VERSION_base(4,10,0)
Type
t
#else
substNameWithKind _kvName starK t
#endif
GenericTvbs
_ -> Type
t
t'' :: Type
t'' = TypeSubst -> Type -> Type
forall a. TypeSubstitution a => TypeSubst -> a -> a
applySubstitution TypeSubst
typeSubst Type
t'
repFieldArg :: GenericTvbs -> Type -> Q Type
repFieldArg :: GenericTvbs -> Type -> Q Type
repFieldArg Gen0{} Type
t = Type -> Q Type
boxT Type
t
repFieldArg (Gen1{gen1LastTvbName :: GenericTvbs -> Name
gen1LastTvbName = Name
name}) (Type -> Type
dustOff -> Type
t0) =
Type -> Q (ArgRes Type)
go Type
t0 Q (ArgRes Type) -> (ArgRes Type -> Q Type) -> Q Type
forall a b. Q a -> (a -> Q b) -> Q b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ArgRes Type
res -> case ArgRes Type
res of
ArgRes Type
NoPar -> Type -> Q Type
boxT Type
t0
ArgRes KindSigOptions
_ Type
r -> Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
r
where
go :: Type -> Q (ArgRes Type)
go :: Type -> Q (ArgRes Type)
go ForallT{} = Q (ArgRes Type)
forall a. Q a
rankNError
#if MIN_VERSION_template_haskell(2,16,0)
go ForallVisT{} = Q (ArgRes Type)
forall a. Q a
rankNError
#endif
go (VarT Name
t) | Name
t Name -> Name -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Name
name = KindSigOptions -> Type -> ArgRes Type
forall a. KindSigOptions -> a -> ArgRes a
ArgRes KindSigOptions
True (Type -> ArgRes Type) -> Q Type -> Q (ArgRes Type)
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT Name
par1TypeName
go (AppT Type
f Type
x) = do
KindSigOptions -> Q () -> Q ()
forall (f :: * -> *).
Applicative f =>
KindSigOptions -> f () -> f ()
when (KindSigOptions -> KindSigOptions
not (Type
f Type -> Name -> KindSigOptions
`ground` Name
name)) Q ()
forall a. Q a
outOfPlaceTyVarError
ArgRes Type
mxr <- Type -> Q (ArgRes Type)
go (Type -> Type
dustOff Type
x)
case ArgRes Type
mxr of
ArgRes Type
NoPar -> ArgRes Type -> Q (ArgRes Type)
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ArgRes Type
forall a. ArgRes a
NoPar
ArgRes KindSigOptions
arg_is_param Type
xr -> do
KindSigOptions
itf <- Type -> Q KindSigOptions
isUnsaturatedType Type
f
KindSigOptions -> Q () -> Q ()
forall (f :: * -> *).
Applicative f =>
KindSigOptions -> f () -> f ()
when KindSigOptions
itf Q ()
forall a. Q a
typeFamilyApplicationError
KindSigOptions -> Type -> ArgRes Type
forall a. KindSigOptions -> a -> ArgRes a
ArgRes KindSigOptions
False (Type -> ArgRes Type) -> Q Type -> Q (ArgRes Type)
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
if KindSigOptions
arg_is_param
then
Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT Name
rec1TypeName Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
f
else
Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT Name
composeTypeName Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
f Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
xr
go Type
_ = ArgRes Type -> Q (ArgRes Type)
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ArgRes Type
forall a. ArgRes a
NoPar
data ArgRes a = NoPar | ArgRes !Bool a
boxT :: Type -> Q Type
boxT :: Type -> Q Type
boxT Type
ty = case Type -> Maybe (Name, Name, Name)
unboxedRepNames Type
ty of
Just (Name
boxTyName, Name
_, Name
_) -> Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT Name
boxTyName
Maybe (Name, Name, Name)
Nothing -> Name -> Q Type
forall (m :: * -> *). Quote m => Name -> m Type
conT Name
rec0TypeName Q Type -> Q Type -> Q Type
forall (m :: * -> *). Quote m => m Type -> m Type -> m Type
`appT` Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
ty
mkCaseExp :: Q Match -> Q Exp
mkCaseExp :: Q Match -> Q Exp
mkCaseExp Q Match
qMatch = do
Name
val <- String -> Q Name
forall (m :: * -> *). Quote m => String -> m Name
newName String
"val"
Q Pat -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Pat -> m Exp -> m Exp
lam1E (Name -> Q Pat
forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
val) (Q Exp -> Q Exp) -> Q Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$ Q Exp -> [Q Match] -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> [m Match] -> m Exp
caseE (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
val) [Q Match
qMatch]
mkFrom :: GenericTvbs -> EmptyCaseOptions -> Name
-> [ConstructorInfo] -> Q Match
mkFrom :: GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match
mkFrom GenericTvbs
gt KindSigOptions
ecOptions Name
dt [ConstructorInfo]
cs = do
Name
y <- String -> Q Name
forall (m :: * -> *). Quote m => String -> m Name
newName String
"y"
Q Pat -> Q Body -> [Q Dec] -> Q Match
forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Match
match (Name -> Q Pat
forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
y)
(Q Exp -> Q Body
forall (m :: * -> *). Quote m => m Exp -> m Body
normalB (Q Exp -> Q Body) -> Q Exp -> Q Body
forall a b. (a -> b) -> a -> b
$ Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
conE Name
m1DataName Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Q Exp -> [Q Match] -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> [m Match] -> m Exp
caseE (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
y) [Q Match]
cases)
[]
where
cases :: [Q Match]
cases = case [ConstructorInfo]
cs of
[] -> KindSigOptions -> Name -> [Q Match]
errorFrom KindSigOptions
ecOptions Name
dt
[ConstructorInfo]
_ -> (Int -> ConstructorInfo -> Q Match)
-> [Int] -> [ConstructorInfo] -> [Q Match]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (GenericTvbs
-> (Q Exp -> Q Exp) -> Int -> Int -> ConstructorInfo -> Q Match
fromCon GenericTvbs
gt Q Exp -> Q Exp
forall a. a -> a
id ([ConstructorInfo] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ConstructorInfo]
cs)) [Int
1..] [ConstructorInfo]
cs
errorFrom :: EmptyCaseOptions -> Name -> [Q Match]
errorFrom :: KindSigOptions -> Name -> [Q Match]
errorFrom KindSigOptions
useEmptyCase Name
dt
| KindSigOptions
useEmptyCase KindSigOptions -> KindSigOptions -> KindSigOptions
&& KindSigOptions
ghc7'8OrLater
= []
| KindSigOptions
otherwise
= [do Name
z <- String -> Q Name
forall (m :: * -> *). Quote m => String -> m Name
newName String
"z"
Q Pat -> Q Body -> [Q Dec] -> Q Match
forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Match
match
(Name -> Q Pat
forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
z)
(Q Exp -> Q Body
forall (m :: * -> *). Quote m => m Exp -> m Body
normalB (Q Exp -> Q Body) -> Q Exp -> Q Body
forall a b. (a -> b) -> a -> b
$
Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
seqValName) (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
z) Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE`
Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
errorValName)
(String -> Q Exp
forall (m :: * -> *). Quote m => String -> m Exp
stringE (String -> Q Exp) -> String -> Q Exp
forall a b. (a -> b) -> a -> b
$ String
"No generic representation for empty datatype "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Name -> String
nameBase Name
dt))
[]]
mkTo :: GenericTvbs -> EmptyCaseOptions -> Name
-> [ConstructorInfo] -> Q Match
mkTo :: GenericTvbs
-> KindSigOptions -> Name -> [ConstructorInfo] -> Q Match
mkTo GenericTvbs
gt KindSigOptions
ecOptions Name
dt [ConstructorInfo]
cs = do
Name
y <- String -> Q Name
forall (m :: * -> *). Quote m => String -> m Name
newName String
"y"
Q Pat -> Q Body -> [Q Dec] -> Q Match
forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Match
match (Name -> [Q Pat] -> Q Pat
forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
m1DataName [Name -> Q Pat
forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
y])
(Q Exp -> Q Body
forall (m :: * -> *). Quote m => m Exp -> m Body
normalB (Q Exp -> Q Body) -> Q Exp -> Q Body
forall a b. (a -> b) -> a -> b
$ Q Exp -> [Q Match] -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> [m Match] -> m Exp
caseE (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
y) [Q Match]
cases)
[]
where
cases :: [Q Match]
cases = case [ConstructorInfo]
cs of
[] -> KindSigOptions -> Name -> [Q Match]
errorTo KindSigOptions
ecOptions Name
dt
[ConstructorInfo]
_ -> (Int -> ConstructorInfo -> Q Match)
-> [Int] -> [ConstructorInfo] -> [Q Match]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (GenericTvbs
-> (Q Pat -> Q Pat) -> Int -> Int -> ConstructorInfo -> Q Match
toCon GenericTvbs
gt Q Pat -> Q Pat
forall a. a -> a
id ([ConstructorInfo] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ConstructorInfo]
cs)) [Int
1..] [ConstructorInfo]
cs
errorTo :: EmptyCaseOptions -> Name -> [Q Match]
errorTo :: KindSigOptions -> Name -> [Q Match]
errorTo KindSigOptions
useEmptyCase Name
dt
| KindSigOptions
useEmptyCase KindSigOptions -> KindSigOptions -> KindSigOptions
&& KindSigOptions
ghc7'8OrLater
= []
| KindSigOptions
otherwise
= [do Name
z <- String -> Q Name
forall (m :: * -> *). Quote m => String -> m Name
newName String
"z"
Q Pat -> Q Body -> [Q Dec] -> Q Match
forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Match
match
(Name -> Q Pat
forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
z)
(Q Exp -> Q Body
forall (m :: * -> *). Quote m => m Exp -> m Body
normalB (Q Exp -> Q Body) -> Q Exp -> Q Body
forall a b. (a -> b) -> a -> b
$
Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
seqValName) (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
z) Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE`
Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
errorValName)
(String -> Q Exp
forall (m :: * -> *). Quote m => String -> m Exp
stringE (String -> Q Exp) -> String -> Q Exp
forall a b. (a -> b) -> a -> b
$ String
"No values for empty datatype " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Name -> String
nameBase Name
dt))
[]]
ghc7'8OrLater :: Bool
#if __GLASGOW_HASKELL__ >= 708
ghc7'8OrLater :: KindSigOptions
ghc7'8OrLater = KindSigOptions
True
#else
ghc7'8OrLater = False
#endif
fromCon :: GenericTvbs -> (Q Exp -> Q Exp) -> Int -> Int
-> ConstructorInfo -> Q Match
fromCon :: GenericTvbs
-> (Q Exp -> Q Exp) -> Int -> Int -> ConstructorInfo -> Q Match
fromCon GenericTvbs
gt Q Exp -> Q Exp
wrap Int
m Int
i
(ConstructorInfo { constructorName :: ConstructorInfo -> Name
constructorName = Name
cn
, constructorVars :: ConstructorInfo -> [TyVarBndrUnit]
constructorVars = [TyVarBndrUnit]
vars
, constructorContext :: ConstructorInfo -> [Type]
constructorContext = [Type]
ctxt
, constructorFields :: ConstructorInfo -> [Type]
constructorFields = [Type]
ts
}) = do
Name -> [TyVarBndrUnit] -> [Type] -> Q ()
checkExistentialContext Name
cn [TyVarBndrUnit]
vars [Type]
ctxt
[Name]
fNames <- String -> Int -> Q [Name]
newNameList String
"f" (Int -> Q [Name]) -> Int -> Q [Name]
forall a b. (a -> b) -> a -> b
$ [Type] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Type]
ts
Q Pat -> Q Body -> [Q Dec] -> Q Match
forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Match
match (Name -> [Q Pat] -> Q Pat
forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
cn ((Name -> Q Pat) -> [Name] -> [Q Pat]
forall a b. (a -> b) -> [a] -> [b]
map Name -> Q Pat
forall (m :: * -> *). Quote m => Name -> m Pat
varP [Name]
fNames))
(Q Exp -> Q Body
forall (m :: * -> *). Quote m => m Exp -> m Body
normalB (Q Exp -> Q Body) -> Q Exp -> Q Body
forall a b. (a -> b) -> a -> b
$ Q Exp -> Q Exp
wrap (Q Exp -> Q Exp) -> Q Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Q Exp -> Q Exp
lrE Int
i Int
m (Q Exp -> Q Exp) -> Q Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$ Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
conE Name
m1DataName Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE`
(Q Exp -> Q Exp -> Q Exp) -> Q Exp -> [Q Exp] -> Q Exp
forall a. (a -> a -> a) -> a -> [a] -> a
foldBal Q Exp -> Q Exp -> Q Exp
prodE (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
conE Name
u1DataName) ((Name -> Type -> Q Exp) -> [Name] -> [Type] -> [Q Exp]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (GenericTvbs -> Name -> Type -> Q Exp
fromField GenericTvbs
gt) [Name]
fNames [Type]
ts)) []
prodE :: Q Exp -> Q Exp -> Q Exp
prodE :: Q Exp -> Q Exp -> Q Exp
prodE Q Exp
x Q Exp
y = Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
conE Name
productDataName Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Q Exp
x Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Q Exp
y
fromField :: GenericTvbs -> Name -> Type -> Q Exp
fromField :: GenericTvbs -> Name -> Type -> Q Exp
fromField GenericTvbs
gt Name
nr Type
t = Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
conE Name
m1DataName Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` (GenericTvbs -> Name -> Type -> Q Exp
fromFieldWrap GenericTvbs
gt Name
nr (Type -> Q Exp) -> Q Type -> Q Exp
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Type -> Q Type
resolveTypeSynonyms Type
t)
fromFieldWrap :: GenericTvbs -> Name -> Type -> Q Exp
fromFieldWrap :: GenericTvbs -> Name -> Type -> Q Exp
fromFieldWrap GenericTvbs
_ Name
_ ForallT{} = Q Exp
forall a. Q a
rankNError
fromFieldWrap GenericTvbs
gt Name
nr (SigT Type
t Type
_) = GenericTvbs -> Name -> Type -> Q Exp
fromFieldWrap GenericTvbs
gt Name
nr Type
t
fromFieldWrap Gen0{} Name
nr Type
t = Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
conE (Type -> Name
boxRepName Type
t) Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
nr
fromFieldWrap (Gen1{gen1LastTvbName :: GenericTvbs -> Name
gen1LastTvbName = Name
name}) Name
nr Type
t = Type -> Name -> Q Exp
wC Type
t Name
name Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
nr
wC :: Type -> Name -> Q Exp
wC :: Type -> Name -> Q Exp
wC (Type -> Type
dustOff -> Type
t0) Name
name =
Type -> Q (ArgRes Exp)
go Type
t0 Q (ArgRes Exp) -> (ArgRes Exp -> Q Exp) -> Q Exp
forall a b. Q a -> (a -> Q b) -> Q b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ArgRes Exp
res -> case ArgRes Exp
res of
ArgRes Exp
NoPar -> Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
conE (Name -> Q Exp) -> Name -> Q Exp
forall a b. (a -> b) -> a -> b
$ Type -> Name
boxRepName Type
t0
ArgRes KindSigOptions
_ Exp
r -> Exp -> Q Exp
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Exp
r
where
go :: Type -> Q (ArgRes Exp)
go :: Type -> Q (ArgRes Exp)
go ForallT{} = Q (ArgRes Exp)
forall a. Q a
rankNError
#if MIN_VERSION_template_haskell(2,16,0)
go ForallVisT{} = Q (ArgRes Exp)
forall a. Q a
rankNError
#endif
go (VarT Name
t) | Name
t Name -> Name -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Name
name = KindSigOptions -> Exp -> ArgRes Exp
forall a. KindSigOptions -> a -> ArgRes a
ArgRes KindSigOptions
True (Exp -> ArgRes Exp) -> Q Exp -> Q (ArgRes Exp)
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
conE Name
par1DataName
go (AppT Type
f Type
x) = do
KindSigOptions -> Q () -> Q ()
forall (f :: * -> *).
Applicative f =>
KindSigOptions -> f () -> f ()
when (KindSigOptions -> KindSigOptions
not (Type
f Type -> Name -> KindSigOptions
`ground` Name
name)) Q ()
forall a. Q a
outOfPlaceTyVarError
ArgRes Exp
mxr <- Type -> Q (ArgRes Exp)
go (Type -> Type
dustOff Type
x)
case ArgRes Exp
mxr of
ArgRes Exp
NoPar -> ArgRes Exp -> Q (ArgRes Exp)
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ArgRes Exp
forall a. ArgRes a
NoPar
ArgRes KindSigOptions
arg_is_param Exp
xr -> do
KindSigOptions
itf <- Type -> Q KindSigOptions
isUnsaturatedType Type
f
KindSigOptions -> Q () -> Q ()
forall (f :: * -> *).
Applicative f =>
KindSigOptions -> f () -> f ()
when KindSigOptions
itf Q ()
forall a. Q a
typeFamilyApplicationError
KindSigOptions -> Exp -> ArgRes Exp
forall a. KindSigOptions -> a -> ArgRes a
ArgRes KindSigOptions
False (Exp -> ArgRes Exp) -> Q Exp -> Q (ArgRes Exp)
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
if KindSigOptions
arg_is_param
then
Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
conE Name
rec1DataName
else
Q Exp -> Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
conE Name
comp1DataName) (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
composeValName) (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
fmapValName Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Exp -> Q Exp
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Exp
xr)
go Type
_ = ArgRes Exp -> Q (ArgRes Exp)
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ArgRes Exp
forall a. ArgRes a
NoPar
boxRepName :: Type -> Name
boxRepName :: Type -> Name
boxRepName = Name
-> ((Name, Name, Name) -> Name) -> Maybe (Name, Name, Name) -> Name
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Name
k1DataName (Name, Name, Name) -> Name
forall a b c. (a, b, c) -> b
snd3 (Maybe (Name, Name, Name) -> Name)
-> (Type -> Maybe (Name, Name, Name)) -> Type -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type -> Maybe (Name, Name, Name)
unboxedRepNames
toCon :: GenericTvbs -> (Q Pat -> Q Pat) -> Int -> Int
-> ConstructorInfo -> Q Match
toCon :: GenericTvbs
-> (Q Pat -> Q Pat) -> Int -> Int -> ConstructorInfo -> Q Match
toCon GenericTvbs
gt Q Pat -> Q Pat
wrap Int
m Int
i
(ConstructorInfo { constructorName :: ConstructorInfo -> Name
constructorName = Name
cn
, constructorVars :: ConstructorInfo -> [TyVarBndrUnit]
constructorVars = [TyVarBndrUnit]
vars
, constructorContext :: ConstructorInfo -> [Type]
constructorContext = [Type]
ctxt
, constructorFields :: ConstructorInfo -> [Type]
constructorFields = [Type]
ts
}) = do
Name -> [TyVarBndrUnit] -> [Type] -> Q ()
checkExistentialContext Name
cn [TyVarBndrUnit]
vars [Type]
ctxt
[Name]
fNames <- String -> Int -> Q [Name]
newNameList String
"f" (Int -> Q [Name]) -> Int -> Q [Name]
forall a b. (a -> b) -> a -> b
$ [Type] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Type]
ts
Q Pat -> Q Body -> [Q Dec] -> Q Match
forall (m :: * -> *).
Quote m =>
m Pat -> m Body -> [m Dec] -> m Match
match (Q Pat -> Q Pat
wrap (Q Pat -> Q Pat) -> Q Pat -> Q Pat
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Q Pat -> Q Pat
lrP Int
i Int
m (Q Pat -> Q Pat) -> Q Pat -> Q Pat
forall a b. (a -> b) -> a -> b
$ Name -> [Q Pat] -> Q Pat
forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
m1DataName
[(Q Pat -> Q Pat -> Q Pat) -> Q Pat -> [Q Pat] -> Q Pat
forall a. (a -> a -> a) -> a -> [a] -> a
foldBal Q Pat -> Q Pat -> Q Pat
forall {m :: * -> *}. Quote m => m Pat -> m Pat -> m Pat
prod (Name -> [Q Pat] -> Q Pat
forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
u1DataName []) ((Name -> Type -> Q Pat) -> [Name] -> [Type] -> [Q Pat]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (GenericTvbs -> Name -> Type -> Q Pat
toField GenericTvbs
gt) [Name]
fNames [Type]
ts)])
(Q Exp -> Q Body
forall (m :: * -> *). Quote m => m Exp -> m Body
normalB (Q Exp -> Q Body) -> Q Exp -> Q Body
forall a b. (a -> b) -> a -> b
$ (Q Exp -> Q Exp -> Q Exp) -> Q Exp -> [Q Exp] -> Q Exp
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
appE (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
conE Name
cn)
((Name -> Type -> Q Exp) -> [Name] -> [Type] -> [Q Exp]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Name
nr -> Type -> Q Type
resolveTypeSynonyms (Type -> Q Type) -> (Type -> Q Exp) -> Type -> Q Exp
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> GenericTvbs -> Name -> Type -> Q Exp
toConUnwC GenericTvbs
gt Name
nr)
[Name]
fNames [Type]
ts)) []
where prod :: m Pat -> m Pat -> m Pat
prod m Pat
x m Pat
y = Name -> [m Pat] -> m Pat
forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
productDataName [m Pat
x,m Pat
y]
toConUnwC :: GenericTvbs -> Name -> Type -> Q Exp
toConUnwC :: GenericTvbs -> Name -> Type -> Q Exp
toConUnwC Gen0{} Name
nr Type
_ = Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
nr
toConUnwC (Gen1{gen1LastTvbName :: GenericTvbs -> Name
gen1LastTvbName = Name
name}) Name
nr Type
t = Type -> Name -> Q Exp
unwC Type
t Name
name Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
nr
toField :: GenericTvbs -> Name -> Type -> Q Pat
toField :: GenericTvbs -> Name -> Type -> Q Pat
toField GenericTvbs
gt Name
nr Type
t = Name -> [Q Pat] -> Q Pat
forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
m1DataName [GenericTvbs -> Name -> Type -> Q Pat
toFieldWrap GenericTvbs
gt Name
nr Type
t]
toFieldWrap :: GenericTvbs -> Name -> Type -> Q Pat
toFieldWrap :: GenericTvbs -> Name -> Type -> Q Pat
toFieldWrap Gen0{} Name
nr Type
t = Name -> [Q Pat] -> Q Pat
forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP (Type -> Name
boxRepName Type
t) [Name -> Q Pat
forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
nr]
toFieldWrap Gen1{} Name
nr Type
_ = Name -> Q Pat
forall (m :: * -> *). Quote m => Name -> m Pat
varP Name
nr
unwC :: Type -> Name -> Q Exp
unwC :: Type -> Name -> Q Exp
unwC (Type -> Type
dustOff -> Type
t0) Name
name =
Type -> Q (ArgRes Exp)
go Type
t0 Q (ArgRes Exp) -> (ArgRes Exp -> Q Exp) -> Q Exp
forall a b. Q a -> (a -> Q b) -> Q b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ArgRes Exp
res -> case ArgRes Exp
res of
ArgRes Exp
NoPar -> Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE (Name -> Q Exp) -> Name -> Q Exp
forall a b. (a -> b) -> a -> b
$ Type -> Name
unboxRepName Type
t0
ArgRes KindSigOptions
_ Exp
r -> Exp -> Q Exp
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Exp
r
where
go :: Type -> Q (ArgRes Exp)
go :: Type -> Q (ArgRes Exp)
go ForallT{} = Q (ArgRes Exp)
forall a. Q a
rankNError
#if MIN_VERSION_template_haskell(2,16,0)
go ForallVisT{} = Q (ArgRes Exp)
forall a. Q a
rankNError
#endif
go (VarT Name
t) | Name
t Name -> Name -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Name
name = KindSigOptions -> Exp -> ArgRes Exp
forall a. KindSigOptions -> a -> ArgRes a
ArgRes KindSigOptions
True (Exp -> ArgRes Exp) -> Q Exp -> Q (ArgRes Exp)
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
unPar1ValName
go (AppT Type
f Type
x) = do
KindSigOptions -> Q () -> Q ()
forall (f :: * -> *).
Applicative f =>
KindSigOptions -> f () -> f ()
when (KindSigOptions -> KindSigOptions
not (Type
f Type -> Name -> KindSigOptions
`ground` Name
name)) Q ()
forall a. Q a
outOfPlaceTyVarError
ArgRes Exp
mxr <- Type -> Q (ArgRes Exp)
go (Type -> Type
dustOff Type
x)
case ArgRes Exp
mxr of
ArgRes Exp
NoPar -> ArgRes Exp -> Q (ArgRes Exp)
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ArgRes Exp
forall a. ArgRes a
NoPar
ArgRes KindSigOptions
arg_is_param Exp
xr -> do
KindSigOptions
itf <- Type -> Q KindSigOptions
isUnsaturatedType Type
f
KindSigOptions -> Q () -> Q ()
forall (f :: * -> *).
Applicative f =>
KindSigOptions -> f () -> f ()
when KindSigOptions
itf Q ()
forall a. Q a
typeFamilyApplicationError
KindSigOptions -> Exp -> ArgRes Exp
forall a. KindSigOptions -> a -> ArgRes a
ArgRes KindSigOptions
False (Exp -> ArgRes Exp) -> Q Exp -> Q (ArgRes Exp)
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
if KindSigOptions
arg_is_param
then
Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
unRec1ValName
else
Q Exp -> Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp -> m Exp
infixApp (Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
fmapValName Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Exp -> Q Exp
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Exp
xr)
(Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
composeValName)
(Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
varE Name
unComp1ValName)
go Type
_ = ArgRes Exp -> Q (ArgRes Exp)
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ArgRes Exp
forall a. ArgRes a
NoPar
unboxRepName :: Type -> Name
unboxRepName :: Type -> Name
unboxRepName = Name
-> ((Name, Name, Name) -> Name) -> Maybe (Name, Name, Name) -> Name
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Name
unK1ValName (Name, Name, Name) -> Name
forall a b c. (a, b, c) -> c
trd3 (Maybe (Name, Name, Name) -> Name)
-> (Type -> Maybe (Name, Name, Name)) -> Type -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type -> Maybe (Name, Name, Name)
unboxedRepNames
lrP :: Int -> Int -> (Q Pat -> Q Pat)
lrP :: Int -> Int -> Q Pat -> Q Pat
lrP Int
i Int
n Q Pat
p
| Int
n Int -> Int -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Int
0 = String -> Q Pat
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"lrP: impossible"
| Int
n Int -> Int -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Int
1 = Q Pat
p
| Int
i Int -> Int -> KindSigOptions
forall a. Ord a => a -> a -> KindSigOptions
<= Int -> Int -> Int
forall a. Integral a => a -> a -> a
div Int
n Int
2 = Name -> [Q Pat] -> Q Pat
forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
l1DataName [Int -> Int -> Q Pat -> Q Pat
lrP Int
i (Int -> Int -> Int
forall a. Integral a => a -> a -> a
div Int
n Int
2) Q Pat
p]
| KindSigOptions
otherwise = Name -> [Q Pat] -> Q Pat
forall (m :: * -> *). Quote m => Name -> [m Pat] -> m Pat
conP Name
r1DataName [Int -> Int -> Q Pat -> Q Pat
lrP (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
m) (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
m) Q Pat
p]
where m :: Int
m = Int -> Int -> Int
forall a. Integral a => a -> a -> a
div Int
n Int
2
lrE :: Int -> Int -> (Q Exp -> Q Exp)
lrE :: Int -> Int -> Q Exp -> Q Exp
lrE Int
i Int
n Q Exp
e
| Int
n Int -> Int -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Int
0 = String -> Q Exp
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"lrE: impossible"
| Int
n Int -> Int -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Int
1 = Q Exp
e
| Int
i Int -> Int -> KindSigOptions
forall a. Ord a => a -> a -> KindSigOptions
<= Int -> Int -> Int
forall a. Integral a => a -> a -> a
div Int
n Int
2 = Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
conE Name
l1DataName Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Int -> Int -> Q Exp -> Q Exp
lrE Int
i (Int -> Int -> Int
forall a. Integral a => a -> a -> a
div Int
n Int
2) Q Exp
e
| KindSigOptions
otherwise = Name -> Q Exp
forall (m :: * -> *). Quote m => Name -> m Exp
conE Name
r1DataName Q Exp -> Q Exp -> Q Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
`appE` Int -> Int -> Q Exp -> Q Exp
lrE (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
m) (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
m) Q Exp
e
where m :: Int
m = Int -> Int -> Int
forall a. Integral a => a -> a -> a
div Int
n Int
2
unboxedRepNames :: Type -> Maybe (Name, Name, Name)
unboxedRepNames :: Type -> Maybe (Name, Name, Name)
unboxedRepNames Type
ty
| Type
ty Type -> Type -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Name -> Type
ConT Name
addrHashTypeName = (Name, Name, Name) -> Maybe (Name, Name, Name)
forall a. a -> Maybe a
Just (Name
uAddrTypeName, Name
uAddrDataName, Name
uAddrHashValName)
| Type
ty Type -> Type -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Name -> Type
ConT Name
charHashTypeName = (Name, Name, Name) -> Maybe (Name, Name, Name)
forall a. a -> Maybe a
Just (Name
uCharTypeName, Name
uCharDataName, Name
uCharHashValName)
| Type
ty Type -> Type -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Name -> Type
ConT Name
doubleHashTypeName = (Name, Name, Name) -> Maybe (Name, Name, Name)
forall a. a -> Maybe a
Just (Name
uDoubleTypeName, Name
uDoubleDataName, Name
uDoubleHashValName)
| Type
ty Type -> Type -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Name -> Type
ConT Name
floatHashTypeName = (Name, Name, Name) -> Maybe (Name, Name, Name)
forall a. a -> Maybe a
Just (Name
uFloatTypeName, Name
uFloatDataName, Name
uFloatHashValName)
| Type
ty Type -> Type -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Name -> Type
ConT Name
intHashTypeName = (Name, Name, Name) -> Maybe (Name, Name, Name)
forall a. a -> Maybe a
Just (Name
uIntTypeName, Name
uIntDataName, Name
uIntHashValName)
| Type
ty Type -> Type -> KindSigOptions
forall a. Eq a => a -> a -> KindSigOptions
== Name -> Type
ConT Name
wordHashTypeName = (Name, Name, Name) -> Maybe (Name, Name, Name)
forall a. a -> Maybe a
Just (Name
uWordTypeName, Name
uWordDataName, Name
uWordHashValName)
| KindSigOptions
otherwise = Maybe (Name, Name, Name)
forall a. Maybe a
Nothing
buildTypeInstance :: GenericClass
-> KindSigOptions
-> Name
-> [Type]
-> Q (Type, Kind)
buildTypeInstance :: GenericClass -> KindSigOptions -> Name -> [Type] -> Q (Type, Type)
buildTypeInstance GenericClass
gClass KindSigOptions
useKindSigs Name
tyConName [Type]
varTysOrig = do
[Type]
varTysExp <- (Type -> Q Type) -> [Type] -> Q [Type]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Type -> Q Type
resolveTypeSynonyms [Type]
varTysOrig
let remainingLength :: Int
remainingLength :: Int
remainingLength = [Type] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Type]
varTysOrig Int -> Int -> Int
forall a. Num a => a -> a -> a
- GenericClass -> Int
forall a. Enum a => a -> Int
fromEnum GenericClass
gClass
#if !(MIN_VERSION_base(4,10,0))
droppedTysExp :: [Type]
droppedTysExp = drop remainingLength varTysExp
droppedStarKindStati :: [StarKindStatus]
droppedStarKindStati = map canRealizeKindStar droppedTysExp
#endif
KindSigOptions -> Q () -> Q ()
forall (f :: * -> *).
Applicative f =>
KindSigOptions -> f () -> f ()
when (Int
remainingLength Int -> Int -> KindSigOptions
forall a. Ord a => a -> a -> KindSigOptions
< Int
0
#if !(MIN_VERSION_base(4,10,0))
|| any (== OtherKind) droppedStarKindStati
#endif
) (Q () -> Q ()) -> Q () -> Q ()
forall a b. (a -> b) -> a -> b
$
Name -> Q ()
forall a. Name -> Q a
derivingKindError Name
tyConName
let varTysExpSubst :: [Type]
#if MIN_VERSION_base(4,10,0)
varTysExpSubst :: [Type]
varTysExpSubst = [Type]
varTysExp
#else
varTysExpSubst = map (substNamesWithKindStar droppedKindVarNames) varTysExp
droppedKindVarNames :: [Name]
droppedKindVarNames = catKindVarNames droppedStarKindStati
#endif
let remainingTysExpSubst, droppedTysExpSubst :: [Type]
([Type]
remainingTysExpSubst, [Type]
droppedTysExpSubst) =
Int -> [Type] -> ([Type], [Type])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
remainingLength [Type]
varTysExpSubst
#if !(MIN_VERSION_base(4,10,0))
unless (all hasKindStar droppedTysExpSubst) $
derivingKindError tyConName
#endif
let varTysOrigSubst :: [Type]
varTysOrigSubst :: [Type]
varTysOrigSubst =
#if MIN_VERSION_base(4,10,0)
[Type] -> [Type]
forall a. a -> a
id
#else
map (substNamesWithKindStar droppedKindVarNames)
#endif
([Type] -> [Type]) -> [Type] -> [Type]
forall a b. (a -> b) -> a -> b
$ [Type]
varTysOrig
remainingTysOrigSubst, droppedTysOrigSubst :: [Type]
([Type]
remainingTysOrigSubst, [Type]
droppedTysOrigSubst) =
Int -> [Type] -> ([Type], [Type])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
remainingLength [Type]
varTysOrigSubst
remainingTysOrigSubst' :: [Type]
remainingTysOrigSubst' :: [Type]
remainingTysOrigSubst' =
if KindSigOptions
useKindSigs
then [Type]
remainingTysOrigSubst
else (Type -> Type) -> [Type] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map Type -> Type
unSigT [Type]
remainingTysOrigSubst
instanceType :: Type
instanceType :: Type
instanceType = Type -> [Type] -> Type
applyTyToTys (Name -> Type
ConT Name
tyConName) [Type]
remainingTysOrigSubst'
instanceKind :: Kind
instanceKind :: Type
instanceKind = [Type] -> Type -> Type
makeFunKind ((Type -> Type) -> [Type] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map Type -> Type
typeKind [Type]
droppedTysOrigSubst) Type
starK
KindSigOptions -> Q () -> Q ()
forall (f :: * -> *).
Applicative f =>
KindSigOptions -> f () -> f ()
unless ([Type] -> [Type] -> KindSigOptions
canEtaReduce [Type]
remainingTysExpSubst [Type]
droppedTysExpSubst) (Q () -> Q ()) -> Q () -> Q ()
forall a b. (a -> b) -> a -> b
$
Type -> Q ()
forall a. Type -> Q a
etaReductionError Type
instanceType
(Type, Type) -> Q (Type, Type)
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return (Type
instanceType, Type
instanceKind)