0

I am practicing some CICS programming and I want to submit a job from CICS program by using spool commands. However, I get the 'NO SPOOL' return which the IBM documentation says:

80 NOSPOOL No subsystem present. Interface being disabled; CICS is quiescing. Interface has been stopped.

I don't know what changes I need to make to correct this. attached below is the sample of the code I made:

   IDENTIFICATION DIVISION.
   PROGRAM-ID.    GDGTEST
  *
   ENVIRONMENT DIVISION.
  *
   DATA DIVISION.
   WORKING-STORAGE SECTION.
   01  WS-MSG-TEXT           PIC X(56).
   01  WS-MSG-LENGTH         PIC S9(4) COMP VALUE 60.
   01  WS-SUBMIT-MSG         PIC X(56)
       VALUE 'GDG BACKUP STARTED'.
   01  WS-END-MSG            PIC X(56)
       VALUE 'BACK UP SUCCESSFULLY CREATED'.
   01  WS-ERROR-MSG          PIC X(56)
       VALUE 'GDG BACKUP FAILED'.
   01  WS-SPOOL-OPTIONS.
       05 WS-TOKEN           PIC X(8) VALUE LOW-VALUES.
       05 WS-NODE            PIC X(8) VALUE 'IBMUSER'.
       05 WS-USERID          PIC X(8) VALUE 'INTRDR'.
       05 WS-CLASS           PIC X    VALUE 'A'.
       05 WS-RESP            PIC X(4).
       05 WS-RESP2           PIC X(4).
   01  WS-JCL-TXT            PIC X(80).
   01  WS-JOB.
       05 FILLER             PIC X(56) VALUE
       '//GDGBCKUP JOB  CLASS=A,MSGCLASS=H,MSGLEVEL=(1,1),      '.
       05 FILLER             PIC X(56) VALUE
       '//         REGION=2048K,NOTIFY=&SYSUID                  '.
       05 FILLER             PIC X(56) VALUE
       '//STEP1    EXEC PGM=IEBGENER                            '.
       05 FILLER             PIC X(56) VALUE
       '//SYSPRINT DD   SYSOUT=*                                '.
       05 FILLER             PIC X(56) VALUE
       '//SYSUT1   DD   DSN=IBMUSER.TEST.CASACONS.MONTHREP,     '.
       05 FILLER             PIC X(56) VALUE
       '//         DISP=SHR                                     '.
       05 FILLER             PIC X(56) VALUE
       '//SYSUT2   DD   DSN=IBMUSER.TEST.MONTHREP.BACKUP(+1),   '.
       05 FILLER             PIC X(56) VALUE
       '//         DISP=(NEW,CATLG,DELETE),                     '.
       05 FILLER             PIC X(56) VALUE
       '//         UNIT=3390,SPACE=(TRK,4),                     '.
       05 FILLER             PIC X(56) VALUE
       '//         DCB=(LRECL=81,BLKSIZE=81,RECFM=FBA,DSORG=PS) '.
       05 FILLER             PIC X(56) VALUE
       '//SYSIN    DD   DUMMY                                   '.
       05 FILLER             PIC X(56) VALUE
       '//SYSOUT   DD   SYSOUT=*                                '.
       05 FILLER             PIC X(56) VALUE
       '//SYSUDUMP DD   SYSOUT=*                                '.
       05 FILLER             PIC X(56) VALUE
       '//                                                      '.
   01  WX-1                  PIC 9(5)  VALUE 0.
  *
   PROCEDURE DIVISION.
   0000-MAIN.
       MOVE WS-SUBMIT-MSG   TO WS-MSG-TEXT.
       PERFORM 0200-SEND-MSG-TEXT.
       IF EIBRESP NOT = DFHRESP(NORMAL)
          MOVE WS-ERROR-MSG TO WS-MSG-TEXT
          PERFORM 0200-SEND-MSG-TEXT
          PERFORM 9999-RETURN-CICS
       ELSE
          PERFORM 0300-SPOOL-OPEN
          ADD 1 TO ZERO GIVING WX-1 
          PERFORM 14 TIMES
             MOVE WS-JOB(WX-1:56) TO WS-JCL-TXT
             PERFORM 0400-SPOOL-WRITE
             ADD 56 TO WX-1
          END-PERFORM
          PERFORM 0500-SPOOL-CLOSE
       END-IF.
       MOVE WS-END-MSG      TO WS-MSG-TEXT.
       PERFORM 0200-SEND-MSG-TEXT.
       PERFORM 9999-RETURN-CICS.
  *
   0200-SEND-MSG-TEXT.
       EXEC CICS SEND TEXT
                 FROM(WS-MSG-TEXT)
                 LENGTH(WS-MSG-LENGTH)
                 ERASE
                 FREEKB
       END-EXEC.
  *
   0300-SPOOL-OPEN.
       EXEC CICS SPOOLOPEN OUTPUT
                 TOKEN(WS-TOKEN)
                 USERID(WS-USERID)
                 NODE(WS-NODE)
                 CLASS(WS-CLASS)
                 RESP(WS-RESP)
                 RESP2(WS-RESP2)
       END-EXEC.
  *
   0400-SPOOL-WRITE.
       EXEC CICS SPOOLWRITE
                 TOKEN (WS-TOKEN)
                 FROM  (WS-JCL-TXT)
                 RESP  (WS-RESP)
                 RESP2 (WS-RESP2)
       END-EXEC.
  *
   0500-SPOOL-CLOSE.
       EXEC CICS SPOOLCLOSE
                 TOKEN (WS-TOKEN)
                 RESP  (WS-RESP)
                 RESP2 (WS-RESP2)
       END-EXEC.
  *
   9999-RETURN-CICS.
       EXEC CICS RETURN END-EXEC.

I have a feeling the problem lies on what I specified in NODE and USER-ID options of the SPOOLOPEN OUTPUT commands. I appreciate your help. Thank you.

  • 1
    Not a CICS-expert here, but: the `NODE` value is most probably wrong. But only your mainframe guys can tell you the correct values for your organisation. The message might also indicate that there is some configuration missing in your CICS setup for this feature. Again, only your CICS people can tell you whether that's the case. – piet.t Sep 14 '21 at 09:33
  • Thanks @piet.t . You're right, I have already corrected the node value + changed the spool interface from NO to YES in the DFHSIT macro (SIT table) as stated in https://www.ibm.com/docs/en/cics-ts/5.4?topic=jes-using-cics-interface. The last thing I need is for CICS to load the updated SIT table, which I don't know how. Unfortunately, since i'm just practicing on my own, I am my own CICS admin so I don't have somebody to do the cics configuration for me. – Roger Strycova Sep 14 '21 at 12:42

0 Answers0