I am trying to implement the interpreter of in higher-order effect.
I have a base effect:
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fplugin=Polysemy.Plugin #-}
module Hetchr.Commons.Cat where
import Polysemy
import Polysemy.Internal.Tactics
data In = In
newtype Out = Out Int
deriving stock (Show)
deriving newtype (Num)
data TargetE (m :: Type -> Type) (a :: Type) where
ActA :: In -> TargetE m Out
makeSem ''TargetE
runTargetE :: InterpreterFor TargetE e
runTargetE = interpret $ \case
ActA _ -> return $ Out 1
And an higher-order effect:
data ProxyE (m :: Type -> Type) (a :: Type) where
ProxyA :: (In -> m Out) -> ProxyE m Out
FunPA :: In -> ProxyE m Out
makeSem ''ProxyE
Which intends to be used as:
main :: IO ()
main = print =<< runM (runTargetE $ runProxyE $ proxyA funPA)
I have an helper for implementation:
proxyAImpl :: Member TargetE r => (In -> Sem r Out) -> Sem r Out
proxyAImpl f = ( ) <$> f In <*> actA In
But, I struggle with the implementation:
runProxyE :: Member TargetE r => InterpreterFor ProxyE r
runProxyE = interpretH $ \case
ProxyA f -> do
f' <- bindT f
??? proxyAImpl f'
FunPA x -> liftT $ actA x
I have not found a lot of examples, and I struggle with the types, any hints?
CodePudding user response:
Actually, if I understood correctly, you cannot create that kind of interpreters, with implementations without polymorphic types, such that I have to tweak my code to:
proxyAImpl :: (Functor f, Member TargetE r) => (In -> Sem r (f Out)) -> Sem r (f Out)
proxyAImpl f = do
left <- f In
right <- actA In
return $ fmap ( right) left
runProxyE :: Member TargetE r => InterpreterFor ProxyE r
runProxyE = interpretH $ \case
ProxyA f -> proxyAImpl (runTSimple . f)
FunPA x -> liftT $ actA x