Download - SQL Codes Decoded

Transcript
Page 1: SQL Codes Decoded

SQL Codes DecodedSQL Codes Decoded

Presented by:Robert Goodman

October 2006

Page 2: SQL Codes Decoded

Where Do We Start?Where Do We Start?

Page 3: SQL Codes Decoded

How Do We Debug?How Do We Debug?

• Sources of Debug Information

– CICS Transaction Abends– Batch Abend Codes– System Codes– Message Logs– DB2 SQL Codes

Page 4: SQL Codes Decoded

Batch Abend CodesBatch Abend Codes

– The system reports abends in the form Sxxx Uxxxx.

• The S literally means "System"

• The U literally means "User".

– One of the most common items mentioned in the table is "subscript out of range".

• This refers to any access to a COBOL array with a subscript <=0 or >n, where n is the number of OCCURS.

• 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.

Page 5: SQL Codes Decoded

Our AgendaOur Agenda

• SQL Code Basics– Where SQL comes

from– SQLCode vs.

SQLState– Good & Bad

• When Should You Check SQL Codes?

• SQL Code Checking– The code– The cause– Responsible party– Corrective actions

• Common SQL Codes– 000– 100– -117– -180 & 181– -501– -803– -805 & -818– -811– -904– -911

• Where to Go for Help

Page 6: SQL Codes Decoded

SQLCA ElementsSQLCA ElementsCOBOL: 01 SQLCA. 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. 10 SQLWARN6 PIC X. 10 SQLWARN7 PIC X.05 SQLEXT. 10 SQLWARN8 PIC X. 10 SQLWARN9 PIC X. 10 SQLWARNA PIC X. 10 SQLSTATE PIC X(5).

An SQLCA is a structure or collection of variables that is updated after each SQL statement executes. An application program that contains executable SQL statements must

provide exactly one SQLCA.

An SQLCA is a structure or collection of variables that is updated after each SQL statement executes. An application program that contains executable SQL statements must

provide exactly one SQLCA.

Page 7: SQL Codes Decoded

Get DiagnosticsGet Diagnostics

• Available in V8• Use for Multi Row

Operations• Use for support long

names• Use to retrieve additional

information

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.

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.

Page 8: SQL Codes Decoded

What Does It Look Like?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); }

Page 9: SQL Codes Decoded

SQL Codes vs. SQL StateSQL Codes vs. SQL State

• SQLCode– More specific information– Have associated tokens

• Error Code• Resource Type

– Can point to object• Resource Name

• SQLState– Std across whole

DB2 family

z/OSz/OS

Page 10: SQL Codes Decoded

Good & Bad SQL CodesGood & 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

Page 11: SQL Codes Decoded

Typical SQL Code Typical SQL Code HistoryHistory

-90436%

Other3%

-91131%

-80312%

-1806%

-1814%

-8114%

-8054%

-904

Other

-911

-803

-180

-181

-811

-805

Page 12: SQL Codes Decoded

When to Check SQL CodesWhen to Check SQL Codes

• Check SQL Codes (cont.)– Misc

• GET DIAGNOSTICS• CALL• CONNECT• SET

• Skip SQL Code Checks– BEGIN DECLARE SECTION– DECLARE STATEMENT– DECLARE TABLE– END DECLARE SECTION– INCLUDE– WHENEVER

• Check SQL Codes– Cursors

• OPEN• FETCH • CLOSE

– Basic I/O• SELECT• INSERT• UPDATE• DELETE

– UOW• COMMIT• ROLLBACK

Page 13: SQL Codes Decoded

Matching SQLCODEs to SQLMatching SQLCODEs to SQL

SQLCODE / SQL SELECT DECLARE OPEN FETCH CLOSE INSERT UPDATE DELETE

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

-803Duplicate Key

N/A -811Multiple Rows N/A

-904Unavailable Resource

N/A

-911Rollback Timeout

N/A

Commonly Handled Could occur but not commonly handled

Page 14: SQL Codes Decoded

0 - Successful Call<>0 - Unsuccessful Call

Overview of SQL CallsOverview of SQL Calls

– SQL is transformed to COBOL calls in precompile

– Host variables loaded before the call

– DB2 Call is executed

– SQLCODE gives feedback• 0 - OK• <0 - failure• >0 - warning

EXEC SQL ~~~~~ ~~~~~ ~~~~~END-EXEC

SQLCODE Checks

Load Host Variables

