Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- data SQLConfig = SQLConfig {
- sql_cli_flds_table_cat :: SQLSMALLINT
- sql_cli_flds_table_schem :: SQLSMALLINT
- sql_cli_flds_table_name :: SQLSMALLINT
- sql_cli_flds_column_name :: SQLSMALLINT
- sql_cli_flds_data_type :: SQLSMALLINT
- sql_cli_flds_type_name :: SQLSMALLINT
- sql_cli_flds_column_size :: SQLSMALLINT
- sql_cli_flds_buffer_length :: SQLSMALLINT
- sql_cli_flds_decimal_digits :: SQLSMALLINT
- sql_cli_flds_num_prec_radix :: SQLSMALLINT
- sql_cli_flds_nullable :: SQLSMALLINT
- sql_cli_flds_remarks :: SQLSMALLINT
- sql_cli_flds_column_def :: SQLSMALLINT
- sql_cli_flds_datetime_code :: SQLSMALLINT
- sql_cli_flds_char_octet_length :: SQLSMALLINT
- sql_cli_flds_ordinal_position :: SQLSMALLINT
- sql_cli_flds_is_nullable :: SQLSMALLINT
- data ColumnInfo = ColumnInfo {
- ci_TableCat :: Maybe String
- ci_TableSchem :: String
- ci_TableName :: String
- ci_ColumnName :: String
- ci_DataType :: SQLSMALLINT
- ci_TypeName :: String
- ci_ColumnSize :: Maybe SQLINTEGER
- ci_BufferLength :: Maybe SQLINTEGER
- ci_DecimalDigits :: Maybe SQLSMALLINT
- ci_NumPrecRadix :: Maybe SQLSMALLINT
- ci_Nullable :: SQLSMALLINT
- ci_Remarks :: Maybe String
- ci_ColumnDef :: Maybe String
- ci_DatetimeCode :: Maybe SQLINTEGER
- ci_CharOctetLength :: Maybe SQLINTEGER
- ci_OrdinalPosition :: SQLINTEGER
- ci_IsNullable :: Maybe String
- collectColumnsInfo :: (MonadIO m, MonadFail m) => SQLHDBC -> String -> ReaderT SQLConfig m [ColumnInfo]
- tableExists :: (MonadIO m, MonadFail m) => SQLHDBC -> String -> m Bool
- data ConciseColInfo = ConciseColInfo {}
- describeCol :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> m ConciseColInfo
- columns :: (MonadIO m, MonadFail m) => SQLHSTMT -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> m ()
- tables :: (MonadIO m, MonadFail m) => SQLHSTMT -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> m ()
- forAllRecords :: (MonadIO m, MonadFail m) => SQLHSTMT -> (a -> m a) -> a -> m a
- getData :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> SQLSMALLINT -> SQLPOINTER -> SQLINTEGER -> Ptr SQLINTEGER -> m Bool
- getDataAndRun :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> SQLSMALLINT -> SQLPOINTER -> SQLINTEGER -> Ptr SQLINTEGER -> m a -> m a -> m a
- fetch :: (MonadIO m, MonadFail m) => SQLHSTMT -> m Bool
- fetchAndRun :: (MonadIO m, MonadFail m) => SQLHSTMT -> m a -> m a -> m a
- bindSmallIntCol :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> Ptr SQLSMALLINT -> Ptr SQLINTEGER -> m ()
- bindIntegerCol :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> Ptr SQLINTEGER -> Ptr SQLINTEGER -> m ()
- bindVarcharCol :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> CString -> SQLINTEGER -> Ptr SQLINTEGER -> m ()
- bindCol :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> SQLSMALLINT -> SQLPOINTER -> SQLINTEGER -> Ptr SQLINTEGER -> m ()
- execDirect :: (MonadIO m, MonadFail m) => SQLHSTMT -> String -> m ()
- connect :: (MonadIO m, MonadFail m) => SQLHENV -> String -> String -> String -> m SQLHDBC
- disconnect :: SQLHDBC -> IO ()
- allocHandle :: (MonadIO m, MonadFail m) => SQLSMALLINT -> SQLINTEGER -> m SQLINTEGER
- freeHandle :: SQLSMALLINT -> SQLINTEGER -> IO ()
- displayDiagInfo :: SQLSMALLINT -> SQLINTEGER -> IO ()
- displayDiagInfo' :: (MonadIO m, MonadFail m) => SQLSMALLINT -> SQLINTEGER -> m ()
- getCountOfDiagRecs :: (MonadIO m, MonadFail m) => SQLSMALLINT -> SQLINTEGER -> m Int
- data DiagRecord = DiagRecord {}
- getDiagRec :: (MonadIO m, MonadFail m) => SQLSMALLINT -> SQLINTEGER -> SQLSMALLINT -> m DiagRecord
- withMaybeCStringLen :: Maybe String -> (CStringLen -> IO a) -> IO a
- peekMaybeCol :: Storable a => Ptr a -> Ptr SQLINTEGER -> IO (Maybe a)
- peekMaybeTextCol :: CString -> Ptr SQLINTEGER -> IO (Maybe String)
Documentation
configuration values dependent on the actual CLI implementation
SQLConfig | |
|
data ColumnInfo Source #
information about column in the database; the meaning of fields is detailed in the SQL CLI specification in the documenation of Columns API call
collectColumnsInfo :: (MonadIO m, MonadFail m) => SQLHDBC -> String -> ReaderT SQLConfig m [ColumnInfo] Source #
tableExists :: (MonadIO m, MonadFail m) => SQLHDBC -> String -> m Bool Source #
Checks if a table exists on the current connection.
data ConciseColInfo Source #
concise information about a column of a result set, mapping the result of SQL CLI API call DescribeCol
describeCol :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> m ConciseColInfo Source #
wrapper for DescribeCol SQL CLI API call
columns :: (MonadIO m, MonadFail m) => SQLHSTMT -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> m () Source #
wrapper for SQL CLI Columns API call
tables :: (MonadIO m, MonadFail m) => SQLHSTMT -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> m () Source #
wrapper for SQL CLI Tables API call
forAllRecords :: (MonadIO m, MonadFail m) => SQLHSTMT -> (a -> m a) -> a -> m a Source #
applies a function through all the records in a statment, passing an accumulator value and combining the actions returned by the function
getData :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> SQLSMALLINT -> SQLPOINTER -> SQLINTEGER -> Ptr SQLINTEGER -> m Bool Source #
getDataAndRun :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> SQLSMALLINT -> SQLPOINTER -> SQLINTEGER -> Ptr SQLINTEGER -> m a -> m a -> m a Source #
Read data available in a column of a fetched database record inside a monadic. It fails if an error occurs, displaying the diagnostics on the standard error. It receives 2 monadic actions parameters:
- more
- end
It executes the more action if there is more data available and it executes the end action if all data in the column has been read.
fetchAndRun :: (MonadIO m, MonadFail m) => SQLHSTMT -> m a -> m a -> m a Source #
Create a monadic action to fetch the next record in an excecuted statement. It, then, executes one of the 2 actions received as parameters -- more and end -- depending on if there are more records available or if the last record has been fetched.
If an error occrus, the monadic action fails, displaying error diagnostics on the standard error.
:: (MonadIO m, MonadFail m) | |
=> SQLHSTMT | statement handle |
-> SQLSMALLINT | column number (starting with 1) |
-> Ptr SQLSMALLINT | buffer to receive the value |
-> Ptr SQLINTEGER | buffer to receive the indicator or length; it can be null |
-> m () |
helper function to bind a SMALLINT column
:: (MonadIO m, MonadFail m) | |
=> SQLHSTMT | statement handle |
-> SQLSMALLINT | column number (starting with 1) |
-> Ptr SQLINTEGER | buffer to receive the value |
-> Ptr SQLINTEGER | buffer to receive the indicator or length; it can be null |
-> m () |
helper function to bind an INTEGER column
:: (MonadIO m, MonadFail m) | |
=> SQLHSTMT | statement handle |
-> SQLSMALLINT | column number (starting with 1) |
-> CString | buffer to receive the null terminated text data |
-> SQLINTEGER | buffer length in bytes, including the null terminating character |
-> Ptr SQLINTEGER | pointer to indicator or length; it can be null |
-> m () |
helper function to bind a VARCHAR column. The buffer length parameter must include the
NULL terminating character of the CString
.
bindCol :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> SQLSMALLINT -> SQLPOINTER -> SQLINTEGER -> Ptr SQLINTEGER -> m () Source #
wrapper for BindCol SQL CLI API call; if an error occurs the computation is stopped and diagnostics are displayed on the standard error
execDirect :: (MonadIO m, MonadFail m) => SQLHSTMT -> String -> m () Source #
wrapper for SQL CLI ExecDirect API call; if an error occurs, the computation exits displaying diagnostics on the standard error
connect :: (MonadIO m, MonadFail m) => SQLHENV -> String -> String -> String -> m SQLHDBC Source #
utility function that allocates a database connection handle and connects to the database.
On success, the computation returns the handle to the database conncection.
On error, the computation exits, displaying diagnostics on the standard error.
disconnect :: SQLHDBC -> IO () Source #
wrapper for SQL CLI Disconnect API call; displays diagnostics on the standard error.
allocHandle :: (MonadIO m, MonadFail m) => SQLSMALLINT -> SQLINTEGER -> m SQLINTEGER Source #
wrapper to SQL CLI AllocHandle API call; it displays diagnostics info on the standard error and fails if the handle could not be allocated
freeHandle :: SQLSMALLINT -> SQLINTEGER -> IO () Source #
wrapper for SQL CLI FreeHandle API call; it displays diagnostics on the standard error; it does not fail
displayDiagInfo :: SQLSMALLINT -> SQLINTEGER -> IO () Source #
create an IO
action that displays diagnostic records for a given handle on the
standard error; this action will not fail
displayDiagInfo' :: (MonadIO m, MonadFail m) => SQLSMALLINT -> SQLINTEGER -> m () Source #
create a monadic action to display the diagnostic records for a given handle on the standard error; it fails if an error occurs while reading diagnostic records.
getCountOfDiagRecs :: (MonadIO m, MonadFail m) => SQLSMALLINT -> SQLINTEGER -> m Int Source #
create a monadic action to read the number of the diagnostic records for a given handle; it fails if an error occurs and it displays diagnostics on standard error
data DiagRecord Source #
information in a diagnostic record
getDiagRec :: (MonadIO m, MonadFail m) => SQLSMALLINT -> SQLINTEGER -> SQLSMALLINT -> m DiagRecord Source #
wrapper for SQL CLI GetDiagRec API call; the computation fails if an error occurs and it displays diagnostics on standard error
withMaybeCStringLen :: Maybe String -> (CStringLen -> IO a) -> IO a Source #
helper function to allocate a CStringLen
; it calls the function
received as parameter with the address of the allocated string or
with a null pointer if no string was received as input (i.e. Nothing
)
peekMaybeCol :: Storable a => Ptr a -> Ptr SQLINTEGER -> IO (Maybe a) Source #
helper function to read a nullable column; returns Nothing if the column is null
peekMaybeTextCol :: CString -> Ptr SQLINTEGER -> IO (Maybe String) Source #
helper function to read a nullable text column; returns Nothing if the column is null