Page 1 of 2

ABEND=S000 U4038 REASON=00000000

PostPosted: Thu Sep 23, 2010 10:53 pm
by GUI1504
Hello again guys, i got a new abend when i'm trying to Input a file on my cobol to do a Redefines: ABEND=S000 U4038 REASON=00000000 . I know that's it happens because the Open/Close clause, but i don't understand why

COBOL - I've comment some lines to repair them after
       IDENTIFICATION DIVISION.
       PROGRAM-ID. REDEFINE.
      *
       ENVIRONMENT DIVISION.
      *
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
           SELECT ENTRADA
           ASSIGN TO ENTRADA.
      *
       DATA DIVISION.
      *
       FILE SECTION.
      *
       FD ENTRADA
           LABEL RECORD IS STANDARD
           RECORDING MODE IS F
           RECORD CONTAINS 36 CHARACTERS.
      *
       01 REG-ENTRADA PIC X(36).
      *
       WORKING-STORAGE SECTION.
      *
       01 WS-REG-FILE.
           05 WS-REG-INDEX     PIC       X(1).
           05 WS-REG-ARQ       PIC       X(35).
           05 WS-REG-HEADER    REDEFINES WS-REG-ARQ.
              10 WS-NOME-PGM   PIC       X(16).
              10 WS-VERSAO-PGM PIC       9(6).
              10 FILLER        PIC       X(13).
           05 WS-REG-DETALHE   REDEFINES WS-REG-ARQ.
              10 WS-CONTA-CLI  PIC       9(10).
              10 WS-NOME-CLI   PIC       X(15).
              10 WS-VALOR-CTA  PIC       9(4).
              10 WS-DATA-CTA   PIC       9(6).
           05 WS-REG-TRAILER   REDEFINES WS-REG-ARQ.
              10 WS-REG-QTD    PIC       9(6).
              10 FILLER        PIC       X(29).
       77 WS-CONT              PIC       X(3) VALUE 'NAO'.
      *
       PROCEDURE DIVISION.
      *
           OPEN I-O ENTRADA
           READ ENTRADA AT END MOVE 'SIM' TO WS-CONT.
      *
      *    IF WS-REG-INDEX EQUAL 'H'
      *       MOVE WS-REG-ARQ TO WS-REG-HEADER
      *    ELSE
      *    IF WS-REG-INDEX EQUAL 'D'
      *       MOVE WS-REG-ARQ TO WS-REG-DETALHE
      *    ELSE
      *    IF WS-REG-INDEX EQUAL 'T'
      *       MOVE WS-REG-ARQ TO WS-REG-TRAILER
      *    ELSE
      *      DISPLAY "ERRO"
      *    END-IF
      *    END-IF
      *    END-IF
      *
      *    DISPLAY WS-NOME-PGM
      *    DISPLAY WS-VERSAO-PGM
      *    DISPLAY WS-CONTA-CLI
      *    DISPLAY WS-NOME-CLI
      *    DISPLAY WS-DATA-CTA
      *    DISPLAY WS-REG-QTD
           DISPLAY WS-CONT
      *
           CLOSE ENTRADA
           STOP RUN.


SYSOUT
IGZ0035S There was an unsuccessful OPEN or CLOSE of file ENTRADA in program REDEFINE at relative location X'0414'.
         Neither FILE STATUS nor an ERROR declarative were specified. The status code was 35.
         From compile unit REDEFINE at entry point REDEFINE at compile unit offset +00000414 at entry offset +00000414
          at address 118AD414.                                                 

Re: ABEND=S000 U4038 REASON=00000000

PostPosted: Thu Sep 23, 2010 11:11 pm
by Robert Sample
A U4038 abend is typically a Language Environment abend. The 4038 means that another error occurred in the program and LE is shutting down the program. The other error is the file status 35 (and why do you not have a FILE STATUS IS clause in your SELECT -- it should be mandatory these days?) means that file ENTRADA could not be opened because there was no DD statement //ENTRADA in the execution step -- and ENTRADA was not specified as OPTIONAL in the SELECT clause.

