Вы находитесь на странице: 1из 41

SQL Codes Decoded

Presented by:
Robert Goodman

October 2006
Where Do We Start?
How Do We Debug?

• Sources of Debug Information

– CICS Transaction Abends


– Batch Abend Codes
– System Codes
– Message Logs
– DB2 SQL Codes
Batch Abend Codes

– The system reports – One of the most common


abends in the form Sxxx items mentioned in the table
Uxxxx. is "subscript out of range".
• This refers to any access to a
• The S literally means
COBOL array with a subscript
"System" <=0 or >n, where n is the
• The U literally means number of OCCURS.
"User". • If the program stores data in the
array with a subscript, memory
outside of the array can be
destroyed; perhaps causing a
later 0C1, 0C4, 0C7 or 04E.
Our Agenda

• SQL Code Basics • Common SQL Codes


– Where SQL comes – 000
from – 100
– SQLCode vs. – -117
SQLState – -180 & 181
– Good & Bad
– -501
• When Should You – -803
Check SQL Codes? – -805 & -818
• SQL Code Checking – -811
– The code – -904
– The cause – -911
– Responsible party • Where to Go for Help
– Corrective actions
COBOL:
01 SQLCA.
SQLCA Elements
05 SQLCAID PIC X(8).
05 SQLCABC PIC S9(9) COMP-4.
05 SQLCODE PIC S9(9) COMP-4.
05 SQLERRM.
49 SQLERRML PIC S9(4) COMP-4.
49 SQLERRMC PIC X(70).
05 SQLERRP PIC X(8).
05 SQLERRD OCCURS 6 TIMES PIC S9(9) COMP-4.
05 SQLWARN.
10 SQLWARN0 PIC X.
10 SQLWARN1 PIC X.
10 SQLWARN2 PIC X.
10 SQLWARN3 PIC X.
10 SQLWARN4 PIC X.
10 SQLWARN5 PIC X. An SQLCA is a structure or
10 SQLWARN6 PIC X. collection of variables that is updated
10 SQLWARN7 PIC X. after each SQL statement executes.
05 SQLEXT.
An application program that contains
10 SQLWARN8 PIC X.
10 SQLWARN9 PIC X. executable SQL statements must
10 SQLWARNA PIC X. provide exactly one SQLCA.
10 SQLSTATE PIC X(5).
Get Diagnostics
Use the GET DIAGNOSTICS statement to handle multiple SQL errors
that might result from the execution of a single SQL statement. First,
check SQLSTATE (or SQLCODE) to determine whether diagnostic
information should be retrieved by using GET DIAGNOSTICS.

• Available in V8
• Use for Multi Row
Operations
• Use for support long
names
• Use to retrieve additional
information
What Does It Look Like?
EXEC SQL BEGIN DECLARE SECTION;
long row_count, num_condns,
i; long ret_sqlcode, row_num; char ret_sqlstate[6]; ...
EXEC SQL END DECLARE SECTION; ...

EXEC SQL INSERT INTO DSN8810.ACT


(ACTNO, ACTKWD, ACTDESC) VALUES (:hva1, :hva2, :hva3)
FOR 10 ROWS NOT ATOMIC CONTINUE ON SQLEXCEPTION;

EXEC SQL GET DIAGNOSTICS :row_count = ROW_COUNT,