Page 15: SQL Codes Decoded

SQL Code SQL Code CheckingChecking

– How’s It Done• Handle expected codes before

call• Call UT97894P-CHECK-

SQLCODE after every SQL call• Catch handled codes after

– Inconsistent SQL Code Checking Leads To

• breaks program logic• weird program errors• can extend debugging time

SET WS960-HANDLE-NOTFND TO TRUE

EXEC SQL ~~~~~~ ~~~~~~END-EXEC

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

IF WS960-R-NOTFND PERFORM ~~~~~~ THRU ~~~~~~-EXITEND-IF

Page 16: SQL Codes Decoded

SQL Code NormalSQL Code Normal

Page 17: SQL Codes Decoded

Standard SQL Code Standard SQL Code CheckingChecking

SELECT

SQLCode

0

<>0 ERROR

Page 18: SQL Codes Decoded

Not FoundNot Found

Page 19: SQL Codes Decoded

Fetch LoopFetch LoopOPEN

CURSOR

SQLCode

FETCH

CLOSE

SQLCode

0

0

0

<>0 ERROR

<0 ERROR

<>0 ERROR

+100

SQLCode

Page 20: SQL Codes Decoded

MismatchMismatch

SQL Code

DB2 Error Code

Cause

Primary Responsibility

Problem Resolution Suggestions

-117 N/A The number of values specified does not match the number of columns implied or specified

SQL coding error

This error typically happens when the column list of an SQL doesn’t match the host variable list. It can happen when SQL is coded to explicitly or implicitly select all columns in an SQL vs. an explicit list of host variables. When a column is added to the table, the explicit list will no longer match the select all list.

SQLState: 42802

Page 21: SQL Codes Decoded

Column MismatchColumn Mismatch

Table_AI_CLIET_CREAI_ACCN_PATN

INSERT INTO TABLE_A VALUES (:I-CLIE ,:T_CREA ,:I_ACCN_PATN )

Alter TableAdd ColumnT_MODF

Table_AI_CLIET_CREAI_ACCN_PATNT_MODF

INSERT INTO TABLE_A VALUES (:I-CLIE ,:T_CREA ,:I_ACCN_PATN )

X

#1

#2

#3

Page 22: SQL Codes Decoded

DB2 Date, Time & DB2 Date, Time & Timestamp ErrorsTimestamp Errors

SQL Code

DB2 Error Code

Cause

Primary Responsibility

Problem Resolution Suggestions

-180 N/A An invalid date, time or timestamp value was entered into a host variable or SQL parameter.

Program Issue In batch programs, it may be helpful to do a DISPLAY of all dates, times and timestamps from the problem SQL to determine the cause of the problem. Make sure that all of these values are validated prior to moving them into host variables 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 date/time value is not valid format

Program Issue This happens when an out of range value is entered into one or more of the components of a date/time value. Display the date in the program and examine the output for the invalid value portion.

SQLState: 22007 for both SQL Codes

Page 23: SQL Codes Decoded

SQL Code: -180 Valid FormatsSQL 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

Page 24: SQL Codes Decoded

SQL Code: -181 RangesSQL 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

Page 25: SQL Codes Decoded

Bogus FETCH or CLOSEBogus FETCH or CLOSE

SQL Code

DB2 Error Code

Cause

Primary Responsibility

Problem Resolution Suggestions

-501 N/A Attempted a FETCH or CLOSE on an unopened cursor

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

SQLState: 24501

Page 26: SQL Codes Decoded

Missing SQL Code CheckingMissing SQL Code Checking

OPENCURSOR

SQLCode

FETCH

SQLCodeUPDATE

CLOSE

SQLCode

<>0 ERROR

<>0 ERROR

<0 ERROR

0

0

+100

0

Missing Check

A Undetected Rollback on the UPDATEWould Cause the Cursor to Be Closed!

Page 27: SQL Codes Decoded

DB2 Duplicate Key DB2 Duplicate Key ErrorsErrors

SQL Code

DB2 Error Code

Cause

Primary Responsibility

Problem Resolution Suggestions

-803 N/A Attempted to INSERT or UPDATE in violation of a UNIQUE INDEX constraint.

Program Issue A table can have multiple UNIQUE INDEXes. First, it is necessary to determine all of the UNIQUE INDEXes on a table. A query of SYSIBM.SYSINDEXES Next, review the program logic to make that it addresses all of the 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

