Hello -

I have a typeclass like this ..

class (Monad m) => DB m where
    query :: Text -> m (Maybe Account) 
    ...

and an instance that uses persistent and sqlite ..

instance (MonadIO m) => DB (SqlPersistT m) where
  query ano = get (AccountKey ano)
  ..

Now I want to move this to using an effect system - Polysemy ..

data DB m a where
    Query :: Text -> DB m (Maybe Account)
    ...

makeSem ''DB

which generates the functions .. I need some help figuring out the type of the function that interpretes the above .. An initial intuition is this ..

runDB :: Member SqlPersistT r => Sem (DB ': r) a -> Sem r a
runDB = interpret $ \case
  Query ano -> get (AccountKey ano)


which doesn't compile .. errors out with ..

Couldn't match type ‘Control.Monad.Trans.Reader.ReaderT backend0 m0 (Maybe Account)’
                 with ‘Sem r (Maybe Account)’
  Expected type: Sem r x
    Actual type: Control.Monad.Trans.Reader.ReaderT
                   backend0 m0 (Maybe Account)
• In the expression: get (AccountKey accountNo)

I think I am missing something here. The type of interpret is shown as 
interpret :: (forall x (m :: * -> *). DB m x -> Sem r x) -> Sem (DB : r) a -> Sem r a

But how do I translate the SqlPersistT part ? Any help will be appreciated.

regards.
--