The BEGIN DECLARE SECTION statement marks the beginning of a host variable declare section.
This statement can only be embedded in an application program. It is not an executable statement. It must not be specified in REXX.
None required.
The BEGIN DECLARE SECTION statement may be coded in the application program wherever variable declarations can appear in accordance with the rules of the host language. It is used to indicate the beginning of a host variable declaration section. A host variable section ends with an END DECLARE SECTION statement.
EXEC SQL BEGIN DECLARE SECTION;
short hv_smint;
struct {
short hv_vchar24_len;
char hv_vchar24_value[24];
} hv_vchar24;
double hv_double;
SQL TYPE IS BLOB(50K) hv_blob_50k;
SQL TYPE IS struct_type AS BLOB(10k) hv_struct;
EXEC SQL END DECLARE SECTION;
WORKING-STORAGE SECTION.
EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 HV-SMINT PIC S9(4) COMP-4.
01 HV-VCHAR24.
49 HV-VCHAR24-LENGTH PIC S9(4) COMP-4.
49 HV-VCHAR24-VALUE PIC X(24).
01 HV-DEC72 PIC S9(5)V9(2) COMP-3.
01 HV-BLOB-50K USAGE SQL TYPE IS BLOB(50K).
EXEC SQL END DECLARE SECTION END-EXEC.
EXEC SQL BEGIN DECLARE SECTION
INTEGER*2 HVSMINT
CHARACTER*24 HVVCHAR24
REAL*8 HVDOUBLE
SQL TYPE IS BLOB(50K) HVBLOB50K
EXEC SQL END DECLARE SECTION
DECLARE :HVCLOBLOC LANGUAGE TYPE CLOB LOCATOR
call sqlexec 'FETCH c1 INTO :HVSMINT, :HVBLOB50K'
Note that the variables HVSMINT and HVBLOB50K were implicitly defined by using them in the FETCH statement.