Problem:
Application runs on the mainframe, using DB2 for Z/OS.
The application is using the following SQL command on a dynamic statement:
EXEC SQL
PREPARE SEL FROM :STMTBUF
END-EXEC.
MOVE 300 TO SQLN.
EXEC SQL
DESCRIBE SEL INTO :SQLDA
END-EXEC.
The DESCRIBE command will populate the SQLDA structure with information about the columns that will be returned in the select statement specified in host variable SEL.
This includes the name of the various columns along with length information.
For columns of type decimal the documentation states that byte one of the SQLLEN field will contain the precision of the decimal field and the second byte will contain the scaling.
So for a decimal field with a length of 10 and no decimal point, byte one will contain the value 10 and byte two will contain 0.
On the mainframe the SQLDA structure used is as follows:
(notice numeric values defined as COMP)
01 SQLDA.
02 SQLDAID PIC X(8) VALUE 'SQLDA '.
02 SQLDABC PIC S9(8) COMP VALUE 13216.
02 SQLN PIC S9(4) COMP VALUE 300.
02 SQLD PIC S9(4) COMP VALUE 0.
02 SQLVAR OCCURS 300 TIMES.
03 SQLTYPE PIC S9(4) COMP.
03 SQLLEN PIC S9(4) COMP.
03 SQLDATA POINTER.
03 SQLIND POINTER.
03 SQLNAME.
49 SQLNAMEL PIC S9(4) COMP.
49 SQLNAMEC PIC X(30).
In Net Express the SQLDA structure used is as follows:
(notice numeric values defined as COMP-5)
01 SQLDA sync.
05 SQLDAID PIC X(8) VALUE "SQLDA ".
05 SQLDABC PIC S9(9) COMP-5 value 0.
05 SQLN PIC S9(4) COMP-5 value 0.
05 SQLD PIC S9(4) COMP-5 value 0.
05 SQLVAR OCCURS 0 TO 1489 TIMES DEPENDING ON SQLD.
10 SQLTYPE PIC S9(4) COMP-5.
10 SQLLEN PIC S9(4) COMP-5.
$IF P64 SET
*> For 64-bit environments, ensure that SQLDATA is
*> aligned on an 8-byte boundary.
10 FILLER PIC S9(9) COMP-5.
$END
10 SQLDATA USAGE POINTER.
10 SQLIND USAGE POINTER.
10 SQLNAME.
15 SQLNAMEL PIC S9(4) COMP-5.
15 SQLNAMEC PIC X(30).
When moving application to Net Express under Windows accessing DB2 LUW the application fails due to incorrect value being returned for SQLLEN field in SQLDA structure.
Application uses following calculation to extract the precision and scaling values from SQLLEN field:
DIVIDE SQLLEN BY 256 GIVING COLUMN-PREC
REMAINDER COLUMN-SCALE.
This works on the mainframe but fails under Net Express, why?
Resolution:
This calculation fails under Net Express because it depends on the value of the SQLLEN field as a whole instead of the individual values of its two bytes.
IBM dictates that the precision always be in byte one and scaling always be in byte two regardless of whether COMP is used on the mainframe or COMP-5 is used on Windows systems.
So for a decimal field with precision of 10 and no decimal positions the following bytes are returned in SQLLEN on the mainframe and under Windows:
0A 00
On the mainframe which uses big-endian COMP storage the actual value of SQLLEN = 2560 whereas
on Windows which uses little-endian COMP-5 storage with the bytes reversed the actual value = 10.
This is why the calculation that works on the mainframe fails in Net Express.
Recommendation:
On Net Express use something like the following to reverse the bytes so the value will be the same as on the mainframe:
...
01 sqllenc pic s9(4) comp.
move SQLLEN(1:1) to sqllenc(1:1)
move SQLLEN(2:1) to sqllenc(2:1)
move sqllenc to SQLLEN
or extract precision and scale as follows:
01 sqllen-hold pic s9(4) comp-5.
01 sqllen-redefine redefines sqllen-hold.
05 COLUMN-PREC pic s9(2) comp-5.
05 COLUMN-SCALE pic s9(2) comp-5.
move SQLLEN to sqllen-hold