[Haskell-cafe] Strange error with HDBC-odbc and MySQL

Justin Bailey jgbailey at gmail.com
Thu Dec 25 02:15:20 EST 2008


I have run into a weird bug with HDBC-odbc that only occurs on my unix
system. When I execute a select which returns more than 435 rows twice
in the same process, the second execution fails with this error
message:

  SQL error: SqlError {seState = "[\"HYT00\"]", seNativeError = -1,
seErrorMsg = "connectODBC/sqlDriverConnect: [\"1045:
[unixODBC][MySQL][ODBC 3.51 Driver]Access denied for user
'dummy'@'localhost' (using password: NO)\"]"}

I think HDBC-odbc is at fault because the same query works fine from
ruby. In both cases the unixODBC library is used. isql (the unixODBC
command line utility) also has no problem. I have these software
packages installed:

  ghc 6.8.3
  HDBC 1.1.5
  HDBC-odbc 1.1.4.4
  unixODBC - 2.2.11
  MySQL - 5.0.38
  Linux - 2.6.16-xenU

The program below demonstrates the problem. It does require a table
with 500+ rows. On most production servers, information_schema.columns
will usually do the trick.

\begin{code}
import System.Environment
import Database.HDBC
import Database.HDBC.ODBC
import System.IO (hPutStrLn, stderr)
import qualified Data.ByteString.Lazy.Char8 as L

-- Execute with DNS name as only argument. E.g.:
--   ./TestMain localdb
main = do
  [dsn] <- getArgs
  testMatches dsn
  testMatches dsn

testMatches dsn = do
  let handler e = do
        hPutStrLn stderr ("SQL error: " ++ show e)

      -- Execute a statement and return all the rows
      getAllRows conn sql = do
        stmt <- prepare conn sql
        _ <- execute stmt []
        fetchAllRows' stmt

  handleSql handler $ do
    conn <- connectODBC $ "dsn=" ++ dsn
      -- 435 rows works fine, but not 445.
    rows <- getAllRows conn "select 1 from information_schema.columns limit 445"
    let evaledRows = filter (\[id] -> (fromSql id) /= (-1 :: Int)) rows
    putStrLn $ "Got " ++ show (length evaledRows)
\end{code}


More information about the Haskell-Cafe mailing list