{-# LANGUAGE CPP #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE BangPatterns #-}
#if __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE Unsafe #-}
#endif
#ifndef MIN_VERSION_template_haskell
#define MIN_VERSION_template_haskell(x,y,z) 1
#endif
module Data.Bifunctor.TH (
deriveBifunctor
, deriveBifunctorOptions
, makeBimap
, makeBimapOptions
, deriveBifoldable
, deriveBifoldableOptions
, makeBifold
, makeBifoldOptions
, makeBifoldMap
, makeBifoldMapOptions
, makeBifoldr
, makeBifoldrOptions
, makeBifoldl
, makeBifoldlOptions
, deriveBitraversable
, deriveBitraversableOptions
, makeBitraverse
, makeBitraverseOptions
, makeBisequenceA
, makeBisequenceAOptions
, makeBimapM
, makeBimapMOptions
, makeBisequence
, makeBisequenceOptions
, Options(..)
, defaultOptions
) where
import Control.Monad (guard, unless, when, zipWithM)
import Data.Bifunctor.TH.Internal
import Data.Either (rights)
import Data.List
import qualified Data.Map as Map (fromList, keys, lookup, size)
import Data.Maybe
import Language.Haskell.TH.Datatype
import Language.Haskell.TH.Lib
import Language.Haskell.TH.Ppr
import Language.Haskell.TH.Syntax
newtype Options = Options
{ Options -> Bool
emptyCaseBehavior :: Bool
} deriving (Options -> Options -> Bool
(Options -> Options -> Bool)
-> (Options -> Options -> Bool) -> Eq Options
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Options -> Options -> Bool
$c/= :: Options -> Options -> Bool
== :: Options -> Options -> Bool
$c== :: Options -> Options -> Bool
Eq, Eq Options
Eq Options =>
(Options -> Options -> Ordering)
-> (Options -> Options -> Bool)
-> (Options -> Options -> Bool)
-> (Options -> Options -> Bool)
-> (Options -> Options -> Bool)
-> (Options -> Options -> Options)
-> (Options -> Options -> Options)
-> Ord Options
Options -> Options -> Bool
Options -> Options -> Ordering
Options -> Options -> Options
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Options -> Options -> Options
$cmin :: Options -> Options -> Options
max :: Options -> Options -> Options
$cmax :: Options -> Options -> Options
>= :: Options -> Options -> Bool
$c>= :: Options -> Options -> Bool
> :: Options -> Options -> Bool
$c> :: Options -> Options -> Bool
<= :: Options -> Options -> Bool
$c<= :: Options -> Options -> Bool
< :: Options -> Options -> Bool
$c< :: Options -> Options -> Bool
compare :: Options -> Options -> Ordering
$ccompare :: Options -> Options -> Ordering
$cp1Ord :: Eq 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
readListPrec :: ReadPrec [Options]
$creadListPrec :: ReadPrec [Options]
readPrec :: ReadPrec Options
$creadPrec :: ReadPrec Options
readList :: ReadS [Options]
$creadList :: ReadS [Options]
readsPrec :: Int -> ReadS Options
$creadsPrec :: Int -> ReadS 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
showList :: [Options] -> ShowS
$cshowList :: [Options] -> ShowS
show :: Options -> String
$cshow :: Options -> String
showsPrec :: Int -> Options -> ShowS
$cshowsPrec :: Int -> Options -> ShowS
Show)
defaultOptions :: Options
defaultOptions :: Options
defaultOptions = Options :: Bool -> Options
Options { emptyCaseBehavior :: Bool
emptyCaseBehavior = Bool
False }
deriveBifunctor :: Name -> Q [Dec]
deriveBifunctor :: Name -> Q [Dec]
deriveBifunctor = Options -> Name -> Q [Dec]
deriveBifunctorOptions Options
defaultOptions
deriveBifunctorOptions :: Options -> Name -> Q [Dec]
deriveBifunctorOptions :: Options -> Name -> Q [Dec]
deriveBifunctorOptions = BiClass -> Options -> Name -> Q [Dec]
deriveBiClass BiClass
Bifunctor
makeBimap :: Name -> Q Exp
makeBimap :: Name -> Q Exp
makeBimap = Options -> Name -> Q Exp
makeBimapOptions Options
defaultOptions
makeBimapOptions :: Options -> Name -> Q Exp
makeBimapOptions :: Options -> Name -> Q Exp
makeBimapOptions = BiFun -> Options -> Name -> Q Exp
makeBiFun BiFun
Bimap
deriveBifoldable :: Name -> Q [Dec]
deriveBifoldable :: Name -> Q [Dec]
deriveBifoldable = Options -> Name -> Q [Dec]
deriveBifoldableOptions Options
defaultOptions
deriveBifoldableOptions :: Options -> Name -> Q [Dec]
deriveBifoldableOptions :: Options -> Name -> Q [Dec]
deriveBifoldableOptions = BiClass -> Options -> Name -> Q [Dec]
deriveBiClass BiClass
Bifoldable
makeBifold :: Name -> Q Exp
makeBifold :: Name -> Q Exp
makeBifold = Options -> Name -> Q Exp
makeBifoldOptions Options
defaultOptions
makeBifoldOptions :: Options -> Name -> Q Exp
makeBifoldOptions :: Options -> Name -> Q Exp
makeBifoldOptions opts :: Options
opts name :: Name
name = [Q Exp] -> Q Exp
appsE [ Options -> Name -> Q Exp
makeBifoldMapOptions Options
opts Name
name
, Name -> Q Exp
varE Name
idValName
, Name -> Q Exp
varE Name
idValName
]
makeBifoldMap :: Name -> Q Exp
makeBifoldMap :: Name -> Q Exp
makeBifoldMap = Options -> Name -> Q Exp
makeBifoldMapOptions Options
defaultOptions
makeBifoldMapOptions :: Options -> Name -> Q Exp
makeBifoldMapOptions :: Options -> Name -> Q Exp
makeBifoldMapOptions = BiFun -> Options -> Name -> Q Exp
makeBiFun BiFun
BifoldMap
makeBifoldr :: Name -> Q Exp
makeBifoldr :: Name -> Q Exp
makeBifoldr = Options -> Name -> Q Exp
makeBifoldrOptions Options
defaultOptions
makeBifoldrOptions :: Options -> Name -> Q Exp
makeBifoldrOptions :: Options -> Name -> Q Exp
makeBifoldrOptions = BiFun -> Options -> Name -> Q Exp
makeBiFun BiFun
Bifoldr
makeBifoldl :: Name -> Q Exp
makeBifoldl :: Name -> Q Exp
makeBifoldl = Options -> Name -> Q Exp
makeBifoldlOptions Options
defaultOptions
makeBifoldlOptions :: Options -> Name -> Q Exp
makeBifoldlOptions :: Options -> Name -> Q Exp
makeBifoldlOptions opts :: Options
opts name :: Name
name = do
Name
f <- String -> Q Name
newName "f"
Name
g <- String -> Q Name
newName "g"
Name
z <- String -> Q Name
newName "z"
Name
t <- String -> Q Name
newName "t"
[PatQ] -> Q Exp -> Q Exp
lamE [Name -> PatQ
varP Name
f, Name -> PatQ
varP Name
g, Name -> PatQ
varP Name
z, Name -> PatQ
varP Name
t] (Q Exp -> Q Exp) -> Q Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$
[Q Exp] -> Q Exp
appsE [ Name -> Q Exp
varE Name
appEndoValName
, [Q Exp] -> Q Exp
appsE [ Name -> Q Exp
varE Name
getDualValName
, [Q Exp] -> Q Exp
appsE [ Options -> Name -> Q Exp
makeBifoldMapOptions Options
opts Name
name
, Name -> Q Exp
foldFun Name
f
, Name -> Q Exp
foldFun Name
g
, Name -> Q Exp
varE Name
t]
]
, Name -> Q Exp
varE Name
z
]
where
foldFun :: Name -> Q Exp
foldFun :: Name -> Q Exp
foldFun n :: Name
n = Q Exp -> Q Exp -> Q Exp -> Q Exp
infixApp (Name -> Q Exp
conE Name
dualDataName)
(Name -> Q Exp
varE Name
composeValName)
(Q Exp -> Q Exp -> Q Exp -> Q Exp
infixApp (Name -> Q Exp
conE Name
endoDataName)
(Name -> Q Exp
varE Name
composeValName)
(Name -> Q Exp
varE Name
flipValName Q Exp -> Q Exp -> Q Exp
`appE` Name -> Q Exp
varE Name
n)
)
deriveBitraversable :: Name -> Q [Dec]
deriveBitraversable :: Name -> Q [Dec]
deriveBitraversable = Options -> Name -> Q [Dec]
deriveBitraversableOptions Options
defaultOptions
deriveBitraversableOptions :: Options -> Name -> Q [Dec]
deriveBitraversableOptions :: Options -> Name -> Q [Dec]
deriveBitraversableOptions = BiClass -> Options -> Name -> Q [Dec]
deriveBiClass BiClass
Bitraversable
makeBitraverse :: Name -> Q Exp
makeBitraverse :: Name -> Q Exp
makeBitraverse = Options -> Name -> Q Exp
makeBitraverseOptions Options
defaultOptions
makeBitraverseOptions :: Options -> Name -> Q Exp
makeBitraverseOptions :: Options -> Name -> Q Exp
makeBitraverseOptions = BiFun -> Options -> Name -> Q Exp
makeBiFun BiFun
Bitraverse
makeBisequenceA :: Name -> Q Exp
makeBisequenceA :: Name -> Q Exp
makeBisequenceA = Options -> Name -> Q Exp
makeBisequenceAOptions Options
defaultOptions
makeBisequenceAOptions :: Options -> Name -> Q Exp
makeBisequenceAOptions :: Options -> Name -> Q Exp
makeBisequenceAOptions opts :: Options
opts name :: Name
name = [Q Exp] -> Q Exp
appsE [ Options -> Name -> Q Exp
makeBitraverseOptions Options
opts Name
name
, Name -> Q Exp
varE Name
idValName
, Name -> Q Exp
varE Name
idValName
]
makeBimapM :: Name -> Q Exp
makeBimapM :: Name -> Q Exp
makeBimapM = Options -> Name -> Q Exp
makeBimapMOptions Options
defaultOptions
makeBimapMOptions :: Options -> Name -> Q Exp
makeBimapMOptions :: Options -> Name -> Q Exp
makeBimapMOptions opts :: Options
opts name :: Name
name = do
Name
f <- String -> Q Name
newName "f"
Name
g <- String -> Q Name
newName "g"
[PatQ] -> Q Exp -> Q Exp
lamE [Name -> PatQ
varP Name
f, Name -> PatQ
varP Name
g] (Q Exp -> Q Exp) -> (Q Exp -> Q Exp) -> Q Exp -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Q Exp -> Q Exp -> Q Exp -> Q Exp
infixApp (Name -> Q Exp
varE Name
unwrapMonadValName) (Name -> Q Exp
varE Name
composeValName) (Q Exp -> Q Exp) -> Q Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$
[Q Exp] -> Q Exp
appsE [ Options -> Name -> Q Exp
makeBitraverseOptions Options
opts Name
name
, Name -> Q Exp
wrapMonadExp Name
f
, Name -> Q Exp
wrapMonadExp Name
g
]
where
wrapMonadExp :: Name -> Q Exp
wrapMonadExp :: Name -> Q Exp
wrapMonadExp n :: Name
n = Q Exp -> Q Exp -> Q Exp -> Q Exp
infixApp (Name -> Q Exp
conE Name
wrapMonadDataName) (Name -> Q Exp
varE Name
composeValName) (Name -> Q Exp
varE Name
n)
makeBisequence :: Name -> Q Exp
makeBisequence :: Name -> Q Exp
makeBisequence = Options -> Name -> Q Exp
makeBisequenceOptions Options
defaultOptions
makeBisequenceOptions :: Options -> Name -> Q Exp
makeBisequenceOptions :: Options -> Name -> Q Exp
makeBisequenceOptions opts :: Options
opts name :: Name
name = [Q Exp] -> Q Exp
appsE [ Options -> Name -> Q Exp
makeBimapMOptions Options
opts Name
name
, Name -> Q Exp
varE Name
idValName
, Name -> Q Exp
varE Name
idValName
]
deriveBiClass :: BiClass -> Options -> Name -> Q [Dec]
deriveBiClass :: BiClass -> Options -> Name -> Q [Dec]
deriveBiClass biClass :: BiClass
biClass opts :: Options
opts name :: Name
name = do
DatatypeInfo
info <- Name -> Q DatatypeInfo
reifyDatatype Name
name
case DatatypeInfo
info of
DatatypeInfo { datatypeContext :: DatatypeInfo -> Cxt
datatypeContext = Cxt
ctxt
, datatypeName :: DatatypeInfo -> Name
datatypeName = Name
parentName
, datatypeInstTypes :: DatatypeInfo -> Cxt
datatypeInstTypes = Cxt
instTys
, datatypeVariant :: DatatypeInfo -> DatatypeVariant
datatypeVariant = DatatypeVariant
variant
, datatypeCons :: DatatypeInfo -> [ConstructorInfo]
datatypeCons = [ConstructorInfo]
cons
} -> do
(instanceCxt :: Cxt
instanceCxt, instanceType :: Type
instanceType)
<- BiClass -> Name -> Cxt -> Cxt -> DatatypeVariant -> Q (Cxt, Type)
buildTypeInstance BiClass
biClass Name
parentName Cxt
ctxt Cxt
instTys DatatypeVariant
variant
(Dec -> [Dec] -> [Dec]
forall a. a -> [a] -> [a]
:[]) (Dec -> [Dec]) -> Q Dec -> Q [Dec]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` CxtQ -> TypeQ -> [Q Dec] -> Q Dec
instanceD (Cxt -> CxtQ
forall (m :: * -> *) a. Monad m => a -> m a
return Cxt
instanceCxt)
(Type -> TypeQ
forall (m :: * -> *) a. Monad m => a -> m a
return Type
instanceType)
(BiClass -> Options -> Name -> Cxt -> [ConstructorInfo] -> [Q Dec]
biFunDecs BiClass
biClass Options
opts Name
parentName Cxt
instTys [ConstructorInfo]
cons)
biFunDecs :: BiClass -> Options -> Name -> [Type] -> [ConstructorInfo] -> [Q Dec]
biFunDecs :: BiClass -> Options -> Name -> Cxt -> [ConstructorInfo] -> [Q Dec]
biFunDecs biClass :: BiClass
biClass opts :: Options
opts parentName :: Name
parentName instTys :: Cxt
instTys cons :: [ConstructorInfo]
cons =
(BiFun -> Q Dec) -> [BiFun] -> [Q Dec]
forall a b. (a -> b) -> [a] -> [b]
map BiFun -> Q Dec
makeFunD ([BiFun] -> [Q Dec]) -> [BiFun] -> [Q Dec]
forall a b. (a -> b) -> a -> b
$ BiClass -> [BiFun]
biClassToFuns BiClass
biClass
where
makeFunD :: BiFun -> Q Dec
makeFunD :: BiFun -> Q Dec
makeFunD biFun :: BiFun
biFun =
Name -> [ClauseQ] -> Q Dec
funD (BiFun -> Name
biFunName BiFun
biFun)
[ [PatQ] -> BodyQ -> [Q Dec] -> ClauseQ
clause []
(Q Exp -> BodyQ
normalB (Q Exp -> BodyQ) -> Q Exp -> BodyQ
forall a b. (a -> b) -> a -> b
$ BiFun -> Options -> Name -> Cxt -> [ConstructorInfo] -> Q Exp
makeBiFunForCons BiFun
biFun Options
opts Name
parentName Cxt
instTys [ConstructorInfo]
cons)
[]
]
makeBiFun :: BiFun -> Options -> Name -> Q Exp
makeBiFun :: BiFun -> Options -> Name -> Q Exp
makeBiFun biFun :: BiFun
biFun opts :: Options
opts name :: Name
name = do
DatatypeInfo
info <- Name -> Q DatatypeInfo
reifyDatatype Name
name
case DatatypeInfo
info of
DatatypeInfo { datatypeContext :: DatatypeInfo -> Cxt
datatypeContext = Cxt
ctxt
, datatypeName :: DatatypeInfo -> Name
datatypeName = Name
parentName
, datatypeInstTypes :: DatatypeInfo -> Cxt
datatypeInstTypes = Cxt
instTys
, datatypeVariant :: DatatypeInfo -> DatatypeVariant
datatypeVariant = DatatypeVariant
variant
, datatypeCons :: DatatypeInfo -> [ConstructorInfo]
datatypeCons = [ConstructorInfo]
cons
} ->
BiClass -> Name -> Cxt -> Cxt -> DatatypeVariant -> Q (Cxt, Type)
buildTypeInstance (BiFun -> BiClass
biFunToClass BiFun
biFun) Name
parentName Cxt
ctxt Cxt
instTys DatatypeVariant
variant
Q (Cxt, Type) -> Q Exp -> Q Exp
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> BiFun -> Options -> Name -> Cxt -> [ConstructorInfo] -> Q Exp
makeBiFunForCons BiFun
biFun Options
opts Name
parentName Cxt
instTys [ConstructorInfo]
cons
makeBiFunForCons :: BiFun -> Options -> Name -> [Type] -> [ConstructorInfo] -> Q Exp
makeBiFunForCons :: BiFun -> Options -> Name -> Cxt -> [ConstructorInfo] -> Q Exp
makeBiFunForCons biFun :: BiFun
biFun opts :: Options
opts _parentName :: Name
_parentName instTys :: Cxt
instTys cons :: [ConstructorInfo]
cons = do
[Name]
argNames <- (String -> Q Name) -> [String] -> Q [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> Q Name
newName ([String] -> Q [Name]) -> [String] -> Q [Name]
forall a b. (a -> b) -> a -> b
$ [Maybe String] -> [String]
forall a. [Maybe a] -> [a]
catMaybes [ String -> Maybe String
forall a. a -> Maybe a
Just "f"
, String -> Maybe String
forall a. a -> Maybe a
Just "g"
, Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (BiFun
biFun BiFun -> BiFun -> Bool
forall a. Eq a => a -> a -> Bool
== BiFun
Bifoldr) Maybe () -> Maybe String -> Maybe String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> Maybe String
forall a. a -> Maybe a
Just "z"
, String -> Maybe String
forall a. a -> Maybe a
Just "value"
]
let ([map1 :: Name
map1, map2 :: Name
map2], others :: [Name]
others) = Int -> [Name] -> ([Name], [Name])
forall a. Int -> [a] -> ([a], [a])
splitAt 2 [Name]
argNames
z :: Name
z = [Name] -> Name
forall a. [a] -> a
head [Name]
others
value :: Name
value = [Name] -> Name
forall a. [a] -> a
last [Name]
others
lastTyVars :: [Name]
lastTyVars = (Type -> Name) -> Cxt -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map Type -> Name
varTToName (Cxt -> [Name]) -> Cxt -> [Name]
forall a b. (a -> b) -> a -> b
$ Int -> Cxt -> Cxt
forall a. Int -> [a] -> [a]
drop (Cxt -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Cxt
instTys Int -> Int -> Int
forall a. Num a => a -> a -> a
- 2) Cxt
instTys
tvMap :: Map Name Name
tvMap = [(Name, Name)] -> Map Name Name
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Name, Name)] -> Map Name Name)
-> [(Name, Name)] -> Map Name Name
forall a b. (a -> b) -> a -> b
$ [Name] -> [Name] -> [(Name, Name)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Name]
lastTyVars [Name
map1, Name
map2]
[PatQ] -> Q Exp -> Q Exp
lamE ((Name -> PatQ) -> [Name] -> [PatQ]
forall a b. (a -> b) -> [a] -> [b]
map Name -> PatQ
varP [Name]
argNames)
(Q Exp -> Q Exp) -> ([Q Exp] -> Q Exp) -> [Q Exp] -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Q Exp] -> Q Exp
appsE
([Q Exp] -> Q Exp) -> [Q Exp] -> Q Exp
forall a b. (a -> b) -> a -> b
$ [ Name -> Q Exp
varE (Name -> Q Exp) -> Name -> Q Exp
forall a b. (a -> b) -> a -> b
$ BiFun -> Name
biFunConstName BiFun
biFun
, Name -> Name -> Map Name Name -> Q Exp
makeFun Name
z Name
value Map Name Name
tvMap
] [Q Exp] -> [Q Exp] -> [Q Exp]
forall a. [a] -> [a] -> [a]
++ (Name -> Q Exp) -> [Name] -> [Q Exp]
forall a b. (a -> b) -> [a] -> [b]
map Name -> Q Exp
varE [Name]
argNames
where
makeFun :: Name -> Name -> TyVarMap -> Q Exp
makeFun :: Name -> Name -> Map Name Name -> Q Exp
makeFun z :: Name
z value :: Name
value tvMap :: Map Name Name
tvMap = do
#if MIN_VERSION_template_haskell(2,9,0)
[Role]
roles <- Name -> Q [Role]
reifyRoles Name
_parentName
#endif
case () of
_
#if MIN_VERSION_template_haskell(2,9,0)
| Just (rs :: [Role]
rs, PhantomR) <- [Role] -> Maybe ([Role], Role)
forall a. [a] -> Maybe ([a], a)
unsnoc [Role]
roles
, Just (_, PhantomR) <- [Role] -> Maybe ([Role], Role)
forall a. [a] -> Maybe ([a], a)
unsnoc [Role]
rs
-> Name -> Name -> Q Exp
biFunPhantom Name
z Name
value
#endif
| [ConstructorInfo] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ConstructorInfo]
cons Bool -> Bool -> Bool
&& Options -> Bool
emptyCaseBehavior Options
opts Bool -> Bool -> Bool
&& Bool
ghc7'8OrLater
-> BiFun -> Name -> Name -> Q Exp
biFunEmptyCase BiFun
biFun Name
z Name
value
| [ConstructorInfo] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ConstructorInfo]
cons
-> BiFun -> Name -> Name -> Q Exp
biFunNoCons BiFun
biFun Name
z Name
value
| Bool
otherwise
-> Q Exp -> [MatchQ] -> Q Exp
caseE (Name -> Q Exp
varE Name
value)
((ConstructorInfo -> MatchQ) -> [ConstructorInfo] -> [MatchQ]
forall a b. (a -> b) -> [a] -> [b]
map (BiFun -> Name -> Map Name Name -> ConstructorInfo -> MatchQ
makeBiFunForCon BiFun
biFun Name
z Map Name Name
tvMap) [ConstructorInfo]
cons)
ghc7'8OrLater :: Bool
#if __GLASGOW_HASKELL__ >= 708
ghc7'8OrLater :: Bool
ghc7'8OrLater = Bool
True
#else
ghc7'8OrLater = False
#endif
#if MIN_VERSION_template_haskell(2,9,0)
biFunPhantom :: Name -> Name -> Q Exp
biFunPhantom :: Name -> Name -> Q Exp
biFunPhantom z :: Name
z value :: Name
value =
Q Exp -> Q Exp -> BiFun -> Name -> Q Exp
biFunTrivial Q Exp
coerce
(Name -> Q Exp
varE Name
pureValName Q Exp -> Q Exp -> Q Exp
`appE` Q Exp
coerce)
BiFun
biFun Name
z
where
coerce :: Q Exp
coerce :: Q Exp
coerce = Name -> Q Exp
varE Name
coerceValName Q Exp -> Q Exp -> Q Exp
`appE` Name -> Q Exp
varE Name
value
#endif
makeBiFunForCon :: BiFun -> Name -> TyVarMap -> ConstructorInfo -> Q Match
makeBiFunForCon :: BiFun -> Name -> Map Name Name -> ConstructorInfo -> MatchQ
makeBiFunForCon biFun :: BiFun
biFun z :: Name
z tvMap :: Map Name Name
tvMap
(ConstructorInfo { constructorName :: ConstructorInfo -> Name
constructorName = Name
conName
, constructorContext :: ConstructorInfo -> Cxt
constructorContext = Cxt
ctxt
, constructorFields :: ConstructorInfo -> Cxt
constructorFields = Cxt
ts }) = do
Cxt
ts' <- (Type -> TypeQ) -> Cxt -> CxtQ
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Type -> TypeQ
resolveTypeSynonyms Cxt
ts
[Name]
argNames <- String -> Int -> Q [Name]
newNameList "_arg" (Int -> Q [Name]) -> Int -> Q [Name]
forall a b. (a -> b) -> a -> b
$ Cxt -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Cxt
ts'
if ((Type -> Bool) -> Cxt -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Type -> [Name] -> Bool
`predMentionsName` Map Name Name -> [Name]
forall k a. Map k a -> [k]
Map.keys Map Name Name
tvMap) Cxt
ctxt
Bool -> Bool -> Bool
|| Map Name Name -> Int
forall k a. Map k a -> Int
Map.size Map Name Name
tvMap Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 2)
Bool -> Bool -> Bool
&& Bool -> Bool
not (BiClass -> Bool
allowExQuant (BiFun -> BiClass
biFunToClass BiFun
biFun))
then Name -> MatchQ
forall a. Name -> a
existentialContextError Name
conName
else BiFun -> Name -> Map Name Name -> Name -> Cxt -> [Name] -> MatchQ
makeBiFunForArgs BiFun
biFun Name
z Map Name Name
tvMap Name
conName Cxt
ts' [Name]
argNames
makeBiFunForArgs :: BiFun
-> Name
-> TyVarMap
-> Name
-> [Type]
-> [Name]
-> Q Match
makeBiFunForArgs :: BiFun -> Name -> Map Name Name -> Name -> Cxt -> [Name] -> MatchQ
makeBiFunForArgs biFun :: BiFun
biFun z :: Name
z tvMap :: Map Name Name
tvMap conName :: Name
conName tys :: Cxt
tys args :: [Name]
args =
PatQ -> BodyQ -> [Q Dec] -> MatchQ
match (Name -> [PatQ] -> PatQ
conP Name
conName ([PatQ] -> PatQ) -> [PatQ] -> PatQ
forall a b. (a -> b) -> a -> b
$ (Name -> PatQ) -> [Name] -> [PatQ]
forall a b. (a -> b) -> [a] -> [b]
map Name -> PatQ
varP [Name]
args)
(Q Exp -> BodyQ
normalB (Q Exp -> BodyQ) -> Q Exp -> BodyQ
forall a b. (a -> b) -> a -> b
$ BiFun -> Name -> Name -> [Name] -> Q [Either Exp Exp] -> Q Exp
biFunCombine BiFun
biFun Name
conName Name
z [Name]
args Q [Either Exp Exp]
mappedArgs)
[]
where
mappedArgs :: Q [Either Exp Exp]
mappedArgs :: Q [Either Exp Exp]
mappedArgs = (Type -> Name -> Q (Either Exp Exp))
-> Cxt -> [Name] -> Q [Either Exp Exp]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM (BiFun
-> Map Name Name -> Name -> Type -> Name -> Q (Either Exp Exp)
makeBiFunForArg BiFun
biFun Map Name Name
tvMap Name
conName) Cxt
tys [Name]
args
makeBiFunForArg :: BiFun
-> TyVarMap
-> Name
-> Type
-> Name
-> Q (Either Exp Exp)
makeBiFunForArg :: BiFun
-> Map Name Name -> Name -> Type -> Name -> Q (Either Exp Exp)
makeBiFunForArg biFun :: BiFun
biFun tvMap :: Map Name Name
tvMap conName :: Name
conName ty :: Type
ty tyExpName :: Name
tyExpName =
BiFun
-> Map Name Name -> Name -> Bool -> Type -> Q (Either Exp Exp)
makeBiFunForType BiFun
biFun Map Name Name
tvMap Name
conName Bool
True Type
ty Q (Either Exp Exp) -> Q Exp -> Q (Either Exp Exp)
`appEitherE` Name -> Q Exp
varE Name
tyExpName
makeBiFunForType :: BiFun
-> TyVarMap
-> Name
-> Bool
-> Type
-> Q (Either Exp Exp)
makeBiFunForType :: BiFun
-> Map Name Name -> Name -> Bool -> Type -> Q (Either Exp Exp)
makeBiFunForType biFun :: BiFun
biFun tvMap :: Map Name Name
tvMap conName :: Name
conName covariant :: Bool
covariant (VarT tyName :: Name
tyName) =
case Name -> Map Name Name -> Maybe Name
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
tyName Map Name Name
tvMap of
Just mapName :: Name
mapName -> (Exp -> Either Exp Exp) -> Q Exp -> Q (Either Exp Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Exp -> Either Exp Exp
forall a b. b -> Either a b
Right (Q Exp -> Q (Either Exp Exp))
-> (Name -> Q Exp) -> Name -> Q (Either Exp Exp)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Q Exp
varE (Name -> Q (Either Exp Exp)) -> Name -> Q (Either Exp Exp)
forall a b. (a -> b) -> a -> b
$
if Bool
covariant
then Name
mapName
else Name -> Name
forall a. Name -> a
contravarianceError Name
conName
Nothing -> (Exp -> Either Exp Exp) -> Q Exp -> Q (Either Exp Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Exp -> Either Exp Exp
forall a b. a -> Either a b
Left (Q Exp -> Q (Either Exp Exp)) -> Q Exp -> Q (Either Exp Exp)
forall a b. (a -> b) -> a -> b
$ BiFun -> Q Exp
biFunTriv BiFun
biFun
makeBiFunForType biFun :: BiFun
biFun tvMap :: Map Name Name
tvMap conName :: Name
conName covariant :: Bool
covariant (SigT ty :: Type
ty _) =
BiFun
-> Map Name Name -> Name -> Bool -> Type -> Q (Either Exp Exp)
makeBiFunForType BiFun
biFun Map Name Name
tvMap Name
conName Bool
covariant Type
ty
makeBiFunForType biFun :: BiFun
biFun tvMap :: Map Name Name
tvMap conName :: Name
conName covariant :: Bool
covariant (ForallT _ _ ty :: Type
ty) =
BiFun
-> Map Name Name -> Name -> Bool -> Type -> Q (Either Exp Exp)
makeBiFunForType BiFun
biFun Map Name Name
tvMap Name
conName Bool
covariant Type
ty
makeBiFunForType biFun :: BiFun
biFun tvMap :: Map Name Name
tvMap conName :: Name
conName covariant :: Bool
covariant ty :: Type
ty =
let tyCon :: Type
tyArgs :: [Type]
tyCon :: Type
tyCon:tyArgs :: Cxt
tyArgs = Type -> Cxt
unapplyTy Type
ty
numLastArgs :: Int
numLastArgs :: Int
numLastArgs = Int -> Int -> Int
forall a. Ord a => a -> a -> a
min 2 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Cxt -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Cxt
tyArgs
lhsArgs, rhsArgs :: [Type]
(lhsArgs :: Cxt
lhsArgs, rhsArgs :: Cxt
rhsArgs) = Int -> Cxt -> (Cxt, Cxt)
forall a. Int -> [a] -> ([a], [a])
splitAt (Cxt -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Cxt
tyArgs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
numLastArgs) Cxt
tyArgs
tyVarNames :: [Name]
tyVarNames :: [Name]
tyVarNames = Map Name Name -> [Name]
forall k a. Map k a -> [k]
Map.keys Map Name Name
tvMap
mentionsTyArgs :: Bool
mentionsTyArgs :: Bool
mentionsTyArgs = (Type -> Bool) -> Cxt -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Type -> [Name] -> Bool
`mentionsName` [Name]
tyVarNames) Cxt
tyArgs
makeBiFunTuple :: ([Q Pat] -> Q Pat) -> (Int -> Name) -> Int
-> Q (Either Exp Exp)
makeBiFunTuple :: ([PatQ] -> PatQ) -> (Int -> Name) -> Int -> Q (Either Exp Exp)
makeBiFunTuple mkTupP :: [PatQ] -> PatQ
mkTupP mkTupleDataName :: Int -> Name
mkTupleDataName n :: Int
n = do
[Name]
args <- (String -> Q Name) -> [String] -> Q [Name]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> Q Name
newName ([String] -> Q [Name]) -> [String] -> Q [Name]
forall a b. (a -> b) -> a -> b
$ [Maybe String] -> [String]
forall a. [Maybe a] -> [a]
catMaybes [ String -> Maybe String
forall a. a -> Maybe a
Just "x"
, Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (BiFun
biFun BiFun -> BiFun -> Bool
forall a. Eq a => a -> a -> Bool
== BiFun
Bifoldr) Maybe () -> Maybe String -> Maybe String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> Maybe String
forall a. a -> Maybe a
Just "z"
]
[Name]
xs <- String -> Int -> Q [Name]
newNameList "_tup" Int
n
let x :: Name
x = [Name] -> Name
forall a. [a] -> a
head [Name]
args
z :: Name
z = [Name] -> Name
forall a. [a] -> a
last [Name]
args
(Exp -> Either Exp Exp) -> Q Exp -> Q (Either Exp Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Exp -> Either Exp Exp
forall a b. b -> Either a b
Right (Q Exp -> Q (Either Exp Exp)) -> Q Exp -> Q (Either Exp Exp)
forall a b. (a -> b) -> a -> b
$ [PatQ] -> Q Exp -> Q Exp
lamE ((Name -> PatQ) -> [Name] -> [PatQ]
forall a b. (a -> b) -> [a] -> [b]
map Name -> PatQ
varP [Name]
args) (Q Exp -> Q Exp) -> Q Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$ Q Exp -> [MatchQ] -> Q Exp
caseE (Name -> Q Exp
varE Name
x)
[ PatQ -> BodyQ -> [Q Dec] -> MatchQ
match ([PatQ] -> PatQ
mkTupP ([PatQ] -> PatQ) -> [PatQ] -> PatQ
forall a b. (a -> b) -> a -> b
$ (Name -> PatQ) -> [Name] -> [PatQ]
forall a b. (a -> b) -> [a] -> [b]
map Name -> PatQ
varP [Name]
xs)
(Q Exp -> BodyQ
normalB (Q Exp -> BodyQ) -> Q Exp -> BodyQ
forall a b. (a -> b) -> a -> b
$ BiFun -> Name -> Name -> [Name] -> Q [Either Exp Exp] -> Q Exp
biFunCombine BiFun
biFun
(Int -> Name
mkTupleDataName Int
n)
Name
z
[Name]
xs
((Type -> Name -> Q (Either Exp Exp))
-> Cxt -> [Name] -> Q [Either Exp Exp]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM Type -> Name -> Q (Either Exp Exp)
makeBiFunTupleField Cxt
tyArgs [Name]
xs)
)
[]
]
makeBiFunTupleField :: Type -> Name -> Q (Either Exp Exp)
makeBiFunTupleField :: Type -> Name -> Q (Either Exp Exp)
makeBiFunTupleField fieldTy :: Type
fieldTy fieldName :: Name
fieldName =
BiFun
-> Map Name Name -> Name -> Bool -> Type -> Q (Either Exp Exp)
makeBiFunForType BiFun
biFun Map Name Name
tvMap Name
conName Bool
covariant Type
fieldTy
Q (Either Exp Exp) -> Q Exp -> Q (Either Exp Exp)
`appEitherE` Name -> Q Exp
varE Name
fieldName
in case Type
tyCon of
ArrowT
| Bool -> Bool
not (BiClass -> Bool
allowFunTys (BiFun -> BiClass
biFunToClass BiFun
biFun)) -> Name -> Q (Either Exp Exp)
forall a. Name -> a
noFunctionsError Name
conName
| Bool
mentionsTyArgs, [argTy :: Type
argTy, resTy :: Type
resTy] <- Cxt
tyArgs ->
do Name
x <- String -> Q Name
newName "x"
Name
b <- String -> Q Name
newName "b"
(Exp -> Either Exp Exp) -> Q Exp -> Q (Either Exp Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Exp -> Either Exp Exp
forall a b. b -> Either a b
Right (Q Exp -> Q (Either Exp Exp))
-> (Q Exp -> Q Exp) -> Q Exp -> Q (Either Exp Exp)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [PatQ] -> Q Exp -> Q Exp
lamE [Name -> PatQ
varP Name
x, Name -> PatQ
varP Name
b] (Q Exp -> Q (Either Exp Exp)) -> Q Exp -> Q (Either Exp Exp)
forall a b. (a -> b) -> a -> b
$
Bool -> Type -> Q Exp
covBiFun Bool
covariant Type
resTy Q Exp -> Q Exp -> Q Exp
`appE` (Name -> Q Exp
varE Name
x Q Exp -> Q Exp -> Q Exp
`appE`
(Bool -> Type -> Q Exp
covBiFun (Bool -> Bool
not Bool
covariant) Type
argTy Q Exp -> Q Exp -> Q Exp
`appE` Name -> Q Exp
varE Name
b))
where
covBiFun :: Bool -> Type -> Q Exp
covBiFun :: Bool -> Type -> Q Exp
covBiFun cov :: Bool
cov = (Either Exp Exp -> Exp) -> Q (Either Exp Exp) -> Q Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Either Exp Exp -> Exp
forall a. Either a a -> a
fromEither (Q (Either Exp Exp) -> Q Exp)
-> (Type -> Q (Either Exp Exp)) -> Type -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BiFun
-> Map Name Name -> Name -> Bool -> Type -> Q (Either Exp Exp)
makeBiFunForType BiFun
biFun Map Name Name
tvMap Name
conName Bool
cov
#if MIN_VERSION_template_haskell(2,6,0)
UnboxedTupleT n :: Int
n
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 0 Bool -> Bool -> Bool
&& Bool
mentionsTyArgs -> ([PatQ] -> PatQ) -> (Int -> Name) -> Int -> Q (Either Exp Exp)
makeBiFunTuple [PatQ] -> PatQ
unboxedTupP Int -> Name
unboxedTupleDataName Int
n
#endif
TupleT n :: Int
n
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 0 Bool -> Bool -> Bool
&& Bool
mentionsTyArgs -> ([PatQ] -> PatQ) -> (Int -> Name) -> Int -> Q (Either Exp Exp)
makeBiFunTuple [PatQ] -> PatQ
tupP Int -> Name
tupleDataName Int
n
_ -> do
Bool
itf <- Type -> Q Bool
isTyFamily Type
tyCon
if (Type -> Bool) -> Cxt -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Type -> [Name] -> Bool
`mentionsName` [Name]
tyVarNames) Cxt
lhsArgs Bool -> Bool -> Bool
|| (Bool
itf Bool -> Bool -> Bool
&& Bool
mentionsTyArgs)
then Name -> Q (Either Exp Exp)
forall a. Name -> a
outOfPlaceTyVarError Name
conName
else if (Type -> Bool) -> Cxt -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Type -> [Name] -> Bool
`mentionsName` [Name]
tyVarNames) Cxt
rhsArgs
then (Exp -> Either Exp Exp) -> Q Exp -> Q (Either Exp Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Exp -> Either Exp Exp
forall a b. b -> Either a b
Right (Q Exp -> Q (Either Exp Exp))
-> ([Q Exp] -> Q Exp) -> [Q Exp] -> Q (Either Exp Exp)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BiFun -> Q Exp -> Q Exp
biFunApp BiFun
biFun (Q Exp -> Q Exp) -> ([Q Exp] -> Q Exp) -> [Q Exp] -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Q Exp] -> Q Exp
appsE ([Q Exp] -> Q (Either Exp Exp)) -> [Q Exp] -> Q (Either Exp Exp)
forall a b. (a -> b) -> a -> b
$
( Name -> Q Exp
varE (Maybe Name -> Name
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Name -> Name) -> Maybe Name -> Name
forall a b. (a -> b) -> a -> b
$ BiFun -> Int -> Maybe Name
biFunArity BiFun
biFun Int
numLastArgs)
Q Exp -> [Q Exp] -> [Q Exp]
forall a. a -> [a] -> [a]
: (Type -> Q Exp) -> Cxt -> [Q Exp]
forall a b. (a -> b) -> [a] -> [b]
map ((Either Exp Exp -> Exp) -> Q (Either Exp Exp) -> Q Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Either Exp Exp -> Exp
forall a. Either a a -> a
fromEither (Q (Either Exp Exp) -> Q Exp)
-> (Type -> Q (Either Exp Exp)) -> Type -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BiFun
-> Map Name Name -> Name -> Bool -> Type -> Q (Either Exp Exp)
makeBiFunForType BiFun
biFun Map Name Name
tvMap Name
conName Bool
covariant)
Cxt
rhsArgs
)
else (Exp -> Either Exp Exp) -> Q Exp -> Q (Either Exp Exp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Exp -> Either Exp Exp
forall a b. a -> Either a b
Left (Q Exp -> Q (Either Exp Exp)) -> Q Exp -> Q (Either Exp Exp)
forall a b. (a -> b) -> a -> b
$ BiFun -> Q Exp
biFunTriv BiFun
biFun
buildTypeInstance :: BiClass
-> Name
-> Cxt
-> [Type]
-> DatatypeVariant
-> Q (Cxt, Type)
buildTypeInstance :: BiClass -> Name -> Cxt -> Cxt -> DatatypeVariant -> Q (Cxt, Type)
buildTypeInstance biClass :: BiClass
biClass tyConName :: Name
tyConName dataCxt :: Cxt
dataCxt instTysOrig :: Cxt
instTysOrig variant :: DatatypeVariant
variant = do
Cxt
varTysExp <- (Type -> TypeQ) -> Cxt -> CxtQ
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Type -> TypeQ
resolveTypeSynonyms Cxt
instTysOrig
let remainingLength :: Int
remainingLength :: Int
remainingLength = Cxt -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Cxt
instTysOrig Int -> Int -> Int
forall a. Num a => a -> a -> a
- 2
droppedTysExp :: [Type]
droppedTysExp :: Cxt
droppedTysExp = Int -> Cxt -> Cxt
forall a. Int -> [a] -> [a]
drop Int
remainingLength Cxt
varTysExp
droppedStarKindStati :: [StarKindStatus]
droppedStarKindStati :: [StarKindStatus]
droppedStarKindStati = (Type -> StarKindStatus) -> Cxt -> [StarKindStatus]
forall a b. (a -> b) -> [a] -> [b]
map Type -> StarKindStatus
canRealizeKindStar Cxt
droppedTysExp
Bool -> Q () -> Q ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
remainingLength Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 0 Bool -> Bool -> Bool
|| (StarKindStatus -> Bool) -> [StarKindStatus] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (StarKindStatus -> StarKindStatus -> Bool
forall a. Eq a => a -> a -> Bool
== StarKindStatus
NotKindStar) [StarKindStatus]
droppedStarKindStati) (Q () -> Q ()) -> Q () -> Q ()
forall a b. (a -> b) -> a -> b
$
BiClass -> Name -> Q ()
forall a. BiClass -> Name -> a
derivingKindError BiClass
biClass Name
tyConName
let droppedKindVarNames :: [Name]
droppedKindVarNames :: [Name]
droppedKindVarNames = [StarKindStatus] -> [Name]
catKindVarNames [StarKindStatus]
droppedStarKindStati
varTysExpSubst :: [Type]
varTysExpSubst :: Cxt
varTysExpSubst = (Type -> Type) -> Cxt -> Cxt
forall a b. (a -> b) -> [a] -> [b]
map ([Name] -> Type -> Type
substNamesWithKindStar [Name]
droppedKindVarNames) Cxt
varTysExp
remainingTysExpSubst, droppedTysExpSubst :: [Type]
(remainingTysExpSubst :: Cxt
remainingTysExpSubst, droppedTysExpSubst :: Cxt
droppedTysExpSubst) =
Int -> Cxt -> (Cxt, Cxt)
forall a. Int -> [a] -> ([a], [a])
splitAt Int
remainingLength Cxt
varTysExpSubst
droppedTyVarNames :: [Name]
droppedTyVarNames :: [Name]
droppedTyVarNames = Cxt -> [Name]
forall a. TypeSubstitution a => a -> [Name]
freeVariables Cxt
droppedTysExpSubst
Bool -> Q () -> Q ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Type -> Bool) -> Cxt -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Type -> Bool
hasKindStar Cxt
droppedTysExpSubst) (Q () -> Q ()) -> Q () -> Q ()
forall a b. (a -> b) -> a -> b
$
BiClass -> Name -> Q ()
forall a. BiClass -> Name -> a
derivingKindError BiClass
biClass Name
tyConName
let preds :: [Maybe Pred]
kvNames :: [[Name]]
kvNames' :: [Name]
(preds :: [Maybe Type]
preds, kvNames :: [[Name]]
kvNames) = [(Maybe Type, [Name])] -> ([Maybe Type], [[Name]])
forall a b. [(a, b)] -> ([a], [b])
unzip ([(Maybe Type, [Name])] -> ([Maybe Type], [[Name]]))
-> [(Maybe Type, [Name])] -> ([Maybe Type], [[Name]])
forall a b. (a -> b) -> a -> b
$ (Type -> (Maybe Type, [Name])) -> Cxt -> [(Maybe Type, [Name])]
forall a b. (a -> b) -> [a] -> [b]
map (BiClass -> Type -> (Maybe Type, [Name])
deriveConstraint BiClass
biClass) Cxt
remainingTysExpSubst
kvNames' :: [Name]
kvNames' = [[Name]] -> [Name]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Name]]
kvNames
remainingTysExpSubst' :: [Type]
remainingTysExpSubst' :: Cxt
remainingTysExpSubst' =
(Type -> Type) -> Cxt -> Cxt
forall a b. (a -> b) -> [a] -> [b]
map ([Name] -> Type -> Type
substNamesWithKindStar [Name]
kvNames') Cxt
remainingTysExpSubst
remainingTysOrigSubst :: [Type]
remainingTysOrigSubst :: Cxt
remainingTysOrigSubst =
(Type -> Type) -> Cxt -> Cxt
forall a b. (a -> b) -> [a] -> [b]
map ([Name] -> Type -> Type
substNamesWithKindStar ([Name] -> [Name] -> [Name]
forall a. Eq a => [a] -> [a] -> [a]
union [Name]
droppedKindVarNames [Name]
kvNames'))
(Cxt -> Cxt) -> Cxt -> Cxt
forall a b. (a -> b) -> a -> b
$ Int -> Cxt -> Cxt
forall a. Int -> [a] -> [a]
take Int
remainingLength Cxt
instTysOrig
isDataFamily :: Bool
isDataFamily :: Bool
isDataFamily = case DatatypeVariant
variant of
Datatype -> Bool
False
Newtype -> Bool
False
DataInstance -> Bool
True
NewtypeInstance -> Bool
True
remainingTysOrigSubst' :: [Type]
remainingTysOrigSubst' :: Cxt
remainingTysOrigSubst' =
if Bool
isDataFamily
then Cxt
remainingTysOrigSubst
else (Type -> Type) -> Cxt -> Cxt
forall a b. (a -> b) -> [a] -> [b]
map Type -> Type
unSigT Cxt
remainingTysOrigSubst
instanceCxt :: Cxt
instanceCxt :: Cxt
instanceCxt = [Maybe Type] -> Cxt
forall a. [Maybe a] -> [a]
catMaybes [Maybe Type]
preds
instanceType :: Type
instanceType :: Type
instanceType = Type -> Type -> Type
AppT (Name -> Type
ConT (Name -> Type) -> Name -> Type
forall a b. (a -> b) -> a -> b
$ BiClass -> Name
biClassName BiClass
biClass)
(Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Name -> Cxt -> Type
applyTyCon Name
tyConName Cxt
remainingTysOrigSubst'
Bool -> Q () -> Q ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((Type -> Bool) -> Cxt -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Type -> [Name] -> Bool
`predMentionsName` [Name]
droppedTyVarNames) Cxt
dataCxt) (Q () -> Q ()) -> Q () -> Q ()
forall a b. (a -> b) -> a -> b
$
Name -> Type -> Q ()
forall a. Name -> Type -> a
datatypeContextError Name
tyConName Type
instanceType
Bool -> Q () -> Q ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Cxt -> Cxt -> Bool
canEtaReduce Cxt
remainingTysExpSubst' Cxt
droppedTysExpSubst) (Q () -> Q ()) -> Q () -> Q ()
forall a b. (a -> b) -> a -> b
$
Type -> Q ()
forall a. Type -> a
etaReductionError Type
instanceType
(Cxt, Type) -> Q (Cxt, Type)
forall (m :: * -> *) a. Monad m => a -> m a
return (Cxt
instanceCxt, Type
instanceType)
deriveConstraint :: BiClass -> Type -> (Maybe Pred, [Name])
deriveConstraint :: BiClass -> Type -> (Maybe Type, [Name])
deriveConstraint biClass :: BiClass
biClass t :: Type
t
| Bool -> Bool
not (Type -> Bool
isTyVar Type
t) = (Maybe Type
forall a. Maybe a
Nothing, [])
| Bool
otherwise = case Int -> Type -> Maybe [Name]
hasKindVarChain 1 Type
t of
Just ns :: [Name]
ns -> ((Name -> Name -> Type
`applyClass` Name
tName) (Name -> Type) -> Maybe Name -> Maybe Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` BiClass -> Int -> Maybe Name
biClassConstraint BiClass
biClass 1, [Name]
ns)
_ -> case Int -> Type -> Maybe [Name]
hasKindVarChain 2 Type
t of
Just ns :: [Name]
ns -> ((Name -> Name -> Type
`applyClass` Name
tName) (Name -> Type) -> Maybe Name -> Maybe Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` BiClass -> Int -> Maybe Name
biClassConstraint BiClass
biClass 2, [Name]
ns)
_ -> (Maybe Type
forall a. Maybe a
Nothing, [])
where
tName :: Name
tName :: Name
tName = Type -> Name
varTToName Type
t
derivingKindError :: BiClass -> Name -> a
derivingKindError :: BiClass -> Name -> a
derivingKindError biClass :: BiClass
biClass tyConName :: Name
tyConName = String -> a
forall a. HasCallStack => String -> a
error
(String -> a) -> ShowS -> String -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "Cannot derive well-kinded instance of form ‘"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
className
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar ' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> ShowS -> ShowS
showParen Bool
True
( String -> ShowS
showString (Name -> String
nameBase Name
tyConName)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString " ..."
)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "‘\n\tClass "
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
className
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString " expects an argument of kind * -> * -> *"
(String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ ""
where
className :: String
className :: String
className = Name -> String
nameBase (Name -> String) -> Name -> String
forall a b. (a -> b) -> a -> b
$ BiClass -> Name
biClassName BiClass
biClass
contravarianceError :: Name -> a
contravarianceError :: Name -> a
contravarianceError conName :: Name
conName = String -> a
forall a. HasCallStack => String -> a
error
(String -> a) -> ShowS -> String -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "Constructor ‘"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (Name -> String
nameBase Name
conName)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "‘ must not use the last type variable(s) in a function argument"
(String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ ""
noFunctionsError :: Name -> a
noFunctionsError :: Name -> a
noFunctionsError conName :: Name
conName = String -> a
forall a. HasCallStack => String -> a
error
(String -> a) -> ShowS -> String -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "Constructor ‘"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (Name -> String
nameBase Name
conName)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "‘ must not contain function types"
(String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ ""
datatypeContextError :: Name -> Type -> a
datatypeContextError :: Name -> Type -> a
datatypeContextError dataName :: Name
dataName instanceType :: Type
instanceType = String -> a
forall a. HasCallStack => String -> a
error
(String -> a) -> ShowS -> String -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "Can't make a derived instance of ‘"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (Type -> String
forall a. Ppr a => a -> String
pprint Type
instanceType)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "‘:\n\tData type ‘"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (Name -> String
nameBase Name
dataName)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "‘ must not have a class context involving the last type argument(s)"
(String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ ""
existentialContextError :: Name -> a
existentialContextError :: Name -> a
existentialContextError conName :: Name
conName = String -> a
forall a. HasCallStack => String -> a
error
(String -> a) -> ShowS -> String -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "Constructor ‘"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (Name -> String
nameBase Name
conName)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "‘ must be truly polymorphic in the last argument(s) of the data type"
(String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ ""
outOfPlaceTyVarError :: Name -> a
outOfPlaceTyVarError :: Name -> a
outOfPlaceTyVarError conName :: Name
conName = String -> a
forall a. HasCallStack => String -> a
error
(String -> a) -> ShowS -> String -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "Constructor ‘"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (Name -> String
nameBase Name
conName)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString "‘ must only use its last two type variable(s) within"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString " the last two argument(s) of a data type"
(String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ ""
etaReductionError :: Type -> a
etaReductionError :: Type -> a
etaReductionError instanceType :: Type
instanceType = String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$
"Cannot eta-reduce to an instance of form \n\tinstance (...) => "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ Type -> String
forall a. Ppr a => a -> String
pprint Type
instanceType
data BiClass = Bifunctor | Bifoldable | Bitraversable
data BiFun = Bimap | Bifoldr | BifoldMap | Bitraverse
deriving BiFun -> BiFun -> Bool
(BiFun -> BiFun -> Bool) -> (BiFun -> BiFun -> Bool) -> Eq BiFun
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BiFun -> BiFun -> Bool
$c/= :: BiFun -> BiFun -> Bool
== :: BiFun -> BiFun -> Bool
$c== :: BiFun -> BiFun -> Bool
Eq
biFunConstName :: BiFun -> Name
biFunConstName :: BiFun -> Name
biFunConstName Bimap = Name
bimapConstValName
biFunConstName Bifoldr = Name
bifoldrConstValName
biFunConstName BifoldMap = Name
bifoldMapConstValName
biFunConstName Bitraverse = Name
bitraverseConstValName
biClassName :: BiClass -> Name
biClassName :: BiClass -> Name
biClassName Bifunctor = Name
bifunctorTypeName
biClassName Bifoldable = Name
bifoldableTypeName
biClassName Bitraversable = Name
bitraversableTypeName
biFunName :: BiFun -> Name
biFunName :: BiFun -> Name
biFunName Bimap = Name
bimapValName
biFunName Bifoldr = Name
bifoldrValName
biFunName BifoldMap = Name
bifoldMapValName
biFunName Bitraverse = Name
bitraverseValName
biClassToFuns :: BiClass -> [BiFun]
biClassToFuns :: BiClass -> [BiFun]
biClassToFuns Bifunctor = [BiFun
Bimap]
biClassToFuns Bifoldable = [BiFun
Bifoldr, BiFun
BifoldMap]
biClassToFuns Bitraversable = [BiFun
Bitraverse]
biFunToClass :: BiFun -> BiClass
biFunToClass :: BiFun -> BiClass
biFunToClass Bimap = BiClass
Bifunctor
biFunToClass Bifoldr = BiClass
Bifoldable
biFunToClass BifoldMap = BiClass
Bifoldable
biFunToClass Bitraverse = BiClass
Bitraversable
biClassConstraint :: BiClass -> Int -> Maybe Name
biClassConstraint :: BiClass -> Int -> Maybe Name
biClassConstraint Bifunctor 1 = Name -> Maybe Name
forall a. a -> Maybe a
Just Name
functorTypeName
biClassConstraint Bifoldable 1 = Name -> Maybe Name
forall a. a -> Maybe a
Just Name
foldableTypeName
biClassConstraint Bitraversable 1 = Name -> Maybe Name
forall a. a -> Maybe a
Just Name
traversableTypeName
biClassConstraint biClass :: BiClass
biClass 2 = Name -> Maybe Name
forall a. a -> Maybe a
Just (Name -> Maybe Name) -> Name -> Maybe Name
forall a b. (a -> b) -> a -> b
$ BiClass -> Name
biClassName BiClass
biClass
biClassConstraint _ _ = Maybe Name
forall a. Maybe a
Nothing
biFunArity :: BiFun -> Int -> Maybe Name
biFunArity :: BiFun -> Int -> Maybe Name
biFunArity Bimap 1 = Name -> Maybe Name
forall a. a -> Maybe a
Just Name
fmapValName
biFunArity Bifoldr 1 = Name -> Maybe Name
forall a. a -> Maybe a
Just Name
foldrValName
biFunArity BifoldMap 1 = Name -> Maybe Name
forall a. a -> Maybe a
Just Name
foldMapValName
biFunArity Bitraverse 1 = Name -> Maybe Name
forall a. a -> Maybe a
Just Name
traverseValName
biFunArity biFun :: BiFun
biFun 2 = Name -> Maybe Name
forall a. a -> Maybe a
Just (Name -> Maybe Name) -> Name -> Maybe Name
forall a b. (a -> b) -> a -> b
$ BiFun -> Name
biFunName BiFun
biFun
biFunArity _ _ = Maybe Name
forall a. Maybe a
Nothing
allowFunTys :: BiClass -> Bool
allowFunTys :: BiClass -> Bool
allowFunTys Bifunctor = Bool
True
allowFunTys _ = Bool
False
allowExQuant :: BiClass -> Bool
allowExQuant :: BiClass -> Bool
allowExQuant Bifoldable = Bool
True
allowExQuant _ = Bool
False
biFunTriv :: BiFun -> Q Exp
biFunTriv :: BiFun -> Q Exp
biFunTriv Bimap = do
Name
x <- String -> Q Name
newName "x"
[PatQ] -> Q Exp -> Q Exp
lamE [Name -> PatQ
varP Name
x] (Q Exp -> Q Exp) -> Q Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$ Name -> Q Exp
varE Name
x
biFunTriv Bifoldr = do
Name
z <- String -> Q Name
newName "z"
[PatQ] -> Q Exp -> Q Exp
lamE [PatQ
wildP, Name -> PatQ
varP Name
z] (Q Exp -> Q Exp) -> Q Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$ Name -> Q Exp
varE Name
z
biFunTriv BifoldMap = [PatQ] -> Q Exp -> Q Exp
lamE [PatQ
wildP] (Q Exp -> Q Exp) -> Q Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$ Name -> Q Exp
varE Name
memptyValName
biFunTriv Bitraverse = Name -> Q Exp
varE Name
pureValName
biFunApp :: BiFun -> Q Exp -> Q Exp
biFunApp :: BiFun -> Q Exp -> Q Exp
biFunApp Bifoldr e :: Q Exp
e = do
Name
x <- String -> Q Name
newName "x"
Name
z <- String -> Q Name
newName "z"
[PatQ] -> Q Exp -> Q Exp
lamE [Name -> PatQ
varP Name
x, Name -> PatQ
varP Name
z] (Q Exp -> Q Exp) -> Q Exp -> Q Exp
forall a b. (a -> b) -> a -> b
$ [Q Exp] -> Q Exp
appsE [Q Exp
e, Name -> Q Exp
varE Name
z, Name -> Q Exp
varE Name
x]
biFunApp _ e :: Q Exp
e = Q Exp
e
biFunCombine :: BiFun
-> Name
-> Name
-> [Name]
-> Q [Either Exp Exp]
-> Q Exp
biFunCombine :: BiFun -> Name -> Name -> [Name] -> Q [Either Exp Exp] -> Q Exp
biFunCombine Bimap = Name -> Name -> [Name] -> Q [Either Exp Exp] -> Q Exp
bimapCombine
biFunCombine Bifoldr = Name -> Name -> [Name] -> Q [Either Exp Exp] -> Q Exp
bifoldrCombine
biFunCombine BifoldMap = Name -> Name -> [Name] -> Q [Either Exp Exp] -> Q Exp
bifoldMapCombine
biFunCombine Bitraverse = Name -> Name -> [Name] -> Q [Either Exp Exp] -> Q Exp
bitraverseCombine
bimapCombine :: Name
-> Name
-> [Name]
-> Q [Either Exp Exp]
-> Q Exp
bimapCombine :: Name -> Name -> [Name] -> Q [Either Exp Exp] -> Q Exp
bimapCombine conName :: Name
conName _ _ = ([Either Exp Exp] -> Exp) -> Q [Either Exp Exp] -> Q Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Exp -> Exp -> Exp) -> Exp -> [Exp] -> Exp
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Exp -> Exp -> Exp
AppE (Name -> Exp
ConE Name
conName) ([Exp] -> Exp)
-> ([Either Exp Exp] -> [Exp]) -> [Either Exp Exp] -> Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either Exp Exp -> Exp) -> [Either Exp Exp] -> [Exp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Either Exp Exp -> Exp
forall a. Either a a -> a
fromEither)
bifoldrCombine :: Name
-> Name
-> [Name]
-> Q [Either Exp Exp]
-> Q Exp
bifoldrCombine :: Name -> Name -> [Name] -> Q [Either Exp Exp] -> Q Exp
bifoldrCombine _ zName :: Name
zName _ = ([Either Exp Exp] -> Exp) -> Q [Either Exp Exp] -> Q Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Exp -> Exp -> Exp) -> Exp -> [Exp] -> Exp
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Exp -> Exp -> Exp
AppE (Name -> Exp
VarE Name
zName) ([Exp] -> Exp)
-> ([Either Exp Exp] -> [Exp]) -> [Either Exp Exp] -> Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Either Exp Exp] -> [Exp]
forall a b. [Either a b] -> [b]
rights)
bifoldMapCombine :: Name
-> Name
-> [Name]
-> Q [Either Exp Exp]
-> Q Exp
bifoldMapCombine :: Name -> Name -> [Name] -> Q [Either Exp Exp] -> Q Exp
bifoldMapCombine _ _ _ = ([Either Exp Exp] -> Exp) -> Q [Either Exp Exp] -> Q Exp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Exp] -> Exp
go ([Exp] -> Exp)
-> ([Either Exp Exp] -> [Exp]) -> [Either Exp Exp] -> Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Either Exp Exp] -> [Exp]
forall a b. [Either a b] -> [b]
rights)
where
go :: [Exp] -> Exp
go :: [Exp] -> Exp
go [] = Name -> Exp
VarE Name
memptyValName
go es :: [Exp]
es = (Exp -> Exp -> Exp) -> [Exp] -> Exp
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 (Exp -> Exp -> Exp
AppE (Exp -> Exp -> Exp) -> (Exp -> Exp) -> Exp -> Exp -> Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Exp -> Exp -> Exp
AppE (Name -> Exp
VarE Name
mappendValName)) [Exp]
es
bitraverseCombine :: Name
-> Name
-> [Name]
-> Q [Either Exp Exp]
-> Q Exp
bitraverseCombine :: Name -> Name -> [Name] -> Q [Either Exp Exp] -> Q Exp
bitraverseCombine conName :: Name
conName _ args :: [Name]
args essQ :: Q [Either Exp Exp]
essQ = do
[Either Exp Exp]
ess <- Q [Either Exp Exp]
essQ
let argTysTyVarInfo :: [Bool]
argTysTyVarInfo :: [Bool]
argTysTyVarInfo = (Either Exp Exp -> Bool) -> [Either Exp Exp] -> [Bool]
forall a b. (a -> b) -> [a] -> [b]
map Either Exp Exp -> Bool
forall l r. Either l r -> Bool
isRight [Either Exp Exp]
ess
argsWithTyVar, argsWithoutTyVar :: [Name]
(argsWithTyVar :: [Name]
argsWithTyVar, argsWithoutTyVar :: [Name]
argsWithoutTyVar) = [Bool] -> [Name] -> ([Name], [Name])
forall a. [Bool] -> [a] -> ([a], [a])
partitionByList [Bool]
argTysTyVarInfo [Name]
args
conExpQ :: Q Exp
conExpQ :: Q Exp
conExpQ
| [Name] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Name]
argsWithTyVar
= [Q Exp] -> Q Exp
appsE (Name -> Q Exp
conE Name
conNameQ Exp -> [Q Exp] -> [Q Exp]
forall a. a -> [a] -> [a]
:(Name -> Q Exp) -> [Name] -> [Q Exp]
forall a b. (a -> b) -> [a] -> [b]
map Name -> Q Exp
varE [Name]
argsWithoutTyVar)
| Bool
otherwise = do
[Name]
bs <- String -> Int -> Q [Name]
newNameList "b" (Int -> Q [Name]) -> Int -> Q [Name]
forall a b. (a -> b) -> a -> b
$ [Name] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Name]
args
let bs' :: [Name]
bs' = [Bool] -> [Name] -> [Name]
forall a. [Bool] -> [a] -> [a]
filterByList [Bool]
argTysTyVarInfo [Name]
bs
vars :: [Q Exp]
vars = [Bool] -> [Q Exp] -> [Q Exp] -> [Q Exp]
forall a. [Bool] -> [a] -> [a] -> [a]
filterByLists [Bool]
argTysTyVarInfo
((Name -> Q Exp) -> [Name] -> [Q Exp]
forall a b. (a -> b) -> [a] -> [b]
map Name -> Q Exp
varE [Name]
bs) ((Name -> Q Exp) -> [Name] -> [Q Exp]
forall a b. (a -> b) -> [a] -> [b]
map Name -> Q Exp
varE [Name]
args)
[PatQ] -> Q Exp -> Q Exp
lamE ((Name -> PatQ) -> [Name] -> [PatQ]
forall a b. (a -> b) -> [a] -> [b]
map Name -> PatQ
varP [Name]
bs') ([Q Exp] -> Q Exp
appsE (Name -> Q Exp
conE Name
conNameQ Exp -> [Q Exp] -> [Q Exp]
forall a. a -> [a] -> [a]
:[Q Exp]
vars))
Exp
conExp <- Q Exp
conExpQ
let go :: [Exp] -> Exp
go :: [Exp] -> Exp
go [] = Name -> Exp
VarE Name
pureValName Exp -> Exp -> Exp
`AppE` Exp
conExp
go [e :: Exp
e] = Name -> Exp
VarE Name
fmapValName Exp -> Exp -> Exp
`AppE` Exp
conExp Exp -> Exp -> Exp
`AppE` Exp
e
go (e1 :: Exp
e1:e2 :: Exp
e2:es :: [Exp]
es) = (Exp -> Exp -> Exp) -> Exp -> [Exp] -> Exp
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\se1 :: Exp
se1 se2 :: Exp
se2 -> Maybe Exp -> Exp -> Maybe Exp -> Exp
InfixE (Exp -> Maybe Exp
forall a. a -> Maybe a
Just Exp
se1) (Name -> Exp
VarE Name
apValName) (Exp -> Maybe Exp
forall a. a -> Maybe a
Just Exp
se2))
(Name -> Exp
VarE Name
liftA2ValName Exp -> Exp -> Exp
`AppE` Exp
conExp Exp -> Exp -> Exp
`AppE` Exp
e1 Exp -> Exp -> Exp
`AppE` Exp
e2) [Exp]
es
Exp -> Q Exp
forall (m :: * -> *) a. Monad m => a -> m a
return (Exp -> Q Exp)
-> ([Either Exp Exp] -> Exp) -> [Either Exp Exp] -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Exp] -> Exp
go ([Exp] -> Exp)
-> ([Either Exp Exp] -> [Exp]) -> [Either Exp Exp] -> Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Either Exp Exp] -> [Exp]
forall a b. [Either a b] -> [b]
rights ([Either Exp Exp] -> Q Exp) -> [Either Exp Exp] -> Q Exp
forall a b. (a -> b) -> a -> b
$ [Either Exp Exp]
ess
biFunEmptyCase :: BiFun -> Name -> Name -> Q Exp
biFunEmptyCase :: BiFun -> Name -> Name -> Q Exp
biFunEmptyCase biFun :: BiFun
biFun z :: Name
z value :: Name
value =
Q Exp -> Q Exp -> BiFun -> Name -> Q Exp
biFunTrivial Q Exp
emptyCase
(Name -> Q Exp
varE Name
pureValName Q Exp -> Q Exp -> Q Exp
`appE` Q Exp
emptyCase)
BiFun
biFun Name
z
where
emptyCase :: Q Exp
emptyCase :: Q Exp
emptyCase = Q Exp -> [MatchQ] -> Q Exp
caseE (Name -> Q Exp
varE Name
value) []
biFunNoCons :: BiFun -> Name -> Name -> Q Exp
biFunNoCons :: BiFun -> Name -> Name -> Q Exp
biFunNoCons biFun :: BiFun
biFun z :: Name
z value :: Name
value =
Q Exp -> Q Exp -> BiFun -> Name -> Q Exp
biFunTrivial Q Exp
seqAndError
(Name -> Q Exp
varE Name
pureValName Q Exp -> Q Exp -> Q Exp
`appE` Q Exp
seqAndError)
BiFun
biFun Name
z
where
seqAndError :: Q Exp
seqAndError :: Q Exp
seqAndError = Q Exp -> Q Exp -> Q Exp
appE (Name -> Q Exp
varE Name
seqValName) (Name -> Q Exp
varE Name
value) Q Exp -> Q Exp -> Q Exp
`appE`
Q Exp -> Q Exp -> Q Exp
appE (Name -> Q Exp
varE Name
errorValName)
(String -> Q Exp
stringE (String -> Q Exp) -> String -> Q Exp
forall a b. (a -> b) -> a -> b
$ "Void " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Name -> String
nameBase (BiFun -> Name
biFunName BiFun
biFun))
biFunTrivial :: Q Exp -> Q Exp -> BiFun -> Name -> Q Exp
biFunTrivial :: Q Exp -> Q Exp -> BiFun -> Name -> Q Exp
biFunTrivial bimapE :: Q Exp
bimapE bitraverseE :: Q Exp
bitraverseE biFun :: BiFun
biFun z :: Name
z = BiFun -> Q Exp
go BiFun
biFun
where
go :: BiFun -> Q Exp
go :: BiFun -> Q Exp
go Bimap = Q Exp
bimapE
go Bifoldr = Name -> Q Exp
varE Name
z
go BifoldMap = Name -> Q Exp
varE Name
memptyValName
go Bitraverse = Q Exp
bitraverseE