Hi! Sorry for the late reply
The "direct" issue is that you're trying to use SqlPersistT as an effect (when using it as an argument to Member in runDB) - Member expects things that are "effects" (produced by polysemy).

If you're not going to be using runDB as an "intermediate" interpreter, but rather running it as a "final" interpreter (to actually run your program) you could instead use something like this:

runDB :: forall b. Members [Embed IO, Input (Pool SqlBackend)] r => SqlPersistT IO b -> Sem r b
runDB query = embed . runSqlPool query =<< input

to run your db queries in IO and embed the IO in the resulting effect stack (in this case by also having an input effect from which you can receive your connection pool)

On Fri, Feb 14, 2020 at 11:08 PM Debasish Ghosh <ghosh.debasish@gmail.com> wrote:
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.
--
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.