View previous topic :: View next topic |
Author |
Message |
tommy123 Beginner
Joined: 04 May 2005 Posts: 21 Topics: 11
|
Posted: Mon Jun 06, 2005 12:53 pm Post subject: ERROR IN COMPILER OPTION 'LIB' FOR COBOL PGM FOR USING COPY |
|
|
Hai,
I am trying to compile a program in which i am using a COPY STATEMENT.So i include the compiler option 'LIB' before the identification divison of my program.I am getting compile time error.Can any one suggest me where i am making a mistake ?
Program
--------
CBL(PROCESS) LIB
IDENTIFICATION DIVISION.
PROGRAM-ID. TESTPGM.
AUTHOR. ABC.
DATE-WRITTEN. 05/06/05.
DATE-COMPILED. 05/06/05.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. IBM-390 WITH DEBUGGING MODE.
OBJEC-COMPUTER. IBM-390.
INPUT-OUTPUT SECTION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 FILLER PIC X(35)
VALUE "TESTPGM WORKING STORAGE AREA BEGINS".
COPY PQR.
COMPILATION MESSAGE
--------------------
Invocation parameters:
NOTERM,
IGYOS4011-E "NOTERM" was not followed by a blank or comma.
IGYOS4000-W Processing for this compiler option or sub-option string was terminated.
IGYDS0139-W Diagnostic messages were issued during processing of compiler options. These messages are located at the
beginning of the listing.
16 IGYDS0010-S A "COPY" statement was found but the "LIB" compiler option was not specified. Scanning was resumed at the
item following the next period.
JCL
----
//COBOL EXEC PGM=IGYCRCTL,REGION=640K,COND=(12,LE),
// PARM=(NOTERM,'')
.
.
.
.
//COPYLIB DD DSN=HIRA.COBOL.COPYLIB,DISP=SHR,
// VOL=SER=DSK1,UNIT=SYSDA |
|
Back to top |
|
 |
kolusu Site Admin

Joined: 26 Nov 2002 Posts: 12378 Topics: 75 Location: San Jose
|
Posted: Mon Jun 06, 2005 1:08 pm Post subject: |
|
|
tommy123,
You have an Unbalanced quotes on your parm statement. Actually you can pass the compiler parameters via CBL statements itself. so remove the parm statement in your JCL.
ie.
Code: |
//COBOL EXEC PGM=IGYCRCTL,REGION=640K,COND=(12,LE)
|
Also you misspelled OBJECT computer. Correct them you should be ok. Below is the modified code.
Code: |
CBL LIB,NOTERM
IDENTIFICATION DIVISION.
PROGRAM-ID. TESTPGM.
AUTHOR. ABC.
DATE-WRITTEN. 05/06/05.
DATE-COMPILED. 05/06/05.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. IBM-370 WITH DEBUGGING MODE.
OBJECT-COMPUTER. IBM-370.
INPUT-OUTPUT SECTION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 FILLER PIC X(35)
VALUE "TESTPGM WORKING STORAGE AREA BEGINS".
COPY PQR.
|
Hope this helps...
Cheers
kolusu
PS: You will become a good programmer if you start solving the errors by yourself. _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
 |
