- type FieldDef = (String, SqlType, Bool)
- data SqlType
- = SqlChar Int
- | SqlVarChar Int
- | SqlLongVarChar Int
- | SqlText
- | SqlWChar Int
- | SqlWVarChar Int
- | SqlWLongVarChar Int
- | SqlDecimal Int Int
- | SqlNumeric Int Int
- | SqlSmallInt
- | SqlMedInt
- | SqlInteger
- | SqlReal
- | SqlFloat
- | SqlDouble
- | SqlBit
- | SqlTinyInt
- | SqlBigInt
- | SqlBinary Int
- | SqlVarBinary Int
- | SqlLongVarBinary Int
- | SqlDate
- | SqlTime
- | SqlTimeTZ
- | SqlAbsTime
- | SqlRelTime
- | SqlTimeInterval
- | SqlAbsTimeInterval
- | SqlTimeStamp
- | SqlDateTime
- | SqlDateTimeTZ
- | SqlYear
- | SqlSET
- | SqlENUM
- | SqlBLOB
- | SqlMoney
- | SqlINetAddr
- | SqlCIDRAddr
- | SqlMacAddr
- | SqlPoint
- | SqlLSeg
- | SqlPath
- | SqlBox
- | SqlPolygon
- | SqlLine
- | SqlCircle
- | SqlUnknown Int
- data SqlError
- = SqlError {
- seState :: String
- seNativeError :: Int
- seErrorMsg :: String
- | SqlNoData
- | SqlInvalidHandle
- | SqlStillExecuting
- | SqlNeedData
- | SqlBadTypeCast { }
- | SqlFetchNull { }
- | SqlUnknownField { }
- | SqlUnsupportedOperation
- | SqlClosedHandle
- = SqlError {
- sqlErrorTc :: TyCon
- data Connection = Connection {
- connDisconnect :: IO ()
- connExecute :: String -> IO ()
- connQuery :: String -> IO Statement
- connTables :: IO [String]
- connDescribe :: String -> IO [FieldDef]
- connBeginTransaction :: IO ()
- connCommitTransaction :: IO ()
- connRollbackTransaction :: IO ()
- connClosed :: MVar Bool
- data Statement = Statement {}
- class SqlBind a where
- fromSqlCStringLen :: FieldDef -> CString -> Int -> IO a
- fromSqlValue :: SqlType -> String -> Maybe a
- toSqlValue :: a -> String
Documentation
SqlChar Int | |
SqlVarChar Int | |
SqlLongVarChar Int | |
SqlText | |
SqlWChar Int | |
SqlWVarChar Int | |
SqlWLongVarChar Int | |
SqlDecimal Int Int | |
SqlNumeric Int Int | |
SqlSmallInt | |
SqlMedInt | |
SqlInteger | |
SqlReal | |
SqlFloat | |
SqlDouble | |
SqlBit | |
SqlTinyInt | |
SqlBigInt | |
SqlBinary Int | |
SqlVarBinary Int | |
SqlLongVarBinary Int | |
SqlDate | |
SqlTime | |
SqlTimeTZ | |
SqlAbsTime | |
SqlRelTime | |
SqlTimeInterval | |
SqlAbsTimeInterval | |
SqlTimeStamp | |
SqlDateTime | |
SqlDateTimeTZ | |
SqlYear | |
SqlSET | |
SqlENUM | |
SqlBLOB | |
SqlMoney | |
SqlINetAddr | |
SqlCIDRAddr | |
SqlMacAddr | |
SqlPoint | |
SqlLSeg | |
SqlPath | |
SqlBox | |
SqlPolygon | |
SqlLine | |
SqlCircle | |
SqlUnknown Int | HSQL returns |
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 | |
|
The Statement
type represents a result from the execution of given SQL query.
fromSqlCStringLen :: FieldDef -> CString -> Int -> IO aSource
fromSqlValue :: SqlType -> String -> Maybe aSource
toSqlValue :: a -> StringSource