IBM Mainframe Forum Index
 
Log In
 
IBM Mainframe Forum Index Mainframe: Search IBM Mainframe Forum: FAQ Register
 

job not submitted


IBM Mainframe Forums -> CICS
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
sivatechdrive

Active User


Joined: 17 Oct 2004
Posts: 191
Location: hyderabad

PostPosted: Thu Sep 11, 2008 7:04 pm
Reply with quote

i wrote the program to submit the jcl through cics, but the job is not getting submitted, the cics program is executed with error

please find the code below

Code:
000100*
000200 IDENTIFICATION DIVISION.
000300************************
000400
000500 PROGRAM-ID.    EBVSP948.
000600 AUTHOR.        IT STRATEGY.
000700
000800     EJECT
000900
001000
001100 ENVIRONMENT DIVISION.
001200*********************
001300     EJECT
001400
001500
001600 DATA DIVISION.
001700**************
001800
001900 WORKING-STORAGE SECTION.
002000*=======================
002100
002200 01  WORKING-STORAGE-START  PIC X(24)   VALUE
002300*    ---------------------
002400                            'OMSPOOL  W/S STARTS HERE'.
002500
002600*    --------------------
002700
002800 01  EIBAREA-AT-END.
002900*    --------------
003000     COPY EIBAREA.
003100
003200* CICS - CICS PARAMETERS
003300 01  CICS-RECORD.
003400*    -----------
003500     COPY CICS.
003600
003700* RUTRCOM - ROUTING COMMAND LITERALS
003800 01  RUTRCOM-RECORD.
003900*    ---------------
004000     COPY RUTRCOM.
004100
004200*    -------------------
004300 01 GEN-REPORT.
004400     05 FILLER PIC X(80) VALUE
004500     '//TFEDCICS JOB MSGCLASS=A,'.
004600     05 FILLER PIC X(80) VALUE
004700     '//         CLASS=L,TIME=1440,NOTIFY=&SYSUID'.
004800     05 FILLER PIC X(80) VALUE
004900     '//STEPA    EXEC PGM=IEFBR14'.
005000     05 FILLER PIC X(80) VALUE
005100     '//FILEA    DD DSN=TFED.DFSS.OUTPUT.BSQL2,'.
005200     05 FILLER PIC X(80) VALUE
005300     '//         DISP=(MOD,DELETE,DELETE),SPACE=(CYL,(2,1),RLSE)'.
005400     05 FILLER PIC X(80) VALUE
005500     '//SYSPRINT DD SYSOUT=*'.
005600     05 FILLER PIC X(80) VALUE
005700     '/*EOF'.
005800 01 FILLER REDEFINES GEN-REPORT.
005900     05 CARD OCCURS 7 TIMES INDEXED BY CARD-INDEX PIC X(80).
006000 01 CARD-EDIT PIC X(72) VALUE SPACES.
006100 01 S-TOKEN   PIC X(08) VALUE SPACES.
006200*01 CARD-INDEX PIC 9(01) VALUE ZEROS.
006300
006400 PROCEDURE DIVISION.
006500*******************
006600
006700 OMSPOOL-CONTROL SECTION.
006800*========================
006900
007000*       ********************************************************
007100*       *** THIS SECTION CONTROLS ENTRY/EXIT FROM THE        ***
007200*       *** PROGRAM                                          ***
007300*       ***                                                  ***
007400*       ********************************************************
007500
007600*    MOVE 'OMSPOOL-CONTROL' TO LAST-SECTION-STARTED
007700
007800     PERFORM A-INITIALISATION
007900     GOBACK.
008000* ENTRY POINTS
008100*    PERFORM XB-PASS-CONTROL
008200     .
008300 OMVSP001-EXIT.
008400*-------------
008500
008600 A-INITIALISATION SECTION.
008700*========================
008800
008900*       ********************************************************
009000*       *** THIS SECTION INITIALISES THE APPLIC ROUTING      ***
009100*       *** PARMS AND TSQ TERMINAL ID                        ***
009200*       ***                                                  ***
009300*       ********************************************************
009400
009500*    MOVE 'A-INITIALISATION'       TO LAST-SECTION-STARTED
009600     EXEC CICS SPOOLOPEN OUTPUT
009700     CLASS('L')
009800     NODE('LOCAL')
009900     USERID('INTRDR')
010000     TOKEN(S-TOKEN)
010100     NOCC
010200     PRINT
010300     NOHANDLE
010400     END-EXEC.
010500
010600     IF  CICS-RESPONSE = DFHRESP (NORMAL)
010700         CONTINUE
010800     ELSE
010900         DISPLAY 'ERROR IN SPOOL GEN'
011000     END-IF
011100     PERFORM VARYING CARD-INDEX FROM 1 BY 1 UNTIL CARD-INDEX > 7
011200      EXEC CICS SPOOLWRITE
011300      TOKEN(S-TOKEN)
011400      FROM(CARD(CARD-INDEX))
011500      FLENGTH(80)
011600      NOHANDLE
011700      END-EXEC
011800      DISPLAY 'CARD(CARD-INDEX)' CARD(CARD-INDEX)
011900     END-PERFORM.
012000     IF  CICS-RESPONSE = DFHRESP (NORMAL)
012100         CONTINUE
012200     ELSE
012300         DISPLAY 'ERROR IN SPOOL WRITE'
012400     END-IF
012500     EXEC CICS SPOOLCLOSE
012600     TOKEN(S-TOKEN)
012700     NOHANDLE
012800     END-EXEC.
012900     IF  CICS-RESPONSE = DFHRESP (NORMAL)
013000         CONTINUE
013100     ELSE
013200         DISPLAY 'ERROR IN SPOOLCLOSE'
013300     END-IF
013400
013500     .
013600 A-EXIT.
013700*------
013800     EXIT.
013900     EJECT
014000
014100

