wxcore-0.10.1: wxHaskell is a portable and native GUI library for Haskell.ContentsIndex
Graphics.UI.WXCore.Db
Contents
Connection
Queries
Changes
Rows
Standard values
Generic values
Column information
Meta information
Data sources
Tables and columns
Dbms
Exceptions
Sql types
Internal
Description

This module provides convenient access to the database classes (Db) of wxWindows. These classes have been donated to the wxWindows library by Remstar International. (Note: these classes are not supported on MacOS X at the time of writing (november 2003)). These database objects support ODBC connections and have been tested with wxWindows on the following databases:

Oracle (v7, v8, v8i), Sybase (ASA and ASE), MS SQL Server (v7 - minimal testing), MS Access (97 and 2000), MySQL, DBase (IV, V) (using ODBC emulation), PostgreSQL, INFORMIX, VIRTUOSO, DB2, Interbase, Pervasive SQL .

The database functions also work with console applications and do not need to initialize the WXCore libraries.

The examples in this document are all based on the pubs database that is available in MS Access 97 and 'comma separated text' format from http://wxhaskell.sourceforge.net/download/pubs.zip. We assume that your system is configured in such a way that pubs is the datasource name of this database. (On Windows XP for example, this is done using the /start - settings - control panel - administrative tools - data sources (ODBC)/ menu.)

The available data sources on your system can be retrieved using dbGetDataSources. Here is an example from my system:

 *Main> dbGetDataSources >>= print
 [("pubs","Microsoft Access Driver (*.mdb)")]

Connections are established with the dbWithConnection call. It takes a datasource name, a user name, a password, and a function that is applied to the resulting database connection:

 dbWithConnection "pubs" "" "" (\db -> ...)

(Note that most database operations automatically raise a database exception (DbError) on failure. These exceptions can be caught using catchDbError.)

The resulting database (Db) can be queried using dbQuery. The dbQuery call applies a function to each row (DbRow) in the result set. Using calls like dbRowGetValue and dbRowGetString, you can retrieve the values from the result rows.

 printAuthorNames
   = do names <- dbWithConnection "pubs" "" "" (\db ->
                  dbQuery db "SELECT au_fname, au_lname FROM authors" 
                    (\row -> do fname <- dbRowGetString row "au_fname"
                                lname <- dbRowGetString row "au_lname"
                                return (fname ++ " " ++ lname)
                    ))
        putStrLn (unlines names)

The overloaded function dbRowGetValue can retrieve any kind of database value (DbValue) (except for strings since standard Haskell98 does not support overlapping instances). For most datatypes, there is also a non-overloaded version, like dbRowGetInteger and dbRowGetString. The dbRowGet... functions are also available as dbRowGet...Mb, which returns Nothing when a NULL value is encountered (instead of raising an exception), for example, dbRowGetIntegerMb and dbRowGetStringMb.

If necessary, more data types can be supported by defining your own DbValue instances and using dbRowGetValue to retrieve those values.

You can use dbRowGetColumnInfo to retrieve column information (ColumnInfo) about a particular column, for example, to retieve the number of decimal digits in a currency value.

Complete meta information about a particular data source can be retrieved using dbGetDataSourceInfo, that takes a data source name, user name, and password as arguments, and returns a DbInfo structure:

 *Main> dbGetDataSourceInfo "pubs" "" "" >>= print
 catalog: C:\daan\temp\db\pubs2
 schema :
 tables :
  ...
  8: name   : authors
     type   : TABLE
     remarks:
     columns:
      1: name   : au_id
         index  : 1
         type   : VARCHAR
         size   : 12
         sqltp  : SqlVarChar
         type id: DbVarChar
         digits : 0
         prec   : 0
         remarks: Author Key
         pkey   : 0
         ptables: []
         fkey   : 0
         ftable :
      2: name   : au_fname
         index  : 2
         type   : VARCHAR
  ...

Changes to the database can be made using dbExecute. All these actions are done in transaction mode and are only comitted when wrapped with a dbTransaction.

