{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
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 consName patStr = eadtPattern' consName patStr Nothing False
eadtInfixPattern
:: Name
-> String
-> Q [Dec]
eadtInfixPattern consName patStr = eadtPattern' consName patStr Nothing True
eadtPatternT
:: Name
-> String
-> Q Type
-> Q [Dec]
eadtPatternT consName patStr qtype =
eadtPattern' consName patStr (Just qtype) False
eadtInfixPatternT
:: Name
-> String
-> Q Type
-> Q [Dec]
eadtInfixPatternT consName patStr qtype =
eadtPattern' consName patStr (Just qtype) True
eadtPattern'
:: Name
-> String
-> Maybe (Q Type)
-> Bool
-> Q [Dec]
eadtPattern' consName patStr mEadtTy isInfix = do
let patName = mkName patStr
typ <- reify consName >>= \case
DataConI _ t _ -> return t
_ -> fail $ show consName ++ " isn't a data constructor"
case typ of
ForallT tvs _ tys -> do
let getConArity = \case
_ :->: b -> 1 + getConArity b
_ -> 0
conArity = getConArity tys
conArgs <- replicateM conArity (newName "c")
let vf = mkName "Haskus.Utils.EADT.VF"
args <- if not isInfix
then return (PrefixPatSyn conArgs)
else case conArgs of
[x,y] -> return (InfixPatSyn x y)
xs -> fail $ "Infix pattern should have exactly two parameters (found " ++ show (length xs) ++ ")"
let pat = PatSynD patName args ImplBidir
(ConP vf [ConP consName (fmap VarP conArgs)])
let
getConTyp (_ :->: b) = getConTyp b
getConTyp (AppT a _) = a
getConTyp _ = error "Invalid constructor type"
conTyp = getConTyp tys
tyToTyList = AppT ListT (AppT (AppT ArrowT StarT) StarT)
KindedTV e StarT = last tvs
(newTvs,eadtTy,ctx) <- do
xsName <- newName "xs"
let
xs = VarT xsName
xsTy = KindedTV xsName tyToTyList
eadtXs <- [t| EADT $(return xs) |]
prd <- [t| $(return conTyp) :<: $(return xs) |]
prd2 <- [t| $(return (VarT e)) ~ $(return eadtXs) |]
case mEadtTy of
Nothing -> return ([xsTy],eadtXs,[prd,prd2])
Just ty -> do
ty' <- ty
let (tvs',ty'',ctx') = case ty' of
ForallT tvs'' ctx'' t -> (tvs'',t,ctx'')
_ -> ([],ty',[])
prd3 <- [t| $(return ty'') ~ $(return eadtXs) |]
return (xsTy:tvs',ty'',prd:prd2:prd3:ctx')
let
tvs' = tvs ++ newTvs
go (VarT x :->: b)
| x == e = eadtTy :->: go b
go (a :->: b) = a :->: go b
go _ = eadtTy
t' = go tys
let sig = PatSynSigD patName (ForallT tvs' ctx t')
return [sig,pat]
_ -> fail $ show consName ++ "'s type doesn't have a free variable, it can't be a functor"
pattern (:->:) :: Type -> Type -> Type
pattern a :->: b = AppT (AppT ArrowT a) b