Page 28: SQL Codes Decoded

Unique Index ElementsUnique Index Elements

SET WS960-DUPKEY TO TRUE

EXEC SQL UPDATE VRS97100 SET I_MRI_PATN = NEW-I-MRI-PATN WHERE I_CLIE = :RS100-I-CLIE AND I_ACCN_PATN = :RS100-I-ACCN-PATNEND-EXEC

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

VRS97100 Unique Indexes

XRS97100 I_CLIE

I_ACCN_PATN

XRS97101I_MRI

Page 29: SQL Codes Decoded

DB2 Precompiler DB2 Precompiler Timestamp ErrorsTimestamp Errors

SQL Code

DB2 Error Code

Cause

Primary Responsibility

Problem Resolution Suggestions

-805 N/A The DBRM or Package in not found in the Plan

Compile Issue or JCL Issue

This can occur when a compile is partially successful or there is attempt to bind a package that is not in the plan. Determine the correct bind parameters and try again.

-818 N/A The DBRM consistency token does not match the load module

Compile Issue of JCL Issue

This can occur when a compile is partially successful and the load module consistency token doesn’t match the current DBRM. If a 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

Page 30: SQL Codes Decoded

Consistency TokensConsistency Tokens

LoadlibDBRMlib

Page 31: SQL Codes Decoded

DB2 Multiple Rows DB2 Multiple Rows ErrorsErrors

SQL Code

DB2 Error Code

Cause

Primary Responsibility

Problem Resolution Suggestions

-811 n/a More than one value was returned on an embedded SELECT.

Program or Data Issue

This usually occurs when new data is added so that an embedded SELECT retrieves more than a single row result set. A comprehensive treatment of this issue is detailed in the DB2 Tips and Techniques #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

Page 32: SQL Codes Decoded

#1 Singleton SELECT#1 Singleton SELECT(SELECTS 1 Row & Columns)(SELECTS 1 Row & Columns)

SET WS960-HANDLE-NOTFND TO TRUE

EXEC SQL SELECT I_MRI_PATN ,N_LAST_PATN INTO :RS100-I-MRI-PATN ,:RS100-N-LAST-PATN WHERE I_CLIE = :RS100-I-CLIE AND I_ACCN_PATN = :RS100-I-ACCN-PATN FROM VRS97100END-EXEC

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

IF WS960-R-NORMAL MOVE RS100-I_MRI_PATN TO….END-IF

– If SQLCODE is OK (=0);• 1) SELECTS 1 row

– SQLCODE = 0– Use host variables

– If SQLCODE fails (<>0);• 1) no rows exist

– SQLCODE = +100– Don’t use host variables!

• 2) more than 1 row exists– SQLCODE = -811– Don’t use host variables!

• 3) other non zero SQLCODE– Don’t use host variables!

Page 33: SQL Codes Decoded

#2 Existence Checking#2 Existence Checking(The Most Efficient Way)(The Most Efficient Way)

– If SQLCODE is OK (=0);• 1) existence of 1 or more

rows– SQLCODE = 0

– If SQLCODE fails (<>0);• 1) existence of no rows

– SQLCODE = +100

• 2) other failure– SQLCODE <0

SET WS960-HANDLE-NOTFND TO TRUE

EXEC SQL SELECT 1 INTO :WS400-NUMBER FROM VRI97000 WHERE I_CLIE = :RI000-I-CLIE AND I_MRI_PATN = :RI000-I-MRI-PATN FETCH FIRST ROW ONLYEND-EXEC

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

IF WS960-R-NOTFND THEN ….END-IF

Page 34: SQL Codes Decoded

#3 Counting Rows#3 Counting Rows

– If SQLCODE is OK (=0);

• 1) existence of >0 rows– SQLCODE = 0– INDICATOR-VAR >= 0

– If SQLCODE fails (<>0);• 1) existence of no rows

– SQLCODE = +100– INDICATOR-VAR < 0

• 2) other failure– SQLCODE < 0

SET WS960-HANDLE-NOTFND TO TRUE

EXEC SQL SELECT COUNT(*) INTO :WS400-NUMB :WS400-INDICATOR-VARIABLE FROM VCP97160 WHERE I_CLIE = :CP160-I-CLIE AND I_CODE = :CP160-I-CODEEND-EXEC

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

IF (WS960-R-NORMAL AND WS400-INDICATOR-VARIABLE >= 0) MOVE WS400-NUMB TO ….END-IF