Re: ABEND=S000 U4038 REASON=00000000

PostPosted: Thu Sep 23, 2010 11:18 pm
by GUI1504
look JCL

//GUI1504R     JOB (GUI1504),GUI1504,CLASS=A,MSGCLASS=X,NOTIFY=GUI1504
//PROCLIB      JCLLIB ORDER=IBMMFS.PROC.IBMCOB                       
//STEP1        EXEC IGYWCG                                           
//ENTRADA      DD DSN=GUI1504.REDEFINE.ENTER,DISP=SHR                 
//COBOL.SYSIN  DD DSN=GUI1504.REDEFINE.COBOL,DISP=SHR                 
//SYSPRINT     DD SYSOUT=*                                           
/*                                                                   


GUI1504.REDEFINE.ENTER
HNOME-DO-PROGRAMA000001         
D0123456789NOME-DO-CLIENTE200009
D0123456789NOME-DO-CLIENTE200009
D0123456789NOME-DO-CLIENTE200009
D0123456789NOME-DO-CLIENTE200009
D0123456789NOME-DO-CLIENTE200009
D0123456789NOME-DO-CLIENTE200009
D0123456789NOME-DO-CLIENTE200009
D0123456789NOME-DO-CLIENTE200009
D0123456789NOME-DO-CLIENTE200009
T000013                         

Re: ABEND=S000 U4038 REASON=00000000

PostPosted: Thu Sep 23, 2010 11:22 pm
by Robert Sample
You have //COBOL.SYSIN after the //ENTRADA statement. If you carefully check the expanded JCL in the job listing, you will discover that //ENTRADA is associated with the COBOL step, not the GO step -- hence the abend, because you have no //ENTRADA DD statement when the program attempts to execute. You need to move //ENTRADA after the //COBOL.SYSIN and if I were you I'd make it //GO.ENTRADA to make it clear which step the DD name applies to.

Re: ABEND=S000 U4038 REASON=00000000

PostPosted: Thu Sep 23, 2010 11:55 pm
by GUI1504
I move //ENTRADA after //COBOL.SYSIN, but the error continues

Re: ABEND=S000 U4038 REASON=00000000

PostPosted: Thu Sep 23, 2010 11:56 pm
by Robert Sample
Post the expanded JCL from the job listing -- we don't need to see anything else at this point.

Re: ABEND=S000 U4038 REASON=00000000

PostPosted: Fri Sep 24, 2010 12:04 am
by dick scherrer
Maybe //GO.ENTRADA . . .? Assuming this is a compile/link/go job. . .

Just a guess.

It will be better if we can see what is actually being used. . .

d

Re: ABEND=S000 U4038 REASON=00000000

PostPosted: Fri Sep 24, 2010 12:26 am
by Robert Sample
Dick: I'm assuming that ICYWCG is the standard IBM compile / go procedure for COBOL from IGY.SIGYPROC. That's why I want to see the expanded JCL -- to make sure the site hasn't changed the IBM default JCL (too much)!

Re: ABEND=S000 U4038 REASON=00000000

PostPosted: Fri Sep 24, 2010 1:24 am
by NicC
GUI1504 wrote:I move //ENTRADA after //COBOL.SYSIN, but the error continues


All step overrides default to the first, or last mentioned, step. Therefore, as this DD is for the GO step, you have to specify the stepname (GO, we are assuming), or, if there are already over-rides for the GO step place the DD after this/these.

Re: ABEND=S000 U4038 REASON=00000000

PostPosted: Fri Sep 24, 2010 3:01 am
by dick scherrer
Hi Robert,

That's why I want to see the expanded JCL
Yup, inquiring minds want to know. . . :)

Maybe TS will post this soon :)

d