tommy123 Beginner
Joined: 04 May 2005 Posts: 21 Topics: 11
|
Posted: Mon Jun 06, 2005 2:15 pm Post subject: ERROR IN COMPILER OPTION 'LIB' FOR COBOL PGM FOR USING COPY |
|
|
Hai Kolusu,
Thanks for an early response but still i am getting compile time error.
PGM
---
CBL LIB,NOTERM
IDENTIFICATION DIVISION.
PROGRAM-ID. TESTPGM.
AUTHOR. ABC.
DATE-WRITTEN. 05/06/05.
DATE-COMPILED. 05/06/05.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. IBM-390 WITH DEBUGGING MODE.
OBJECT-COMPUTER. IBM-390.
INPUT-OUTPUT SECTION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 FILLER PIC X(35)
VALUE "TESTPGM WORKING STORAGE AREA BEGINS".
COPY PQR.
JCL
----
//COBOL EXEC PGM=IGYCRCTL,REGION=640K,COND=(12,LE)
//COPYLIB DD DSN=HIRA.COBOL.COPYLIB,DISP=SHR,
// VOL=SER=DSK1,UNIT=SYSDA
COMPILER MESSAGE
-----------------
0PROCESS(CBL) statements:
CBL LIB,NOTERM
0Options in effect:
NOADATA
ADV
NOANALYZE
QUOTE
NOAWO
BUFSIZE(4096)
NOCMPR2
NOCOMPILE(S)
NOCURRENCY
DATA(31)
NODATEPROC
NODBCS
NODECK
NODLL
NODUMP
NODYNAM
NOEXIT
NOEXPORTALL
NOFASTSRT
FLAG(I)
NOFLAGMIG
NOFLAGSTD
NOIDLGEN
INTDATE(ANSI)
LANGUAGE(EN)
LIB
LINECOUNT(60)
NOLIST
NOMAP
NONAME
NONUMBER
NUMPROC(NOPFD)
OBJECT
NOOFFSET
NOOPTIMIZE
OUTDD(SYSOUT)
PGMNAME(COMPAT)
NORENT
RMODE(AUTO)
SEQUENCE
SIZE(MAX)
SOURCE
SPACE(1)
NOSSRANGE
NOTERM
NOTEST
TRUNC(STD)
NOTYPECHK
NOVBREF
NOWORD
NOXREF
YEARWINDOW(1900)
ZWB
0LineID Message code Library phase message text
16 IGYLI0048-S The member was not found in the "COPY" library.Skipped to the period terminating the "COPY" statement.
1
IGYSC0185-I Messages were issued during library phase processing.Refer to the beginning of the listing. |
|
Back to top |
|
 |
kolusu Site Admin

Joined: 26 Nov 2002 Posts: 12378 Topics: 75 Location: San Jose
|
Posted: Mon Jun 06, 2005 2:26 pm Post subject: |
|
|
Quote: |
16 IGYLI0048-S The member was not found in the "COPY" library.Skipped to the period terminating the "COPY" statement
|
Tommy123,
The message is so clear that any one can easily undestand it. It says that the member PQR is not found in the library HIRA.COBOL.COPYLIB. And the reason for that is the COBOL looks at SYSLIB ddname for copying the copylib members . But you named assigned your pds to COPYLIB instead of syslib. So change the COPYLIB ddname to SYSLIB and re-run your Job.
Code: |
//COBOL EXEC PGM=IGYCRCTL,REGION=640K,COND=(12,LE)
//SYSLIB DD DSN=HIRA.COBOL.COPYLIB,DISP=SHR
|
Hope this helps...
Cheers
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
 |
tommy123 Beginner
Joined: 04 May 2005 Posts: 21 Topics: 11
|
Posted: Mon Jun 06, 2005 3:12 pm Post subject: ERROR IN 'LIB' COMPILER OPTION USING FOR COPY |
|
|
Thanks Kolusu,
Actually i was not knowing that COBOL looks for SYSLIB DD name for copying COPYLIB MEMBERS.Now i am clear with that.Morever i am also clear with the compiler options being used in the program using CBL ......Can we code the compiler options like as i am using in the pgm 'LIB' AND 'NOTERM' to be passed from the JCL instead of directly coding them in the program.If it were how would the JCL look like ,can u please let me know ?
//COBOL EXEC PGM=IGYCRCTL,REGION=640K,COND=(12,LE)
//SYSLIB DD DSN=HIRA.COBOL.COPYLIB,DISP=SHR,
// VOL=SER=DSK1,UNIT=SYSDA
//* PARM=(NOTERM,'') |
|
Back to top |
|
 |
kolusu Site Admin