:num_condns = NUMBER; printf("Number of rows inserted = %d\n",
row_count);
for (i=1; i<=num_condns; i++)
{ EXEC SQL GET DIAGNOSTICS CONDITION :i :ret_sqlcode =
DB2_RETURNED_SQLCODE, :ret_sqlstate = RETURNED_SQLSTATE,
:row_num = DB2_ROW_NUMBER; printf("SQLCODE = %d, SQLSTATE =
%s, ROW NUMBER = %d\n", ret_sqlcode, ret_sqlstate, row_num); }
SQL Codes vs. SQL State

• SQLCode • SQLState
– More specific information – Std across whole
– Have associated tokens DB2 family
• Error Code
• Resource Type
– Can point to object
• Resource Name

z/OS
z/OS
Good & Bad SQL Codes

If SQLCODE = 0 Execution Was


Successful
If SQLCODE > 0 Execution Was
Successful With a
Warning
If SQLCODE < 0 Execution Was
Not Successful
Typical SQL Code
History

-181-811 -805 -904


-180 4% 4% 4% Other
-904
6% -911
-803 36%
12% -803
-180
-181
Other
-911 -811
3%
31% -805
When to Check SQL Codes
• Check SQL Codes • Check SQL Codes (cont.)
– Cursors – Misc
• GET DIAGNOSTICS
• OPEN
• CALL
• FETCH
• CONNECT
• CLOSE
• SET
– Basic I/O
• SELECT
• Skip SQL Code Checks
• INSERT
– BEGIN DECLARE SECTION
• UPDATE – DECLARE STATEMENT
• DELETE – DECLARE TABLE
– UOW – END DECLARE SECTION
• COMMIT – INCLUDE
• ROLLBACK – WHENEVER
Matching SQLCODEs to SQL

SQLCODE / SQL SELECT DECLARE OPEN FETCH CLOSE INSERT UPDATE DELETE

+000
Normal
 N/A      
+100
Not Found
 N/A   
-180 –181
Invalid Date / Time
 N/A    

-803
Duplicate Key
N/A  
-811
Multiple Rows
 N/A

-904  N/A      
Unavailable Resource
-911  N/A      
Rollback Timeout

 Commonly Handled  Could occur but not commonly handled


Overview of SQL Calls
– SQL is transformed to COBOL calls
in precompile
Load Host Variables

– Host variables loaded before the


EXEC SQL call
~~~~~
~~~~~
~~~~~
– DB2 Call is executed
END-EXEC
– SQLCODE gives feedback
• 0 - OK
SQLCODE Checks
• <0 - failure
0 - Successful Call
<>0 - Unsuccessful Call • >0 - warning
SQL Code
Checking
– How’s It Done
SET WS960-HANDLE-NOTFND TO TRUE
• Handle expected codes before
EXEC SQL
call ~~~~~~
~~~~~~
• Call UT97894P-CHECK- END-EXEC

SQLCODE after every SQL call PERFORM UT97894P-CHECK-SQLCODE


THRU UT97894P-CHECK-SQLCODE-EXIT

• Catch handled codes after IF WS960-R-NOTFND


PERFORM ~~~~~~
– Inconsistent SQL Code END-IF
THRU ~~~~~~-EXIT

Checking Leads To
• breaks program logic
• weird program errors
• can extend debugging time
SQL Code Normal
Standard SQL Code
Checking

SELECT

SQL <>0
ERROR
Code
0
Not Found
Fetch Loop
OPEN
CURSOR

SQL <>0
ERROR
Code
0

FETCH

0 SQL <0
ERROR
Code
+100

CLOSE

SQL <>0
ERROR
Code
0
Mismatch

DB2
SQL Error Primary
Code Code Cause Responsibility Problem Resolution Suggestions

-117 N/A The number of SQL coding This error typically happens when the column list
values specified error of an SQL doesn’t match the host variable list. It
does not match can happen when SQL is coded to explicitly or
the number of implicitly select all columns in an SQL vs. an
columns explicit list of host variables. When a column is
implied or added to the table, the explicit list will no longer
specified match the select all list.

SQLState: 42802
Column Mismatch
INSERT INTO
Table_A
TABLE_A
VALUES
(:I-CLIE
#1 I_CLIE
T_CREA
I_ACCN_PATN
,:T_CREA
,:I_ACCN_PATN
)
Alter Table
#2 Add Column
T_MODF

INSERT INTO
TABLE_A Table_A
VALUES I_CLIE

#3
X
T_CREA
(:I-CLIE
I_ACCN_PATN
,:T_CREA T_MODF
,:I_ACCN_PATN
)
DB2 Date, Time &
Timestamp Errors

DB2
SQL Error Primary
Code Code Cause Responsibility Problem Resolution Suggestions

-180 N/A An invalid date, Program Issue In batch programs, it may be helpful to do a
time or DISPLAY of all dates, times and timestamps from
timestamp value the problem SQL to determine the cause of the
was entered into a problem. Make sure that all of these values are
host variable or validated prior to moving them into host variables
SQL parameter. or SQL parameters. Failure to move a valid value
to a newly added date, time or timestamp column
after a program recompile can also cause this error.
-181 N/A The value of a Program Issue This happens when an out of range value is entered
date/time value is into one or more of the components of a date/time
not valid format value. Display the date in the program and
examine the output for the invalid value portion.

SQLState: 22007 for both SQL Codes


SQL Code: -180 Valid Formats

Timestamp yyyy-mm-dd-hh-mm-ss-msmsms
yyyy-mm-dd-hh-mm-ss

Date mm/dd/yyyy
yyyy-mm-dd
dd.mm.yyyy
Time hh:mm:ss
hh:mm
hh.mm.ss
hh.mm
hh:mm AM or hh:mm PM
SQL Code: -181 Ranges
Component Valid Range
Year 0001 - 9999

Month 1 – 12

Day 1 – 31 (depends upon month


& year)
Hour 0 - 24

Minute 0 – 59

Second 0 - 59

Microsecond 0 - 9999
Bogus FETCH or CLOSE

DB2
SQL Error Primary
Code Code Cause Responsibility Problem Resolution Suggestions

-501 N/A Attempted a Program logic error Check previous SQL codes for something that
FETCH or may have closed the cursor. If SQL codes are
CLOSE on an not methodically checked, an undetected
unopened cursor rollback will cause a FETCH or CLOSE to
get this return code.

SQLState: 24501
Missing SQL Code Checking
OPEN
CURSOR

SQL <>0
ERROR
Code
0

FETCH A Undetected Rollback on the UPDATE


Would Cause the Cursor to Be Closed!

0 SQL <0
UPDATE Code ERROR

+100
Missing Check
CLOSE

SQL <>0
Code ERROR

0
DB2 Duplicate Key
Errors

DB2
SQL Error Primary
Code Code Cause Responsibility Problem Resolution Suggestions

-803 N/A Attempted to Program Issue A table can have multiple UNIQUE INDEXes.
INSERT or First, it is necessary to determine all of the
UPDATE in UNIQUE INDEXes on a table. A query of
violation of a SYSIBM.SYSINDEXES Next, review the
UNIQUE INDEX program logic to make that it addresses all of the
constraint. UNIQUE constraints. It may be necessary to
handle this (-803) SQLCODE on an INSERT or
UPDATE and automatically increment a sequence
number or timestamp milliseconds if the
application dictates.

SQLState: 23505
Unique Index Elements

SET WS960-DUPKEY TO TRUE

EXEC SQL VRS97100 Unique Indexes


UPDATE VRS97100
SET I_MRI_PATN = NEW-I-MRI-PATN XRS97100
WHERE I_CLIE
I_CLIE = :RS100-I-CLIE I_ACCN_PATN
AND
I_ACCN_PATN = :RS100-I-ACCN-PATN XRS97101
END-EXEC I_MRI

PERFORM UT97894P-CHECK-SQLCODE
THRU UT97894P-CHECK-SQLCODE-EXIT

DB2 Precompiler
Timestamp Errors
DB2
SQL Error Primary
Code Code Cause Responsibility Problem Resolution Suggestions

-805 N/A The DBRM or Compile Issue or This can occur when a compile is partially
Package in not JCL Issue successful or there is attempt to bind a package
found in the Plan that is not in the plan. Determine the correct
bind parameters and try again.
-818 N/A The DBRM Compile Issue of This can occur when a compile is partially
consistency token JCL Issue successful and the load module consistency
does not match the token doesn’t match the current DBRM. If a
load module recompile doesn’t resolve the problem, it may
be necessary to STEPLIB over to the proper
load libraries. In the production environment,
this is usually caused by a failed production
move. It may be necessary to recompile the
program and move it back into production
recompile can also cause this error.

SQLState: 51002 & 51003


Consistency Tokens

DBRMlib Loadlib
DB2 Multiple Rows
Errors
DB2
SQL Error Primary
Code Code Cause Responsibility Problem Resolution Suggestions

-811 n/a More than one Program or Data This usually occurs when new data is added so that
value was Issue an embedded SELECT retrieves more than a single
returned on an row result set. A comprehensive treatment of this
embedded issue is detailed in the DB2 Tips and Techniques
SELECT. #8 Existence Checking With a SELECT SQL
Statement. If you need to get the first row of a set
based in a specific order, then the SELECT logic
should be converted to a CURSOR with an
ORDER BY clause followed by a FETCH.

SQLState: 21000
#1 Singleton SELECT
(SELECTS 1 Row & Columns)

SET WS960-HANDLE-NOTFND TO TRUE


– If SQLCODE is OK (=0);
EXEC SQL
• 1) SELECTS 1 row SELECT
– SQLCODE = 0 I_MRI_PATN
– Use host variables ,N_LAST_PATN
INTO
– If SQLCODE fails (<>0); :RS100-I-MRI-PATN
• 1) no rows exist ,:RS100-N-LAST-PATN
WHERE
– SQLCODE = +100
I_CLIE = :RS100-I-CLIE
– Don’t use host variables! AND
• 2) more than 1 row exists I_ACCN_PATN = :RS100-I-ACCN-PATN
FROM VRS97100
– SQLCODE = -811 END-EXEC
– Don’t use host variables!
• 3) other non zero SQLCODE PERFORM UT97894P-CHECK-SQLCODE
THRU UT97894P-CHECK-SQLCODE-EXIT
– Don’t use host variables!
IF WS960-R-NORMAL
MOVE RS100-I_MRI_PATN TO….
END-IF
#2 Existence Checking
(The Most Efficient Way)