Page 35: SQL Codes Decoded

#4 Checking for MULTROWs#4 Checking for MULTROWswith a Singleton SELECTwith a Singleton SELECT

• If SQLCODE is OK (=0);• 1) existence of 1 row

– SQLCODE = 0

– If SQLCODE fails (<>0);• 1) existence of no rows

– SQLCODE = +100

• 2) existence of +1 rows– SQLCODE=-811

• 3) other failure– SQLCODE < 0

SET WS960-HANDLE-NOTFND TO TRUESET WS960-HANDLE-MULTROW TO TRUE

EXEC SQL SELECT 1 INTO :WS400-NUMB FROM VCP97160 WHERE I_CLIE = :CP160-I-CLIE AND I_CODE = :CP160-I-CODEEND-EXEC

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

EVALUATE TRUE WHEN WS960-R-NOTFND …. WHEN WS960-R-MULTROW ….END-EVALUATE

Page 36: SQL Codes Decoded

#5 #5 Returning a ValueReturning a ValueFrom Any RowFrom Any Row

– If SQLCODE is OK (=0);• 1) SELECTS 1 row

– SQLCODE = 0– Use host variables

– If SQLCODE fails (<>0);• 1) no rows exist

– SQLCODE = +100– Don’t use host variables!

• 2) other non zero SQLCODE– Don’t use host variables!

SET WS960-HANDLE-NOTFND TO TRUE

EXEC SQL SELECT C_N_STAN INTO :CP270-C-N-STAN WHERE I_CLIE = :CP270-I-CLIE AND I_N_STAN = :CP270-I-N-STAN AND I_N_STAN_ASSC = :CP270-I-N-STAN-ASSC FROM VRS97100 FETCH FIRST ROW ONLYEND-EXEC

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

IF WS960-R-NORMAL ….END-IF

Page 37: SQL Codes Decoded

DB2 Unavailable DB2 Unavailable ResourcesResources

SQLCode

DB2 ErrorCode Cause

PrimaryResponsibil

ityProblem Resolution Suggestions

-904 C90080 orC90081 or

C90097

The databaseresource is in aREAD ONLY,STOPPED orCOPYPENDING state.

DBA Issue This condition may appear for a few secondsduring some database modifications and utilityfunctions. DBAs will diagnose the cause of theproblem and reset the pageset status. If thishappens persistently or repeatedly, notify the DBAimmediately!

C90096 The maximumnumber of locksfor a package orpageset hasbeen exceeded.

ProgramIssue

This is caused by a program which is eithermissing commit logic or is not committingfrequently enough. If commit logic is not found, itmust be added to the unit of work cycle in theprogram. If commit logic is present, loweringcommit WS002-ROWS-TO-COMMIT in the inputparms may resolve the problem.

C900BA A utility DRAINrequestexceeded themaximum timelimit.

DBA Issue This normally caused by a database reorg whoseDRAIN request holds resources for a period thatexceed the system timeout limit. This shouldresolve itself within a matter of seconds. If thissituation persists, then contact the DBAimmediately!

D70014 orD70025

A databasetablespace failedto extend or findsufficient spaceallocation.

DBA Issue This happens when a tablespace extends to themaximum number of extents or there is insufficientspace to expand in the tablespace or indexspaceSTOGROUP. The DBA should be contactedimmediately!

SQLState: 57011

Page 38: SQL Codes Decoded

Common Resource Type Common Resource Type CodesCodes

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

Page 39: SQL Codes Decoded

DB2 Deadlocks & DB2 Deadlocks & TimeoutsTimeouts

SQL Code

DB2 Error Code

Cause

Primary Responsibility

Problem Resolution Suggestions

-911 C90088 The current unit of work has been rolled back due to a deadlock.

Program Issue This problem can be resolved by my making sure that the logic of conflicting programs updates tables and rows in the same order. The offending programs can be identified in the DB2 logs or in the Insight DB2 Contention History trace.

C9008E The current unit of work has been rolled back due to a timeout.

Program Issue This program waited on a lock for a DB2 pageset for a period that exceeded the system timeout limit. This can occur when 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

Page 40: SQL Codes Decoded

Other Technical Other Technical ResourcesResources

• Area Experts

• DB2 Messages

• DB2 Codes

• DB2 Web Sitewww.ibm.com

Page 41: SQL Codes Decoded

QuestionsQuestions


Top Related