First, I would go to www.ibm.link and look up the details on the compiler procs
https://www.ibm.com/support/knowledgecenter/SSLTBW_2.1.0/com.ibm.zos.v2r1.ceea200/clccat2.htm

These have not changed in a long time so any version of z/OS or OS/390 should 
be okay to use for understanding the JCL.

Next, review the JCL Manual to understand how to use the PROCs and override JCL 
statements.

When executing a proc, it can be made up of multiple Steps.  Each step will 
have a requirement for input and output.  From your error of

IEC130I SYSIN    DD STATEMENT MISSING

That is a JCL error and should be addressed. 

The other errors
  IGZ0017S The open of DISPLAY or ACCEPT file with environment name SYSIN was 
unsuccessful.
  CEE3201S The system detected an operation exception (System Completion 
Code=0C1 ).
           From compile unit CALC1000 at entry point CALC1000 at compile unit 
offset +000002DC at entry offset +000002DC
            at address 1EE312DC.
  Abend 0C1000 hex occurred processing command 'CALL    '.
  ***

Are related to your missing SYSIN DD Statement.

When you resolve your SYSIN DD Missing condition the other errors should be 
resolved.


I might suggest that you add some error handling to your COBOL program for 
failed opens.

Lizette


> -----Original Message-----
> From: IBM Mainframe Discussion List [mailto:IBM-MAIN@LISTSERV.UA.EDU] On
> Behalf Of Cameron Seay
> Sent: Friday, July 08, 2016 11:41 PM
> To: IBM-MAIN@LISTSERV.UA.EDU
> Subject: Error in a simple COBOL program
> 
> I am experiencing a run time error with a simple COBOL program.  It compiles
> fine.  Here is the source code  IDENTIFICATION DIVISION.
>       *
>        PROGRAM-ID. CALC1000.
>       *
>        ENVIRONMENT DIVISION.
>       *
>        INPUT-OUTPUT SECTION.
>       *
>        DATA DIVISION.
>       *
>        FILE SECTION.
>       *
>        WORKING-STORAGE SECTION.
>       *
>        77  END-OF-SESSION-SWITCH       PIC X       VALUE "N".
>        77  SALES-AMOUNT                PIC 9(5)V99.
>        77  SALES-TAX                   PIC Z,ZZZ.99.
>       *
>        PROCEDURE DIVISION.
>       *
>        000-CALCULATE-SALES-TAX.
>       *
>            PERFORM 100-CALCULATE-ONE-SALES-TAX
>                UNTIL END-OF-SESSION-SWITCH = "Y".
>            DISPLAY "END OF SESSION.".
>            STOP RUN.
>       *
>        100-CALCULATE-ONE-SALES-TAX.
>       *
>            DISPLAY "-----------------------------------------------".
>            DISPLAY "TO END PROGRAM, ENTER 0.".
>            DISPLAY "TO CALCULATE SALES TAX, ENTER THE SALES AMOUNT.".
>            ACCEPT SALES-AMOUNT.
>            IF SALES-AMOUNT = ZERO
>                MOVE "Y" TO END-OF-SESSION-SWITCH
>            ELSE
>                COMPUTE SALES-TAX ROUNDED =
>                    SALES-AMOUNT * .0785
>                DISPLAY "SALES TAX = " SALES-TAX.
> 
> Here is the JCL:
> 
>  ==MSG>           your edit profile using the command RECOVERY ON.
>  000100 //CALC1000 JOB 1,'A. STUDENT',NOTIFY=&SYSUID
>  000110 //**************************************************
>  000120 //* COMPILE COBOL PROGRAM
>  000130 //**************************************************
>  000140 //STEP1 EXEC IGYWCLG
>  000150 //SYSIN        DD DSN=&SYSUID..LANG.SOURCE(CALC1001),DISP=SHR
>  000160 //COBOL.SYSLIB DD DSN=CEE.SCEESAMP,DISP=SHR
>  000170 //LKED.SYSLMOD DD DSN=&SYSUID..LANG.LOAD(CALC1001),DISP=SHR
> 
> Here is the error:
> 
> -----------------------------------------------
> TO END PROGRAM, ENTER 0.
> TO CALCULATE SALES TAX, ENTER THE SALES AMOUNT.
> IEC130I SYSIN    DD STATEMENT MISSING
> ***
> 
>  IGZ0017S The open of DISPLAY or ACCEPT file with environment name SYSIN was
> uns
> uccessful.
>  CEE3201S The system detected an operation exception (System Completion
> Code=0C1
> ).
>           From compile unit CALC1000 at entry point CALC1000 at compile unit
> off
> set +000002DC at entry offset +000002DC
>            at address 1EE312DC.
>  Abend 0C1000 hex occurred processing command 'CALL    '.
>  ***
> 
> I can't find what is missing.
> 

----------------------------------------------------------------------
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

Reply via email to