module SQL.CLI.Utils where
import Prelude hiding (fail, log)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Fail (MonadFail, fail)
import Control.Logging (log, debugS)
import System.IO (hPutStrLn, stderr)
import Foreign.C.String (withCStringLen, peekCString, peekCStringLen, CStringLen, CString)
import Foreign.Marshal.Alloc (alloca, allocaBytes)
import Foreign.Storable (Storable, peek, peekElemOff, sizeOf, poke)
import Foreign.Ptr (nullPtr, castPtr, Ptr)
import Data.Maybe (maybe)
import Data.String (IsString(fromString))
import Data.Text (Text)
import Data.List (insert)
import Control.Monad.Trans.Maybe (MaybeT, runMaybeT)
import Control.Monad.Trans.Reader (ReaderT, asks)
import SQL.CLI (sqlallochandle,
sqlfreehandle,
sqlgetdiagfield,
sqlgetdiagrec,
sqlconnect,
sqldescribecol,
sqldisconnect,
sqlexecdirect,
sqlexecute,
sqlprepare,
sqlbindcol,
sqlfetch,
sqlgetdata,
sqltables,
sqlcolumns,
sqlparamdata,
sqlputdata,
sqlbindparam,
sqlgetstmtattr,
sqlnumresultcols,
sqlgetdescrec,
sqlsetdescrec,
sqlgetdescfield,
sqlsetdescfield,
sqlsetconnectattr,
sqlendtran,
sql_handle_env,
sql_handle_dbc,
sql_handle_stmt,
sql_handle_desc,
sql_null_handle,
sql_error,
sql_diag_number,
sql_success,
sql_success_with_info,
sql_invalid_handle,
sql_no_data,
sql_need_data,
sql_max_message_length,
sql_null_data,
sql_char,
sql_smallint,
sql_integer,
sql_numeric,
sql_decimal,
sql_integer,
sql_smallint,
sql_float,
sql_real,
sql_double,
sql_datetime,
sql_varchar,
sql_no_nulls,
SQLSMALLINT,
SQLINTEGER,
SQLHENV,
SQLHDBC,
SQLHSTMT,
SQLHDESC,
SQLCHAR,
SQLPOINTER,
SQLHANDLE,
SQLLEN,
SQLULEN)
logsrc :: Text
logsrc = fromString "SQL.CLI.Utils"
toCLIType :: SQLSMALLINT -> SQLSMALLINT
toCLIType t = if elem t [sql_char, sql_numeric, sql_decimal, sql_integer, sql_smallint,
sql_float, sql_real, sql_double, sql_datetime, sql_varchar]
then t
else sql_char
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 }
deriving (Eq, Show)
instance Ord ColumnInfo where
compare c1 c2 = compare (ci_OrdinalPosition c1) (ci_OrdinalPosition c2)
collectColumnsInfo :: (MonadIO m, MonadFail m) => SQLHDBC
-> String
-> String
-> ReaderT SQLConfig m [ColumnInfo]
collectColumnsInfo hdbc schemaName tableName = do
hstmt <- allocHandle sql_handle_stmt hdbc
columns hstmt Nothing (Just schemaName) (Just tableName) Nothing
collectColumnsInfo' hstmt
collectColumnsInfo' :: (MonadIO m, MonadFail m) => SQLHSTMT -> ReaderT SQLConfig m [ColumnInfo]
collectColumnsInfo' hstmt = do
table_cat_fld <- asks sql_cli_flds_table_cat
table_schem_fld <- asks sql_cli_flds_table_schem
table_name_fld <- asks sql_cli_flds_table_name
column_name_fld <- asks sql_cli_flds_column_name
data_type_fld <- asks sql_cli_flds_data_type
type_name_fld <- asks sql_cli_flds_type_name
column_size_fld <- asks sql_cli_flds_column_size
buffer_length_fld <- asks sql_cli_flds_buffer_length
decimal_digits_fld <- asks sql_cli_flds_decimal_digits
num_prec_radix_fld <- asks sql_cli_flds_num_prec_radix
nullable_fld <- asks sql_cli_flds_nullable
remarks_fld <- asks sql_cli_flds_remarks
column_def_fld <- asks sql_cli_flds_column_def
datetime_code_fld <- asks sql_cli_flds_datetime_code
char_octet_length_fld <- asks sql_cli_flds_char_octet_length
ordinal_position_fld <- asks sql_cli_flds_ordinal_position
is_nullable_fld <- asks sql_cli_flds_is_nullable
cols <- liftIO $
allocaBytes 129
(\ p_table_cat ->
alloca
(\ p_table_cat_ind ->
allocaBytes 129
(\ p_table_schem ->
allocaBytes 129
(\ p_table_name ->
allocaBytes 129
(\ p_column_name ->
alloca
(\ p_data_type ->
allocaBytes 129
(\ p_type_name ->
alloca
(\ p_column_size ->
alloca
(\ p_column_size_ind ->
alloca
( \ p_buffer_length ->
alloca
(\ p_buffer_length_ind ->
alloca
(\ p_decimal_digits ->
alloca
(\ p_decimal_digits_ind ->
alloca
(\ p_num_prec_radix ->
alloca
(\ p_num_prec_radix_ind ->
alloca
(\ p_nullable ->
allocaBytes 255
(\ p_remarks ->
alloca
(\ p_remarks_ind ->
allocaBytes 255
(\ p_column_def ->
alloca
(\ p_column_def_ind ->
alloca
(\ p_datetime_code ->
alloca
(\ p_datetime_code_ind ->
alloca
(\ p_char_octet_length ->
alloca
(\ p_char_octet_length_ind ->
alloca
(\ p_ordinal_position ->
allocaBytes 255
(\ p_is_nullable ->
alloca
(\ p_is_nullable_ind ->
let readColumnInfo :: [ColumnInfo] -> MaybeT IO [ColumnInfo]
readColumnInfo cols' = do
col <- liftIO $ ColumnInfo
<$> (peekMaybeTextCol p_table_cat p_table_cat_ind)
<*> (peekCString p_table_schem)
<*> (peekCString p_table_name)
<*> (peekCString p_column_name)
<*> (peek p_data_type)
<*> (peekCString p_type_name)
<*> (peekMaybeCol p_column_size p_column_size_ind)
<*> (peekMaybeCol p_buffer_length p_buffer_length_ind)
<*> (peekMaybeCol p_decimal_digits p_decimal_digits_ind)
<*> (peekMaybeCol p_num_prec_radix p_num_prec_radix_ind)
<*> (peek p_nullable)
<*> (peekMaybeTextCol p_remarks p_remarks_ind)
<*> (peekMaybeTextCol p_column_def p_column_def_ind)
<*> (peekMaybeCol p_datetime_code p_datetime_code_ind)
<*> (peekMaybeCol p_char_octet_length p_char_octet_length_ind)
<*> (peek p_ordinal_position)
<*> (peekMaybeTextCol p_is_nullable p_is_nullable_ind)
liftIO $ poke p_data_type 0
liftIO $ poke p_column_size 0
liftIO $ poke p_buffer_length 0
liftIO $ poke p_decimal_digits 0
liftIO $ poke p_num_prec_radix 0
liftIO $ poke p_nullable 0
liftIO $ poke p_datetime_code 0
liftIO $ poke p_char_octet_length 0
liftIO $ poke p_ordinal_position 0
liftIO $ poke p_table_cat_ind 0
liftIO $ poke p_column_size_ind 0
liftIO $ poke p_buffer_length_ind 0
liftIO $ poke p_decimal_digits_ind 0
liftIO $ poke p_num_prec_radix_ind 0
liftIO $ poke p_remarks_ind 0
liftIO $ poke p_column_def_ind 0
liftIO $ poke p_datetime_code_ind 0
liftIO $ poke p_char_octet_length_ind 0
liftIO $ poke p_is_nullable_ind 0
return $ insert col cols'
in runMaybeT $ do
bindVarcharCol hstmt table_cat_fld p_table_cat 129 p_table_cat_ind
bindVarcharCol hstmt table_schem_fld p_table_schem 129 nullPtr
bindVarcharCol hstmt table_name_fld p_table_name 129 nullPtr
bindVarcharCol hstmt column_name_fld p_column_name 129 nullPtr
bindSmallIntCol hstmt data_type_fld p_data_type nullPtr
bindVarcharCol hstmt type_name_fld p_type_name 129 nullPtr
bindIntegerCol hstmt column_size_fld p_column_size p_column_size_ind
bindIntegerCol hstmt buffer_length_fld p_buffer_length p_buffer_length_ind
bindSmallIntCol hstmt decimal_digits_fld p_decimal_digits p_decimal_digits_ind
bindSmallIntCol hstmt num_prec_radix_fld p_num_prec_radix p_num_prec_radix_ind
bindSmallIntCol hstmt nullable_fld p_nullable nullPtr
bindVarcharCol hstmt remarks_fld p_remarks 255 p_remarks_ind
bindVarcharCol hstmt column_def_fld p_column_def 255 p_column_def_ind
bindIntegerCol hstmt datetime_code_fld p_datetime_code p_datetime_code_ind
bindIntegerCol hstmt char_octet_length_fld p_char_octet_length p_char_octet_length_ind
bindIntegerCol hstmt ordinal_position_fld p_ordinal_position nullPtr
bindVarcharCol hstmt is_nullable_fld p_is_nullable 255 p_is_nullable_ind
liftIO $ log $ fromString "reading columns info records"
forAllRecords hstmt readColumnInfo [])))))))))))))))))))))))))))
liftIO $ freeHandle sql_handle_stmt hstmt
maybe (fail "collectColumnsInfo failed") return cols
tableExists :: (MonadIO m, MonadFail m) => SQLHDBC
-> String
-> String
-> m Bool
tableExists hdbc schemaName tableName = do
tables_stmt <- allocHandle sql_handle_stmt hdbc
tables tables_stmt Nothing (Just schemaName) (Just tableName) Nothing
exists <- fetch tables_stmt
liftIO $ freeHandle sql_handle_stmt tables_stmt
return exists
endTran :: (MonadIO m, MonadFail m) =>
SQLSMALLINT
-> SQLHANDLE
-> SQLSMALLINT
-> m ()
endTran handleType handle completion = do
result <- liftIO $ sqlendtran handleType handle completion
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
let err = "call to SQL/CLI function EndTran failed, on handle type: " ++ (show handleType)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo handleType handle
fail err
| x == sql_success_with_info -> do
liftIO $ log $ fromString $ "call to SQL/CLI function EndTran generated warnings for handle type: " ++ (show handleType)
liftIO $ displayDiagInfo handleType handle
| x == sql_invalid_handle -> do
let err = "invalid handle was given to a call to the SQL/CLI function EndTran, for handle type: " ++ (show handleType)
liftIO $ log $ fromString err
fail err
| otherwise -> do
let err = "unexpected result was returned by a call to SQL/CLI function EndTran for handleType " ++ (show handleType) ++ ": " ++ (show x)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo handleType handle
fail err
setConnectAttr :: (MonadIO m, MonadFail m) => SQLHDBC -> SQLINTEGER -> SQLPOINTER -> SQLINTEGER -> m ()
setConnectAttr hdbc attribute value stringLen = do
result <- liftIO $ sqlsetconnectattr hdbc attribute value stringLen
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
let err = "call to SQL/CLI function SetConnectAttr failed for attribute: " ++ (show attribute)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_dbc hdbc
fail err
| x == sql_success_with_info -> do
liftIO $ log $ fromString $ "call to SQL/CLI function SetConnectAttr returned warnings for attribute " ++ (show attribute)
liftIO $ displayDiagInfo sql_handle_dbc hdbc
| x == sql_invalid_handle -> do
let err = "invalid handle given to SQL/CLI function SetConnectAtr when setting attribute: " ++ (show attribute)
liftIO $ log $ fromString err
fail err
| otherwise -> do
let err = "unknown result returned by the call of SQL/CLI function SetConnectAttr for attribute " ++ (show attribute) ++ ": " ++ (show attribute)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_dbc hdbc
fail err
setDescField :: (MonadIO m, MonadFail m) => SQLHDESC
-> SQLSMALLINT
-> SQLSMALLINT
-> Ptr a
-> SQLINTEGER
-> m ()
setDescField hdesc recno field pbuf buflen = do
result <- liftIO $ sqlsetdescfield hdesc recno field (castPtr pbuf) buflen
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
let err = "call to SQL/CLI function SetDescField failed, for record " ++ (show recno) ++ ", field " ++ (show field)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_desc hdesc
fail err
| x == sql_success_with_info -> do
liftIO $ log $ fromString $ "call to SQL/CLI function SetDescField for record " ++ (show recno) ++ ", field " ++ (show field) ++ " generated warnings"
liftIO $ displayDiagInfo sql_handle_desc hdesc
| x == sql_invalid_handle -> do
let err = "invalid handle was given to a call to SQL/CLI function SetDescField for record " ++ (show recno) ++ ", field " ++ (show field)
liftIO $ log $ fromString err
fail err
| otherwise -> do
let err = "unexpected result code was returned by the call to SQL/CLI function SetDescField for record " ++ (show recno) ++ ", field " ++ (show field) ++ ": " ++ (show x)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_desc hdesc
fail err
getDescField :: (MonadIO m, MonadFail m) => SQLHDESC
-> SQLSMALLINT
-> SQLSMALLINT
-> Ptr a
-> SQLINTEGER
-> Ptr SQLINTEGER
-> m ()
getDescField hdesc recno field pbuf buflen plen = do
result <- liftIO $ sqlgetdescfield hdesc recno field (castPtr pbuf) buflen plen
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
let err = "call to SQL/CLI function GetDescField failed for record " ++ (show recno) ++", field " ++ (show field)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_desc hdesc
fail err
| x == sql_success_with_info -> do
liftIO $ log $ fromString $ "call to SQL/CLI function for record " ++ (show recno) ++ ", field " ++ (show field) ++ " generated warnings"
liftIO $ displayDiagInfo sql_handle_desc hdesc
| x == sql_invalid_handle -> do
let err = "invalid handle was given to the call of getDescField for record " ++ (show recno) ++ ", field " ++ (show field)
liftIO $ log $ fromString err
fail err
| otherwise -> do
let err = "unexpected result code returned by the call to SQL/CLI function GetDescField for record " ++ (show recno) ++ ", field " ++ (show field) ++ ": " ++ (show x)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_desc hdesc
fail err
setDescRec :: (MonadIO m, MonadFail m) => SQLHDESC
-> SQLSMALLINT
-> SQLSMALLINT
-> SQLSMALLINT
-> SQLINTEGER
-> SQLSMALLINT
-> SQLSMALLINT
-> Ptr a
-> Ptr SQLLEN
-> Ptr SQLLEN
-> m ()
setDescRec hdesc recno coltype subtype len precision scale p_data p_stringlength p_indicator = do
result <- liftIO $ sqlsetdescrec hdesc recno coltype subtype len precision scale (castPtr p_data) p_stringlength p_indicator
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
let err = "call to SQL/CLI function SetDescRec failed for record number " ++ (show recno)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_desc hdesc
fail err
| x == sql_success_with_info -> do
liftIO $ log $ fromString $ "call to SQL/CLI function SetDescRec generated warnings for record number " ++ (show recno)
liftIO $ displayDiagInfo sql_handle_desc hdesc
| x == sql_invalid_handle -> do
let err = "invalid handle was given to the call of SQL/CLI function SetDescRec for record number " ++ (show recno)
liftIO $ log $ fromString err
fail err
| otherwise -> do
let err = "unexpected result code (" ++ (show x) ++ ") returned by the call to SQL/CLI function SetDescRec for record number " ++ (show recno)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_desc hdesc
fail err
getDescRec :: (MonadIO m, MonadFail m) => SQLHDESC
-> SQLSMALLINT
-> Ptr SQLCHAR
-> SQLSMALLINT
-> Ptr SQLSMALLINT
-> Ptr SQLSMALLINT
-> Ptr SQLSMALLINT
-> Ptr SQLLEN
-> Ptr SQLSMALLINT
-> Ptr SQLSMALLINT
-> Ptr SQLSMALLINT
-> m ()
getDescRec hdesc recno p_colname buflen p_namelen p_type p_subtype p_length p_precision p_scale p_nullable = do
result <- liftIO $ sqlgetdescrec hdesc recno p_colname buflen p_namelen p_type p_subtype p_length p_precision p_scale p_nullable
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
let err = "call to SQL/CLI function GetDescRec failed"
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_desc hdesc
fail err
| x == sql_success_with_info -> do
let err = "call to SQL/CLI function GetDescRec returned warnings"
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_desc hdesc
| x == sql_invalid_handle -> do
let err = "invalid handle was given to the call of SQL/CLI functiion GetDescRec"
liftIO $ log $ fromString err
fail err
| x == sql_no_data -> do
let err = "(GetDescRec) there is no record in the descriptor for this record number: " ++ (show recno)
liftIO $ log $ fromString err
fail err
| otherwise -> do
let err = "unexpected result code was returned by the call to SQL/CLI function GetDescRec: " ++ (show x)
liftIO $ log $ fromString err
fail err
numResultCols :: (MonadIO m, MonadFail m) => SQLHSTMT -> m SQLSMALLINT
numResultCols hstmt = do
cols <- liftIO $ alloca
(\ p_cols -> do
result <- sqlnumresultcols hstmt p_cols
let cols = Just <$> peek p_cols
case result of
x | x == sql_success -> cols
| x == sql_error -> do
log $ fromString "call to SQL/CLI function NumResultCols failed"
displayDiagInfo sql_handle_stmt hstmt
return Nothing
| x == sql_success_with_info -> do
log $ fromString "call to SQL/CLI function NumResultColss returned warnings"
displayDiagInfo sql_handle_stmt hstmt
cols
| x == sql_invalid_handle -> do
log $ fromString "invalid handle given to call to SQL/CLI function NumResultCols"
return Nothing
| otherwise -> do
log $ fromString $ "unexpected value returned by a call to NumResultCols: " ++ (show x)
displayDiagInfo sql_handle_stmt hstmt
return Nothing )
maybe (fail "numResultCols failed") return cols
getStorableStmtAttr :: (MonadIO m, MonadFail m, Storable a) => SQLHSTMT -> SQLINTEGER -> m a
getStorableStmtAttr hstmt attr = do
value <- liftIO $ alloca
(\ p_value -> runMaybeT $ do
getStmtAttr hstmt attr p_value 0 nullPtr
liftIO $ peek p_value)
maybe (fail $ "failed to get the statement's attribute value for attribute: " ++ (show attr)) return value
getStmtAttr :: (MonadIO m, MonadFail m) => SQLHSTMT
-> SQLINTEGER
-> Ptr a
-> SQLINTEGER
-> Ptr SQLINTEGER
-> m ()
getStmtAttr hstmt attribute p_buf buflen p_vallen = do
result <- liftIO $ sqlgetstmtattr hstmt attribute (castPtr p_buf) buflen p_vallen
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
let err = "error calling SQL/CLI function 'GetStmtAttr' for attribute " ++ (show attribute)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail err
| x == sql_success_with_info -> do
liftIO $ log $ fromString $ "getting statement attribute " ++ (show attribute) ++ " returned warnings"
liftIO $ displayDiagInfo sql_handle_stmt hstmt
| x == sql_invalid_handle -> do
let err = "invalid handle was given to a call to SQL/CLI function GetStmtAttr for attribute " ++ (show attribute)
liftIO $ log $ fromString err
fail err
| otherwise -> do
let err = "unexpected result returned by a call to SQL/CLI function GetStmtAttr for attribute " ++ (show attribute)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail err
bindParam :: (MonadIO m, MonadFail m) => SQLHSTMT
-> SQLSMALLINT
-> SQLSMALLINT
-> SQLSMALLINT
-> SQLULEN
-> SQLSMALLINT
-> Ptr a
-> Ptr SQLLEN
-> m ()
bindParam hstmt paramno valtype paramtype paramlenprec paramscale p_value p_strlen_or_ind = do
result <- liftIO $ sqlbindparam hstmt paramno valtype paramtype paramlenprec paramscale (castPtr p_value) p_strlen_or_ind
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
let err = "Error binding parameter " ++ (show paramno)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail err
| x == sql_success_with_info -> do
liftIO $ log $ fromString $ "binding parameter " ++ (show paramno) ++ " returned with warnings"
liftIO $ displayDiagInfo sql_handle_stmt hstmt
| x == sql_invalid_handle -> do
let err = "biniding parameter " ++ (show paramno) ++ " was invoked with an invalid statement handler"
liftIO $ log $ fromString err
fail err
| otherwise -> do
let err = "binding parameter " ++ (show paramno) ++ " returned unexepcted result: " ++ (show x)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail err
putData :: (MonadIO m, MonadFail m) => SQLHSTMT -> Ptr a -> SQLLEN -> m ()
putData hstmt p_buf len = do
result <- liftIO $ sqlputdata hstmt (castPtr p_buf) len
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
let err = "error in the call of SQL/CLI function PutData"
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail err
| x == sql_success_with_info -> do
liftIO $ log $ fromString "call to SQL/CLI function PutData returned warnings"
liftIO $ displayDiagInfo sql_handle_stmt hstmt
| x == sql_invalid_handle -> do
let err = "an invalid handle was used when calling putData"
liftIO $ log $ fromString err
fail err
| otherwise -> do
let err = "call to SQL/CLI function PutData returned unexpected result: " ++ (show x)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail err
paramData :: (MonadIO m, MonadFail m) => SQLHSTMT -> (SQLPOINTER -> m ()) -> m ()
paramData hstmt f = do
(result, value) <- liftIO $ alloca (\ p_value -> do
result' <- sqlparamdata hstmt p_value
value' <- peek p_value
return (result', value'))
case result of
x | x == sql_need_data -> do
f value
paramData hstmt f
| x == sql_error -> do
let err = "call to SQL/CLI function ParamData failed"
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail err
| x == sql_success -> return ()
| x == sql_success_with_info -> do
liftIO $ log $ fromString "(ParamData) statement executed but generated warnings"
liftIO $ displayDiagInfo sql_handle_stmt hstmt
| x == sql_no_data -> do
liftIO $ log $ fromString "ParamData: statement executed but returned no_data"
liftIO $ displayDiagInfo sql_handle_stmt hstmt
| x == sql_invalid_handle -> do
let err = "invalid handle has been given to paramData"
liftIO $ log $ fromString err
fail err
| otherwise -> do
let err = "unexpected result returned by a call to SQL/CLI function ParamData: " ++ (show x)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail err
prepare :: (MonadIO m, MonadFail m) => SQLHSTMT -> String -> m ()
prepare hstmt sql = do
result <- liftIO $ withCStringLen sql
(\ (p_sql, len_sql) -> sqlprepare hstmt (castPtr p_sql) (fromIntegral len_sql))
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
let err = "Failed preparing statement: " ++ sql
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail err
| x == sql_success_with_info -> liftIO $ do
log $ fromString $ "Statement prepared but warnings were returned: " ++ sql
displayDiagInfo sql_handle_stmt hstmt
| x == sql_invalid_handle -> do
let err = "Failed preparing statement because an invalid handle was given to 'prepare' call: " ++ sql
liftIO $ log $ fromString err
fail err
| otherwise -> do
let err = "Unexpected returned code (" ++ (show x) ++ ") was returned by 'sqlprepare' call when preparing statement: " ++ sql
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail err
execute :: (MonadIO m, MonadFail m) => SQLHSTMT -> m () -> m ()
execute hstmt feeddata = do
result <- liftIO $ sqlexecute hstmt
case result of
x | x == sql_success -> return ()
| x == sql_success_with_info -> do
liftIO $ log $ fromString "'Execute' API call succeded but returned more info"
liftIO $ displayDiagInfo sql_handle_stmt hstmt
| x == sql_error -> do
let err = "'Execute' API call failed"
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail err
| x == sql_invalid_handle -> do
let err = "'Execute' has been called with invalid statement handle"
liftIO $ log $ fromString err
fail err
| x == sql_no_data -> do
liftIO $ log $ fromString "'Execute' returned SQL_NO_DATA"
liftIO $ displayDiagInfo sql_handle_stmt hstmt
| x == sql_need_data -> do
feeddata
| otherwise -> do
let err = "'Execute' call returned unexpected result: " ++ (show x)
liftIO $ log $ fromString err
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail err
data ConciseColInfo = ConciseColInfo {
cci_ColumnName :: String,
cci_DataType :: SQLSMALLINT,
cci_ColumnSize :: SQLULEN,
cci_DecimalDigits :: SQLSMALLINT,
cci_Nullable :: Bool }
describeCol :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> m ConciseColInfo
describeCol hstmt colnum = do
info <- liftIO $ allocaBytes 255
(\ p_columnName ->
alloca
(\ p_nameLength ->
alloca
(\ p_dataType ->
alloca
(\ p_columnSize ->
alloca
(\ p_decimalDigits ->
alloca
(\ p_nullable -> do
result <- sqldescribecol hstmt colnum p_columnName 255 p_nameLength p_dataType p_columnSize p_decimalDigits p_nullable
let readInfo = Just <$> do
nameLength <- peek p_nameLength
nullable <- peek p_nullable
ConciseColInfo
<$> peekCStringLen (castPtr p_columnName, fromIntegral nameLength)
<*> peek p_dataType
<*> peek p_columnSize
<*> peek p_decimalDigits
<*> (return $ if nullable == sql_no_nulls then False else True)
case result of
x | x == sql_success -> readInfo
| x == sql_success_with_info -> do
log $ fromString "More information returned by DescribeCol"
displayDiagInfo sql_handle_stmt hstmt
readInfo
| x == sql_error -> do
log $ fromString "Error calling DescribeCol"
displayDiagInfo sql_handle_stmt hstmt
return Nothing
| x == sql_invalid_handle -> do
log $ fromString "Invalid handle calling DescribeCol"
return Nothing
| otherwise -> do
log $ fromString $ "Unexpected result returned by the call to DescribeCol: " ++ (show x)
displayDiagInfo sql_handle_stmt hstmt
return Nothing))))))
maybe (fail $ "describeCol " ++ (show colnum) ++ " failed") return info
columns :: (MonadIO m, MonadFail m) => SQLHSTMT -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> m ()
columns hstmt catalogName schemaName tableName columnName = do
result <- liftIO $ withMaybeCStringLen catalogName
(\ (p_catalogName, catalogNameLen) ->
withMaybeCStringLen schemaName
(\ (p_schemaName, schemaNameLen) ->
withMaybeCStringLen tableName
(\ (p_tableName, tableNameLen) ->
withMaybeCStringLen columnName
(\ (p_columnName, columnNameLen) ->
sqlcolumns hstmt
(castPtr p_catalogName) (fromIntegral catalogNameLen)
(castPtr p_schemaName) (fromIntegral schemaNameLen)
(castPtr p_tableName) (fromIntegral tableNameLen)
(castPtr p_columnName) (fromIntegral columnNameLen)))))
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
liftIO $ log $ fromString "Error calling Columns"
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail "Columns failed"
| x == sql_success_with_info -> do
liftIO $ log $ fromString "Columns returned more info"
liftIO $ displayDiagInfo sql_handle_stmt hstmt
| x == sql_invalid_handle -> do
liftIO $ log $ fromString "Invalid statement handle passed to Columns call"
fail "Columns failed"
| otherwise -> do
liftIO $ log $ fromString "Unexpected return code returned by call to Columns. Trying to display diagnostic info:"
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fail "Columns failed"
tables :: (MonadIO m, MonadFail m) => SQLHSTMT -> Maybe String -> Maybe String -> Maybe String -> Maybe String -> m ()
tables hstmt catalogName schemaName tableName tableType = do
result <- liftIO $
withMaybeCStringLen catalogName
(\ (p_catalogName, catalogNameLen) ->
withMaybeCStringLen schemaName
( \ (p_schemaName, schemaNameLen) ->
withMaybeCStringLen tableName
( \ (p_tableName, tableNameLen) ->
withMaybeCStringLen tableType
( \ (p_tableType, tableTypeLen) ->
sqltables hstmt
(castPtr p_catalogName) (fromIntegral catalogNameLen)
(castPtr p_schemaName) (fromIntegral schemaNameLen)
(castPtr p_tableName) (fromIntegral tableNameLen)
(castPtr p_tableType) (fromIntegral tableTypeLen)))))
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
liftIO $ do
log $ fromString "Error calling Tables"
displayDiagInfo sql_handle_stmt hstmt
fail "Tables failed"
| x == sql_success_with_info -> do
liftIO $ do
log $ fromString "Tables returned more info"
displayDiagInfo sql_handle_stmt hstmt
| x == sql_invalid_handle -> do
liftIO $ log $ fromString "Invalid handle calling Tables"
fail "Tables failed"
| otherwise -> do
liftIO $ do
log $ fromString $ "Tables returned unexpected result: " ++ (show x)
displayDiagInfo sql_handle_stmt hstmt
fail "Tables failed"
forAllRecords :: (MonadIO m, MonadFail m) => SQLHSTMT -> (a -> m a) -> a -> m a
forAllRecords stmt f = forAllRecordsWithEndAndFail stmt f return (const fail)
forAllRecordsWithEndAndFail :: (MonadIO m, MonadFail m) => SQLHSTMT -> (a -> m a) -> (a -> m a) -> (a -> String -> m a) -> a -> m a
forAllRecordsWithEndAndFail stmt onRecord onEnd onFail accum = fetchAndRunWithFail stmt (onRecord accum >>= (\ accum' -> forAllRecordsWithEndAndFail stmt onRecord onEnd onFail accum')) (onEnd accum) (onFail accum)
forAllData :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> SQLSMALLINT -> SQLPOINTER -> SQLLEN -> Ptr SQLLEN -> (a -> m a) -> a -> m a
forAllData hstmt colNum targetType p_buf bufLen p_lenOrInd f accum =
getDataAndRun hstmt colNum targetType p_buf bufLen p_lenOrInd
(f accum >>= (\ accum' -> forAllData hstmt colNum targetType p_buf bufLen p_lenOrInd f accum'))
(f accum)
getData :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> SQLSMALLINT -> SQLPOINTER -> SQLLEN -> Ptr SQLLEN -> m Bool
getData hstmt colNum targetType p_buf bufLen p_lenOrInd = getDataAndRun hstmt colNum targetType p_buf bufLen p_lenOrInd (return True) (return False)
getDataAndRun :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> SQLSMALLINT -> SQLPOINTER -> SQLLEN -> Ptr SQLLEN -> m a -> m a -> m a
getDataAndRun hstmt colNum targetType p_buf bufLen p_lenOrInd more end = do
result <- liftIO $ sqlgetdata hstmt colNum targetType p_buf bufLen p_lenOrInd
case result of
x | x == sql_success -> end
| x == sql_invalid_handle -> do
liftIO $ log $ fromString "Invalid handle when calling GetData"
fail "GetData failed"
| x == sql_error -> do
liftIO $ do
log $ fromString "Error calling GetData"
displayDiagInfo sql_handle_stmt hstmt
fail "GetData failed"
| x == sql_no_data -> do
liftIO $ log $ fromString "GetData -> no data available"
fail "GetData failed"
| x == sql_success_with_info -> do
moreData <- isMoreData
lenOrInd <- liftIO $ peek p_lenOrInd
if moreData
then if lenOrInd == sql_null_data || lenOrInd <= bufLen
then do liftIO $ log $ fromString "GetData returned 01004, but no more data is available"
end
else more
else do
if lenOrInd == sql_null_data || lenOrInd <= bufLen
then end
else do liftIO $ log $ fromString "More data but no 01004 diagnostic record found"
more
| otherwise -> do
liftIO $ do
log $ fromString $ "GetData returned unexpected result: " ++ (show x)
displayDiagInfo sql_handle_stmt hstmt
fail "GetData failed"
where isMoreData :: (MonadIO m, MonadFail m) => m Bool
isMoreData = do
recs <- getCountOfDiagRecs sql_handle_stmt hstmt
if recs < 0
then do liftIO $ log $ fromString $ "GetData - wrong diag info records: " ++ (show recs)
return False
else do let diags = [getDiagRec sql_handle_stmt hstmt (fromIntegral i) | i <- [1..recs]]
isMoreData' <- liftIO $ runMaybeT $
let hasMoreDataRecord [] = return False
hasMoreDataRecord (x:xs) = do
drec <- x
if sqlstate drec == "01004"
then return True
else do liftIO $ log $ fromString $ "GetData warning: <" ++ (show $ sqlstate drec) ++ ">"
liftIO $ displayDiagRec drec
hasMoreDataRecord xs
in
hasMoreDataRecord diags
return $ maybe False id isMoreData'
fetch :: (MonadIO m, MonadFail m) => SQLHSTMT -> m Bool
fetch hstmt = fetchAndRun hstmt (return True) (return False)
fetchAndRun :: (MonadIO m, MonadFail m) => SQLHSTMT -> m a -> m a -> m a
fetchAndRun hstmt fetchaction endaction = fetchAndRunWithFail hstmt fetchaction endaction fail
fetchAndRunWithFail :: (MonadIO m, MonadFail m) => SQLHSTMT -> m a -> m a -> (String -> m a) -> m a
fetchAndRunWithFail hstmt fetchedaction endaction failaction = do
result <- liftIO $ sqlfetch hstmt
case result of
x | x == sql_success -> fetchedaction
| x == sql_error -> do
liftIO $ log $ fromString "Error fetching record"
liftIO $ displayDiagInfo sql_handle_stmt hstmt
failaction "Fetch failed"
| x == sql_invalid_handle -> do
liftIO $ log $ fromString "Invalid handle when fetching record"
failaction "Fetch failed due to invalid handle"
| x == sql_no_data -> do
liftIO $ log $ fromString "All records have been fetched"
endaction
| x == sql_success_with_info -> do
liftIO $ log $ fromString "More diagnostic info returned for record"
liftIO $ displayDiagInfo sql_handle_stmt hstmt
fetchedaction
| otherwise -> do
liftIO $ log $ fromString $ "Fetch returned unexepected result: " ++ (show x)
liftIO $ displayDiagInfo sql_handle_stmt hstmt
failaction "Fetch failed"
bindSmallIntCol :: (MonadIO m, MonadFail m) =>
SQLHSTMT
-> SQLSMALLINT
-> Ptr SQLSMALLINT
-> Ptr SQLLEN
-> m ()
bindSmallIntCol hstmt colNum p_buf p_ind = bindCol hstmt colNum sql_smallint (castPtr p_buf) (fromIntegral $ sizeOf (undefined :: SQLSMALLINT)) p_ind
bindIntegerCol :: (MonadIO m, MonadFail m) =>
SQLHSTMT
-> SQLSMALLINT
-> Ptr SQLINTEGER
-> Ptr SQLLEN
-> m ()
bindIntegerCol hstmt colNum p_buf p_ind = bindCol hstmt colNum sql_integer (castPtr p_buf) (fromIntegral $ sizeOf (undefined :: SQLINTEGER)) p_ind
bindVarcharCol :: (MonadIO m, MonadFail m) =>
SQLHSTMT
-> SQLSMALLINT
-> CString
-> SQLLEN
-> Ptr SQLLEN
-> m ()
bindVarcharCol hstmt colNum p_buf buflen p_ind = bindCol hstmt colNum sql_char (castPtr p_buf) buflen p_ind
bindCol :: (MonadIO m, MonadFail m) => SQLHSTMT -> SQLSMALLINT -> SQLSMALLINT -> SQLPOINTER -> SQLLEN -> Ptr SQLLEN -> m ()
bindCol hstmt colNum colType p_buf len_buf p_ind = do
result <- liftIO $ sqlbindcol hstmt colNum colType p_buf len_buf p_ind
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
liftIO $ do
log $ fromString $ "Error binding column " ++ (show colNum)
displayDiagInfo sql_handle_stmt hstmt
fail "Binding column failed"
| x == sql_success_with_info -> do
liftIO $ do
log $ fromString $ "Binding col " ++ (show colNum) ++ " returned warnings:"
displayDiagInfo sql_handle_stmt hstmt
| x == sql_invalid_handle -> do
liftIO $ log $ fromString $ "Invalid handle when binding column " ++ (show colNum)
fail "Binding column failed"
| otherwise -> do
liftIO $ do
log $ fromString $ "Invalid result when binding column " ++ (show colNum)
displayDiagInfo sql_handle_stmt hstmt
fail "Biniding column failed"
execDirect :: (MonadIO m, MonadFail m) => SQLHSTMT -> String -> m () -> m ()
execDirect hstmt sqlstr feeddata = do
result <- liftIO $ withCStringLen sqlstr
(\(sql, sqlLen) -> sqlexecdirect hstmt (castPtr sql) (fromIntegral sqlLen))
case result of
x | x == sql_success -> liftIO $ log $ fromString "sql statement executed"
| x == sql_success_with_info -> liftIO $ do
log $ fromString "Execution of sql returned more info"
displayDiagInfo sql_handle_stmt hstmt
| x == sql_error -> do
liftIO $ do
log $ fromString "Execution of sql returned error"
displayDiagInfo sql_handle_stmt hstmt
fail "execute sql statement failed"
| x == sql_invalid_handle -> do
liftIO $ do
log $ fromString "Invaild statement handle"
displayDiagInfo sql_handle_stmt hstmt
fail "execute statemnt failed"
| x == sql_need_data -> feeddata
| x == sql_no_data -> do
liftIO $ log $ fromString "Execution of statement returned no data"
fail "execute statement failed"
| otherwise -> do
liftIO $ do
log $ fromString $ "Execute statement returned unexpected result: " ++ (show x)
displayDiagInfo sql_handle_stmt hstmt
fail "Execute statement failed"
connect :: (MonadIO m, MonadFail m) => SQLHENV -> String -> String -> String -> m SQLHDBC
connect henv server user pass = do
liftIO $ log $ fromString $ "connect to server " ++ server
hdbc <- allocHandle sql_handle_dbc henv
result <- liftIO $ withCStringLen server
(\(p_server, serverLen) -> withCStringLen user
(\(p_user, userLen) -> withCStringLen pass
(\(p_pass, passLen) -> sqlconnect hdbc (castPtr p_server) (fromIntegral serverLen) (castPtr p_user) (fromIntegral userLen) (castPtr p_pass) (fromIntegral passLen))))
case result of
x | x == sql_success -> return hdbc
| x == sql_success_with_info -> do
liftIO $ log $ fromString $ "connect to server " ++ server ++ " returned warnings:"
liftIO $ displayDiagInfo sql_handle_dbc hdbc
return hdbc
| x == sql_error -> do
liftIO $ log $ fromString $ "connection to server " ++ server ++ " failed:"
liftIO $ displayDiagInfo sql_handle_dbc hdbc
liftIO $ freeHandle sql_handle_dbc hdbc
fail $ "connection to server " ++ server ++ " failed"
| x == sql_invalid_handle -> do
liftIO $ log $ fromString $ "connection to server " ++ server ++ " failed because of invalid handle"
fail $ "connection to server " ++ server ++ " failed because of invalid handle"
| otherwise -> do
liftIO $ do
log $ fromString $ "Unexpected response code got from connecting to server " ++ server ++ ": " ++ (show x)
log $ fromString "Trying to extract diagnostic info:"
displayDiagInfo sql_handle_dbc hdbc
log $ fromString "Try call disconnect on the connection handle, to make sure we release all resources"
disconnect hdbc
fail $ "Unexpected response code got from connecting to server " ++ server ++ ": " ++ (show x)
disconnect :: SQLHDBC -> IO ()
disconnect hdbc = do
result <- sqldisconnect hdbc
case result of
x | x == sql_success -> return ()
| x == sql_success_with_info -> do
log $ fromString "disconnect returned warnings:"
displayDiagInfo sql_handle_dbc hdbc
| x == sql_error -> do
log $ fromString "disconnect failed:"
displayDiagInfo sql_handle_dbc hdbc
| x == sql_invalid_handle -> do
log $ fromString "disconnect failed because of invalid handle"
| otherwise -> do
log $ fromString "Unexpected response code got from Disconnect function"
log $ fromString "Trying to extract diagnostic info:"
displayDiagInfo sql_handle_dbc hdbc
freeHandle sql_handle_dbc hdbc
allocHandle :: (MonadIO m, MonadFail m) => SQLSMALLINT -> SQLHANDLE -> m SQLHANDLE
allocHandle handleType handleParent = do
handle <- liftIO $ alloca
(\p_handle -> do
poke p_handle sql_null_handle
result <- sqlallochandle handleType handleParent p_handle
case result of
x | x == sql_success -> Just <$> peek p_handle
| x == sql_invalid_handle -> do
log $ fromString $ "alloc handle failed because of invalid parent handle, for handle type " ++ (show handleType)
displayDiagnostic
return Nothing
| x == sql_error -> do
log $ fromString $ "alloc handle failed with error for handle type " ++ (show handleType)
displayDiagnostic
return Nothing
| otherwise -> do
log $ fromString $ "alloc handle returned unexpected result for handle type " ++ (show handleType) ++ ": " ++ (show x)
displayDiagnostic
return Nothing
where displayDiagnostic = if handleType == sql_handle_env
then peek p_handle >>= displayDiagInfo sql_handle_env
else displayDiagInfo handleParentType handleParent
handleParentType = case handleType of
h | h == sql_handle_dbc -> sql_handle_env
| h == sql_handle_stmt -> sql_handle_dbc
| h == sql_handle_desc -> sql_handle_stmt
| otherwise -> 0)
maybe (fail $ "AllocHandle failed for handle type " ++ (show handleType)) return handle
freeHandle :: SQLSMALLINT -> SQLHANDLE -> IO ()
freeHandle handleType handle = do
result <- sqlfreehandle handleType handle
case result of
x | x == sql_success -> return ()
| x == sql_error -> do
log $ fromString $ "Error freeing handle of type " ++ (show handleType)
displayDiagInfo handleType handle
| x == sql_invalid_handle -> do
log $ fromString "FreeHandle failed because of invalid handle"
displayDiagInfo handleType handle
| otherwise -> do
log $ fromString $ "FreeHandle returned unexpected result " ++ (show x)
log $ fromString "Trying to get diagnostic info on FreeHandle:"
displayDiagInfo handleType handle
displayDiagInfo :: SQLSMALLINT -> SQLHANDLE -> IO ()
displayDiagInfo handleType handle = (runMaybeT $ displayDiagInfo' handleType handle) >> return ()
displayDiagInfo' :: (MonadIO m, MonadFail m) => SQLSMALLINT -> SQLHANDLE -> m ()
displayDiagInfo' handleType handle = do
recs <- getCountOfDiagRecs handleType handle
liftIO $ log $ fromString $ "there "
++ (if recs /= 1 then "are " else "is ")
++ (show recs) ++ " diagnostic record"
++ (if recs /= 1 then "s" else "")
let diags = [showDiag $ fromIntegral i | i <- [1..recs]]
showDiag i = do
liftIO $ log $ fromString $ "Diagnostic record " ++ (show i)
r <- getDiagRec handleType handle i
liftIO $ displayDiagRec r
in sequence_ diags
displayDiagRec :: DiagRecord -> IO ()
displayDiagRec r = log $ fromString $ (show $ diagrec_i r) ++ ": " ++ (sqlstate r) ++ " - " ++ (show $ nativeError r) ++ " - " ++ (messageText r)
getCountOfDiagRecs :: (MonadIO m, MonadFail m) => SQLSMALLINT -> SQLHANDLE -> m SQLINTEGER
getCountOfDiagRecs handleType handle = do
recs <- liftIO $ alloca
(\ptrRecs -> do
liftIO $ poke ptrRecs 0
result <- sqlgetdiagfield handleType handle 0 sql_diag_number (castPtr ptrRecs) 0 nullPtr
case result of
x | x == sql_success -> Just <$> peek ptrRecs
| x == sql_invalid_handle -> do
log $ fromString $ "Count of diagnostic records could not be retrieved due to an invalid handle, for handle type: " ++ (show handleType)
return Nothing
| x == sql_error -> do
log $ fromString $ "Count of diagnostic records could not be retrieved because wrong arguments were passed to GetDiagField function, for handle type" ++ (show handleType)
return Nothing
| x == sql_no_data -> do
log $ fromString $ "No diagnostic data available for handle type: " ++ (show handleType)
return $ Just 0
| otherwise -> do
log $ fromString $ "Getting the number of diagnostic records returned unexpected return code for handle type " ++ (show handleType) ++ ": " ++ (show x)
return Nothing)
maybe (fail "GetDiagField api call failed when reading number of diagnostic errors") return recs
data DiagRecord = DiagRecord {
diagrec_i :: SQLSMALLINT,
sqlstate :: String,
nativeError :: SQLINTEGER,
messageText :: String
}
getDiagRec :: (MonadIO m, MonadFail m) => SQLSMALLINT -> SQLHANDLE -> SQLSMALLINT -> m DiagRecord
getDiagRec handleType handle recnum = do
diagrecord <- liftIO $ allocaBytes 5
(\p_sqlstate -> alloca
(\p_nativeErr -> allocaBytes sql_max_message_length
(\p_messageText -> alloca
(\p_textLen -> do
result <- sqlgetdiagrec handleType handle recnum p_sqlstate p_nativeErr p_messageText sql_max_message_length p_textLen
case result of
x | x == sql_success -> do
l_sqlstate <- (map (toEnum . fromIntegral)) <$> (sequence [peekElemOff p_sqlstate j | j <- [0..4]])
l_nativeErr <- peek p_nativeErr
textLen <- fromIntegral <$> peek p_textLen
l_messageText <- (map (toEnum . fromIntegral)) <$> (sequence [peekElemOff p_messageText j | j <- [0..textLen]])
return $ Just $ DiagRecord recnum l_sqlstate l_nativeErr l_messageText
| x == sql_error -> do
log $ fromString $ (show recnum) ++ ": Diagnostic information could not be retrieved becuase wrong arguments passed to GetDagRec function"
return Nothing
| x == sql_invalid_handle -> do
log $ fromString $ (show recnum) ++ ": Diagnosic information could not be retrieved because of wrong handler"
return Nothing
| x == sql_no_data -> do
log $ fromString $ (show recnum) ++ ": No diagnostic data available"
return Nothing
| otherwise -> do
log $ fromString $ (show recnum) ++ ": Getting diagnostic information returned unexpected error code " ++ (show x)
return Nothing))))
maybe (fail "GetDiagRec call failed") return diagrecord
withMaybeCStringLen :: Maybe String -> (CStringLen -> IO a) -> IO a
withMaybeCStringLen Nothing f = f (nullPtr, 0)
withMaybeCStringLen (Just s) f = withCStringLen s f
peekMaybeCol :: (Storable a) => Ptr a -> Ptr SQLLEN -> IO (Maybe a)
peekMaybeCol p_col p_ind = do
ind <- peek p_ind
if ind == sql_null_data
then return Nothing
else do col <- peek p_col
debugS logsrc $ fromString $ "reading value of len " ++ (show ind) ++ " from buffer with len " ++ (show $ sizeOf col)
return $ Just col
peekMaybeTextCol :: CString -> Ptr SQLLEN -> IO (Maybe String)
peekMaybeTextCol p_col p_ind = do
ind <- peek p_ind
if ind == sql_null_data
then return Nothing
else Just <$> peekCString p_col