Safe Haskell | None |
---|
Basic type class & type definitions for DB interfacing.
- type SQL = String
- type TableId = String
- data Connection = Connection {
- connDisconnect :: IO ()
- connExecute :: SQL -> IO ()
- connQuery :: SQL -> IO Statement
- connTables :: IO [TableId]
- connDescribe :: TableId -> IO [ColDef]
- connBeginTransaction :: IO ()
- connCommitTransaction :: IO ()
- connRollbackTransaction :: IO ()
- connClosed :: MVar Bool
- type ColId = String
- type Nullability = Bool
- type ColDef = (ColId, SqlType, Nullability)
- type FieldReader t = ColDef -> CString -> Int -> IO t
- type FieldReading = forall t. Int -> ColDef -> FieldReader t -> IO t
- data Statement = Statement {
- stmtConn :: Connection
- stmtClose :: IO ()
- stmtFetch :: IO Bool
- stmtGetCol :: FieldReading
- stmtFields :: [ColDef]
- stmtClosed :: MVar Bool
- class SqlBind a where
- toSqlValue :: a -> SQL
- fromSqlValue :: SqlType -> SQL -> Maybe a
- fromSqlCStringLen :: ColDef -> CString -> Int -> IO a
- data SqlType
- = SqlInteger
- | SqlBigInt
- | SqlSmallInt
- | SqlTinyInt
- | SqlMedInt
- | SqlDecimal {
- typeSize :: Int
- typeDecimals :: Int
- | SqlNumeric {
- typeSize :: Int
- typeDecimals :: Int
- | SqlReal
- | SqlDouble
- | SqlFloat
- | SqlMoney
- | SqlChar { }
- | SqlVarChar { }
- | SqlLongVarChar { }
- | SqlText
- | SqlWChar { }
- | SqlWVarChar { }
- | SqlWLongVarChar { }
- | SqlDate
- | SqlTime
- | SqlTimeTZ
- | SqlAbsTime
- | SqlRelTime
- | SqlTimeInterval
- | SqlAbsTimeInterval
- | SqlTimeStamp
- | SqlDateTime
- | SqlDateTimeTZ
- | SqlYear
- | SqlBit
- | SqlENUM
- | SqlPoint
- | SqlLSeg
- | SqlPath
- | SqlBox
- | SqlPolygon
- | SqlLine
- | SqlCircle
- | SqlINetAddr
- | SqlCIDRAddr
- | SqlMacAddr
- | SqlBinary { }
- | SqlVarBinary { }
- | SqlLongVarBinary { }
- | SqlSET
- | SqlBLOB
- | SqlUnknown { }
- data SqlError
- = SqlError {
- seState :: String
- seNativeError :: Int
- seErrorMsg :: String
- | SqlNoMoreData
- | SqlInvalidHandle
- | SqlStillExecuting
- | SqlNeedMoreData
- | SqlBadTypeCast { }
- | SqlFetchNull { }
- | SqlUnknownField { }
- | SqlUnsupportedOperation
- | SqlClosedHandle
- = SqlError {
Documentation
data Connection Source
A Connection
type represents a connection to a database,
through which you can operate on the it.
In order to create the connection you need to use the connect
function
from the module for your prefered backend.
Connection | |
|
type Nullability = BoolSource
Whether fields of a table col may be NULL.
type ColDef = (ColId, SqlType, Nullability)Source
Description of the properties of a table column.
type FieldReader tSource
= ColDef | field type spec |
-> CString | field content code |
-> Int | field content length |
-> IO t | field read action |
A DB generic field extraction function, specifiable by field definition, receiving the content code and its length.
type FieldReadingSource
= forall t . | |
=> Int | field (column) index |
-> ColDef | source field type spec |
-> FieldReader t | field reader to be applied |
-> IO t | field read action |
An extraction of a field of type to be specified by requester,
from a row index with source ColDef
, applying an appropriate
FieldReader
.
The Statement
type represents a result from the execution of given
SQL query.
Statement | |
|
Equivalent to Show and Read adapted to SQL expressions.
toSqlValue :: a -> SQLSource
show as an SQL expression
fromSqlValue :: SqlType -> SQL -> Maybe aSource
read from an SQL expression in text representation,
by support of its SqlType
read from SQL expression in binary representation,
by support of its ColDef
and code size info.
This allows for faster conversion for e.g. integral numeric types,
etc.
Variety of common data types used in databases.
SqlInteger | |
SqlBigInt | |
SqlSmallInt | |
SqlTinyInt | |
SqlMedInt | |
SqlDecimal | |
| |
SqlNumeric | |
| |
SqlReal | |
SqlDouble | |
SqlFloat | |
SqlMoney | |
SqlChar | |
SqlVarChar | |
SqlLongVarChar | |
SqlText | |
SqlWChar | |
SqlWVarChar | |
SqlWLongVarChar | |
SqlDate | |
SqlTime | |
SqlTimeTZ | |
SqlAbsTime | |
SqlRelTime | |
SqlTimeInterval | |
SqlAbsTimeInterval | |
SqlTimeStamp | |
SqlDateTime | |
SqlDateTimeTZ | |
SqlYear | |
SqlBit | |
SqlENUM | |
SqlPoint | |
SqlLSeg | |
SqlPath | |
SqlBox | |
SqlPolygon | |
SqlLine | |
SqlCircle | |
SqlINetAddr | |
SqlCIDRAddr | |
SqlMacAddr | |
SqlBinary | |
SqlVarBinary | |
SqlLongVarBinary | |
SqlSET | |
SqlBLOB | |
SqlUnknown | HSQL returns |
SqlError | generic error condition, with further specification |
| |
SqlNoMoreData | no more data was available |
SqlInvalidHandle | requested handle is invalid |
SqlStillExecuting | connection is blocked by running transaction |
SqlNeedMoreData | more data is needed, e.g. additional connection specs |
SqlBadTypeCast | requested field can't be converted to requested type |
| |
SqlFetchNull | requested field returns NULL |
SqlUnknownField | requested field isn't known |
SqlUnsupportedOperation | requested operation isn't supported |
SqlClosedHandle | referenced handle is already closed |