Synopsis
dbWithConnection :: DataSourceName -> String -> String -> (Db () -> IO b) -> IO b
dbConnect :: DataSourceName -> String -> String -> IO (Db ())
dbDisconnect :: Db a -> IO ()
dbWithDirectConnection :: DataSourceName -> String -> String -> (Db () -> IO b) -> IO b
dbConnectDirect :: DataSourceName -> String -> String -> IO (Db ())
dbQuery :: Db a -> String -> (DbRow a -> IO b) -> IO [b]
dbQuery_ :: Db a -> String -> (DbRow a -> IO b) -> IO ()
dbExecute :: Db a -> String -> IO ()
dbTransaction :: Db a -> IO b -> IO b
data DbRow a = DbRow Db a [ColumnInfo]
dbRowGetString :: DbRow a -> ColumnName -> IO String
dbRowGetStringMb :: DbRow a -> ColumnName -> IO (Maybe String)
dbRowGetBool :: DbRow a -> ColumnName -> IO Bool
dbRowGetBoolMb :: DbRow a -> ColumnName -> IO (Maybe Bool)
dbRowGetInt :: DbRow a -> ColumnName -> IO Int
dbRowGetIntMb :: DbRow a -> ColumnName -> IO (Maybe Int)
dbRowGetDouble :: DbRow a -> ColumnName -> IO Double
dbRowGetDoubleMb :: DbRow a -> ColumnName -> IO (Maybe Double)
dbRowGetInteger :: DbRow a -> ColumnName -> IO Integer
dbRowGetIntegerMb :: DbRow a -> ColumnName -> IO (Maybe Integer)
dbRowGetClockTime :: DbRow a -> ColumnName -> IO ClockTime
dbRowGetClockTimeMb :: DbRow a -> ColumnName -> IO (Maybe ClockTime)
class DbValue a where
dbValueRead :: Db b -> ColumnInfo -> IO (Maybe a)
toSqlValue :: a -> String
dbRowGetValue :: DbValue b => DbRow a -> ColumnName -> IO b
dbRowGetValueMb :: DbValue b => DbRow a -> ColumnName -> IO (Maybe b)
dbRowGetColumnInfo :: DbRow a -> ColumnName -> IO ColumnInfo
dbRowGetColumnInfos :: DbRow a -> [ColumnInfo]
type DataSourceName = String
dbGetDataSources :: IO [(DataSourceName, String)]
dbGetDataSourceInfo :: DataSourceName -> String -> String -> IO DbInfo
dbGetDataSourceTableInfo :: DataSourceName -> TableName -> String -> String -> IO TableInfo
type TableName = String
type ColumnName = String
type ColumnIndex = Int
data DbInfo = DbInfo {
dbCatalog :: String
dbSchema :: String
dbTables :: [TableInfo]
}
data TableInfo = TableInfo {
tableName :: TableName
tableType :: String
tableRemarks :: String
tableColumns :: [ColumnInfo]
}
data ColumnInfo = ColumnInfo {
columnName :: ColumnName
columnIndex :: ColumnIndex
columnSize :: Int
columnNullable :: Bool
columnType :: DbType
columnSqlType :: SqlType
columnTypeName :: String
columnRemarks :: String
columnDecimalDigits :: Int
columnNumPrecRadix :: Int
columnForeignKey :: Int
columnPrimaryKey :: Int
columnForeignKeyTableName :: TableName
columnPrimaryKeyTableNames :: [TableName]
}
dbGetInfo :: Db a -> IO DbInfo
dbGetTableInfo :: Db a -> TableName -> IO TableInfo
dbGetTableColumnInfos :: Db a -> TableName -> IO [ColumnInfo]
dbGetColumnInfos :: Db a -> IO [ColumnInfo]
data Dbms
= DbmsORACLE
| DbmsSYBASE_ASA
| DbmsSYBASE_ASE
| DbmsMS_SQL_SERVER
| DbmsMY_SQL
| DbmsPOSTGRES
| DbmsACCESS
| DbmsDBASE
| DbmsINFORMIX
| DbmsVIRTUOSO
| DbmsDB2
| DbmsINTERBASE
| DbmsPERVASIVE_SQL
| DbmsXBASE_SEQUITER
| DbmsUNIDENTIFIED
dbGetDbms :: Db a -> IO Dbms
data DbError = DbError {
dbErrorMsg :: String
dbDataSource :: DataSourceName
dbErrorCode :: DbStatus
dbNativeCode :: Int
dbSqlState :: String
}
catchDbError :: IO a -> (DbError -> IO a) -> IO a
raiseDbError :: DbError -> IO a
dbHandleExn :: Db a -> IO Bool -> IO ()
dbCheckExn :: Db a -> IO ()
dbRaiseExn :: Db a -> IO b
dbGetErrorMessages :: Db a -> IO [String]
dbGetDbStatus :: Db a -> IO DbStatus
data DbStatus
= DB_FAILURE
| DB_SUCCESS
| DB_ERR_NOT_IN_USE
| DB_ERR_GENERAL_WARNING
| DB_ERR_DISCONNECT_ERROR
| DB_ERR_DATA_TRUNCATED
| DB_ERR_PRIV_NOT_REVOKED
| DB_ERR_INVALID_CONN_STR_ATTR
| DB_ERR_ERROR_IN_ROW
| DB_ERR_OPTION_VALUE_CHANGED
| DB_ERR_NO_ROWS_UPD_OR_DEL
| DB_ERR_MULTI_ROWS_UPD_OR_DEL
| DB_ERR_WRONG_NO_OF_PARAMS
| DB_ERR_DATA_TYPE_ATTR_VIOL
| DB_ERR_UNABLE_TO_CONNECT
| DB_ERR_CONNECTION_IN_USE
| DB_ERR_CONNECTION_NOT_OPEN
| DB_ERR_REJECTED_CONNECTION
| DB_ERR_CONN_FAIL_IN_TRANS
| DB_ERR_COMM_LINK_FAILURE
| DB_ERR_INSERT_VALUE_LIST_MISMATCH
| DB_ERR_DERIVED_TABLE_MISMATCH
| DB_ERR_STRING_RIGHT_TRUNC
| DB_ERR_NUMERIC_VALUE_OUT_OF_RNG
| DB_ERR_ERROR_IN_ASSIGNMENT
| DB_ERR_DATETIME_FLD_OVERFLOW
| DB_ERR_DIVIDE_BY_ZERO
| DB_ERR_STR_DATA_LENGTH_MISMATCH
| DB_ERR_INTEGRITY_CONSTRAINT_VIOL
| DB_ERR_INVALID_CURSOR_STATE
| DB_ERR_INVALID_TRANS_STATE
| DB_ERR_INVALID_AUTH_SPEC
| DB_ERR_INVALID_CURSOR_NAME
| DB_ERR_SYNTAX_ERROR_OR_ACCESS_VIOL
| DB_ERR_DUPLICATE_CURSOR_NAME
| DB_ERR_SERIALIZATION_FAILURE
| DB_ERR_SYNTAX_ERROR_OR_ACCESS_VIOL2
| DB_ERR_OPERATION_ABORTED
| DB_ERR_UNSUPPORTED_FUNCTION
| DB_ERR_NO_DATA_SOURCE
| DB_ERR_DRIVER_LOAD_ERROR
| DB_ERR_SQLALLOCENV_FAILED
| DB_ERR_SQLALLOCCONNECT_FAILED
| DB_ERR_SQLSETCONNECTOPTION_FAILED
| DB_ERR_NO_DATA_SOURCE_DLG_PROHIB
| DB_ERR_DIALOG_FAILED
| DB_ERR_UNABLE_TO_LOAD_TRANSLATION_DLL
| DB_ERR_DATA_SOURCE_NAME_TOO_LONG
| DB_ERR_DRIVER_NAME_TOO_LONG
| DB_ERR_DRIVER_KEYWORD_SYNTAX_ERROR
| DB_ERR_TRACE_FILE_ERROR
| DB_ERR_TABLE_OR_VIEW_ALREADY_EXISTS
| DB_ERR_TABLE_NOT_FOUND
| DB_ERR_INDEX_ALREADY_EXISTS
| DB_ERR_INDEX_NOT_FOUND
| DB_ERR_COLUMN_ALREADY_EXISTS
| DB_ERR_COLUMN_NOT_FOUND
| DB_ERR_NO_DEFAULT_FOR_COLUMN
| DB_ERR_GENERAL_ERROR
| DB_ERR_MEMORY_ALLOCATION_FAILURE
| DB_ERR_INVALID_COLUMN_NUMBER
| DB_ERR_PROGRAM_TYPE_OUT_OF_RANGE
| DB_ERR_SQL_DATA_TYPE_OUT_OF_RANGE
| DB_ERR_OPERATION_CANCELLED
| DB_ERR_INVALID_ARGUMENT_VALUE
| DB_ERR_FUNCTION_SEQUENCE_ERROR
| DB_ERR_OPERATION_INVALID_AT_THIS_TIME
| DB_ERR_INVALID_TRANS_OPERATION_CODE
| DB_ERR_NO_CURSOR_NAME_AVAIL
| DB_ERR_INVALID_STR_OR_BUF_LEN
| DB_ERR_DESCRIPTOR_TYPE_OUT_OF_RANGE
| DB_ERR_OPTION_TYPE_OUT_OF_RANGE
| DB_ERR_INVALID_PARAM_NO
| DB_ERR_INVALID_SCALE_VALUE
| DB_ERR_FUNCTION_TYPE_OUT_OF_RANGE
| DB_ERR_INF_TYPE_OUT_OF_RANGE
| DB_ERR_COLUMN_TYPE_OUT_OF_RANGE
| DB_ERR_SCOPE_TYPE_OUT_OF_RANGE
| DB_ERR_NULLABLE_TYPE_OUT_OF_RANGE
| DB_ERR_UNIQUENESS_OPTION_TYPE_OUT_OF_RANGE
| DB_ERR_ACCURACY_OPTION_TYPE_OUT_OF_RANGE
| DB_ERR_DIRECTION_OPTION_OUT_OF_RANGE
| DB_ERR_INVALID_PRECISION_VALUE
| DB_ERR_INVALID_PARAM_TYPE
| DB_ERR_FETCH_TYPE_OUT_OF_RANGE
| DB_ERR_ROW_VALUE_OUT_OF_RANGE
| DB_ERR_CONCURRENCY_OPTION_OUT_OF_RANGE
| DB_ERR_INVALID_CURSOR_POSITION
| DB_ERR_INVALID_DRIVER_COMPLETION
| DB_ERR_INVALID_BOOKMARK_VALUE
| DB_ERR_DRIVER_NOT_CAPABLE
| DB_ERR_TIMEOUT_EXPIRED
| DB_ERR_FETCH_NULL
| DB_ERR_INVALID_TABLE_NAME
| DB_ERR_INVALID_COLUMN_NAME
| DB_ERR_TYPE_MISMATCH
| DB_ERR_CONNECT
data DbType
= DbUnknown
| DbVarChar
| DbInteger
| DbFloat
| DbDate
| DbBlob
data SqlType
= SqlChar
| SqlNumeric
| SqlDecimal
| SqlInteger
| SqlSmallInt
| SqlFloat
| SqlReal
| SqlDouble
| SqlDate
| SqlTime
| SqlTimeStamp
| SqlVarChar
| SqlBit
| SqlBinary
| SqlVarBinary
| SqlBigInt
| SqlTinyInt
| SqlUnknown Int
toSqlTableName :: Db a -> TableName -> TableName
toSqlColumnName :: Db a -> ColumnName -> ColumnName
toSqlString :: String -> String
toSqlTime :: ClockTime -> String
toSqlDate :: ClockTime -> String
toSqlTimeStamp :: ClockTime -> String
dbStringRead :: Db a -> ColumnInfo -> IO (Maybe String)
dbGetDataNull :: Db a -> (Ptr CInt -> IO Bool) -> IO Bool
toSqlType :: Int -> SqlType
fromSqlType :: SqlType -> Int
Connection
dbWithConnection :: DataSourceName -> String -> String -> (Db () -> IO b) -> IO b
Open a (cached) connection and automatically close it after the computation returns. Takes the name of the data source, a user name, and password as arguments. Raises a database exception (DbError) when the connection fails.
dbConnect :: DataSourceName -> String -> String -> IO (Db ())
(dbConnect name userId password) creates a (cached) connection to a data source name. Raises a database exception (DbError) when the connection fails. Use dbDisconnect to close the connection.
dbDisconnect :: Db a -> IO ()
Closes a connection opened with dbConnect (or dbConnectDirect).
dbWithDirectConnection :: DataSourceName -> String -> String -> (Db () -> IO b) -> IO b
Open a direct database connection and automatically close it after the computation returns. This method is not recommended in general as -- the dbWithConnection function is potentially much more efficient since it -- caches database connections and meta information, greatly reducing network traffic.
dbConnectDirect :: DataSourceName -> String -> String -> IO (Db ())
Open a direct database connection. This method is in general not recommended as the dbConnect function is potentially much more efficient since it caches database connections and meta information, greatly reducing network traffic.
Queries
dbQuery :: Db a -> String -> (DbRow a -> IO b) -> IO [b]

