[Haskell-cafe]
Re: Strictness, order of IO operations: NewCGI & HDBC
Tim Smith
trangayesi at gmail.com
Mon Oct 9 18:01:02 EDT 2006
Hello, Haskell Cafe.
I posted a question a while ago about this, but didn't receive any
responses. I'd like to try again. I've got a test case which uses
John Goerzen's HDBC.ODBC. The problem I have is that it appears too
lazy - using the results of a query after disconnecting causes an
"unknown exception". If I use the results before disconnecting, it
works fine.
module Main
where
import Data.List (intersperse)
import qualified Database.HDBC as DB
import Database.HDBC.ODBC (connectODBC)
main :: IO ()
main =
do
dbh <- connectODBC "DSN=test"
res <- DB.getTables dbh
-- print (show ((concat . intersperse ", ") res))
DB.disconnect dbh
print (show ((concat . intersperse ", ") res))
Compiling and running this will show:
$ ./db-discon
db-discon: unknown exception
If I uncomment the first 'print' line, then it works as expected:
$ ./db-discon
"\"d1, foo, odbctest\""
"\"d1, foo, odbctest\""
Am I just expecting the wrong thing from Haskell? Is there a
technical reason why HDBC can't synchronize the IO so that everything
is resolved before the disconnect? Or is this a bug in HDBC?
Thanks,
Timothy
--
If you're not part of the solution, you're part of the precipitate.
More information about the Haskell-Cafe
mailing list