SET WS960-HANDLE-NOTFND TO TRUE

EXEC SQL
SELECT
– If SQLCODE is OK (=0);
1 • 1) existence of 1 or more
INTO
:WS400-NUMBER rows
FROM VRI97000 – SQLCODE = 0
WHERE
I_CLIE = :RI000-I-CLIE AND – If SQLCODE fails (<>0);
I_MRI_PATN = :RI000-I-MRI-PATN
FETCH FIRST ROW ONLY • 1) existence of no rows
END-EXEC
– SQLCODE = +100
PERFORM UT97894P-CHECK-SQLCODE • 2) other failure
THRU UT97894P-CHECK-SQLCODE-EXIT
– SQLCODE <0
IF WS960-R-NOTFND
THEN ….
END-IF
#3 Counting Rows
SET WS960-HANDLE-NOTFND TO TRUE
– If SQLCODE is OK (=0); EXEC SQL
• 1) existence of >0 rows SELECT
COUNT(*)
– SQLCODE = 0 INTO
:WS400-NUMB
– INDICATOR-VAR >= 0 :WS400-INDICATOR-VARIABLE
FROM VCP97160
– If SQLCODE fails (<>0); WHERE
I_CLIE = :CP160-I-CLIE AND
• 1) existence of no rows I_CODE = :CP160-I-CODE
– SQLCODE = +100 END-EXEC

