{-# LANGUAGE TemplateHaskell, CPP #-}
module Data.Express.Utils.TH
( reallyDeriveCascading
, deriveWhenNeeded
, deriveWhenNeededOrWarn
, typeConArgs
, typeConArgsThat
, typeConCascadingArgsThat
, normalizeType
, normalizeTypeUnits
, isInstanceOf
, isntInstanceOf
, typeArity
, typeConstructors
, isTypeSynonym
, typeSynonymType
, mergeIFns
, mergeI
, lookupValN
, showJustName
, typeConstructorsArgNames
, (|=>|)
, (|++|)
, whereI
, unboundVars
, toBounded
, toBoundedQ
, module Language.Haskell.TH
)
where
import Control.Monad
import Data.List
import Language.Haskell.TH
import Language.Haskell.TH.Lib
deriveWhenNeeded :: Name -> (Name -> DecsQ) -> Name -> DecsQ
deriveWhenNeeded :: Name -> (Name -> DecsQ) -> Name -> DecsQ
deriveWhenNeeded = Bool -> Name -> (Name -> DecsQ) -> Name -> DecsQ
deriveWhenNeededX Bool
False
deriveWhenNeededOrWarn :: Name -> (Name -> DecsQ) -> Name -> DecsQ
deriveWhenNeededOrWarn :: Name -> (Name -> DecsQ) -> Name -> DecsQ
deriveWhenNeededOrWarn = Bool -> Name -> (Name -> DecsQ) -> Name -> DecsQ
deriveWhenNeededX Bool
True
deriveWhenNeededX :: Bool -> Name -> (Name -> DecsQ) -> Name -> DecsQ
deriveWhenNeededX :: Bool -> Name -> (Name -> DecsQ) -> Name -> DecsQ
deriveWhenNeededX Bool
warnExisting Name
cls Name -> DecsQ
reallyDerive Name
t = do
Bool
is <- Name
t Name -> Name -> Q Bool
`isInstanceOf` Name
cls
if Bool
is
then do
Bool -> Q () -> Q ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
warnExisting
(String -> Q ()
reportWarning (String -> Q ()) -> String -> Q ()
forall a b. (a -> b) -> a -> b
$ String
"Instance " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Name -> String
showJustName Name
cls String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Name -> String
showJustName Name
t
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" already exists, skipping derivation")
[Dec] -> DecsQ
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return []
else
Name -> DecsQ
reallyDerive Name
t
showJustName :: Name -> String
showJustName :: Name -> String
showJustName = String -> String
forall a. [a] -> [a]
reverse (String -> String) -> (Name -> String) -> Name -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'.') (String -> String) -> (Name -> String) -> Name -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
forall a. [a] -> [a]
reverse (String -> String) -> (Name -> String) -> Name -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> String
forall a. Show a => a -> String
show
reallyDeriveCascading :: Name -> (Name -> DecsQ) -> Name -> DecsQ
reallyDeriveCascading :: Name -> (Name -> DecsQ) -> Name -> DecsQ
reallyDeriveCascading Name
cls Name -> DecsQ
reallyDerive Name
t =
[Dec] -> DecsQ
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Dec] -> DecsQ) -> ([[Dec]] -> [Dec]) -> [[Dec]] -> DecsQ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Dec]] -> [Dec]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
([[Dec]] -> DecsQ) -> Q [[Dec]] -> DecsQ
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (Name -> DecsQ) -> [Name] -> Q [[Dec]]
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 Name -> DecsQ
reallyDerive
([Name] -> Q [[Dec]]) -> Q [Name] -> Q [[Dec]]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (Name -> Q Bool) -> [Name] -> Q [Name]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM ((Bool -> Bool) -> Q Bool -> Q Bool
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> Bool
not (Q Bool -> Q Bool) -> (Name -> Q Bool) -> Name -> Q Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Q Bool
isTypeSynonym)
([Name] -> Q [Name]) -> Q [Name] -> Q [Name]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Name] -> Q [Name]
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Name] -> Q [Name]) -> ([Name] -> [Name]) -> [Name] -> Q [Name]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name
tName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:) ([Name] -> [Name]) -> ([Name] -> [Name]) -> [Name] -> [Name]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> [Name] -> [Name]
forall a. Eq a => a -> [a] -> [a]
delete Name
t
([Name] -> Q [Name]) -> Q [Name] -> Q [Name]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Name
t Name -> (Name -> Q Bool) -> Q [Name]
`typeConCascadingArgsThat` (Name -> Name -> Q Bool
`isntInstanceOf` Name
cls)
typeConArgs :: Name -> Q [Name]
typeConArgs :: Name -> Q [Name]
typeConArgs Name
t = do
Bool
is <- Name -> Q Bool
isTypeSynonym Name
t
if Bool
is
then Type -> [Name]
typeConTs (Type -> [Name]) -> Q Type -> Q [Name]
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
typeSynonymType Name
t
else ([[Name]] -> [Name]
forall a. Ord a => [[a]] -> [a]
nubMerges ([[Name]] -> [Name])
-> ([(Name, [Type])] -> [[Name]]) -> [(Name, [Type])] -> [Name]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Type -> [Name]) -> [Type] -> [[Name]]
forall a b. (a -> b) -> [a] -> [b]
map Type -> [Name]
typeConTs ([Type] -> [[Name]])
-> ([(Name, [Type])] -> [Type]) -> [(Name, [Type])] -> [[Name]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Name, [Type]) -> [Type]) -> [(Name, [Type])] -> [Type]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Name, [Type]) -> [Type]
forall a b. (a, b) -> b
snd) ([(Name, [Type])] -> [Name]) -> Q [(Name, [Type])] -> Q [Name]
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Name -> Q [(Name, [Type])]
typeConstructors Name
t
where
typeConTs :: Type -> [Name]
typeConTs :: Type -> [Name]
typeConTs (AppT Type
t1 Type
t2) = Type -> [Name]
typeConTs Type
t1 [Name] -> [Name] -> [Name]
forall a. Ord a => [a] -> [a] -> [a]
`nubMerge` Type -> [Name]
typeConTs Type
t2
typeConTs (SigT Type
t Type
_) = Type -> [Name]
typeConTs Type
t
typeConTs (VarT Name
_) = []
typeConTs (ConT Name
n) = [Name
n]
#if __GLASGOW_HASKELL__ >= 800
typeConTs (InfixT Type
t1 Name
n Type
t2) = Type -> [Name]
typeConTs Type
t1 [Name] -> [Name] -> [Name]
forall a. Ord a => [a] -> [a] -> [a]
`nubMerge` Type -> [Name]
typeConTs Type
t2
typeConTs (UInfixT Type
t1 Name
n Type
t2) = Type -> [Name]
typeConTs Type
t1 [Name] -> [Name] -> [Name]
forall a. Ord a => [a] -> [a] -> [a]
`nubMerge` Type -> [Name]
typeConTs Type
t2
typeConTs (ParensT Type
t) = Type -> [Name]
typeConTs Type
t
#endif
typeConTs Type
_ = []
typeConArgsThat :: Name -> (Name -> Q Bool) -> Q [Name]
Name
t typeConArgsThat :: Name -> (Name -> Q Bool) -> Q [Name]
`typeConArgsThat` Name -> Q Bool
p = (Name -> Q Bool) -> [Name] -> Q [Name]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM Name -> Q Bool
p ([Name] -> Q [Name]) -> Q [Name] -> Q [Name]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Name -> Q [Name]
typeConArgs Name
t
typeConCascadingArgsThat :: Name -> (Name -> Q Bool) -> Q [Name]
Name
t typeConCascadingArgsThat :: Name -> (Name -> Q Bool) -> Q [Name]
`typeConCascadingArgsThat` Name -> Q Bool
p = do
[Name]
ts <- Name
t Name -> (Name -> Q Bool) -> Q [Name]
`typeConArgsThat` Name -> Q Bool
p
let p' :: Name -> Q Bool
p' Name
t' = (Name
t' Name -> [Name] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` Name
tName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:[Name]
ts Bool -> Bool -> Bool
&&) (Bool -> Bool) -> Q Bool -> Q Bool
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Name -> Q Bool
p Name
t'
[[Name]]
tss <- (Name -> Q [Name]) -> [Name] -> Q [[Name]]
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 (Name -> (Name -> Q Bool) -> Q [Name]
`typeConCascadingArgsThat` Name -> Q Bool
p') [Name]
ts
[Name] -> Q [Name]
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Name] -> Q [Name]) -> [Name] -> Q [Name]
forall a b. (a -> b) -> a -> b
$ [[Name]] -> [Name]
forall a. Ord a => [[a]] -> [a]
nubMerges ([Name]
ts[Name] -> [[Name]] -> [[Name]]
forall a. a -> [a] -> [a]
:[[Name]]
tss)
normalizeType :: Name -> Q (Type, [Type])
normalizeType :: Name -> Q (Type, [Type])
normalizeType Name
t = do
Int
ar <- Name -> Q Int
typeArity Name
t
[Type]
vs <- Int -> Q [Type]
newVarTs Int
ar
(Type, [Type]) -> Q (Type, [Type])
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Type -> Type -> Type) -> Type -> [Type] -> Type
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Type -> Type -> Type
AppT (Name -> Type
ConT Name
t) [Type]
vs, [Type]
vs)
where
newNames :: [String] -> Q [Name]
newNames :: [String] -> Q [Name]
newNames = (String -> Q Name) -> [String] -> Q [Name]
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 String -> Q Name
forall (m :: * -> *). Quote m => String -> m Name
newName
newVarTs :: Int -> Q [Type]
newVarTs :: Int -> Q [Type]
newVarTs Int
n = (Name -> Type) -> [Name] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map Name -> Type
VarT
([Name] -> [Type]) -> Q [Name] -> Q [Type]
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` [String] -> Q [Name]
newNames (Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
n ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> String) -> String -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Char -> String -> String
forall a. a -> [a] -> [a]
:[]) (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$ String -> String
forall a. HasCallStack => [a] -> [a]
cycle [Char
'a'..Char
'z'])
normalizeTypeUnits :: Name -> Q Type
normalizeTypeUnits :: Name -> Q Type
normalizeTypeUnits Name
t = do
Int
ar <- Name -> Q Int
typeArity Name
t
Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Type -> Type -> Type) -> Type -> [Type] -> Type
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Type -> Type -> Type
AppT (Name -> Type
ConT Name
t) (Int -> Type -> [Type]
forall a. Int -> a -> [a]
replicate Int
ar (Int -> Type
TupleT Int
0)))
isInstanceOf :: Name -> Name -> Q Bool
isInstanceOf :: Name -> Name -> Q Bool
isInstanceOf Name
tn Name
cl = do
Type
ty <- Name -> Q Type
normalizeTypeUnits Name
tn
Name -> [Type] -> Q Bool
isInstance Name
cl [Type
ty]
isntInstanceOf :: Name -> Name -> Q Bool
isntInstanceOf :: Name -> Name -> Q Bool
isntInstanceOf Name
tn = (Bool -> Bool) -> Q Bool -> Q Bool
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> Bool
not (Q Bool -> Q Bool) -> (Name -> Q Bool) -> Name -> Q Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Name -> Q Bool
isInstanceOf Name
tn
typeArity :: Name -> Q Int
typeArity :: Name -> Q Int
typeArity Name
t = (Info -> Int) -> Q Info -> Q Int
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Info -> Int
arity (Q Info -> Q Int) -> Q Info -> Q Int
forall a b. (a -> b) -> a -> b
$ Name -> Q Info
reify Name
t
where
arity :: Info -> Int
arity = [TyVarBndr ()] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([TyVarBndr ()] -> Int) -> (Info -> [TyVarBndr ()]) -> Info -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Info -> [TyVarBndr ()]
args
#if __GLASGOW_HASKELL__ < 800
args (TyConI (DataD _ _ ks _ _)) = ks
args (TyConI (NewtypeD _ _ ks _ _)) = ks
#else
args :: Info -> [TyVarBndr ()]
args (TyConI (DataD [Type]
_ Name
_ [TyVarBndr ()]
ks Maybe Type
_ [Con]
_ [DerivClause]
_)) = [TyVarBndr ()]
ks
args (TyConI (NewtypeD [Type]
_ Name
_ [TyVarBndr ()]
ks Maybe Type
_ Con
_ [DerivClause]
_)) = [TyVarBndr ()]
ks
#endif
args (TyConI (TySynD Name
_ [TyVarBndr ()]
ks Type
_)) = [TyVarBndr ()]
ks
args Info
_ = String -> String -> [TyVarBndr ()]
forall a. String -> String -> a
errorOn String
"typeArity"
(String -> [TyVarBndr ()]) -> String -> [TyVarBndr ()]
forall a b. (a -> b) -> a -> b
$ String
"neither newtype nor data nor type synonym: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Name -> String
forall a. Show a => a -> String
show Name
t
typeConstructors :: Name -> Q [(Name,[Type])]
typeConstructors :: Name -> Q [(Name, [Type])]
typeConstructors Name
t = (Info -> [(Name, [Type])]) -> Q Info -> Q [(Name, [Type])]
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Con -> (Name, [Type])) -> [Con] -> [(Name, [Type])]
forall a b. (a -> b) -> [a] -> [b]
map Con -> (Name, [Type])
normalize ([Con] -> [(Name, [Type])])
-> (Info -> [Con]) -> Info -> [(Name, [Type])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Info -> [Con]
cons) (Q Info -> Q [(Name, [Type])]) -> Q Info -> Q [(Name, [Type])]
forall a b. (a -> b) -> a -> b
$ Name -> Q Info
reify Name
t
where
#if __GLASGOW_HASKELL__ < 800
cons (TyConI (DataD _ _ _ cs _)) = cs
cons (TyConI (NewtypeD _ _ _ c _)) = [c]
#else
cons :: Info -> [Con]
cons (TyConI (DataD [Type]
_ Name
_ [TyVarBndr ()]
_ Maybe Type
_ [Con]
cs [DerivClause]
_)) = [Con]
cs
cons (TyConI (NewtypeD [Type]
_ Name
_ [TyVarBndr ()]
_ Maybe Type
_ Con
c [DerivClause]
_)) = [Con
c]
#endif
cons Info
_ = String -> String -> [Con]
forall a. String -> String -> a
errorOn String
"typeConstructors"
(String -> [Con]) -> String -> [Con]
forall a b. (a -> b) -> a -> b
$ String
"neither newtype nor data: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Name -> String
forall a. Show a => a -> String
show Name
t
normalize :: Con -> (Name, [Type])
normalize (NormalC Name
n [BangType]
ts) = (Name
n,(BangType -> Type) -> [BangType] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map BangType -> Type
forall a b. (a, b) -> b
snd [BangType]
ts)
normalize (RecC Name
n [VarBangType]
ts) = (Name
n,(VarBangType -> Type) -> [VarBangType] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map VarBangType -> Type
forall {a} {b} {c}. (a, b, c) -> c
trd [VarBangType]
ts)
normalize (InfixC BangType
t1 Name
n BangType
t2) = (Name
n,[BangType -> Type
forall a b. (a, b) -> b
snd BangType
t1,BangType -> Type
forall a b. (a, b) -> b
snd BangType
t2])
normalize Con
_ = String -> String -> (Name, [Type])
forall a. String -> String -> a
errorOn String
"typeConstructors"
(String -> (Name, [Type])) -> String -> (Name, [Type])
forall a b. (a -> b) -> a -> b
$ String
"unexpected unhandled case when called with " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Name -> String
forall a. Show a => a -> String
show Name
t
trd :: (a, b, c) -> c
trd (a
x,b
y,c
z) = c
z
isTypeSynonym :: Name -> Q Bool
isTypeSynonym :: Name -> Q Bool
isTypeSynonym = (Info -> Bool) -> Q Info -> Q Bool
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Info -> Bool
is (Q Info -> Q Bool) -> (Name -> Q Info) -> Name -> Q Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Q Info
reify
where
is :: Info -> Bool
is (TyConI (TySynD Name
_ [TyVarBndr ()]
_ Type
_)) = Bool
True
is Info
_ = Bool
False
typeSynonymType :: Name -> Q Type
typeSynonymType :: Name -> Q Type
typeSynonymType Name
t = (Info -> Type) -> Q Info -> Q Type
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Info -> Type
typ (Q Info -> Q Type) -> Q Info -> Q Type
forall a b. (a -> b) -> a -> b
$ Name -> Q Info
reify Name
t
where
typ :: Info -> Type
typ (TyConI (TySynD Name
_ [TyVarBndr ()]
_ Type
t')) = Type
t'
typ Info
_ = String -> String -> Type
forall a. String -> String -> a
errorOn String
"typeSynonymType" (String -> Type) -> String -> Type
forall a b. (a -> b) -> a -> b
$ String
"not a type synonym: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Name -> String
forall a. Show a => a -> String
show Name
t
(|=>|) :: Cxt -> DecsQ -> DecsQ
[Type]
c |=>| :: [Type] -> DecsQ -> DecsQ
|=>| DecsQ
qds = (Dec -> Dec) -> [Dec] -> [Dec]
forall a b. (a -> b) -> [a] -> [b]
map (Dec -> [Type] -> Dec
=>++ [Type]
c) ([Dec] -> [Dec]) -> DecsQ -> DecsQ
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` DecsQ
qds
where
#if __GLASGOW_HASKELL__ < 800
(InstanceD c ts ds) =>++ c' = InstanceD (c++c') ts ds
#else
(InstanceD Maybe Overlap
o [Type]
c Type
ts [Dec]
ds) =>++ :: Dec -> [Type] -> Dec
=>++ [Type]
c' = Maybe Overlap -> [Type] -> Type -> [Dec] -> Dec
InstanceD Maybe Overlap
o ([Type]
c[Type] -> [Type] -> [Type]
forall a. [a] -> [a] -> [a]
++[Type]
c') Type
ts [Dec]
ds
#endif
Dec
d =>++ [Type]
_ = Dec
d
(|++|) :: DecsQ -> DecsQ -> DecsQ
|++| :: DecsQ -> DecsQ -> DecsQ
(|++|) = ([Dec] -> [Dec] -> [Dec]) -> DecsQ -> DecsQ -> DecsQ
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 [Dec] -> [Dec] -> [Dec]
forall a. [a] -> [a] -> [a]
(++)
mergeIFns :: DecsQ -> DecsQ
mergeIFns :: DecsQ -> DecsQ
mergeIFns = ([Dec] -> [Dec]) -> DecsQ -> DecsQ
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] -> [Dec]
forall a b. (a -> b) -> [a] -> [b]
map Dec -> Dec
m')
where
#if __GLASGOW_HASKELL__ < 800
m' (InstanceD c ts ds) = InstanceD c ts [foldr1 m ds]
#else
m' :: Dec -> Dec
m' (InstanceD Maybe Overlap
o [Type]
c Type
ts [Dec]
ds) = Maybe Overlap -> [Type] -> Type -> [Dec] -> Dec
InstanceD Maybe Overlap
o [Type]
c Type
ts [(Dec -> Dec -> Dec) -> [Dec] -> Dec
forall a. (a -> a -> a) -> [a] -> a
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 Dec -> Dec -> Dec
m [Dec]
ds]
#endif
FunD Name
n [Clause]
cs1 m :: Dec -> Dec -> Dec
`m` FunD Name
_ [Clause]
cs2 = Name -> [Clause] -> Dec
FunD Name
n ([Clause]
cs1 [Clause] -> [Clause] -> [Clause]
forall a. [a] -> [a] -> [a]
++ [Clause]
cs2)
mergeI :: DecsQ -> DecsQ -> DecsQ
mergeI :: DecsQ -> DecsQ -> DecsQ
mergeI = ([Dec] -> [Dec] -> [Dec]) -> DecsQ -> DecsQ -> DecsQ
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 [Dec] -> [Dec] -> [Dec]
m
where
#if __GLASGOW_HASKELL__ < 800
[InstanceD c ts ds1] `m` [InstanceD _ _ ds2] = [InstanceD c ts (ds1 ++ ds2)]
#else
[InstanceD Maybe Overlap
o [Type]
c Type
ts [Dec]
ds1] m :: [Dec] -> [Dec] -> [Dec]
`m` [InstanceD Maybe Overlap
_ [Type]
_ Type
_ [Dec]
ds2] = [Maybe Overlap -> [Type] -> Type -> [Dec] -> Dec
InstanceD Maybe Overlap
o [Type]
c Type
ts ([Dec]
ds1 [Dec] -> [Dec] -> [Dec]
forall a. [a] -> [a] -> [a]
++ [Dec]
ds2)]
#endif
whereI :: DecsQ -> [Dec] -> DecsQ
DecsQ
qds whereI :: DecsQ -> [Dec] -> DecsQ
`whereI` [Dec]
w = ([Dec] -> [Dec]) -> DecsQ -> DecsQ
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] -> [Dec]
forall a b. (a -> b) -> [a] -> [b]
map (Dec -> [Dec] -> Dec
`aw` [Dec]
w)) DecsQ
qds
where
#if __GLASGOW_HASKELL__ < 800
aw (InstanceD c ts ds) w' = InstanceD c ts (ds++w')
#else
aw :: Dec -> [Dec] -> Dec
aw (InstanceD Maybe Overlap
o [Type]
c Type
ts [Dec]
ds) [Dec]
w' = Maybe Overlap -> [Type] -> Type -> [Dec] -> Dec
InstanceD Maybe Overlap
o [Type]
c Type
ts ([Dec]
ds[Dec] -> [Dec] -> [Dec]
forall a. [a] -> [a] -> [a]
++[Dec]
w')
#endif
aw Dec
d [Dec]
_ = Dec
d
nubMerge :: Ord a => [a] -> [a] -> [a]
nubMerge :: forall a. Ord a => [a] -> [a] -> [a]
nubMerge [] [a]
ys = [a]
ys
nubMerge [a]
xs [] = [a]
xs
nubMerge (a
x:[a]
xs) (a
y:[a]
ys) | a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
y = a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs [a] -> [a] -> [a]
forall a. Ord a => [a] -> [a] -> [a]
`nubMerge` (a
ya -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
ys)
| a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
y = a
y a -> [a] -> [a]
forall a. a -> [a] -> [a]
: (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
xs) [a] -> [a] -> [a]
forall a. Ord a => [a] -> [a] -> [a]
`nubMerge` [a]
ys
| Bool
otherwise = a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs [a] -> [a] -> [a]
forall a. Ord a => [a] -> [a] -> [a]
`nubMerge` [a]
ys
nubMerges :: Ord a => [[a]] -> [a]
nubMerges :: forall a. Ord a => [[a]] -> [a]
nubMerges = ([a] -> [a] -> [a]) -> [a] -> [[a]] -> [a]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr [a] -> [a] -> [a]
forall a. Ord a => [a] -> [a] -> [a]
nubMerge []
typeConstructorsArgNames :: Name -> Q [(Name,[Name])]
typeConstructorsArgNames :: Name -> Q [(Name, [Name])]
typeConstructorsArgNames Name
t = do
[(Name, [Type])]
cs <- Name -> Q [(Name, [Type])]
typeConstructors Name
t
[Q (Name, [Name])] -> Q [(Name, [Name])]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [ do [Name]
ns <- [Q Name] -> Q [Name]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [String -> Q Name
forall (m :: * -> *). Quote m => String -> m Name
newName String
"x" | Type
_ <- [Type]
ts]
(Name, [Name]) -> Q (Name, [Name])
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name
c,[Name]
ns)
| (Name
c,[Type]
ts) <- [(Name, [Type])]
cs ]
lookupValN :: String -> Q Name
lookupValN :: String -> Q Name
lookupValN String
s = do
Maybe Name
mn <- String -> Q (Maybe Name)
lookupValueName String
s
case Maybe Name
mn of
Just Name
n -> Name -> Q Name
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Name
n
Maybe Name
Nothing -> String -> Q Name
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Q Name) -> String -> Q Name
forall a b. (a -> b) -> a -> b
$ String
"lookupValN: cannot find " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
unboundVars :: Type -> [Name]
unboundVars :: Type -> [Name]
unboundVars (VarT Name
n) = [Name
n]
unboundVars (AppT Type
t1 Type
t2) = [Name] -> [Name] -> [Name]
forall a. Ord a => [a] -> [a] -> [a]
nubMerge (Type -> [Name]
unboundVars Type
t1) (Type -> [Name]
unboundVars Type
t2)
unboundVars (SigT Type
t Type
_) = Type -> [Name]
unboundVars Type
t
unboundVars (ForallT [TyVarBndr Specificity]
vs [Type]
_ Type
t) = Type -> [Name]
unboundVars Type
t [Name] -> [Name] -> [Name]
forall a. Eq a => [a] -> [a] -> [a]
\\ (TyVarBndr Specificity -> Name)
-> [TyVarBndr Specificity] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map TyVarBndr Specificity -> Name
forall {flag}. TyVarBndr flag -> Name
nm [TyVarBndr Specificity]
vs
where
#if __GLASGOW_HASKELL__ < 900
nm (PlainTV n) = n
nm (KindedTV n _) = n
#else
nm :: TyVarBndr flag -> Name
nm (PlainTV Name
n flag
_) = Name
n
nm (KindedTV Name
n flag
_ Type
_) = Name
n
#endif
unboundVars Type
_ = []
toBounded :: Type -> Type
#if __GLASGOW_HASKELL__ < 900
toBounded t = ForallT [PlainTV n | n <- unboundVars t] [] t
#else
toBounded :: Type -> Type
toBounded Type
t = [TyVarBndr Specificity] -> [Type] -> Type -> Type
ForallT [Name -> Specificity -> TyVarBndr Specificity
forall flag. Name -> flag -> TyVarBndr flag
PlainTV Name
n Specificity
SpecifiedSpec | Name
n <- Type -> [Name]
unboundVars Type
t] [] Type
t
#endif
toBoundedQ :: TypeQ -> TypeQ
toBoundedQ :: Q Type -> Q Type
toBoundedQ = (Type -> Type) -> Q Type -> Q Type
forall a b. (a -> b) -> Q a -> Q b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Type -> Type
toBounded
errorOn :: String -> String -> a
errorOn :: forall a. String -> String -> a
errorOn String
fn String
msg = String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"Data.Express.Derive.Utils." String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fn String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
msg