Joined: 26 Nov 2002 Posts: 12378 Topics: 75 Location: San Jose
|
Posted: Mon Jun 06, 2005 3:18 pm Post subject: |
|
|
Tommy123,
Everything you ask are clearly explained in the manuals. Just read them and understand the basic concepts. you can pass the compiler parameters enclosed in single parenthesis and seperated by a comma.
ex:
Code: |
//COBOL EXEC PGM=IGYCRCTL,REGION=640K,COND=(12,LE),PARM=('LIB,NOTERM')
|
Hope this helps...
Cheers
kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
 |
tommy123 Beginner
Joined: 04 May 2005 Posts: 21 Topics: 11
|
Posted: Tue Jun 07, 2005 2:38 pm Post subject: ERROR IN COMPILATION WITH COPYBOOK MEMBER |
|
|
Hai,
I am trying to use a copybook in my program and it is working fine .But when i purposefully try to code comment in the group 01 level of my copybook member,i am getting my compilation unsuccessful the display being below.But when i uncomment 01 level of my copybook member back,it works fine.My understanding is when i am coding a comment in 01 level,the copybook it self is not copied into the program,that is why i am getting compilation error.Can anyone please reply to my query as if any copybook member is commented in the group 01 level at the begining,it cannot be used / it is more or less meaning program cannot use that copybook for any purpose ?
PGM
----
000001 IDENTIFICATION DIVISION.
000002 PROGRAM-ID. COMPPGM.
000003 AUTHOR. ABC.
000004 DATE-WRITTEN. 05/06/05.
000005 DATE-COMPILED. 06/08/05.
000006 ENVIRONMENT DIVISION.
000007 CONFIGURATION SECTION.
000008 SOURCE-COMPUTER. IBM-390 WITH DEBUGGING MODE.
000009 *SOURCE-COMPUTER. IBM-390.
000010 OBJECT-COMPUTER. IBM-390.
000011 INPUT-OUTPUT SECTION.
000012 DATA DIVISION.
000013 WORKING-STORAGE SECTION.
000014 COPY PQR.
000015C *01 PQR.
000016C 05 P PIC 9(10).
000017C 05 Q PIC 9(10).
000018C 05 R PIC 9(10).
000019 01 FILLER PIC X(35)
000020 VALUE "COMPPGM WORKING STORAGE AREA BEGINS".
000021 PROCEDURE DIVISION.
000022 0000-MAIN.
000023 D DISPLAY "ENTERING COMPPGM ".
000024 MOVE 1 TO P.
000025 MOVE 2 TO Q.
000026 COMPUTE R = P + Q.
000027 DISPLAY "R IS " R.
000028 D DISPLAY "EXITING COMPPGM ".
000029 0000-EXIT.
000030 EXIT.
000031 STOP RUN.
COPYBOOK STRUCTURE PQR
-----------------------
*01 PQR.
05 P PIC 9(2).
05 Q PIC 9(2).
05 R PIC 9(2).
COMPILATION ERROR
-------------------
16 IGYDS1176-E The first level-number was not 01 for item "P". A level-number of 01 was assumed.
16 IGYDS1052-E Group item "P" contained the "PICTURE" clause. The clause was discarded.
26 IGYPA3074-S "P (GROUP)" was not numeric, but was a sender in an arithmetic expression.The statement was discarded.
Messages Total Informational Warning Error Severe Terminating
Printed: 3 2 1
* Statistics for COBOL program COMPPGM:
* Source records = 31
* Data Division statements = 3
* Procedure Division statements = 8
End of compilation 1, program COMPPGM, highest severity 12.
Return code 12 |
|
Back to top |
|
 |
kolusu Site Admin

