Migrating 2 IBMCOBOLAIX
Migrating 2 IBMCOBOLAIX
This document presents topics to help you migrate COBOL source programs to
IBM COBOL for AIX®, V3.1 or later.
COBOL programs created using a COBOL compiler other than the IBM COBOL for
AIX compiler will normally have some source code differences that will need to be
modified to become compatible with IBM COBOL for AIX. These differences are
often the result of implementer extensions to Standard COBOL, but might also be
due to differences in the operating system, or maybe for items in the COBOL
standard that are specified as "implementor defined", or some combination of
these. The number of differences will depend largely on how many extensions to
Standard COBOL were coded in the COBOL source members that you are
migrating.
In this document, the term Standard COBOL 2002 refers to ISO/IEC 1989:2002(E)
Information technology — Programming languages — COBOL. This does not
imply that IBM COBOL for AIX has implemented the new features found in
Standard COBOL 2002 (although some have been implemented), we are simply
using Standard COBOL 2002 to help you to identify extensions to Standard
COBOL that you might encounter as you do your migration, differences between
IBM COBOL for AIX and Standard COBOL, and to help you to determine the
changes you might need to make to resolve these. It will be useful for you to refer
to the IBM COBOL for AIX Language Reference and Programming Guide when
modifying COBOL code. You can find these books at the IBM COBOL for AIX
Library website: www.ibm.com/software/awdtools/cobol/aix/library/.
IBM COBOL for AIX supports the .cob suffix for COBOL source files.
When you use IBM COBOL for AIX to compile source code that contains
free-format COBOL source, you will receive the error messages in the following
example:
$ cat tcFreeFormat.cbl
000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. FreeFormat.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500
000600 PROCEDURE DIVISION.
000700 BEGIN-MY-PROGRAM.
000800 DISPLAY "COBOL ON AIX 5.1.0...".
000900 STOP RUN.
$ cob2 tcFreeFormat.cbl
PP 5724-Z87 IBM COBOL for AIX 5.1.0 in progress ...
LineID Message code Message text
6 IGYPS0017-E "PROCEDURE" should begin in area "A". It was
processed as if found in area "A".
8 IGYPS0009-E "DISPLAY" should not begin in area "A". It was
processed as if found in area "B".
Messages Total Informational Warning Error Severe Terminating
Printed: 2 2
End of compilation 1, program FREEFORMAT, highest severity: Error.
Return code 8
You can rewrite your source in fixed format, or use scu to convert your source
from free-format source to fixed-format source:
$ cat sol-tcFreeFormat.cbl
000001 IDENTIFICATION DIVISION.
000002 PROGRAM-ID. FreeFormat.
000003 ENVIRONMENT DIVISION.
000004 DATA DIVISION.
000005 PROCEDURE DIVISION.
000006
000007 BEGIN-MY-PROGRAM.
When you use IBM COBOL for AIX to compile source code that contains one or
more alphanumeric literals longer than 160 characters, you will receive the error
message in the following example:
$ cat tcAlphanumeric160.cbl
000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. TEST-CASE.
000300 ENVIRONMENT DIVISION.
000400
000500 DATA DIVISION.
000600 WORKING-STORAGE SECTION.
000700
000800 01 VARIABLE PIC N(300) VALUE "BEGIN = = = = = = =
000900- " = = = = = = = = = = = = = = = = = = = = =
001000- " = = = = = = = = = = = = = = = = = = = = =
001100- " = = = = = = = = = = = = = = = = = = = = =
001200- "= = = = = = = = = = = = = = = END".
001300
001400 PROCEDURE DIVISION.
001500 DISPLAY VARIABLE.
001600 STOP RUN.
Change your COBOL source to follow Standard COBOL 2002. You can change your
code to split long literals. As shown in the following example, MOVE “longliteral”
to ITEM-1 can be split:
MOVE “long” to ITEM-1(1:4).
MOVE “literal” to ITEM-1(5:).
When you use IBM COBOL for AIX to compile source code that contains extra and
misplaced periods, you will receive the error messages in the following example:
Change your COBOL source to follow Standard COBOL 2002, or use scu to remove
extra and misplaced periods:
$ cat sol-tcPeriods.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000040 DATA DIVISION.
000050
000060 PROCEDURE DIVISION.
000070 PERFORM GREETING.
000080
000090
000100 PERFORM END-PROGRAM.
000110
000120 GREETING.
000130
000140
000150 DISPLAY "HELLO FROM IBM.".
000160 END-PROGRAM.
000170 STOP RUN.
User-defined words
Within a source element, a user-defined word can be used as only one type of
source element.
Example 1
In the following example, the procedure name is the same as the program
identifier:
Example 2
In the following example, GREETING is used as both a data name and a procedure
name:
$ cat tcSameName2.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000040 DATA DIVISION.
000050
000060 WORKING-STORAGE SECTION.
000070
000080 01 GREETING PIC X(20) VALUE "FROM IBM.".
000090 PROCEDURE DIVISION.
000100 MY-PROGRAM.
000110 PERFORM GREETING.
000120 PERFORM END-PROGRAM.
000130
000140 GREETING.
000150 DISPLAY "HELLO " GREETING.
000160 END-PROGRAM.
000170 STOP RUN.
For Example 1:
$ cat sol-tcSameName.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. GREETING.
000030 ENVIRONMENT DIVISION.
000040 DATA DIVISION.
000050
000060 PROCEDURE DIVISION.
000070
000060 MY-PARAGRAPH.
000080 PERFORM HELLO.
000090 PERFORM END-PARAGRAPH.
000100
000110 HELLO.
000120 DISPLAY "WELCOME TO IBM COBOL FOR AIX 5.1.0...".
000130
000140 END-PARAGRAPH.
000150 DISPLAY "HAVE A NICE DAY!".
000160 STOP RUN.
For Example 2:
$ cat sol-tcSameName2.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000040 DATA DIVISION.
000050
000060 WORKING-STORAGE SECTION.
000070
000080 01 GREETING PIC X(20) VALUE "FROM IBM.".
000090 PROCEDURE DIVISION.
000100 MY-PROGRAM.
000110 PERFORM MY-GREETING.
000120 PERFORM END-PROGRAM.
000130
000140 MY-GREETING.
000150 DISPLAY "HELLO " GREETING.
000160 END-PROGRAM.
000170 STOP RUN.
When you use IBM COBOL for AIX to compile source code that contains REPORT
SECTION or SCREEN SECTION, you will receive the error messages in the following
example:
$ cat tcReportScreenSection.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000040 DATA DIVISION.
000050
000060 REPORT SECTION.
000070 01 TYPE IS PAGE HEADING.
For details about REPORT SECTION and SCREEN SECTION, see Standard COBOL 2002,
section 13.7, Report section, and section 13.8, Screen section.
See the output of MY-DATA in the following example. The null characters are
removed.
$ cat tcBlankReplaceNull.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. "TEST-CASE".
000030 ENVIRONMENT DIVISION.
000040 CONFIGURATION SECTION.
000050 DATA DIVISION.
000060 WORKING-STORAGE SECTION.
000080 77 MY-DATA PIC X(5) VALUE X"4F4E00004E".
000120 PROCEDURE DIVISION.
000125 DISPLAY MY-DATA "<-".
000130 STOP RUN.
$ cob2 tcBlankReplaceNull.cbl
PP 5724-Z87 IBM COBOL for AIX 5.1.0 in progress ...
End of compilation 1, program TEST-CASE, no statements flagged.
$ a.out
ONN<-
When you use IBM COBOL for AIX to compile source programs containing
floating point literals that do not use an E-notation; for example, if 1500.0 is used
instead of 1.5E3, you will receive the error messages in the following example:
$ cat tcFloatingFormat.cbl
000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. TEST-CASE.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500
You can also use scu to convert such format of floating point literals.
If your source contains the RECORD SEQUENTIAL file organization, you will receive
the error messages in the following example.
Change RECORD SEQUENTIAL to LINE SEQUENTIAL, and then compile again. You can
also use scu to replace RECORD SEQUENTIAL with LINE SEQUENTIAL.
$cat tcRecordSequential.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000031
000032 INPUT-OUTPUT SECTION.
000033 FILE-CONTROL.
000034 SELECT CONTACTS
000035 ASSIGN TO "MYFILE.DAT"
000036 ORGANIZATION IS RECORD SEQUENTIAL.
000037
000040 DATA DIVISION.
000050 FILE SECTION.
000051 FD CONTACTS
000052 RECORD CONTAINS 20 CHARACTERS.
000053 01 CONTACT-RECORD.
000054 05 FNAME PIC X(10).
000055 05 LNAME PIC X(10).
000073
000090 PROCEDURE DIVISION.
000100 PERFORM OPEN-FILE.
000110 PERFORM INPUT-DATA.
000120 PERFORM SAVE-DATA.
000130 PERFORM CLOSE-FILE.
000140 PERFORM END-PROGRAM.
000150
000160 INPUT-DATA.
000170 DISPLAY "ENTER FIRST NAME.".
000180 ACCEPT FNAME.
000190 DISPLAY "ENTER LAST NAME.".
000200 ACCEPT LNAME.
000210
When you use IBM COBOL for AIX to compile source code that contains an
IDENTIFICATION DIVISION not as the first division in a COBOL source program,
you will receive the error messages in the following example:
$ cat tcIdentificationDivision.cbl
000010 ENVIRONMENT DIVISION.
000020 DATA DIVISION.
000030
000040 WORKING-STORAGE SECTION.
000050 01 GREETING GLOBAL PIC X(50) VALUE "HELLO FROM IBM...".
000060 01 GOODBYE GLOBAL PIC X(50) VALUE "HAVE A NICE DAY...".
000070
000080 IDENTIFICATION DIVISION.
000090 PROGRAM-ID. TEST-CASE.
000100
000110 PROCEDURE DIVISION.
000120 DISPLAY GREETING.
000130 DISPLAY GOODBYE.
000140 STOP RUN.$
When you use IBM COBOL for AIX to compile source code that contains a hyphen
in the ASSIGN statement, you will receive the error message in the following
example:
$ cat tcHyphenAssign.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. "TEST-CASE".
000030 ENVIRONMENT DIVISION.
000040 CONFIGURATION SECTION.
000050 INPUT-OUTPUT SECTION.
000060 FILE-CONTROL.
000070 SELECT DATA-INFO
ASSIGN TO "SYS-FILENAME"
ORGANIZATION IS LINE SEQUENTIAL.
000080 DATA DIVISION.
000090 FILE SECTION.
000100 FD DATA-INFO.
000110 01 INFO-1 PIC N(132).
000120 PROCEDURE DIVISION.
000130 STOP RUN.
$ cob2 -o tcHyphenAssign tcHyphenAssign.cbl
PP 5724-Z87 IBM COBOL for AIX 5.1.0 in progress ...
LineID Message code Message text
12 IGYGR1387-S File system id SYS was specified for a file with
"ORGANIZATION LINE SEQUENTIAL". The file system id was changed
to NAT.
Messages Total Informational Warning Error Severe Terminating
Printed: 1 1
End of compilation 1, program TEST-CASE, highest severity: Severe.
Return code 12$
As described in the COBOL for AIX Language Reference, the format of the ASSIGN
clause is '<file-system-ID>-<system-file name>'. If a hyphen exists in the environment
variable or the data name value, the first 3 characters to the left of the leftmost
hyphen are treated as the file system identifier. The character string to the right of
the leftmost hyphen is then used as the system file name, possibly including drive
and path names.
In the previous example, the compiler takes the first 3 characters to the left of the
leftmost hyphen; in this case, SYS is treated as the file system identifier. The
character string to the right of the leftmost hyphen is then used as the system file
name, in this case, FILENAME, is used as the system file name.
If no hyphen exists, or the character string to the left of the leftmost hyphen has
fewer than 3 characters, the entire character string is used as the system file name,
possibly including drive and path names.
Specifying S-FILENAME in the ASSIGN clause works instead because the number of
characters before the hyphen is fewer than 3 characters. Alternatively, you can
specify SYSFILENAME in the ASSIGN clause.
IBM COBOL for AIX also handles LINE SEQUENTIAL by using the native (NAT) file
system identifier. The same behavior results if you specified STL-FILENAME.
When you use IBM COBOL for AIX to compile source code that contains an OCCURS
clause in level 01, you will receive the error messages in the following example:
$ cat tcOccursClause.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000040 DATA DIVISION.
000050
000060 WORKING-STORAGE SECTION.
000061
000062
000063 01 EMPLOYEES OCCURS 100 TIMES.
000064 05 FNAME PIC X(10).
000065 05 LNAME PIC X(10).
000066 05 SALARY PIC 9(5).
000067000068 77 COUNTER PIC 9.
000070
000071 PROCEDURE DIVISION.
000072 MOVE "DAVID" TO FNAME(1).
000073 MOVE "SMITH" TO LNAME(1).
000074 MOVE "60000" TO SALARY(1).
000075 MOVE "JENNY" TO FNAME(2).
000076 MOVE "HU" TO LNAME(2).
000077 MOVE "55000" TO SALARY(2).
000078
000080 DISPLAY-RESULT.
000081 PERFORM VARYING COUNTER FROM 1 BY 1 UNTIL COUNTER > 2
000082 DISPLAY "EMPLOYEE: " FNAME IN EMPLOYEES(COUNTER)" "
000083 LNAME IN EMPLOYEES(COUNTER)" "
000084 "Salary: " SALARY IN EMPLOYEES(COUNTER)
000085 END-PERFORM.
000086 STOP-PROGRAM.
000090 STOP RUN.
Change your COBOL source to follow Standard COBOL 2002. For example, if you
change the code in the previous example by using the definition of EMPLOYEES
that is moved from level 01 to level 03, it compiles without messages.
$ cat sol-tcOccursClause.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000040 DATA DIVISION.
000050
000060 WORKING-STORAGE SECTION.
000061
000062 01.
000063 03 EMPLOYEES OCCURS 100 TIMES.
000065 05 FNAME PIC X(10).
000066 05 LNAME PIC X(10).
000067 05 SALARY PIC 9(5).
000068
000069 77 COUNTER PIC 9.000070
000071 PROCEDURE DIVISION.
000072 MOVE "DAVID" TO FNAME(1).
000073 MOVE "SMITH" TO LNAME(1).
000074 MOVE "60000" TO SALARY(1).
000075 MOVE "JENNY" TO FNAME(2).
000076 MOVE "HU" TO LNAME(2).
000077 MOVE "55000" TO SALARY(2).
000078
000080 DISPLAY-RESULT.
000082 PERFORM VARYING COUNTER FROM 1 BY 1 UNTIL COUNTER > 2
000084 DISPLAY "EMPLOYEE: " FNAME IN EMPLOYEE(COUNTER) " "
000085 LNAME IN EMPLOYEE(COUNTER) " "
000085 "Salary: " SALARY IN EMPLOYEE(COUNTER)
000086 END-PERFORM.
000087 STOP-PROGRAM.
000120 STOP RUN.
COMP-X
IBM COBOL for AIX does not support COMP-X.
When you use IBM COBOL for AIX to compile source code that contains COMP-X,
you will receive the error message in the following example:
$ cat tcCompX.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000040 DATA DIVISION.
000050
000060 WORKING-STORAGE SECTION.
000070 01 STU-ID PIC S9(4) COMP-X VALUE ZERO.
Change COMP-X to COMP-5, and make corresponding changes to the PICTURE clause.
You must keep the same allocated storage for the data item.
When you use IBM COBOL for AIX to compile source code that contains an
uninitialized variable, you will receive the error messages in the following
example:
$cat tcConvert2DisplayType.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. "TEST-CASE".
000030 ENVIRONMENT DIVISION.
000040 CONFIGURATION SECTION.
000050 DATA DIVISION.
000060 WORKING-STORAGE SECTION.
000070 01 EMP-INFO.
000080 05 EMP-ID PIC S9(5) sign is trailing separate.
000090 01 EMP-ID2 PIC S9(4).
000100 PROCEDURE DIVISION.
000120 MOVE EMP-ID OF EMP-INFO TO EMP-ID2.
000130 STOP RUN.
$ cob2 -o tcConvert2DisplayType tcConvert2DisplayType.cbl
PP 5724-Z87 IBM COBOL for AIX 5.1.0 in progress ...
End of compilation 1, program TEST-CASE, no statements flagged.
$ tcConvert2DisplayType
IWZ040S An invalid separate sign was detected.
Message routine called from offset 0x48 of routine
iwzWriteERRmsg. iwzWriteERRmsg called from offset
0xb4 of routine _iwzcBCD_CONV_ZndTS_To_ZndTO.
_iwzcBCD_CONV_ZndTS_To_ZndTO called from offset
0x130 of routine TEST-CASE.
IWZ901S Program exits due to severe or critical error.
IOT/Abort trap(coredump)
When you use IBM COBOL for AIX to compile source code that contains a
redefined object and the OCCURS clause, you will receive the error messages in the
following example:
$ cat tcRedefineOccurs.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000040
000050 DATA DIVISION.
000060 WORKING-STORAGE SECTION.
000070
000080 01 EMPLOYEE-INFO.
000090 03 EMPLOYEE OCCURS 50 TIMES.
000100 05 NAME PIC X(10).
000110 05 AGE PIC 9(3).
000120 03 NEW-EMPLOYEE REDEFINES EMPLOYEE.
000130 05 FNAME PIC X(10).
000130 05 LNAME PIC X(20).
000140 05 AGE PIC 9(3).
000150
000160 PROCEDURE DIVISION.
000170 STOP RUN.
According to Standard COBOL 2002, section 13.16.42.2, Syntax rules, the data item
being redefined cannot contain an OCCURS clause.
Change the PICTURE character-string symbol to X and use hexadecimal notation for
alphanumeric literals for the values of X.
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000040 DATA DIVISION.
000050
000060 WORKING-STORAGE SECTION.
000061
000062 01 IND-AREA.
000063 05 MESSAGES OCCURS 99 TIMES PIC X.
000064 88 MESSAGE-OFF VALUE X’00’.
000065 88 MESSAGE-ON VALUE X’01’ THROUGH X’FF’.
000066 01 MESSAGE-SET.
000067 05 MESSAGE-1 PIC 9(2) VALUE 01.
000070
000071 PROCEDURE DIVISION.
000072 SET MESSAGE-OFF(MESSAGE-1) TO TRUE.
000074
000075 IF MESSAGE-ON(MESSAGE-1)
000076 DISPLAY "IT’S TRUE"
000077 ELSE
000078 DISPLAY "IT’S FALSE"
000079 END-IF.
000080 STOP-PROGRAM.
000081 STOP RUN.
When you use IBM COBOL for AIX to compile source code that contains a MOVE
statement from a national data item to an alphanumeric data item, you will receive
the error message in the following example:
$ cat tcNational2Alphanumeric.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. ND2AD.
000030 ENVIRONMENT DIVISION.
000040 CONFIGURATION SECTION.
000050
000060 DATA DIVISION.
000070 WORKING-STORAGE SECTION.
000080
000090 01 DataNational PIC N(100).
000100
000110 01 DataAlphanumeric PIC X(100).
000120
000130 PROCEDURE DIVISION.
000140 MOVE DataNational TO DataAlphanumeric.
000150 STOP-MY-PROGRAM.
000160 STOP RUN.
According to Standard COBOL 2002, section 14.8.24.2, Syntax rules for the MOVE
statement, you cannot move a national data item to an alphanumeric data item.
When you use IBM COBOL for AIX to compile source code that contains a call to a
C function in mixed or lowercase characters, you will receive the error messages in
the following example:
IBM COBOL for AIX folds program-names to uppercase. If you have COBOL
source that contains a call to a C function in mixed or lowercase characters, this
function is folded to uppercase characters. The linker will not find the program,
and an error message is displayed to indicate an unresolved symbol.
You can use the PGMNAME compiler option to control how the compiler handles
program-names. The default is PGMNAME(UPPER), but you can use PGMNAME(MIXED) to
process the program-name as is, without truncation, translation, or folding to
uppercase. When you specify PGMNAME(MIXED), use the literal format of the
program-name; that is, make the program-name a literal string such as
“programname”, or you will see the following message:
IGYDS1046-E A user-defined word was found as a "PROGRAM-ID" name under
the "PGMNAME(LONGMIXED)" compiler option.
For an example about a COBOL program that calls C functions, see Example:
COBOL program calling C functions in the COBOL for AIX Programming Guide.
$ cat sol-tcCallCFunction.cbl
000010 CBL PGMNAME(LONGMIXED)
000020 IDENTIFICATION DIVISION.
000030 PROGRAM-ID. "TEST-CASE".
000040 ENVIRONMENT DIVISION.
000050 CONFIGURATION SECTION.
000060 DATA DIVISION.
000070 WORKING-STORAGE SECTION.
000080
000090 PROCEDURE DIVISION.
000100 CALL "CFunction"
000110 DISPLAY "HELLO FROM COBOL...".
000120 STOP RUN.
$ cob2 -o sol-tcCallCFunction sol-tcCallCFunction.cbl cTest.o
PP 5724-Z87 IBM COBOL for AIX 5.1.0 in progress ...
End of compilation 1, program TEST-CASE, no statements flagged.
$ sol-tcCallCFunction
HELLO FROM C...
HELLO FROM COBOL...
If the input data is longer than the receiving area, then IBM COBOL for AIX pads
the area with spaces of the appropriate representation for the receiving area.
According to Standard COBOL 2002, section 14.8.1.3, General rules for the ACCEPT
statement, the implementer must define the size of a data transfer for each
hardware device.
When you use IBM COBOL for AIX to compile source code that contains BINARY
formatted data in an ACCEPT statement, you will receive the error message in the
following example:
$ cat tcAcceptBinary.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000040 DATA DIVISION.
000050
000060 WORKING-STORAGE SECTION.
000070 01 EMPLOYEE-ID PIC S9(4) COMP-5 VALUE ZERO.
000080
000090 PROCEDURE DIVISION.
000100 MY-PROGRAM.
000110 DISPLAY "PLEASE INSERT EMPLOYEE’S ID NUMBER..".
000120 ACCEPT EMPLOYEE-ID.
000130
000140 STOP RUN.
Change the data type from COMP-5 to DISPLAY, and make further changes to the
input source as well.
When you use IBM COBOL for AIX to compile source code that contains NULL
parameters in a CALL statement, you will receive the error message in the following
example:
$ cat tcCallNull.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000040 DATA DIVISION.
000050
000060 WORKING-STORAGE SECTION.
000070
000080 PROCEDURE DIVISION.
000090 CALL "TEST-CASE2" USING NULL.
000100 STOP RUN.
According to Standard COBOL 2002, section 14.4.8.2, syntax rules do not identify
NULL as a valid parameter for the CALL statement.
$ cat sol-tcCallNull.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000040 DATA DIVISION.
000050
000060 WORKING-STORAGE SECTION.
000070 01 NULLPTR USAGE POINTER VALUE NULL.
000080
000110 PROCEDURE DIVISION.
000140 CALL "TEST-CASE2" USING VARIABLE.
000150 STOP RUN.
For example, when you use IBM COBOL for AIX to compile source code that
contains a positive number, the output does not display the plus sign (+):
$ cat tcPlusSign.cbl
000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. TEST-CASE.
000030 ENVIRONMENT DIVISION.
000040
000050 INPUT-OUTPUT SECTION.
000060
000070 DATA DIVISION.
000080 WORKING-STORAGE SECTION.
000090 01 POSITIVE-NUM PIC S9(4) COMP-5 VALUE ZERO.
000100 01 NEGATIVE-NUM PIC S9(4) COMP-5 VALUE ZERO.
000110
000120 PROCEDURE DIVISION.
000130 COMPUTE POSITIVE-NUM = 10 - 3.
000140 COMPUTE NEGATIVE-NUM = 3 - 10.
000150 DISPLAY "10 - 3 = " POSITIVE-NUM.
000160 DISPLAY "3 - 10 = " NEGATIVE-NUM.
000170 STOP RUN.
$ tcPlusSign
10 - 3 = 00007
3 - 10 = -00007
Note: This rule does not apply to numeric-edited items. If you use an editing sign
control symbol in a variable declared with USAGE DISPLAY or NATIONAL, such as the
plus sign (+) in the following example:
000090 01 POSITIVE-NUM PIC +9(4).
000100 01 NEGATIVE-NUM PIC +9(4).
This information was developed for products and services offered in the U.S.A.
IBM may not offer the products, services, or features discussed in this document in
other countries. Consult your local IBM representative for information on the
products and services currently available in your area. Any reference to an IBM
product, program, or service is not intended to state or imply that only that IBM
product, program, or service may be used. Any functionally equivalent product,
program, or service that does not infringe any IBM intellectual property right may
be used instead. However, it is the user's responsibility to evaluate and verify the
operation of any non-IBM product, program, or service.
IBM may have patents or pending patent applications covering subject matter
described in this document. The furnishing of this document does not give you
any license to these patents. You can send license inquiries, in writing, to:
For license inquiries regarding double-byte (DBCS) information, contact the IBM
Intellectual Property Department in your country or send inquiries, in writing, to:
The following paragraph does not apply to the United Kingdom or any other
country where such provisions are inconsistent with local law:
INTERNATIONAL BUSINESS MACHINES CORPORATION PROVIDES THIS
PUBLICATION "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER
EXPRESS OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
WARRANTIES OF NON-INFRINGEMENT, MERCHANTABILITY OR FITNESS
FOR A PARTICULAR PURPOSE. Some states do not allow disclaimer of express or
implied warranties in certain transactions, therefore, this statement may not apply
to you.
IBM may use or distribute any of the information you supply in any way it
believes appropriate without incurring any obligation to you.
Licensees of this program who want to have information about it for the purpose
of enabling: (i) the exchange of information between independently created
programs and other programs (including this one) and (ii) the mutual use of the
information which has been exchanged, should contact:
The licensed program described in this document and all licensed material
available for it are provided by IBM under terms of the IBM Customer Agreement,
IBM International Program License Agreement or any equivalent agreement
between us.
All statements regarding IBM's future direction or intent are subject to change or
withdrawal without notice, and represent goals and objectives only.
This information contains examples of data and reports used in daily business
operations. To illustrate them as completely as possible, the examples include the
names of individuals, companies, brands, and products. All of these names are
fictitious and any similarity to the names and addresses used by an actual business
enterprise is entirely coincidental.
COPYRIGHT LICENSE:
Each copy or any portion of these sample programs or any derivative work, must
include a copyright notice as follows:
© (your company name) (year). Portions of this code are derived from IBM Corp.
Sample Programs. © Copyright IBM Corp. 2010, 2015.
This Software Offering does not use cookies or other technologies to collect
personally identifiable information.
If the configurations deployed for this Software Offering provide you as customer
the ability to collect personally identifiable information from end users via cookies
and other technologies, you should seek your own legal advice about any laws
applicable to such data collection, including any requirements for notice and
consent.
For more information about the use of various technologies, including cookies, for
these purposes, see IBM's Privacy Policy at http://www.ibm.com/privacy and
IBM's Online Privacy Statement at http://www.ibm.com/privacy/details in the
section entitled “Cookies, Web Beacons and Other Technologies,” and the “IBM
Software Products and Software-as-a-Service Privacy Statement” at
http://www.ibm.com/software/info/product-privacy.
Trademarks
IBM, the IBM logo, and ibm.com are trademarks or registered trademarks of
International Business Machines Corp., registered in many jurisdictions worldwide.
Other product and service names might be trademarks of IBM or other companies.
A current list of IBM trademarks is available on the web at “Copyright and
trademark information” at www.ibm.com/legal/copytrade.shtml.
Notices 29
30 Migrating to IBM COBOL for AIX
Printed in USA