-
We're currently using Here's my translation of our hasql effect: import Effectful
import Effectful.Dispatch.Dynamic
import Effectful.Error.Static
import Effectful.Reader.Static
import Hasql.Pool (Pool, UsageError, use)
import Hasql.Session (Session)
data Hasql :: Effect where
RunSession :: Session a -> Hasql m a
type instance DispatchOf Hasql = Dynamic
runSession :: (Hasql :> es) => Session a -> Eff es a
runSession = send . RunSession
runHasqlIO ::
forall es a.
( IOE :> es,
Reader Pool :> es,
Error UsageError :> es
) =>
Eff (Hasql : es) a ->
Eff es a
runHasqlIO = interpret $ \_ -> \case
RunSession session -> do
pool <- ask @Pool
r <- liftIO $ use pool session
either throwError pure r Here's an example demonstrating its usage: data User
userDecoder :: D.Row User
userDecoder = undefined
userEncoder :: E.Params User
userEncoder = undefined
insertUser_ :: Statement User Int32
insertUser_ = undefined
findUserById_ :: Statement Int32 (Maybe User)
findUserById_ = undefined
findUserById :: Int32 -> Session (Maybe User)
findUserById = undefined
insertUser :: User -> Session Int32
insertUser = undefined
createUser :: (Hasql :> es) => User -> Eff es Int32
createUser user = undefined
findUser :: (Hasql :> es) => Int32 -> Eff es (Maybe User)
findUser userId = undefined
newUser :: User
newUser = undefined
exampleApp :: (Hasql :> es) => Eff es (Maybe User)
exampleApp = do
userId <- createUser newUser
findUser userId Given the setup above, I'd like to ask if it's advisable to encapsulate the Currently running the effect would look something like that: run :: Pool -> Eff [Hasql, Reader Pool, Error UsageError, IOE] a -> IO (Either (CallStack, UsageError) a)
run pool = runEff . runError @UsageError . runReader pool . runHasqlIO
runWithErrorHandler :: Pool -> (CallStack -> UsageError -> Eff '[IOE] a) -> Eff [Hasql, Reader Pool, Error UsageError, IOE] a -> IO a
runWithErrorHandler pool errHandler = runEff . runErrorWith @UsageError errHandler . runReader pool . runHasqlIO |
Beta Was this translation helpful? Give feedback.
Replies: 1 comment 2 replies
-
Looks good to me 👍 You might want to include
I'd not include runHasqlIO ::
forall es a.
( IOE :> es,
Error UsageError :> es
) =>
Eff (Hasql : es) a ->
Eff es a
runHasqlIO pool = interpret $ \_ -> \case
RunSession session -> do
r <- liftIO $ use pool session
either throwError pure r since I don't think you'll use As for the error handling, you can have a look at #149, it has some pondering that might be helpful, especially this comment. If you do this, then it would be import Effectful
import Effectful.Dispatch.Dynamic
import Effectful.Error.Static
import Effectful.Reader.Static
import Hasql.Pool (Pool, UsageError, use)
import Hasql.Session (Session)
data Hasql :: Effect where
RunSession :: Error UsageError :> es => Session a -> Hasql (Eff es) a
type instance DispatchOf Hasql = Dynamic
runSession :: (HasCallStack, Error UsageError :> es, Hasql :> es) => Session a -> Eff es a
runSession = send . RunSession
runHasqlIO ::
forall es a.
( IOE :> es,
) =>
Pool ->
Eff (Hasql : es) a ->
Eff es a
runHasqlIO pool = interpret $ \env -> \case
RunSession session -> do
r <- liftIO $ use pool session
localSeqUnlift env $ \unlift -> unlift $ do
either throwError pure r The difference is that now you don't need the |
Beta Was this translation helpful? Give feedback.
Looks good to me 👍 You might want to include
HasCallStack
constraint in the signature ofrunSession
to be able to get accurate stack traces in case of errors.I'd not include
Reader
at all and just pass pool as a parameter torunHasqlIO
:since I don't think you'll use
local
from outside to modify the pool?A…