
Hello, Could anyone explain strange behavior of Takusen with OracleDB (OraClient 11.x)? Several sequential sessions give "Seqmentation Fault" error. In case of nested sessions it works well. {-# LANGUAGE ScopedTypeVariables #-} module Main where import Database.Oracle.Enumerator import Control.Monad(replicateM) import Control.Monad.Trans(liftIO) main = do {- -- This gives an Segmentation Fault for the second session replicateM 2 (do res <- withSession (connect "x" "x" "x") (do doQuery (sql "SELECT dummy FROM dual") (\(d::String) (_::Maybe String) -> result' $ Just d) Nothing ) print res ) -} -- This is works well withSession (connect "x" "x" "x") (do r1 <- doQuery (sql "SELECT dummy FROM dual") (\(d::String) (_::Maybe String) -> result' $ Just d) Nothing liftIO $ print r1 liftIO $ withSession (connect "x" "x" "x") (do r2 <- doQuery (sql "SELECT dummy FROM dual") (\(d::String) (_::Maybe String) -> result' $ Just d) Nothing liftIO $ print r2 ) ) Best regards, Dmitry

On Wed, Jun 1, 2011 at 7:44 AM, Dmitry Olshansky
Hello,
Could anyone explain strange behavior of Takusen with OracleDB (OraClient 11.x)? Several sequential sessions give "Seqmentation Fault" error. In case of nested sessions it works well.
I'm CC'ing the takusen email list so that Oleg and Alistair will see your message. They are more familiar with the Oracle support than I am. Nothing in your code strikes me as an obvious error. Jason

On Wed, Jun 1, 2011 at 9:01 AM, Jason Dagit
I'm CC'ing the takusen email list so that Oleg and Alistair will see your message. They are more familiar with the Oracle support than I am.
I should really link to the original message: http://www.haskell.org/pipermail/haskell-cafe/2011-June/092602.html

Dmitry,
I'm not directly familiar with Takusen or its use with OracleDB, but I
would hazard a guess that the withSession is doing FFI resource management
and that resources obtained inside the withSession environment are no
longer valid outside of the withSession.
If this is the case then I would expect the following to work:
replicateM 2 (do
withSession (connect "x" "x" "x") (do
res <- doQuery ...
liftIO $ print res
)
)
If this really is the case then it seems that withSession shouldn't be
exporting FFI-based resources.
-KQ
On Wed, 01 Jun 2011 07:44:10 -0700, Dmitry Olshansky
Hello,
Could anyone explain strange behavior of Takusen with OracleDB (OraClient 11.x)? Several sequential sessions give "Seqmentation Fault" error. In case of nested sessions it works well.
{-# LANGUAGE ScopedTypeVariables #-} module Main where import Database.Oracle.Enumerator import Control.Monad(replicateM) import Control.Monad.Trans(liftIO) main = do {- -- This gives an Segmentation Fault for the second session
replicateM 2 (do res <- withSession (connect "x" "x" "x") (do doQuery (sql "SELECT dummy FROM dual") (\(d::String) (_::Maybe String) -> result' $ Just d) Nothing ) print res ) -}
-- This is works well
withSession (connect "x" "x" "x") (do r1 <- doQuery (sql "SELECT dummy FROM dual") (\(d::String) (_::Maybe String) -> result' $ Just d) Nothing liftIO $ print r1 liftIO $ withSession (connect "x" "x" "x") (do r2 <- doQuery (sql "SELECT dummy FROM dual") (\(d::String) (_::Maybe String) -> result' $ Just d) Nothing liftIO $ print r2 ) ) Best regards, Dmitry
-- -KQ

On 3 June 2011 05:35, Kevin Quick
Dmitry,
I'm not directly familiar with Takusen or its use with OracleDB, but I would hazard a guess that the withSession is doing FFI resource management and that resources obtained inside the withSession environment are no longer valid outside of the withSession.
If this is the case then I would expect the following to work:
replicateM 2 (do withSession (connect "x" "x" "x") (do res <- doQuery ... liftIO $ print res ) )
If this really is the case then it seems that withSession shouldn't be exporting FFI-based resources.
-KQ
You're right, withSession shouldn't be exporting FFI obtained resources, and I don't think it does. There are some known issues with the Oracle code, where it allows buffers to fall out of reference (and thus be gc'd) before the C libs have finished with them, thereby causing segfaults. The known problems are around bind variable buffers, so this looks like a new issue. At least we're collecting a nice corpus of programs that cause the Oracle backend to fail :-) I'd love to have more time to work on it... If you don't need the Oracle-specific functionality, for now I suggest using the ODBC driver as a substitute, as this seems to be (more) reliable. Alistair
participants (4)
-
Alistair Bayley
-
Dmitry Olshansky
-
Jason Dagit
-
Kevin Quick