Joined: 26 Nov 2002 Posts: 12378 Topics: 75 Location: San Jose
|
Posted: Tue Jun 07, 2005 3:03 pm Post subject: |
|
|
Quote: |
My understanding is when i am coding a comment in 01 level,the copybook it self is not copied into the program,that is why i am getting compilation error.Can anyone please reply to my query as if any copybook member is commented in the group 01 level at the begining,it cannot be used / it is more or less meaning program cannot use that copybook for any purpose ?
|
Tommy123,
Wrong assumption. The copybook is copied(check the sysprint listing) but subordinate items did not have a corresponding group item which resulted in a compilation error. Check this link for a detailed explantion of Level-numbers
Also check this link for a detailed explanation of Data relationships.
Read the topics 5.1.6.1 and 5.1.6.2
Hope this helps...
Cheers
Kolusu
Ps: You are on the verge of loosing your privelges to post in this board. As I said earlier please refer the manuals and try to understand the basics of programming. _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
 |
tommy123 Beginner
Joined: 04 May 2005 Posts: 21 Topics: 11
|
Posted: Tue Jun 07, 2005 8:07 pm Post subject: ERROR IN COMPILATION WITH COPYBOOK MEMBER |
|
|
Kolusu,
I have tried by putting the subordinate items under the group item 05 as below.But still i get error,if i change the level
number to 01 it works fine.Is it required to code 01 level only,can we not code 05 as group level and define the subordnate items as i have done below ? My understanding after the seeing the compiler messages is that compiler tries to define group item as 01 level only.Can u please emphasize on this more as i am not clear why compiler always tries to see the group item as 01 why not 05 or any other ?
PGM
-----
000001 IDENTIFICATION DIVISION.
000002 PROGRAM-ID. COMPPGM.
000003 AUTHOR. ABC.
000004 DATE-WRITTEN. 05/06/05.
000005 DATE-COMPILED. 06/08/05.
000006 ENVIRONMENT DIVISION.
000007 CONFIGURATION SECTION.
000008 SOURCE-COMPUTER. IBM-390 WITH DEBUGGING MODE.
000009 *SOURCE-COMPUTER. IBM-390.
000010 OBJECT-COMPUTER. IBM-390.
000011 INPUT-OUTPUT SECTION.
000012 DATA DIVISION.
000013 WORKING-STORAGE SECTION.
000014 COPY PQR.
000015C *01 PQR.
000016C
000017C 05 GROUPAB.
000018C 10 P PIC 9(2).
000019C 10 Q PIC 9(2).
000020C 10 R PIC 9(2).
000021 01 FILLER PIC X(35
000022 VALUE "COMPPGM WORKING STORAGE AREA BEGINS"
000023 PROCEDURE DIVISION.
000024 0000-MAIN.
000025 D DISPLAY "ENTERING COMPPGM ".
000026 MOVE 1 TO P.
000027 MOVE 2 TO Q.
000028 COMPUTE R = P + Q.
000029 DISPLAY "R IS " R.
000030 D DISPLAY "EXITING COMPPGM ".
000031 0000-EXIT.
000032 EXIT.
000033 STOP RUN.
COPYBOOK
--------
*01 PQR.
05 GROUPAB.
10 P PIC 9(2).
10 Q PIC 9(2).
10 R PIC 9(2).
COMPILER MESSAGES
--------------------------
17 IGYDS1176-E The first level-number was not 01 for item "GROUPAB". A level-number of 01 was assumed.
Messages Total Informational Warning Error Severe Terminating
Printed: 1 1
* Statistics for COBOL program COMPPGM:
* Source records = 33
* Data Division statements = 4
* Procedure Division statements = 8
End of compilation 1, program COMPPGM, highest severity 8.
Return code 8 |
|
Back to top |
|
 |
Mervyn Moderator

Joined: 02 Dec 2002 Posts: 415 Topics: 6 Location: Hove, England
|
Posted: Wed Jun 08, 2005 3:53 am Post subject: |
|
|
Tommy123,
You need to start with 01. 05 will not do. _________________ The day you stop learning the dinosaur becomes extinct |
|
Back to top |
|
 |
kolusu Site Admin

Joined: 26 Nov 2002 Posts: 12378 Topics: 75 Location: San Jose
|
Posted: Wed Jun 08, 2005 4:44 am Post subject: |
|
|
tommy123,
Did you even bother to read the links provided by me? It seems that you don't even have time to read the manuals.
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
 |
|
|