Execute a SQL query against a database. Takes a function as argument that is applied to every database row (DbRow). The results of these applications are returned as a list. Raises a DbError on failure.

  do names <- dbQuery db "SELECT au_fname FROM authors" 
                (\row -> dbRowGetString row "au_fname")
     putStr (unlines names)
dbQuery_ :: Db a -> String -> (DbRow a -> IO b) -> IO ()

Execute a SQL query against a database. Takes a function as argument that is applied to every row in the database. Raises a DbError on failure.

  dbQuery_ db "SELECT au_fname FROM authors" 
    (\row -> do fname <- dbRowGetString row "au_fname"
                putStrLn fname)
Changes
dbExecute :: Db a -> String -> IO ()
Execute a SQL statement against the database. Raises a DbError on failure.
dbTransaction :: Db a -> IO b -> IO b

Execute an IO action as a transaction on a particular database. When no exception is raised, the changes to a database are committed. Always use this when using dbExecute statements that update the database.

 do dbWithConnection "pubs" "" "" $ \db -> 
     dbTransaction db $
       dbExecute db "CREATE TABLE TestTable ( TestField LONG)"
Rows
data DbRow a
An abstract database row.
Constructors
DbRow Db a [ColumnInfo]
Standard values
dbRowGetString :: DbRow a -> ColumnName -> IO String
Read a string value from the database. Returns the empty string when a NULL value is encountered. Raises a DbError on failure.
dbRowGetStringMb :: DbRow a -> ColumnName -> IO (Maybe String)
Read a string from the database. Returns Nothing when a NULL value is encountered. Raises a DbError on failure.
dbRowGetBool :: DbRow a -> ColumnName -> IO Bool
Read an Bool from the database. Raises a DbError on failure or when a NULL value is encountered.
dbRowGetBoolMb :: DbRow a -> ColumnName -> IO (Maybe Bool)
Read an Bool from the database. Returns Nothing when a NULL value is encountered. Raises a DbError on failure.
dbRowGetInt :: DbRow a -> ColumnName -> IO Int
Read an Int from the database. Raises a DbError on failure or when a NULL value is encountered.
dbRowGetIntMb :: DbRow a -> ColumnName -> IO (Maybe Int)
Read an Int from the database. Returns Nothing when a NULL value is encountered. Raises a DbError on failure.
dbRowGetDouble :: DbRow a -> ColumnName -> IO Double
Read an Double from the database. Raises a DbError on failure or when a NULL value is encountered.
dbRowGetDoubleMb :: DbRow a -> ColumnName -> IO (Maybe Double)
Read an Double from the database. Returns Nothing when a NULL value is encountered. Raises a DbError on failure.
dbRowGetInteger :: DbRow a -> ColumnName -> IO Integer
Read an Integer from the database. Raises a DbError on failure or when a NULL value is encountered.
dbRowGetIntegerMb :: DbRow a -> ColumnName -> IO (Maybe Integer)
Read an Integer from the database. Returns Nothing when a NULL value is encountered. Raises a DbError on failure.
dbRowGetClockTime :: DbRow a -> ColumnName -> IO ClockTime
Read an ClockTime from the database (from a SQL Time, TimeStamp, or Date field). Raises a DbError on failure or when a NULL value is encountered.
dbRowGetClockTimeMb :: DbRow a -> ColumnName -> IO (Maybe ClockTime)
Read an ClockTime from the database (from a SQL Time, TimeStamp, or Date field). Returns Nothing when a NULL value is encountered. Raises a DbError on failure.
Generic values
class DbValue a where
Class of values that are supported by the database.
Methods
dbValueRead :: Db b -> ColumnInfo -> IO (Maybe a)
Read a value at a specified column from the database. Return Nothing when a NULL value is encountered Raises a DbError on failure. (dbGetDataNull can be used when implementing this behaviour).
toSqlValue :: a -> String
Convert a value to a string representation that can be used directly in a SQL statement.
show/hide Instances
dbRowGetValue :: DbValue b => DbRow a -> ColumnName -> IO b
Get a database value (DbValue) from a row. Raises a DbError on failure or when a NULL value is encountered.
dbRowGetValueMb :: DbValue b => DbRow a -> ColumnName -> IO (Maybe b)
Get a database value (DbValue) from a row. Returns Nothing when a NULL value is encountered. Raises a DbError on failure.
Column information
dbRowGetColumnInfo :: DbRow a -> ColumnName -> IO ColumnInfo
The column information of a particular column. Raises a DbError on failure.
dbRowGetColumnInfos :: DbRow a -> [ColumnInfo]
Get the column information of a row.
Meta information
Data sources
type DataSourceName = String
dbGetDataSources :: IO [(DataSourceName, String)]
Returns the name and description of the data sources on the system.
dbGetDataSourceInfo :: DataSourceName -> String -> String -> IO DbInfo

