Search code examples
cobolmainframezos

How to fix a U4038 in a simple program


I am trying to execute a simple COBOL program on z/OS Mainframe System. The program only opens and closes a file. It compiles with no errors but when I run it I get a U4038 abend.

This is the code of the program:

----+-*A-1-B--+----2----+----3----+----4----+----5----+----6----+----7-|--+----8
        IDENTIFICATION DIVISION.
        PROGRAM-ID. LISTKSDS
        AUTHOR. TestingUser

        ENVIRONMENT DIVISION.
        CONFIGURATION SECTION.
        INPUT-OUTPUT SECTION.
        FILE-CONTROL.
           SELECT INFILE ASSIGN TO DATAIN
             ORGANIZATION IS INDEXED
             ACCESS MODE IS SEQUENTIAL
             RECORD KEY EST-KEY
             FILE STATUS IS WS-FILE-STATUS.

        DATA DIVISION.
        FILE SECTION.
        FD INFILE.
        COPY EST01.

        WORKING-STORAGE SECTION.
        01 VARIABLES.
           05 WS-FILE-STATUS    PIC X(2).

        LINKAGE SECTION.

        PROCEDURE DIVISION.
             DISPLAY "STARTING PROGRAM.."
             PERFORM INITIALIZATION
             PERFORM TERMINATION
             GOBACK.

        INITIALIZATION.
             DISPLAY "OPENING FILE.."
             OPEN INPUT INFILE
             IF WS-FILE-STATUS IS NOT EQUAL TO '00'
             THEN
             GO TO ERROR-EXIT
             END-IF.

        TERMINATION.
             CLOSE INFILE.

        ERROR-EXIT.

Job to compile:

//TESTUSEC  JOB NERT4587,CLASS=C,MSGCLASS=X,NOTIFY=&SYSUID
//*
//STEP1   EXEC IGYWCL,PARM=(LIB)
//SYSLIB DD DSN=TES.COPIES.TEST,DISP=SHR
//COBOL.SYSIN DD DSN=TES.SOFT.SRC(SRC04),DISP=SHR
//LKED.SYSLMOD DD DISP=SHR,DSN=TES.SOFT.LIB
//LKED.SYSIN   DD *
   ENTRY LISTKSDS
   NAME  LISTKSDS(R)
/*
//*

Job to submit:

//TESTUSEC  JOB NERT4587,CLASS=C,MSGCLASS=X,NOTIFY=&SYSUID
//*
//JOBLIB  DD DSN=TES.SOFT.LIB,DISP=SHR
//*
//STEP1   EXEC PGM=LISTKSDS,REGION=2M
//DATAIN  DD DSN=TES.VS.TEST,DISP=SHR
//*

Solution

  • A U4038 abend is a user-abend which comes from Language Environment, the "run-time" for Mainframe programs (it supports multiple Mainframe languages).

    You have more information about this. If you look at your spool output, I'd expect you to be able to find more information.

    You have specified a FILE STATUS clause on the SELECT for your file, so the U4038 is unlikely to be file-related.

    However, it is likely that you have a file problem which is leading to this program problem.

    This is likely to be the problem. If it is not the problem, it is a problem:

             IF WS-FILE-STATUS IS NOT EQUAL TO '00'
             THEN
             GO TO ERROR-EXIT
             END-IF.
    

    I suspect you are getting a non-zero in WS-FILE-STATUS. The paragraph containing this is PERFORMed, and the GO TO is taking you outside the range of the PERFORM. When you test for a non-zero file-status, it is always a good idea to DISPLAY the non-zero value that you encounter.

    Using GO TO outside the range of a PERFORM is especially bad. Your program will continue from the target paragraph of the GO TO and just keep falling through sequentially into the next code.

    You have no "next code". So the program "falls off the end". This is not a valid thing to do, so you get an abend.

    Although we can't see the content of the copybook, the thing which has given the presumed non-zero file-status probably lies between that, the file definition, and the file you have specified on the DATAIN DD statement.

    Most likely is that there is a mismatch in the size of the data defined in your program to the file named in the JCL or the key defined in the program does not match the file in the JCL.

    You need to locate the additional message in your spool output. That will normally help a lot. If you can't get it from that, paste the entire SYSOUT output from the step.

    You are using a minimal number of full-stops/periods, but it is best to put those on a line of their own, in column 12, so they are not attached to any code. Then you can't copy code and accidentally end up with a full-stop/period in a crucially wrong place.

    You would also have received a compiler diagnostic, as your ERROR-EXIT contains no code. Always look at your messages and correct the code accordingly.

    Also pay attention to indentation. It has no significance to the compiler, but you format the code for the human reader, so please pay attention to that, as you never know when it will be you some time later, or one of your team-mates at 2am. Or your tutor/mentor reviewing your work.

    On your linkedit/bind you have specified DISP=SHR. Change that to DISP=OLD, please. If you manage to run two linkedits at the same time, you can trash your library.