[Haskell-cafe] Oracle Sessions in Takusen
Dmitry Olshansky
olshanskydr at gmail.com
Wed Jun 1 16:44:10 CEST 2011
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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110601/5e949692/attachment.htm>
More information about the Haskell-Cafe
mailing list