Warm tip: This article is reproduced from serverfault.com, please click

Writing to Sequential Dataset in COBOL makes it an inaccesible binary

发布于 2020-12-01 02:50:26

The following code should take a sequential dataset as input through DDINPUT describing bank accounts and output a sequential dataset through DDOUTPUT with the names of those bank account owners with a balance greater than $8,500,000. But, as we are in Stack Overflow, it doesn't.

       IDENTIFICATION DIVISION.
       PROGRAM-ID.    TOPACCTS.
      *
       ENVIRONMENT DIVISION.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
           SELECT INFILE ASSIGN TO DDINPUT
           ORGANIZATION IS SEQUENTIAL.
           SELECT OUTFILE ASSIGN TO DDOUTPUT
           ORGANIZATION IS SEQUENTIAL.
      *
       DATA DIVISION.
       FILE SECTION.
       FD  INFILE RECORD CONTAINS 80 CHARACTERS RECORDING MODE F.
       01  ACCT-FIELDS.
           05  LAST-NAME        PIC A(11).
           05  FIRST-NAME       PIC A(22).
           05  ACCT-NO-A        PIC 9(8).
           05  FILLER           PIC X(3) VALUE SPACES.
           05  ACCT-NO-B        PIC 9(8).
           05  FILLER           PIC X(9) VALUE SPACES.
           05  ACCT-BALANCE     PIC $,$$$,$$9.99.
      *
       FD  OUTFILE RECORD CONTAINS 80 CHARACTERS RECORDING MODE F.
       01  PRINT-ACC.
           05  LAST-NAME-O      PIC A(11) VALUE SPACES.
           05  FILLER           PIC X(2) VALUE SPACES.
           05  FIRST-NAME-O     PIC A(22) VALUE SPACES.
      *
       WORKING-STORAGE SECTION.
       01  WS-EOF   PIC A VALUE SPACE.
       01  RES      PIC 9(7)V99.
       01  WS-RECORD.
           05  WS-LAST-NAME        PIC A(11).
           05  WS-FIRST-NAME       PIC A(22).
           05  WS-ACCT-NO-A        PIC 9(8).
           05  WS-ACCT-NO-B        PIC 9(8).
           05  WS-ACCT-BALANCE     PIC $,$$$,$$9.99.

      *
       PROCEDURE DIVISION.
      *
           OPEN INPUT  INFILE.
           OPEN OUTPUT OUTFILE.
           PERFORM UNTIL WS-EOF = 'Y'
              READ INFILE INTO WS-RECORD
              AT END MOVE 'Y' TO WS-EOF
              NOT AT END PERFORM WRITE-RECORD
              END-READ
           END-PERFORM.
           CLOSE INFILE.
           CLOSE OUTFILE.
           STOP RUN.
      *
       WRITE-RECORD.
           COMPUTE RES = FUNCTION NUMVAL-C (ACCT-BALANCE).
           IF RES > 8500000
              DISPLAY "Adding " WS-FIRST-NAME " " WS-LAST-NAME "..."
              MOVE SPACES TO PRINT-ACC 
              MOVE WS-LAST-NAME    TO LAST-NAME-O
              MOVE WS-FIRST-NAME   TO FIRST-NAME-O
              DISPLAY "Writing " FIRST-NAME-O " " LAST-NAME-O "..."
              WRITE PRINT-ACC
              END-IF.

The code gets right the name of the owners with balances greater than $8,500,000 but doesn't write properly as, when the output dataset is accessed, VS Code throws the following error:

cannot open file:zowe_path. Detail: File seems to be binary and cannot be opened as text.

I'm quite new at COBOL and I have no clue what I'm doing wrong when writing to output. Maybe the JCL is causing the problem:

//TOPACJCL  JOB 1,NOTIFY=&SYSUID
//***************************************************/
//COBRUN  EXEC IGYWCL
//COBOL.SYSIN  DD DSN=&SYSUID..SOURCE(TOPACCTS),DISP=SHR
//LKED.SYSLMOD DD DSN=&SYSUID..LOAD(TOPACCTS),DISP=SHR
//***************************************************/
// IF RC = 0 THEN
//***************************************************/
//RUN     EXEC PGM=TOPACCTS
//STEPLIB   DD DSN=&SYSUID..LOAD,DISP=SHR
//DDINPUT   DD DSN=MY.DATA(INPUTD),DISP=SHR
//DDOUTPUT  DD DSN=MY.DATA(OUTPUTD),DISP=SHR
//SYSOUT    DD SYSOUT=*,OUTLIM=15000
//CEEDUMP   DD DUMMY
//SYSUDUMP  DD DUMMY
//***************************************************/
// ELSE
// ENDIF

Hopefully you can help me as I've been trying to fix this for the past hours. Thanks in advance!

EDIT #1: Added "MOVE SPACES TO PRINT-ACC", still doesn't work.

Questioner
Sergio Rivera
Viewed
0
Bruce Martin 2020-12-01 16:05:25

Try moving spaces to the output-record before updating it

 WRITE-RECORD.
           COMPUTE RES = FUNCTION NUMVAL-C (ACCT-BALANCE).
           IF RES > 8500000
              DISPLAY "Adding " WS-FIRST-NAME " " WS-LAST-NAME "..."

              Move space           to PRINT-ACC

              MOVE WS-LAST-NAME    TO LAST-NAME-O
              MOVE WS-FIRST-NAME   TO FIRST-NAME-O
              DISPLAY "Writing " FIRST-NAME-O " " LAST-NAME-O "..."
              WRITE PRINT-ACC
              END-IF.

basically you are only updating LAST-NAME-O and FIRST-NAME-O the rest of the record will be hex-zero's hence being recognized as binary. You will be able to edit the file on the mainframe with ISPF edit or File-Aid etc.