Get the complete meta information of a data source. Takes the data source name, a user id, and password as arguments.

 dbGetDataSourceInfo dsn userid password
   = dbWithConnection dsn userId password dbGetInfo 
dbGetDataSourceTableInfo :: DataSourceName -> TableName -> String -> String -> IO TableInfo
Get the meta information of a table in a data source. Takes the data source name, table name, a user id, and password as arguments.
Tables and columns
type TableName = String
type ColumnName = String
Column names. Note that a column name consisting of a number can be used to retrieve a value by index, for example: dbGetString db "1".
type ColumnIndex = Int
data DbInfo
Database information.
Constructors
DbInfo
dbCatalog :: StringSystem name of the database
dbSchema :: StringSchema name
dbTables :: [TableInfo]The tables of the database
show/hide Instances
data TableInfo
Database table information.
Constructors
TableInfo
tableName :: TableNameName of the table.
tableType :: StringType of the table (ie. SYSTEM TABLE, TABLE, etc)
tableRemarks :: StringComments
tableColumns :: [ColumnInfo]The columns of the table.
show/hide Instances
data ColumnInfo
Database column information.
Constructors
ColumnInfo
columnName :: ColumnNameColumn name.
columnIndex :: ColumnIndex1-based column index.
columnSize :: IntLength of the column.
columnNullable :: BoolAre NULL values allowed?
columnType :: DbTypeLogical type
columnSqlType :: SqlTypeSQL type
columnTypeName :: StringSQL type name (ie. VARCHAR, INTEGER etc.)
columnRemarks :: StringComments
columnDecimalDigits :: IntNumber of decimal digits
columnNumPrecRadix :: IntRadix precision
columnForeignKey :: IntIs this a foreign key column? 0 = no, 1 = first key, 2 = second key, etc. (not supported on all systems)
columnPrimaryKey :: IntIs this a primary key column? 0 = no, 1 = first key, 2 = second key, etc. (not supported on all systems)
columnForeignKeyTableName :: TableNameTable that has this foreign key as a primary key.
columnPrimaryKeyTableNames :: [TableName]Tables that use this primary key as a foreign key.
show/hide Instances
dbGetInfo :: Db a -> IO DbInfo
Get the complete meta information of a database.
dbGetTableInfo :: Db a -> TableName -> IO TableInfo
Get the meta information of a table in a database.
dbGetTableColumnInfos :: Db a -> TableName -> IO [ColumnInfo]
Return the column information of a certain table. Use an empty table name to get the column information of the current query (dbGetColumnInfos).
dbGetColumnInfos :: Db a -> IO [ColumnInfo]
Return the column information of the current query.
Dbms
data Dbms
Constructors
DbmsORACLE
DbmsSYBASE_ASAAdaptive Server Anywhere
DbmsSYBASE_ASEAdaptive Server Enterprise
DbmsMS_SQL_SERVER
DbmsMY_SQL
DbmsPOSTGRES
DbmsACCESS
DbmsDBASE
DbmsINFORMIX
DbmsVIRTUOSO
DbmsDB2
DbmsINTERBASE
DbmsPERVASIVE_SQL
DbmsXBASE_SEQUITER
DbmsUNIDENTIFIED
show/hide Instances
dbGetDbms :: Db a -> IO Dbms
Retrieve the database backend system.
Exceptions
data DbError
Database error type.
Constructors
DbErrorGeneral error.
dbErrorMsg :: String
dbDataSource :: DataSourceName
dbErrorCode :: DbStatus
dbNativeCode :: Int
dbSqlState :: String
show/hide Instances
catchDbError :: IO a -> (DbError -> IO a) -> IO a
Handle database errors.
raiseDbError :: DbError -> IO a
Raise a database error.
dbHandleExn :: Db a -> IO Bool -> IO ()

