Signature information bytes

The tables in this topic show program signature information that is part of the listing of program initialization code provided when you use the LIST compiler option.

Table 1. Compiler options in the INFO BYTE section
Offset in decimal Option Value
00 CODEPAGE CCSID value specified for EBCDIC code page
02 ARCH 10
11
12
13
14
03 OPTIMIZE 0
1
2
The INFO BYTE section of the listing also provides the following values:
  • The number of DATA DIVISION statements
  • The number of PROCEDURE DIVISION statements
In the following table, different signature bytes represent different information:
  • Signature bytes 1-5, and 26-35 refer to compiler options
  • Signature bytes 6-7 refer to DATA DIVISION items
  • Signature byte 8 refers to ENVIRONMENT DIVISION items
  • Signature bytes 9-25 refer to PROCEDURE DIVISION statements and items
Table 2. Signature information bytes
Offset in decimal Signature byte Bit Item
On Off
04 28 0 SQL NOSQL
1 CICS NOCICS
2 MDECK NOMDECK
3 SQLCCSID NOSQLCCSID
4 OPTFILE NOOPTFILE
5 XMLPARSE(XMLSS) XMLPARSE(COMPAT)
6 BLOCK0 NOBLOCK0
7 DISPSIGN(SEP) DISPSIGN(COMPAT)
05 29 0 Program uses Java™-based OO syntax  
1 Program uses RANDOM function  
2 Program uses NATIONAL data (Unicode)  
3 XML PARSE with schema validation  
4 STGOPT NOSTGOPT
5 AFP(VOLATILE) AFP(NOVOLATILE)
6 HGPR(PRESERVE) HGPR(NOPRESERVE)
7 NOTEST(DWARF) Not NOTEST(DWARF)
06 30 0 QUALIFY(EXTEND) QUALIFY(COMPAT)
1 VLR(COMPAT) VLR(STANDARD)
2 COPYRIGHT string specified COPYRIGHT string not specified
3 SERVICE string specified SERVICE string not specified
4 INVDATA(FNC,x) Not INVDATA(FNC,x)
Note: When bits 4 and 5 are both off, NOINVDATA is in effect.
5 INVDATA(NOFNC,x) Not INVDATA(NOFNC,x)
Note: When bits 4 and 5 are both off, NOINVDATA is in effect
6 INVDATA(x,NOCS) INVDATA(x,CS), should be zero when bits 4 and 5 are zero.
7 NUMCHECK(ZON(LAX)) NUMCHECK(ZON(STRICT))
07 31 0 NUMCHECK(ZON) Not NUMCHECK(ZON)
1 NUMCHECK(PAC) Not NUMCHECK(PAC)
2 NUMCHECK(BIN) Not NUMCHECK(BIN)
    NONUMCHECK is in effect if bits 0, 1, and 2 are off
