| Safe Haskell | None |
|---|
Database.HSQL
Contents
Description
- data Connection
- disconnect :: Connection -> IO ()
- tables :: Connection -> IO [TableId]
- type ColDef = (ColId, SqlType, Nullability)
- describe :: Connection -> TableId -> IO [ColDef]
- type SQL = String
- execute :: Connection -> SQL -> IO ()
- data Statement
- query :: Connection -> SQL -> IO Statement
- closeStatement :: Statement -> IO ()
- fetch :: Statement -> IO Bool
- class SqlBind a where
- fromSqlCStringLen :: ColDef -> CString -> Int -> IO a
- getFieldValue :: SqlBind a => Statement -> String -> IO a
- getFieldValueMB :: SqlBind a => Statement -> String -> IO (Maybe a)
- getFieldValue' :: SqlBind a => Statement -> String -> a -> IO a
- getFieldValueType :: Statement -> String -> (SqlType, Bool)
- getFieldsTypes :: Statement -> [(String, SqlType, Bool)]
- inTransaction :: Connection -> (Connection -> IO a) -> IO a
- forEachRow :: (Statement -> s -> IO s) -> Statement -> s -> IO s
- forEachRow' :: (Statement -> IO ()) -> Statement -> IO ()
- collectRows :: (Statement -> IO a) -> Statement -> IO [a]
- data SqlError
- = SqlError {
- seState :: String
- seNativeError :: Int
- seErrorMsg :: String
- | SqlNoMoreData
- | SqlInvalidHandle
- | SqlStillExecuting
- | SqlNeedMoreData
- | SqlBadTypeCast { }
- | SqlFetchNull { }
- | SqlUnknownField { }
- | SqlUnsupportedOperation
- | SqlClosedHandle
- = SqlError {
- catchSql :: IO a -> (SqlError -> IO a) -> IO a
- handleSql :: (SqlError -> IO a) -> IO a -> IO a
- sqlExceptions :: Exception x => x -> Maybe SqlError
- data Point = Point {}
- data Line = Line {}
- data Path
- = OpenPath {
- pathPoints :: [Point]
- | ClosedPath {
- pathPoints :: [Point]
- = OpenPath {
- data Box = Box {}
- data Circle = Circle {}
- data Polygon = Polygon {
- polygonPoints :: [Point]
- data INetAddr = INetAddr {}
- data MacAddr = MacAddr {}
- 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 { }
Connect/Disconnect
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.
disconnect :: Connection -> IO ()Source
Closes the connection. Performing disconnect on a connection that has
already been closed has no effect.
All other operations on a closed connection will fail.
Metadata
Arguments
| :: Connection | Database connection |
| -> IO [TableId] | The names of all tables in the database. |
List all tables in the database.
type ColDef = (ColId, SqlType, Nullability)Source
Description of the properties of a table column.
Arguments
| :: Connection | Database connection |
| -> TableId | Name of a database table |
| -> IO [ColDef] | The list of fields in the table |
List all columns in a table along with their types and nullable flags
Command Execution Functions
Once a connection to a database has been successfully established, the functions described here are used to perform SQL queries and commands.
Arguments
| :: Connection | the database connection |
| -> SQL | the text of SQL command |
| -> IO () |
Submits a command to the database.
Arguments
| :: Connection | the database connection |
| -> SQL | the text of SQL query |
| -> IO Statement | the associated statement. Must be closed with
the |
Executes a query and returns a result set
closeStatement :: Statement -> IO ()Source
closeStatement stops processing associated with a specific statement,
closes any open cursors associated with the statement, discards pending
results, and frees all resources associated with the statement.
Performing closeStatement on a statement that has already been closed
has no effect. All other operations on a closed statement will fail.
fetch :: Statement -> IO BoolSource
fetch fetches the next rowset of data from the result set.
The values from columns can be retrieved with getFieldValue function.
Retrieving Statement values and types
Equivalent to Show and Read adapted to SQL expressions.
Methods
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.
Retrieves the value of field with the specified name.
getFieldValueMB :: SqlBind a => Statement -> String -> IO (Maybe a)Source
Deprecated: Use getFieldValue instead.
Retrieves the value of field with the specified name.
If the field value is null then the function will return the default value.
getFieldValueType :: Statement -> String -> (SqlType, Bool)Source
Returns the type and the nullable flag for field with specified name
getFieldsTypes :: Statement -> [(String, SqlType, Bool)]Source
Returns the list of fields with their types and nullable flags
Transactions
Arguments
| :: Connection | Database connection |
| -> (Connection -> IO a) | an action |
| -> IO a | the returned value is the result returned from action |
The inTransaction function executes the specified action in transaction
mode.
If the action completes successfully then the transaction will be commited.
If the action completes with an exception then the transaction will be
rolled back and the exception will be throw again.
A transaction is to catch ANY exception, so SomeException is adequate.
Utilities
Arguments
| :: (Statement -> s -> IO s) | an action |
| -> Statement | the statement |
| -> s | initial state |
| -> IO s | final state |
The forEachRow function iterates through the result set in Statement
and executes the given action for each row in the set.
The function closes the Statement after the last row processing or if
the given action raises an exception.
forEachRow' :: (Statement -> IO ()) -> Statement -> IO ()Source
The 'forEachRow\'' function is analogous to forEachRow but doesn't
provide state.
The function closes the Statement after the last row processing or if the
given action raises an exception.
collectRows :: (Statement -> IO a) -> Statement -> IO [a]Source
The collectRows function iterates through the result set in Statement
and executes the given action for each row in the set. The values returned
from action are collected and returned as list. The function closes the
Statement after the last row processing or if the given action raises an
exception.
SQL Exceptions handling
Constructors
| SqlError | generic error condition, with further specification |
Fields
| |
| 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 |
Fields
| |
| SqlFetchNull | requested field returns NULL |
Fields | |
| SqlUnknownField | requested field isn't known |
Fields | |
| SqlUnsupportedOperation | requested operation isn't supported |
| SqlClosedHandle | referenced handle is already closed |
catchSql :: IO a -> (SqlError -> IO a) -> IO aSource
Deprecated: Use Control.Exception.catch instead.
Deprecated: Use catch instead.
handleSql :: (SqlError -> IO a) -> IO a -> IO aSource
Deprecated: Use Control.Exception.handle instead.
Deprecated: Use handle instead.
Extra types
A 2D point.
A 2D straight line.
A 2D path, either open, or closed (looping).
Constructors
| OpenPath | An open path |
Fields
| |
| ClosedPath | A looping path |
Fields
| |
A 2D rectangle.
A 2D circle
Constructors
| Circle | |
Fields
| |
A 2D polygon (without holes).
Constructors
| Polygon | |
Fields
| |
An IP4 address with netmask in CIDR notation.
Constructors
| INetAddr | |
A MAC network address.
Constructors
| MacAddr | |
Variety of common data types used in databases.
Constructors
| SqlInteger | |
| SqlBigInt | |
| SqlSmallInt | |
| SqlTinyInt | |
| SqlMedInt | |
| SqlDecimal | |
Fields
| |
| SqlNumeric | |
Fields
| |
| 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 |