Automatically raise a database exception when False is returned. You can use this method around basic database methods to conveniently throw Haskell exceptions.

  dbHandleExn db $ dbExecSql db "SELECT au_fname FROM authors"           
dbCheckExn :: Db a -> IO ()
Raise a database exception based on the current error status of the database. Does nothing when no error is set.
dbRaiseExn :: Db a -> IO b
Raise a database exception based on the current error status of the database.
dbGetErrorMessages :: Db a -> IO [String]
Get the raw error message history. More recent error messages come first.
dbGetDbStatus :: Db a -> IO DbStatus
Retrieve the current status of the database
data DbStatus
Status of the database.
Constructors
DB_FAILUREGeneral failure.
DB_SUCCESSNo error.
DB_ERR_NOT_IN_USE
DB_ERR_GENERAL_WARNINGSqlState = 01000
DB_ERR_DISCONNECT_ERRORSqlState = 01002
DB_ERR_DATA_TRUNCATEDSqlState = 01004
DB_ERR_PRIV_NOT_REVOKEDSqlState = 01006
DB_ERR_INVALID_CONN_STR_ATTRSqlState = 01S00
DB_ERR_ERROR_IN_ROWSqlState = 01S01
DB_ERR_OPTION_VALUE_CHANGEDSqlState = 01S02
DB_ERR_NO_ROWS_UPD_OR_DELSqlState = 01S03
DB_ERR_MULTI_ROWS_UPD_OR_DELSqlState = 01S04
DB_ERR_WRONG_NO_OF_PARAMSSqlState = 07001
DB_ERR_DATA_TYPE_ATTR_VIOLSqlState = 07006
DB_ERR_UNABLE_TO_CONNECTSqlState = 08001
DB_ERR_CONNECTION_IN_USESqlState = 08002
DB_ERR_CONNECTION_NOT_OPENSqlState = 08003
DB_ERR_REJECTED_CONNECTIONSqlState = 08004
DB_ERR_CONN_FAIL_IN_TRANSSqlState = 08007
DB_ERR_COMM_LINK_FAILURESqlState = 08S01
DB_ERR_INSERT_VALUE_LIST_MISMATCHSqlState = 21S01
DB_ERR_DERIVED_TABLE_MISMATCHSqlState = 21S02
DB_ERR_STRING_RIGHT_TRUNCSqlState = 22001
DB_ERR_NUMERIC_VALUE_OUT_OF_RNGSqlState = 22003
DB_ERR_ERROR_IN_ASSIGNMENTSqlState = 22005
DB_ERR_DATETIME_FLD_OVERFLOWSqlState = 22008
DB_ERR_DIVIDE_BY_ZEROSqlState = 22012
DB_ERR_STR_DATA_LENGTH_MISMATCHSqlState = 22026
DB_ERR_INTEGRITY_CONSTRAINT_VIOLSqlState = 23000
DB_ERR_INVALID_CURSOR_STATESqlState = 24000
DB_ERR_INVALID_TRANS_STATESqlState = 25000
DB_ERR_INVALID_AUTH_SPECSqlState = 28000
DB_ERR_INVALID_CURSOR_NAMESqlState = 34000
DB_ERR_SYNTAX_ERROR_OR_ACCESS_VIOLSqlState = 37000
DB_ERR_DUPLICATE_CURSOR_NAMESqlState = 3C000
DB_ERR_SERIALIZATION_FAILURESqlState = 40001
DB_ERR_SYNTAX_ERROR_OR_ACCESS_VIOL2SqlState = 42000
DB_ERR_OPERATION_ABORTEDSqlState = 70100
DB_ERR_UNSUPPORTED_FUNCTIONSqlState = IM001
DB_ERR_NO_DATA_SOURCESqlState = IM002
DB_ERR_DRIVER_LOAD_ERRORSqlState = IM003
DB_ERR_SQLALLOCENV_FAILEDSqlState = IM004
DB_ERR_SQLALLOCCONNECT_FAILEDSqlState = IM005
DB_ERR_SQLSETCONNECTOPTION_FAILEDSqlState = IM006
DB_ERR_NO_DATA_SOURCE_DLG_PROHIBSqlState = IM007
DB_ERR_DIALOG_FAILEDSqlState = IM008
DB_ERR_UNABLE_TO_LOAD_TRANSLATION_DLLSqlState = IM009
DB_ERR_DATA_SOURCE_NAME_TOO_LONGSqlState = IM010
DB_ERR_DRIVER_NAME_TOO_LONGSqlState = IM011
DB_ERR_DRIVER_KEYWORD_SYNTAX_ERRORSqlState = IM012
DB_ERR_TRACE_FILE_ERRORSqlState = IM013
DB_ERR_TABLE_OR_VIEW_ALREADY_EXISTSSqlState = S0001
DB_ERR_TABLE_NOT_FOUNDSqlState = S0002
DB_ERR_INDEX_ALREADY_EXISTSSqlState = S0011
DB_ERR_INDEX_NOT_FOUNDSqlState = S0012
DB_ERR_COLUMN_ALREADY_EXISTSSqlState = S0021
DB_ERR_COLUMN_NOT_FOUNDSqlState = S0022
DB_ERR_NO_DEFAULT_FOR_COLUMNSqlState = S0023
DB_ERR_GENERAL_ERRORSqlState = S1000
DB_ERR_MEMORY_ALLOCATION_FAILURESqlState = S1001
DB_ERR_INVALID_COLUMN_NUMBERSqlState = S1002
DB_ERR_PROGRAM_TYPE_OUT_OF_RANGESqlState = S1003
DB_ERR_SQL_DATA_TYPE_OUT_OF_RANGESqlState = S1004
DB_ERR_OPERATION_CANCELLEDSqlState = S1008
DB_ERR_INVALID_ARGUMENT_VALUESqlState = S1009
DB_ERR_FUNCTION_SEQUENCE_ERRORSqlState = S1010
DB_ERR_OPERATION_INVALID_AT_THIS_TIMESqlState = S1011
DB_ERR_INVALID_TRANS_OPERATION_CODESqlState = S1012
DB_ERR_NO_CURSOR_NAME_AVAILSqlState = S1015
DB_ERR_INVALID_STR_OR_BUF_LENSqlState = S1090
DB_ERR_DESCRIPTOR_TYPE_OUT_OF_RANGESqlState = S1091
DB_ERR_OPTION_TYPE_OUT_OF_RANGESqlState = S1092
DB_ERR_INVALID_PARAM_NOSqlState = S1093
DB_ERR_INVALID_SCALE_VALUESqlState = S1094
DB_ERR_FUNCTION_TYPE_OUT_OF_RANGESqlState = S1095
DB_ERR_INF_TYPE_OUT_OF_RANGESqlState = S1096
DB_ERR_COLUMN_TYPE_OUT_OF_RANGESqlState = S1097
DB_ERR_SCOPE_TYPE_OUT_OF_RANGESqlState = S1098
DB_ERR_NULLABLE_TYPE_OUT_OF_RANGESqlState = S1099
DB_ERR_UNIQUENESS_OPTION_TYPE_OUT_OF_RANGESqlState = S1100
DB_ERR_ACCURACY_OPTION_TYPE_OUT_OF_RANGESqlState = S1101
DB_ERR_DIRECTION_OPTION_OUT_OF_RANGESqlState = S1103
DB_ERR_INVALID_PRECISION_VALUESqlState = S1104
DB_ERR_INVALID_PARAM_TYPESqlState = S1105
DB_ERR_FETCH_TYPE_OUT_OF_RANGESqlState = S1106
DB_ERR_ROW_VALUE_OUT_OF_RANGESqlState = S1107
DB_ERR_CONCURRENCY_OPTION_OUT_OF_RANGESqlState = S1108
DB_ERR_INVALID_CURSOR_POSITIONSqlState = S1109
DB_ERR_INVALID_DRIVER_COMPLETIONSqlState = S1110
DB_ERR_INVALID_BOOKMARK_VALUESqlState = S1111
DB_ERR_DRIVER_NOT_CAPABLESqlState = S1C00
DB_ERR_TIMEOUT_EXPIREDSqlState = S1T00
DB_ERR_FETCH_NULLUnexpected NULL value
DB_ERR_INVALID_TABLE_NAMEInvalid (or unknown) table name
DB_ERR_INVALID_COLUMN_NAMEInvalid (or unknown) column name
DB_ERR_TYPE_MISMATCHTrying to convert a SQL value of the wrong type
DB_ERR_CONNECTUnable to establish a connection
show/hide Instances
Sql types
data DbType
Standard logical database types.
Constructors
DbUnknown
DbVarCharStrings
DbInteger
DbFloat
DbDate
DbBlobBinary
show/hide Instances
data SqlType
Standard SQL types.
Constructors
SqlCharFixed Strings
SqlNumeric
SqlDecimal
SqlInteger
SqlSmallInt
SqlFloat
SqlReal
SqlDouble
SqlDate
SqlTime
SqlTimeStamp
SqlVarCharStrings
SqlBit
SqlBinary
SqlVarBinary
SqlBigInt
SqlTinyInt
SqlUnknown IntUnknown SQL type. Argument specifies the system sql type.
show/hide Instances
toSqlTableName :: Db a -> TableName -> TableName
Convert a table name to a format that can be used directly in SQL statements. For example, this call can do case conversion and quoting.
toSqlColumnName :: Db a -> ColumnName -> ColumnName
Convert a column name to a format that can be used directly in SQL statements. For example, this call can do case conversion and quoting.
toSqlString :: String -> String
Convert a string to SQL string
toSqlTime :: ClockTime -> String
Convert a ClockTime to a SQL time string (without year/month/day).
toSqlDate :: ClockTime -> String
Convert a ClockTime to a SQL date string (without hours/minutes/seconds).
toSqlTimeStamp :: ClockTime -> String
Convert a ClockTime to a SQL full date (timestamp) string.
Internal
dbStringRead :: Db a -> ColumnInfo -> IO (Maybe String)
Low level string reading.
dbGetDataNull :: Db a -> (Ptr CInt -> IO Bool) -> IO Bool
Internal: used to implement dbReadValue methods. Takes a dbGetData... method and supplies the Ptr CInt argument. It raises and exception on error. Otherwise, it returns True when a NULL value is read.
toSqlType :: Int -> SqlType
Convert a system SQL type (like wxSQL_C_CHAR) to a standard SqlType.
fromSqlType :: SqlType -> Int
Convert to a system SQL type (like wxSQL_C_INTEGER) from a standard SqlType.
Produced by Haddock version 2.1.0