3 NUMCHECK(ABD) NUMCHECK(MSG) (if any bit of 0, 1, or 2 is on)
4 PARMCHECK NOPARMCHECK
5 PARMCHECK(ABD) (if bit 4 is on) PARMCHECK(MSG) (if bit 4 is on)
6 NUMCHECK(ZON(NOALPHNUM)) NUMCHECK(ZON(ALPHNUM))
7 TEST|NOTEST(SEPARATE(DSNAME)) TEST|NOTEST(SEPARATE(NODSNAME))
08 1 0 ADV NOADV
1 APOST QUOTE
2 DATA(31) DATA(24)
3 DECK NODECK
4 DUMP NODUMP
5 DYNAM NODYNAM
6 FASTSRT NOFASTSRT
7 SQLIMS NOSQLIMS
09 2 0 LIB (always on)  
1 LIST NOLIST
2 MAP(HEX), MAP(DEC) NOMAP
3 NUM NONUM
4 OBJECT NOOBJECT
5 OFFSET NOOFFSET
6 OPT(1), OPT(2) NOOPT, OPT(0)
7 OUTDD NOOUTDD
10 3 0 NUMPROC(PFD) NUMPROC(NOPFD)
1 RENT NORENT
2 RESIDENT (always on)  
3 SEQUENCE NOSEQUENCE
4 Reserved  
5 SOURCE NOSOURCE
6 Not NOSSRANGE NOSSRANGE
7 TERM NOTERM
11 4 0 TEST NOTEST
1 TRUNC(STD) Not TRUNC(STD)
2 WORD NOWORD
3 VBREF NOVBREF
4 XREF NOXREF
5 ZWB NOZWB
6 NAME NONAME
7   NOCMPR2 (always off)
12 5 0 Reserved  
1 NUMCLS=ALT NUMCLS=PRIM
2 DBCS NODBCS
3 AWO NOAWO
4 TRUNC(BIN) Not TRUNC(BIN)
5 ADATA NOADATA
6 CURRENCY NOCURRENCY
7 Compilation unit is a class Compilation unit is a program
13 6 0 QSAM file descriptor
1 VSAM sequential file descriptor
2 VSAM indexed file descriptor
3 VSAM relative file descriptor
4 CODE-SET clause (ASCII files) in file descriptor
5 Spanned records
6 PIC G or PIC N (DBCS data item)
7 OCCURS DEPENDING ON clause in data description entry
14 7 0 SYNCHRONIZED clause in data description entry
1 JUSTIFIED clause in data description entry
2 USAGE IS POINTER item
3 Complex OCCURS DEPENDING ON clause
4 External floating-point items in the DATA DIVISION
5 Internal floating-point items in the DATA DIVISION
6 Line-sequential file
7 USAGE IS PROCEDURE-POINTER or FUNCTION-POINTER item
15 8 0 FILE STATUS clause in FILE-CONTROL paragraph
1 RERUN clause in I-O-CONTROL paragraph of INPUT-OUTPUT SECTION
2 UPSI switch defined in SPECIAL-NAMES paragraph
3 WSOPT: Bit to indicate the method used by the compiler to manage WORKING-STORAGE SECTION. For more information, see COBOL-specific vendor interfaces in the z/OS® Language Environment® Vendor Interfaces.
4 VSAMOPENFS
5
1=NUMCHECK(BIN(NOTRUNCBIN))
0=NUMCHECK(BIN(TRUNCBIN))
16 9 0 ACCEPT
1 ADD
2 ALTER
3 CALL
4 CANCEL
6 CLOSE
17 10 0 COMPUTE
2 DELETE
4 DISPLAY
5 DIVIDE
18 11 1 END-PERFORM
2 ENTER
3 ENTRY
4 EXIT
5 EXEC
6 GO TO
7 IF
19 12 0 INITIALIZE
1 INVOKE
2 INSPECT
3 MERGE
4 MOVE
5 MULTIPLY
6 OPEN
7 PERFORM
20 13 0 READ
2 RELEASE
3 RETURN
4 REWRITE
5 SEARCH
7 SET
21 14 0 SORT
1 START
2 STOP
3 STRING
4 SUBTRACT
7 UNSTRING
22 15 0 USE
1 WRITE
2 CONTINUE
3 END-ADD
4 END-CALL
5 END-COMPUTE
6 END-DELETE
7 END-DIVIDE
23 16 0 END-EVALUATE
1 END-IF
2 END-MULTIPLY
3 END-READ
4 END-RETURN
5 END-REWRITE
6 END-SEARCH
7 END-START
24 17 0 END-STRING
1 END-SUBTRACT
2 END-UNSTRING
3 END-WRITE
4 GOBACK
5 EVALUATE
7 SERVICE
25 18 0 END-INVOKE
1 END-EXEC
2 XML
3 END-XML
4 ALLOCATE
5 FREE
6 JSON
7 END-JSON
26 19 0-7 Reserved
27 20 0-7 Reserved
28 21 0 Hexadecimal literal
1 Altered GO TO
2 I-O ERROR declarative
3 DECIMAL-POINT IS COMMA clause
4 DEBUGGING declarative
5 Program segmentation
6 OPEN . . . EXTEND
7 EXIT PROGRAM
29 22 0 CALL literal
1 CALL identifier
2 CALL . . . ON OVERFLOW
3 CALL . . . LENGTH OF
4 CALL . . . ADDRESS OF
5 CLOSE . . . REEL/UNIT
6 Exponentiation used
7 Floating-point items used
30 23 0 COPY
1 BASIS
2 DBCS name in program
3 Shift-out and Shift-in in program
4 SUPPRESS|NOSUPPRESS
5 SSRANGE(ZLEN) (if bit 6 in byte 3 is on) SSRANGE(NOZLEN) (if bit 6 in byte 3 is on)
6 SSRANGE(ABD) (if bit 6 in byte 3 is on) SSRANGE(MSG) (if bit 6 in byte 3 is on)
7 INLINE|NOINLINE
40 24 0 DBCS literal
1 REPLACE
2 Reference modification was used.
3 Nested program
4 INITIAL (either IS INITIAL or compiler option INITIAL)
5 COMMON
6 SELECT . . . OPTIONAL
7 EXTERNAL
41 25 0 GLOBAL
1 RECORD IS VARYING
2 VOLATILE
3 Program uses UTF-8 data
5 Intrinsic function was used
6 Z-literal found
7 RECURSIVE
42 26 0 RMODE(ANY) Not RMODE(ANY)
1-3 Reserved  
4 Reserved  
5 INTDATE(LILIAN) INTDATE(ANSI)
6 TEST|NOTEST(SEPARATE) TEST|NOTEST(NOSEPARATE)
7 Reserved  
43 27 0 PGMNAME(LONGUPPER) Not PGMNAME(LONGUPPER)
1 PGMNAME(LONGMIXED) Not PGMNAME(LONGMIXED)
2 DLL NODLL
3 EXPORTALL NOEXPORTALL
4 TEST|NOTEST(SOURCE) TEST|NOTEST(NOSOURCE)
5 ARITH(EXTEND) ARITH(COMPAT)
6 THREAD NOTHREAD
7 TEST(EJPD) TEST(NOEJPD)
44 28 0-7 Build level info
52 32 0 LP(64) LP(32)
1 Reserved
2 SOURCE(HEX) SOURCE(DEC)
3 SMARTBIN NOSMARTBIN
4 Compilation unit is a function. Compilation unit is not a function.
5 Reserved
6 Program contains at least one JAVA-SHAREABLE directive. Program does not contain a JAVA-SHAREABLE directive.
7 Program contains one or more calls to Java using a CALL statement. Program does not contain a call to Java using a CALL statement.
53 33 0 JAVAIOP(JAVA64) JAVAIOP(NOJAVA64)
1 LSACHECK NOLSACHECK
2-7 Reserved
54 34 0-7 Reserved
55 35 0-7 TUNE architecture level

Check return code: A return code greater than 4 from the compiler could mean that some of the statements shown in the information bytes might have been discarded from the program.

Related references  
LIST
z/OS Language Environment Vendor Interfaces (COBOL-specific vendor interfaces)