sqlcli-0.1.0.0: Sql Call-Level Interface bindings for Haskell.

Safe HaskellSafe
LanguageHaskell2010

SQL.CLI.Utils

Synopsis

Documentation

data SQLConfig Source #

configuration values dependent on the actual CLI implementation

Constructors

SQLConfig 

Fields

collectColumnsInfo :: (MonadIO m, MonadFail m) => SQLHDBC -> String -> ReaderT SQLConfig m [ColumnInfo] Source #

Read columns information for a given table on a database connection. It returns a ReaderT value that will get implementation dependent fieled numbers in the result set returned by Columns API call from a SQLConfig value.

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 #

Read data from a column and checks the diagnostics, returning a True or False value inside a monadic action. It returns True if more data is available for read, and False otherwise. It fails in MaybeT IO monad if an error occured. It displays the diagnostics on the error on the standard error.

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.

fetch :: (MonadIO m, MonadFail m) => SQLHSTMT -> m Bool Source #

Create a monadic action to fetch the next record in an executed statement producing True if there are more records available or False if all the records have been read.

If an error occurs, the monadic action fails, displaying the error diagnostics on the standard error.

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.

bindSmallIntCol Source #

Arguments

:: (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

bindIntegerCol Source #

Arguments

:: (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

bindVarcharCol Source #

Arguments

:: (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