module Database.MetaHDBC.OdbcInferTypes
    ( dbInferTypes, strictList
    )
where
import Database.HDBC
import Database.HDBC.ODBC
dbInferTypes :: String                            
             -> String                            
             -> IO ([SqlColDesc], [SqlColDesc])   
dbInferTypes dsn sqlExpr =
    do c <- connectODBC dsn                                 `catchSql` connectError
       (paramInfo', description') <- getQueryInfo c sqlExpr `catchSql` queryInfoError
       
       paramInfo <- strictList paramInfo'
       description <- strictList description'
       let desc = map snd description
       
       
       
       
       
       return (paramInfo, desc)
    where
      connectError e   = fail ("Could not connect to: " ++ dsn ++ ".\n" ++
                               "Error message ODBC: " ++ seErrorMsg e)
      queryInfoError e = fail ("Error while getting type information from the database server.\n" ++
                               "Error message from database: " ++ seErrorMsg e ++
                               "\nThe error orcurred while preparing:\n" ++
                               sqlExpr ++ "\n")
strictList :: [a] -> IO [a]
strictList [] = return []
strictList ys = (last ys) `seq` (return ys)