Closed GitMensch closed 1 year ago
Note: I'd have to recheck but very likely the data should be stored and an sqlcode for "field truncated" be set.
I have added a test case (commits 5dce10a9df2dd76b6470c9c53869aec7101e3fa1 and 03b576b93476c9d95be626d272c374ac403b6155):
IDENTIFICATION DIVISION.
PROGRAM-ID. TSQL036A.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. IBM-AT.
OBJECT-COMPUTER. IBM-AT.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
DATA DIVISION.
FILE SECTION.
WORKING-STORAGE SECTION.
01 DATASRC PIC X(64).
01 DBUSR PIC X(64).
01 DBPWD PIC X(64).
01 TESTGRP.
03 TESTNUM PIC S9(8).
03 TESTREM PIC 9(2).
EXEC SQL
INCLUDE SQLCA
END-EXEC.
PROCEDURE DIVISION.
000-CONNECT.
DISPLAY "DATASRC" UPON ENVIRONMENT-NAME.
ACCEPT DATASRC FROM ENVIRONMENT-VALUE.
DISPLAY "DATASRC_USR" UPON ENVIRONMENT-NAME.
ACCEPT DBUSR FROM ENVIRONMENT-VALUE.
DISPLAY "DATASRC_PWD" UPON ENVIRONMENT-NAME.
ACCEPT DBPWD FROM ENVIRONMENT-VALUE.
EXEC SQL
CONNECT TO :DATASRC USER :DBUSR USING :DBPWD
END-EXEC.
DISPLAY 'CONNECT SQLCODE: ' SQLCODE
IF SQLCODE <> 0 THEN
GO TO 100-EXIT
END-IF.
100-MAIN.
EXEC SQL
SELECT
TESTNUM INTO :TESTNUM FROM TAB01
END-EXEC.
DISPLAY 'SELECT SQLCODE: ' SQLCODE.
IF SQLCODE <> 0 THEN
GO TO 100-EXIT
END-IF.
DISPLAY 'RES: [' TESTNUM ']'.
DISPLAY 'RES: [' TESTREM ']'.
EXEC SQL CONNECT RESET END-EXEC.
100-EXIT.
STOP RUN.
When initializing the test database with:
CREATE TABLE TAB01 (TESTNUM INTEGER)
INSERT INTO TAB01 (TESTNUM) VALUES (2147483647)
It currently fails:
Output: D:\gix_tmp_test\TSQL036A.exe (14848 bytes)
Running TSQL036A.exe
CONNECT SQLCODE: +0000000000
SELECT SQLCODE: +0000000000
RES: [+21474836]
RES: [47]
Output mismatch (index: 2, expected: RES: [+47483647]
Expected: True
But was: False
Working from here, thanks for spotting this
Note: I'd have to recheck but very likely the data should be stored and an sqlcode for "field truncated" be set.
From what I see in the IBM docs, this situation should be flagged by using indicator variables (that are not currently supported). I cannot find any mention of setting a SQLCODE
value, but it might be a DB-specific thing.
From what I've seen there would be a message in SQLERRM
and the SQLSTATE
according to https://www.ibm.com/docs/en/informix-servers/12.10?topic=code-list-sqlstate-codes to 22003
(22001 for string fields) and possibly one of the indicator variables set to the matching argument number.
SQLCODE
would be set to some negative number "The meanings of these codes are documented in the online error message file" which is at https://www.ibm.com/docs/en/db2-for-zos/11?topic=codes-sql-error and for this specific case: 410
.
From what I've seen there would be a message in
SQLERRM
and theSQLSTATE
according to
You are right, I missed that
Hint: edited with specifying the correct SQLSTATE
- note: this is, other than SQLCODE
and similar the actual message stored in SQLERRM
, is "in most places" not depending on the dbms.
Oracle would also set SQLSTATE
to 22003
, according to https://docs.oracle.com/cd/A57673_01/DOC/api/doc/PCC18/ch08.htm#SVrulesASno and for SQLCODE
"Negative return codes correspond to error codes listed in Oracle7 Server Messages."
https://github.com/mridoni/gixsql/commit/fdd261b05f1965ec40e143042129e79b011e9e27 should fix this particular problem, it needs some more accurate testing.
Thanks for the update. I tend to think that the implementation is not correct yet:
Wouldn't it be reasonable to have an int status = DBERR_NO_ERROR
variable that gets updated to DBERR_INVALID_COLUMN_DATA
/ sqlcode
on error so that all columns are handled in the error case (and logging be done for all and only a single calloc/free is done)?
In this case the last lines in the referenced code above and similar places would be
// set result params
int datalen = 0, sqlcode = 0;
bool has_invalid_column_data = false;
int bsize = _res_sql_var_list.getMaxLength() + VARLEN_LENGTH_SZ + 1;
char* buffer = (char*)calloc(1, bsize);
for (int i = 0; i < _res_sql_var_list.size(); i++) {
SqlVar* v = _res_sql_var_list.at(i);
if (!dbi->get_resultset_value(ResultSetContextType::PreparedStatement, stmt_name, 0, i, buffer, bsize, &datalen)) {
setStatus(st, dbi, DBERR_INVALID_COLUMN_DATA);
sql_code = DBERR_INVALID_COLUMN_DATA;
// log here if not done in setStatus
continue;
}
int sql_code_local;
v->createCobolData(buffer, datalen, &sql_code_local);
spdlog::trace(FMT_FILE_FUNC "result parameter {} - addr: {}", __FILE__, __func__, i + 1, (void*)v->getAddr());
if (sql_code_local) {
setStatus(st, dbi, sql_code_local);
sql_code = sql_code_local;
// log here if not done in setStatus
// continue;
}
}
free(buffer);
if (sql_code != 0) {
return RESULT_FAILED;
}
setStatus(st, NULL, DBERR_NO_ERROR);
return RESULT_SUCCESS;
Makes sense, I will look into it in the next few days.
Thanks
Do you consider anything to be open here?
Do you consider anything to be open here?
No, not really, I am closing it
This code is currently wrong:
https://github.com/mridoni/gixsql/blob/b01a1c932586ee690f6307058de31a6fe8b3dd7d/runtime/libgixsql/SqlVar.cpp#L380-L542
The point here:
... so far: totally correct.
The issue for
COBOL_TYPE_UNSIGNED_NUMBER
,COBOL_TYPE_SIGNED_NUMBER
andCOBOL_TYPE_SIGNED_NUMBER_LS
the data is copied based on the data length (*ptr != '\0'
/strlen()
) without appropriate check and truncation.Other than "origin" that writes to a local buffer and then copies the result to the COBOL address (and also writing before the buffer as there's no check like gixsql does with
fill_zero < 0
) gixsql directly writes the COBOL data, which is fine; but it doesn't handle truncation either if the COBOL field is smaller, for example anS9(8)
.With "origin" one will very likely get a SIGSEGV or double free error because the 2147483647 will be copied two bytes before the local buffer, then the buffer is copied to the COBOL data: "2147483647" -> data-2; if the memory layout does not result in a crash, then the "expected" truncation happens out of luck, because the COBOL data itself will point to "47483647".
With GixSQL there's a check to ensure we don't write "before" the data, but this means we end in "21474836" being written to the COBOL field (wrong truncation) and likely "47" being written to the following COBOL field (which often won't be seen as often the COBOL field behind the original one will be written to afterwards in the same SQL statement. If the "strlen" size is much bigger than the COBOL field or the COBOL field is "at the end", the memcpy done may write to other data (in GnuCOBOL modules: "module locale" data like CALL pointers) which can crash the program at some unexpected place.
TODO: explicit handle truncation (
strlen(restr) > this->length
).