[Haskell-cafe] Oracle Sessions in Takusen

Kevin Quick quick at sparq.org
Thu Jun 2 19:35:51 CEST 2011


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  
<olshanskydr at gmail.com> wrote:

> 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



More information about the Haskell-Cafe mailing list