{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE CPP #-}
module Haskus.Utils.EADT.TH
( eadtPattern
, eadtInfixPattern
, eadtPatternT
, eadtInfixPatternT
)
where
import Language.Haskell.TH
import Control.Monad
import Haskus.Utils.EADT
eadtPattern
:: Name
-> String
-> Q [Dec]
eadtPattern :: Name -> String -> Q [Dec]
eadtPattern Name
consName String
patStr = Name -> String -> Maybe (Q Type) -> Bool -> Q [Dec]
eadtPattern' Name
consName String
patStr Maybe (Q Type)
forall a. Maybe a
Nothing Bool
False
eadtInfixPattern
:: Name
-> String
-> Q [Dec]
eadtInfixPattern :: Name -> String -> Q [Dec]
eadtInfixPattern Name
consName String
patStr = Name -> String -> Maybe (Q Type) -> Bool -> Q [Dec]
eadtPattern' Name
consName String
patStr Maybe (Q Type)
forall a. Maybe a
Nothing Bool
True
eadtPatternT
:: Name
-> String
-> Q Type
-> Q [Dec]
eadtPatternT :: Name -> String -> Q Type -> Q [Dec]
eadtPatternT Name
consName String
patStr Q Type
qtype =
Name -> String -> Maybe (Q Type) -> Bool -> Q [Dec]
eadtPattern' Name
consName String
patStr (Q Type -> Maybe (Q Type)
forall a. a -> Maybe a
Just Q Type
qtype) Bool
False
eadtInfixPatternT
:: Name
-> String
-> Q Type
-> Q [Dec]
eadtInfixPatternT :: Name -> String -> Q Type -> Q [Dec]
eadtInfixPatternT Name
consName String
patStr Q Type
qtype =
Name -> String -> Maybe (Q Type) -> Bool -> Q [Dec]
eadtPattern' Name
consName String
patStr (Q Type -> Maybe (Q Type)
forall a. a -> Maybe a
Just Q Type
qtype) Bool
True
eadtPattern'
:: Name
-> String
-> Maybe (Q Type)
-> Bool
-> Q [Dec]
eadtPattern' :: Name -> String -> Maybe (Q Type) -> Bool -> Q [Dec]
eadtPattern' Name
consName String
patStr Maybe (Q Type)
mEadtTy Bool
isInfix = do
let patName :: Name
patName = String -> Name
mkName String
patStr
Type
typ <- Name -> Q Info
reify Name
consName Q Info -> (Info -> 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
>>= \case
DataConI Name
_ Type
t Name
_ -> Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
t
Info
_ -> String -> Q Type
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Q Type) -> String -> Q Type
forall a b. (a -> b) -> a -> b
$ Name -> String
forall a. Show a => a -> String
show Name
consName String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" isn't a data constructor"
case Type
typ of
ForallT [TyVarBndr Specificity]
tvs Cxt
_ Type
tys -> do
let getConArity :: Type -> Int
getConArity = \case
AppT (AppT Type
ArrowT Type
_a) Type
b -> Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Type -> Int
getConArity Type
b
#if MIN_VERSION_base(4,15,0)
AppT (AppT (AppT Type
MulArrowT Type
_m) Type
_a) Type
b -> Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Type -> Int
getConArity Type
b
#endif
Type
_ -> Int
0
conArity :: Int
conArity = Type -> Int
getConArity Type
tys
[Name]
conArgs <- Int -> Q Name -> Q [Name]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
conArity (String -> Q Name
forall (m :: * -> *). Quote m => String -> m Name
newName String
"c")
let vf :: Name
vf = String -> Name
mkName String
"Haskus.Utils.EADT.VF"
PatSynArgs
args <- if Bool -> Bool
not Bool
isInfix
then PatSynArgs -> Q PatSynArgs
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Name] -> PatSynArgs
PrefixPatSyn [Name]
conArgs)
else case [Name]
conArgs of
[Name
x,Name
y] -> PatSynArgs -> Q PatSynArgs
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> Name -> PatSynArgs
InfixPatSyn Name
x Name
y)
[Name]
xs -> String -> Q PatSynArgs
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Q PatSynArgs) -> String -> Q PatSynArgs
forall a b. (a -> b) -> a -> b
$ String
"Infix pattern should have exactly two parameters (found " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show ([Name] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Name]
xs) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
let pat :: Dec
pat = Name -> PatSynArgs -> PatSynDir -> Pat -> Dec
PatSynD Name
patName PatSynArgs
args PatSynDir
ImplBidir
#if MIN_VERSION_base(4,16,0)
(Name -> Cxt -> [Pat] -> Pat
ConP Name
vf [] [Name -> Cxt -> [Pat] -> Pat
ConP Name
consName [] ((Name -> Pat) -> [Name] -> [Pat]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Name -> Pat
VarP [Name]
conArgs)])
#else
(ConP vf [ConP consName (fmap VarP conArgs)])
#endif
let
getConTyp :: Type -> Type
getConTyp (AppT (AppT Type
ArrowT Type
_a) Type
b) = Type -> Type
getConTyp Type
b
#if MIN_VERSION_base(4,15,0)
getConTyp (AppT (AppT (AppT Type
MulArrowT Type
_m) Type
_a) Type
b) = Type -> Type
getConTyp Type
b
#endif
getConTyp (AppT Type
a Type
_) = Type
a
getConTyp Type
_ = String -> Type
forall a. HasCallStack => String -> a
error String
"Invalid constructor type"
conTyp :: Type
conTyp = Type -> Type
getConTyp Type
tys
tyToTyList :: Type
tyToTyList = Type -> Type -> Type
AppT Type
ListT (Type -> Type -> Type
AppT (Type -> Type -> Type
AppT Type
ArrowT Type
StarT) Type
StarT)
#if MIN_VERSION_base(4,16,0)
e :: Name
e = case [TyVarBndr Specificity] -> TyVarBndr Specificity
forall a. HasCallStack => [a] -> a
last [TyVarBndr Specificity]
tvs of
KindedTV Name
nm Specificity
_ Type
_ -> Name
nm
PlainTV Name
nm Specificity
_ -> Name
nm
#elif MIN_VERSION_base(4,15,0)
KindedTV e _ StarT = last tvs
#else
KindedTV e StarT = last tvs
#endif
([TyVarBndr Specificity]
newTvs,Type
eadtTy,Cxt
ctx) <- do
Name
xsName <- String -> Q Name
forall (m :: * -> *). Quote m => String -> m Name
newName String
"xs"
let
xs :: Type
xs = Name -> Type
VarT Name
xsName
#if MIN_VERSION_base(4,15,0)
xsTy :: TyVarBndr Specificity
xsTy = Name -> Specificity -> Type -> TyVarBndr Specificity
forall flag. Name -> flag -> Type -> TyVarBndr flag
KindedTV Name
xsName Specificity
SpecifiedSpec Type
tyToTyList
#else
xsTy = KindedTV xsName tyToTyList
#endif
Type
eadtXs <- [t| EADT $(Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
xs) |]
Type
prd <- [t| $(Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
conTyp) :<: $(Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
xs) |]
Type
prd2 <- [t| $(Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> Type
VarT Name
e)) ~ $(Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
eadtXs) |]
case Maybe (Q Type)
mEadtTy of
Maybe (Q Type)
Nothing -> ([TyVarBndr Specificity], Type, Cxt)
-> Q ([TyVarBndr Specificity], Type, Cxt)
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return ([TyVarBndr Specificity
xsTy],Type
eadtXs,[Type
prd,Type
prd2])
Just Q Type
ty -> do
Type
ty' <- Q Type
ty
let ([TyVarBndr Specificity]
tvs',Type
ty'',Cxt
ctx') = case Type
ty' of
ForallT [TyVarBndr Specificity]
tvs'' Cxt
ctx'' Type
t -> ([TyVarBndr Specificity]
tvs'',Type
t,Cxt
ctx'')
Type
_ -> ([],Type
ty',[])
Type
prd3 <- [t| $(Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
ty'') ~ $(Type -> Q Type
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return Type
eadtXs) |]
([TyVarBndr Specificity], Type, Cxt)
-> Q ([TyVarBndr Specificity], Type, Cxt)
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return (TyVarBndr Specificity
xsTyTyVarBndr Specificity
-> [TyVarBndr Specificity] -> [TyVarBndr Specificity]
forall a. a -> [a] -> [a]
:[TyVarBndr Specificity]
tvs',Type
ty'',Type
prdType -> Cxt -> Cxt
forall a. a -> [a] -> [a]
:Type
prd2Type -> Cxt -> Cxt
forall a. a -> [a] -> [a]
:Type
prd3Type -> Cxt -> Cxt
forall a. a -> [a] -> [a]
:Cxt
ctx')
let
tvs' :: [TyVarBndr Specificity]
tvs' = [TyVarBndr Specificity]
tvs [TyVarBndr Specificity]
-> [TyVarBndr Specificity] -> [TyVarBndr Specificity]
forall a. [a] -> [a] -> [a]
++ [TyVarBndr Specificity]
newTvs
go :: Type -> Type
go (AppT (AppT Type
ArrowT Type
a) Type
b)
| VarT Name
v <- Type
a
, Name
v Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
e = Type -> Type -> Type
AppT (Type -> Type -> Type
AppT Type
ArrowT Type
eadtTy) (Type -> Type
go Type
b)
| Bool
otherwise = Type -> Type -> Type
AppT (Type -> Type -> Type
AppT Type
ArrowT Type
a) (Type -> Type
go Type
b)
#if MIN_VERSION_base(4,15,0)
go (AppT (AppT (AppT Type
MulArrowT Type
m) Type
a) Type
b)
| VarT Name
v <- Type
a
, Name
v Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
e = Type -> Type -> Type
AppT (Type -> Type -> Type
AppT (Type -> Type -> Type
AppT Type
MulArrowT Type
m) Type
eadtTy) (Type -> Type
go Type
b)
| Bool
otherwise = Type -> Type -> Type
AppT (Type -> Type -> Type
AppT (Type -> Type -> Type
AppT Type
MulArrowT Type
m) Type
a) (Type -> Type
go Type
b)
#endif
go Type
_ = Type
eadtTy
t' :: Type
t' = Type -> Type
go Type
tys
let sig :: Dec
sig = Name -> Type -> Dec
PatSynSigD Name
patName ([TyVarBndr Specificity] -> Cxt -> Type -> Type
ForallT [TyVarBndr Specificity]
tvs' Cxt
ctx Type
t')
[Dec] -> Q [Dec]
forall a. a -> Q a
forall (m :: * -> *) a. Monad m => a -> m a
return [Dec
sig,Dec
pat]
Type
_ -> String -> Q [Dec]
forall a. String -> Q a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Q [Dec]) -> String -> Q [Dec]
forall a b. (a -> b) -> a -> b
$ Name -> String
forall a. Show a => a -> String
show Name
consName String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"'s type doesn't have a free variable, it can't be a functor"