View previous topic :: View next topic
|
Author |
Message |
raghu_4412 Warnings : 1 New User
Joined: 01 Mar 2004 Posts: 4 Location: Bangalore
|
|
|
|
Hello sir,
I am sending cobol program,complieJCL,runJCL & KSDS program.
In this
1) compile jcl the execution is successful i.e maxcc=0.
2)creation of KSDS cluster execution is successful i.e.maxcc=0.
3)RUNJCL EXECUTION IS SUCCESSFUL i.e. maxcc=0 but if i go & check in the spool message is file not opened with error no.37.
so that our i/p is not written to the KSDS file.
please give me solution how to remove the error & my data should written to KSDS file.
I) COBOL INDEXED FILE PROGRAM:
ID DIVISION.
PROGRAM-ID. FIWRITE.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT FILE1 ASSIGN TO D1
ORGANIZATION IS INDEXED
ACCESS MODE IS SEQUENTIAL
RECORD KEY IS ID1
FILE STATUS IS FS.
DATA DIVISION.
FILE SECTION.
FD FILE1.
01 IN-REC.
02 ID1 PIC 999.
02 NAME1 PIC X(10).
02 FILLER PIC X(67) VALUE SPACES.
WORKING-STORAGE SECTION.
77 FS PIC XX.
77 PER PIC X VALUE 'Y'.
PROCEDURE DIVISION.
MAIN-PARA.
OPEN OUTPUT FILE1.
IF FS = 00
DISPLAY " FILE OPENED" FS
ELSE
DISPLAY " FILE NOT OPENED" FS.
PERFORM ACP-PARA UNTIL PER = 'N'.
CLOSE FILE1.
STOP RUN.
ACP-PARA.
ACCEPT ID1.
ACCEPT NAME1.
WRITE IN-REC.
ACCEPT PER.
II) COMPLILE JCL:
//ITES20S JOB CLASS=A,MSGCLASS=H,REGION=80M,MSGLEVEL= (1,1),
// NOTIFY=&SYSUID,PRTY=15
//COMPLINK EXEC PROC=IGYWCL
//COBOL.SYSIN DD DSN=ITES20.TCR.PGMKSDS(FINDWR),DISP=SHR
//LKED.SYSLMOD DD DSN=ITES20.RAGHU.LOAD(FINDWR2),DISP=SHR
//
III) KSDS PROGRAM:
//ITES20B JOB NOTIFY=&SYSUID,PRTY=15
//STEP1 EXEC PGM=IDCAMS
//SYSPRINT DD SYSOUT=*
//SYSIN DD *
DEFINE CLUSTER -
( -
NAME(ITES20.TCR.KSDS6) -
VOLUMES(STD003) -
CYLINDERS(5,2) -
CONTROLINTERVALSIZE(4096) -
FREESPACE(10,20) -
KEYS(3,1) -
RECORDSIZE(80,80) -
) -
DATA(NAME(ITES20.TCR.DATA6)) -
INDEX(NAME(ITES20.TCR.INDEX6))
/*
//
IV) RUN-JCL PROGRAM:
//ITES20N JOB MSGCLASS=H,CLASS=A,MSGLEVEL=(1,1),NOTIFY=ITES20,
// PRTY=15
//STEP1 EXEC PGM=FINDWR2
//STEPLIB DD DSN=ITES20.RAGHU.LOAD,DISP=SHR
//SYSPRINT DD SYSOUT=*
//D1 DD DSN=ITES20.TCR.KSDS6,DISP=SHR
//SYSPRINT DD SYSOUT=*
//SYSIN DD *
100
RAGHU
Y
200
SACHIN
Y
300
SANJU
N
/*
//
[/url][/list][/list][/code][/quote] |
|
Back to top |
|
|
mdtendulkar
Active User
Joined: 29 Jul 2003 Posts: 237 Location: USA
|
|
|
|
Hello raghu_4412,
I think you will need to define your VSAM file once again with KEYS parameter as KEYS(3,0)
Hope this helps,
Regards
Mayuresh Tendulkar |
|
Back to top |
|
|
raghu_4412 Warnings : 1 New User
Joined: 01 Mar 2004 Posts: 4 Location: Bangalore
|
|
|
|
sir,
I tried by changing key(3,0) still it is giving the same error |
|
Back to top |
|
|
mmwife
Super Moderator
Joined: 30 May 2003 Posts: 1592
|
|
|
|
Hi raghu,
I'm fairly sure that you can specify an OP file as SHR. In spit of that, try changing the disp for D1 to OLD. It's a good idea to do that anyway. You don't want someone else accessing your file while you're updating it.
Also,
although using IN-REC, etc. is permissable, it can be confusing to the reader (i.e. the maintainer of the code). It's a good idea to change all input data name refs to output.
Check the file status after every I/O includeing read/writes/close.
Regards, Jack. |
|
Back to top |
|
|
bluebird
Active User
Joined: 03 Feb 2004 Posts: 127
|
|
|
|
you are passing input using sysin, it maybe a good idea to add
a configuration section to your pgm and do a single accept and then
parse results from accept into variables. |
|
Back to top |
|
|
bluebird
Active User
Joined: 03 Feb 2004 Posts: 127
|
|
|
|
and then to run your JCL
Code: |
//HH594DN JOB MSGCLASS=A,CLASS=A,MSGLEVEL=(1,1),NOTIFY=ITES20
//STEP1 EXEC PGM=yourpgm
//STEPLIB DD DSN=yourloadlib,DISP=SHR
//SYSPRINT DD SYSOUT=*
//OUTFILE DD DSN=user.TCR.KSDS6,DISP=SHR
//SYSPRINT DD SYSOUT=*
//SYSIN DD *
552name 2525696
/*
|
|
|
Back to top |
|
|
muthukumar
New User
Joined: 24 Mar 2004 Posts: 29
|
|
|
|
hi
I guess you didnt initialize your ksds file before using it in the program..this should be the probable reason for that... if this is done the code must work fine.
regards
Muthu |
|
Back to top |
|
|
bluebird
Active User
Joined: 03 Feb 2004 Posts: 127
|
|
|
|
The file is open for output so it should be ok.
I tested a load direct from a deldef step with a pgm that opened the ksds as output and it went thru ok.
If the file was open as I-O then you'll need one record in it. |
|
Back to top |
|
|
|