| ... WORKING-STORAGE SECTION. ... EXEC SQL INCLUDE SQLCA END-EXEC ... | 
| 01  SQLCA.     05  SQLCAID                PIC X(8).     05  SQLCABC                PIC S9(9) COMP-5.     05  SQLCODE                PIC S9(9) COMP-5.     05  SQLERRML               PIC S9(4) COMP-5.     05  SQLERRMC               PIC X(254).     05  SQLERRP                PIC X(8).     05  SQLERRD OCCURS 6 TIMES PIC S9(9) COMP-5.     05  SQLWARN.         10 SQLWARN0            PIC X(1).         10 SQLWARN1            PIC X(1).         10 SQLWARN2            PIC X(1).         10 SQLWARN3            PIC X(1).         10 SQLWARN4            PIC X(1).         10 SQLWARN5            PIC X(1).         10 SQLWARN6            PIC X(1).         10 SQLWARN7            PIC X(1).     05  SQLSTATE               PIC X(5).     05  SQLEXT                 PIC S9(5) COMP-3 VALUE 1. | 
| SQLCAID | Not used | 
| SQLCABC  | Not used | 
| SQLCODE  | Contains the SQL return code. Code                        Means 0                      Successful execution (although one or more SQLWARN indicators may be set). positive          Successful execution, but with a warning condition. negative         Error condition. | 
| SQLERRML  | Contains the length of sqlerrmc. 0 means that the value of sqlerrmc is not relevant. | 
| SQLERRMC  | Contains the description of the error condition. | 
| SQLERRP  | Not used | 
| SQLERRD(1) | Not used | 
| SQLERRD(2) | Not used | 
| SQLERRD(3) | Contains the number of rows affected by the SQL statement | 
| SQLERRD(4) | Not used | 
| SQLERRD(5) | Not used | 
| SQLERRD(6) | Not used | 
| SQLWARN  | A set of warning indicators, each containing a blank or W. The meaning of each indicator is database dependent. | 
| SQLSTATE  | SQLSTATE status codes consist of a 2-character class code immediately followed by a 3-character subclass code. Aside from class code 00 ("successful completion",) the class code denotes a category of exceptions. And, aside from subclass code 000 ("not applicable",) the subclass code denotes a specific exception within that category. The meaning of codes is database dependent. | 
| SQLEXT  | Not used |