valderman / selda

A type-safe, high-level SQL library for Haskell
https://selda.link
MIT License
478 stars 58 forks source link

SQL Errors running two queries over the same connection - Change MonadSelda to support Pool #108

Closed seanhess closed 5 years ago

seanhess commented 5 years ago

I get errors when running two queries at the exact same time over the same connection. (This happened using servant, and a web page that loads two pieces of information at once, over a local connection). (The errors actually displayed on the same line, with every other character corresponding to a different error)

DbError fromSql: RowID column with non-int"
DbError "unable to submit query to server"

Since the code worked fine when loading separately, I suspected it had something to do with using the same SeldaConnection for two queries at once. I started to refactor my app to use Data.Pool. However, MonadSelda only asks for a seldaConnection and doesn't allow for any way of knowing when someone is done using it.

I was forced to create a duplicate of MonadSelda, which I called Selda, that looked like this:

{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
module Control.Monad.Selda
  ( Selda(..)
  , insert
  , query
  , deleteFrom
  , tryCreateTable
  ) where

import Control.Monad.IO.Class (MonadIO)
import qualified Database.Selda as Selda
import Database.Selda hiding (insert, query, deleteFrom, tryCreateTable)
import Database.Selda.Backend (runSeldaT, SeldaConnection)

class (MonadIO m, MonadMask m) => Selda m where
    withConnection :: (SeldaConnection -> m a) -> m a

query q          = withConnection $ runSeldaT $ Selda.query q
insert t vs      = withConnection $ runSeldaT $ Selda.insert t vs
deleteFrom t p   = withConnection $ runSeldaT $ Selda.deleteFrom t p
tryCreateTable t = withConnection $ runSeldaT $ Selda.tryCreateTable t
-- there are more functions we need to export here. 

Would it make sense to change MonadSelda to be more like this? It would then make it trivial to implement MonadSelda with Data.Pool, and prevent the error.

If MonadSelda is defined this way, you can make a custom instance using Pool like this:

data AppState = AppState
    { dbConn :: Pool SeldaConnection
    }

type AppM = ReaderT AppState IO

instance Selda AppM where
    withConnection action = do
      pool <- asks dbConn
      Pool.withResource pool action

It's impossible to write this instance for a Pool and MonadSelda as defined today.

seanhess commented 5 years ago

Also, I'd be happy to create a pull request with the above if you want to go this direction. Just let me know.

tungd commented 5 years ago

Why not creating ‘MonadSelda’ directly?

instance MonadSelda AppM where
  seldaConnection = ...
seanhess commented 5 years ago

@tungd I was getting an error when two threads wanted to use the connection at the same time. I think the messages were getting mixed together.

So I wanted to use Data.Pool, and it's not possible to write a MonadSelda instance for Data.Pool

http://hackage.haskell.org/package/resource-pool-0.2.3.2/docs/Data-Pool.html

instance MonadSelda AppM where
   seldaConnection = do
      pool <- asks dbConn
      (a, _) <- Pool.takeResource pool
      -- You can't call Pool.takeResource without later calling Pool.putResource!
      -- Even, better, we should use Pool.withResource
      pure a
tungd commented 5 years ago

I see no problem at all, I've been using Selda in combination for quite a few projects and have not encountered the issue you listed. This is how I usually do it, hope it would help in your case:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Control.Monad.Catch (MonadCatch, MonadMask, MonadThrow)
import Control.Monad.Except
import Data.Has
import Data.Pool
import Database.Selda
import Database.Selda.Backend
import RIO
import Servant

type Env = (LogFunc, Pool SeldaConnection)

newtype App a = App { runApp_ :: ReaderT Env (ExceptT ServantErr IO) a }
  deriving ( Applicative, Functor, Monad
           , MonadReader Env
           , MonadIO
           , MonadError ServantErr
           , MonadThrow, MonadCatch, MonadMask
           )

instance MonadSelda App where
  seldaConnection = do
    pool <- asks getter
    liftIO $ withResource pool pure

runApp :: Env -> App a -> Servant.Handler a
runApp env = Servant.Handler . flip runReaderT env . runApp_

main = do
  (logger, closeLogger) <- newLogFunc =<< logOptionsHandle stdout True
  pool <- createPool (pgOpen' Nothing "") seldaClose 1 2 4
  serve api (hoistServer api (runApp (logger, pool)) handler)
  closeLogger
seanhess commented 5 years ago

Wait, if you do that, you return the connection outside of withConnection. It’s already been checked back in to the pool and could be used by another resource. Or destroyed. Pool can’t guarantee you’re the only one using it or that it’s still valid!

Perhaps you haven’t run into any issues yet but I’m fairly certain doing this will cause major issues once your application has many concurrent connections.

Le dim. 13 janv. 2019 à 10:09, Tung Dao notifications@github.com a écrit :

I see no problem at all, I've been using Selda in combination for quite a few projects and have not encountered the issue you listed. This is how I usually do it, hope it would help in your case:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}import Control.Monad.Catch (MonadCatch, MonadMask, MonadThrow)import Control.Monad.Exceptimport Data.Hasimport Data.Poolimport Database.Seldaimport Database.Selda.Backendimport RIOimport Servant type Env = (LogFunc, Pool SeldaConnection) newtype App a = App { runApp :: ReaderT Env (ExceptT ServantErr IO) a } deriving ( Applicative, Functor, Monad , MonadReader Env , MonadIO , MonadError ServantErr , MonadThrow, MonadCatch, MonadMask ) instance MonadSelda App where seldaConnection = do pool <- asks getter liftIO $ withResource pool pure runApp :: Env -> App a -> Servant.Handler a runApp env = Servant.Handler . flip runReaderT env . runApp

main = do (logger, closeLogger) <- newLogFunc =<< logOptionsHandle stdout True pool <- createPool (pgOpen' Nothing "") seldaClose 1 2 4 serve api (hoistServer api runApp (logger, pool) handler) closeLogger

— You are receiving this because you authored the thread. Reply to this email directly, view it on GitHub https://github.com/valderman/selda/issues/108#issuecomment-453847125, or mute the thread https://github.com/notifications/unsubscribe-auth/AAA_eQFUdPw35BRrIOOwttTD1_Y1xx2_ks5vC2g2gaJpZM4Z8HAK .

valderman commented 5 years ago

Potentially using a different database connection for each call to a Selda primitive is unsafe in the general case. Any computation making use of transaction runs the risk of calling BEGIN TRANSACTION, the queries within the transaction, and COMMIT/ROLLBACK on different connections, causing runtime errors in the best case and silently doing the wrong thing in the worst case. Some Selda functions (mainly upserts) use transactions internally, and so are also not safe under this scheme.

This problem is not unavoidable: you could use wrapTransaction to grab a connection at the beginning of a transaction and always use that connection until the transaction is done. This complicates your instance slightly though, so it might be easier to implement pooling on the level of your MonadSelda instance's runner function instead.

That said, I like the proposed API better than the current one, so switching to it is probably a good idea regardless.

valderman commented 5 years ago

The new API should support this new use case nicely. Do remember, however, to implement the transact method for connection pooling MonadSelda instances, or you're going to have horrible data consistency bugs when using transactions.