Back to top
View user's profile Send private message
Robert Sample

Global Moderator


Joined: 06 Jun 2008
Posts: 8696
Location: Dubuque, Iowa, USA

PostPosted: Thu Sep 11, 2008 7:35 pm
Reply with quote

This is not the way to submit a job through CICS. SPOOLOPEN is for JES output, not JES input. The discussion in the CICS manual about carriage control was a clue to this, by the way.

The proper way to submit a job through CICS is to define a TDQ that points to a DD statement that is defined DD SYSOUT=(A,INTRDR) and write your JCL to the TDQ. Use a trigger level of 1 for the TDQ definition.
Back to top
View user's profile Send private message
CICS Guy

Senior Member


Joined: 18 Jul 2007
Posts: 2146
Location: At my coffee table

PostPosted: Thu Sep 11, 2008 10:16 pm
Reply with quote

Robert Sample wrote:
This is not the way to submit a job through CICS. SPOOLOPEN is for JES output, not JES input.
I disagree, SPOOL is quite capable of writing to INTRDR....
One such destination is the JES internal reader, which normally has the reserved name INTRDR.
Back to top
View user's profile Send private message
Robert Sample

Global Moderator


Joined: 06 Jun 2008
Posts: 8696
Location: Dubuque, Iowa, USA

PostPosted: Thu Sep 11, 2008 10:36 pm
Reply with quote

I stand corrected ... learning a lot today!
Back to top
View user's profile Send private message
Earl Haigh

Active User


Joined: 25 Jul 2006
Posts: 475

PostPosted: Fri Sep 12, 2008 11:38 pm
Reply with quote

CICS Guy is correct, SPOOL is capable of submitting job.

the cics program is executed with error


Sample code looks ok, so what is the error condition you are getting ?

Discuss with CICS Systems programmer to ensure class and node is
correct for using INTRDR
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> CICS

 


Similar Topics
Topic Forum Replies
No new posts JCL to get submitted once dataset has... JCL & VSAM 17
This topic is locked: you cannot edit posts or make replies. Get a job submitted itself every time... JCL & VSAM 3
No new posts RFE for SuperC submitted TSO/ISPF 0
No new posts RFE for ISREMSPY submitted TSO/ISPF 2
No new posts Submitted by one TSO user on behalf o... JCL & VSAM 4
Search our Forums:

Back to Top