– INDICATOR-VAR < 0 PERFORM UT97894P-CHECK-SQLCODE


THRU UT97894P-CHECK-SQLCODE-EXIT
• 2) other failure
IF (WS960-R-NORMAL AND
– SQLCODE < 0 WS400-INDICATOR-VARIABLE >= 0)
MOVE WS400-NUMB TO ….
END-IF
#4 Checking for MULTROWs
with a Singleton SELECT
• If SQLCODE is OK (=0);
SET WS960-HANDLE-NOTFND TO TRUE • 1) existence of 1 row
SET WS960-HANDLE-MULTROW TO TRUE
– SQLCODE = 0
EXEC SQL
SELECT
1 – If SQLCODE fails (<>0);
INTO
:WS400-NUMB • 1) existence of no rows
FROM VCP97160
WHERE – SQLCODE = +100
I_CLIE = :CP160-I-CLIE AND
I_CODE = :CP160-I-CODE • 2) existence of +1 rows
END-EXEC
– SQLCODE=-811
PERFORM UT97894P-CHECK-SQLCODE
THRU UT97894P-CHECK-SQLCODE- • 3) other failure
EXIT
– SQLCODE < 0
EVALUATE TRUE
WHEN WS960-R-NOTFND
….
WHEN WS960-R-MULTROW
….
END-EVALUATE
#5 Returning a Value
From Any Row
SET WS960-HANDLE-NOTFND TO TRUE
– If SQLCODE is OK (=0);
EXEC SQL • 1) SELECTS 1 row
SELECT
C_N_STAN – SQLCODE = 0
INTO – Use host variables
:CP270-C-N-STAN
WHERE – If SQLCODE fails (<>0);
I_CLIE = :CP270-I-CLIE AND
I_N_STAN = :CP270-I-N-STAN AND
• 1) no rows exist
I_N_STAN_ASSC = :CP270-I-N-STAN-ASSC – SQLCODE = +100
FROM VRS97100
– Don’t use host variables!
FETCH FIRST ROW ONLY
END-EXEC • 2) other non zero SQLCODE
– Don’t use host variables!
PERFORM UT97894P-CHECK-SQLCODE
THRU UT97894P-CHECK-SQLCODE-EXIT

