
I forgot to add a couple of things. First, you mentioned the unknown exception. If you were to replace the "main =" line with "main = handleSqlError $ ", then you would find a more useful error message. That will cause HDBC to automatically transform any uncaught HDBC exception into a standard Haskell I/O error. You can't do as much with it programmatically that way, but it will autoamtically be displayed in a useful fashion. Second, you could make sure you always get it right with regard to when to disconnect. For instance: main = handleSqlError $ bracket (DB.connectODBC "DSN=test") (DB.disconnect) procdb procdb dbh = do res <- DB.getTables dbh print (show ((concat . intersperse ", ") res)) bracket is defined in Control.Exception. While HDBC will automatically clean up connections when a HDBC Connection is garbage-collected, this is probably the most correct way to use it anyway, and is analogous to the example in the GHC library reference: bracket (openFile "filename" ReadMode) (hClose) (\handle -> do { ... }) It will ensure that DB.disconnect is always called, either after your code completes, or after an uncaught exception. But moreover, you isolate all of your code that requires the Connection within a single function (or functions that it calls). The Connection does not escape the bracket, so there is no danger you might use it after it has been closed. It may be a useful idiom for you if you are struggling with synchronization issues. You can also consider it for use with HDBC Statements, regular disk files, etc. Note that the following is NOT correct: bracket (connectAndReadTables) (printTables) (disconnect) -- John On Mon, Oct 09, 2006 at 04:01:02PM -0600, Tim Smith wrote:
"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.
-- John Goerzen Author, Foundations of Python Network Programming http://www.amazon.com/exec/obidos/tg/detail/-/1590593715