IF WS960-R-NORMAL
….
END-IF
DB2 Unavailable
Resources
SQL DB2 Error Primary
Code Code Cause Responsibil Problem Resolution Suggestions
ity
-904 C90080 or The database DBA Issue This condition may appear for a few seconds
C90081 or resource is in a during some database modifications and utility
C90097 READ ONLY, functions. DBAs will diagnose the cause of the
STOPPED or problem and reset the pageset status. If this
COPY happens persistently or repeatedly, notify the DBA
PENDING state. immediately!
C90096 The maximum Program This is caused by a program which is either
number of locks Issue missing commit logic or is not committing
for a package or frequently enough. If commit logic is not found, it
pageset has must be added to the unit of work cycle in the
been exceeded. program. If commit logic is present, lowering
commit WS002-ROWS-TO-COMMIT in the input
parms may resolve the problem.
C900BA A utility DRAIN DBA Issue This normally caused by a database reorg whose
request DRAIN request holds resources for a period that
exceeded the exceed the system timeout limit. This should
maximum time resolve itself within a matter of seconds. If this
limit. situation persists, then contact the DBA
immediately!
D70014 or A database DBA Issue This happens when a tablespace extends to the
D70025 tablespace failed maximum number of extents or there is insufficient
to extend or find space to expand in the tablespace or indexspace
sufficient space STOGROUP. The DBA should be contacted
allocation. immediately!
SQLState: 57011
Common Resource Type
Codes

Type Object Type Object


100 Database 302 Tablespace Page
200 & 202 Tablespace 303 Indexspace Page
201 Indexspace 500 Storage Group
210 Partition 600 EDM Pool
220 Dataset 700 Bufferpool
230 Temporary File 800 Plan
240 Procedure 801 Package
300 Page 901 Sort Storage
DB2 Deadlocks &
Timeouts
DB2
SQL Error Primary
Code Code Cause Responsibility Problem Resolution Suggestions
-911 C90088 The current unit Program Issue This problem can be resolved by my making
of work has been sure that the logic of conflicting programs
rolled back due updates tables and rows in the same order.
to a deadlock. The offending programs can be identified in
the DB2 logs or in the Insight DB2
Contention History trace.
C9008E The current unit Program Issue This program waited on a lock for a DB2
of work has been pageset for a period that exceeded the
rolled back due system timeout limit. This can occur when
to a timeout. there are long running units of work in the
system or programs that do not commit
frequently enough. The offending programs
can be identified in the DB2 logs or in the
Insight DB2 Contention History trace. The
lock holding program should be adjusted so
that it commits more frequently. If the
program receiving this error is read-only,
the SQL could be adjust to do uncommitted
reading (WITH UR) to eliminate the
locking problem.
SQLState: 40001
Other Technical
Resources
• Area Experts

• DB2 Messages

• DB2 Codes

• DB2 Web Site


www.ibm.com
Questions

Вам также может понравиться