hi,
please look at the program.
iam trying to access some details of file using the alternate key:
PROD-WHOU.
1.i get a file error :39 (before opening ) and 47(after performing the operation,with a max cc = 0.
2.this program works fine with the primary key and not the AIX.
3. how do i specify the AIX in the RUN jcl?
Code:
//XY65TST JOB 1,'TEST JCL',MSGCLASS=Y,CLASS=4,RESTART=*,
// NOTIFY=&SYSUID
//P1COMPIL EXEC PGM=IGYCRCTL,
// PARM='OFFSET,MAP,OPT,NOSSR'
//STEPLIB DD DSN=SYS1.COB2COMP,DISP=SHR
//SYSPRINT DD SYSOUT=*
//SYSLIN DD DSN=&&LOADSET,
// UNIT=SYSDA,
// DISP=(MOD,PASS),
// SPACE=(TRK,(1,1))
//SYSUT1 DD UNIT=SYSDA,SPACE=(TRK,(1,1))
//SYSUT2 DD UNIT=SYSDA,SPACE=(TRK,(1,1))
//SYSUT3 DD UNIT=SYSDA,SPACE=(TRK,(1,1))
//SYSUT4 DD UNIT=SYSDA,SPACE=(TRK,(1,1))
//SYSUT5 DD UNIT=SYSDA,SPACE=(TRK,(1,1))
//SYSUT6 DD UNIT=SYSDA,SPACE=(TRK,(1,1))
//SYSUT7 DD UNIT=SYSDA,SPACE=(TRK,(1,1))
//SYSIN DD *
IDENTIFICATION DIVISION.
PROGRAM-ID. KSDSAIX.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT KSDS-FILE ASSIGN TO DD1
ORGANIZATION IS INDEXED
ACCESS MODE IS DYNAMIC
RECORD KEY IS PROD-WHOU
* ALTERNATE KEY IS PROD-WHOU WITH DUPLICATES
FILE STATUS IS KSDS-FILE-STATUS.
DATA DIVISION.
FILE SECTION.
FD KSDS-FILE.
01 KSDS-REC.
05 PROD-NUM PIC 9(03).
05 F PIC X.
05 PROD-NAME PIC X(10).
05 F PIC X.
05 PROD-UNIT PIC X(02).
05 F PIC X(03).
05 PROD-RATE PIC 9(04)V9(02).
05 F PIC X.
05 PROD-TYPE PIC X(07).
05 F PIC XX.
05 PROD-WHOU PIC X(02).
05 F PIC X(42).
WORKING-STORAGE SECTION.
01 KSDS-FILE-STATUS PIC XX.
01 PRODWHOU PIC XX.
PROCEDURE DIVISION.
ACCEPT PRODWHOU.
OPEN I-O KSDS-FILE.
MOVE PRODWHOU TO PROD-WHOU.
DISPLAY "KSDS STATUS AFTER OPENING:", KSDS-FILE-STATUS.
START KSDS-FILE KEY = PROD-WHOU.
READ-PARA.
READ KSDS-FILE NEXT AT END GO TO STOP-PARA.
DISPLAY KSDS-REC.
DISPLAY KSDS-FILE-STATUS.
GO TO READ-PARA.
STOP-PARA.
CLOSE KSDS-FILE.
STOP RUN.
*
/P2LINK EXEC PGM=IEWL,REGION=1024K,COND=(8,LE),
/ PARM=(LIST,LET,MAP,XREF,,
/ '')
/SYSPRINT DD SYSOUT=*
/SYSLIB DD DSN=SYS1.COB2LIB,
/ DISP=SHR
/SYSLIN DD DSN=&&LOADSET,
/ DISP=(OLD,DELETE)
/****************************************************
/* SPECIFY THE PDS IN WHICH THE PROGRAM LOAD MODULE *
/* IS TO BE CREATED *
/* FOR EG. <SYSUID.QUALIFIER1.QUALIFIER2(MEMBER)> *
/****************************************************
/SYSLMOD DD DSN=XY65.XY.LOAD(KSDSAIX),
// DISP=SHR
//SYSUT1 DD UNIT=SYSDA,
// SPACE=(TRK,(1,1)),
// DISP=NEW
//****************************************************
//* RUN JCL
//****************************************************
//STEP1 EXEC PGM=KSDSAIX
//STEPLIB DD DSN=XY65.XY.LOAD,DISP=SHR
//*DD1 DD DSN=XY65.KSDS.CLUSTER,DISP=SHR
//DD1 DD DSN=XY65.KSDS.CLUSTER.AIX,DISP=SHR
//SYSOUT DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
//SYSUDUMP DD SYSOUT=*
//SYSABEND DD SYSOUT=*
//SYSIN DD *
LI
/*
Joined: 29 Jun 2006 Posts: 1436 Location: Bangalore,India
Gayathri,
File status 39 -
Quote:
The OPEN statement was unsuccessful
because a conflict was detected between
the fixed file attributes and the
attributes specified for that file in the
program. These attributes include the
organization of the file (sequential,
relative, or indexed), the prime record
key, the alternate record keys, the code
set, the maximum record size, the record
type (fixed or variable), and the blocking
factor.
File status 47 -
Quote:
The execution of a READ statement was
attempted on a file not open in the input
or I-O mode.
i have gone through these,but iam still not able to fix the problem.
the same program works fine without alternate key.
and i forgot to include one more thing about the SYSOUT:
the read was an infinite loop.and hence
47 and LI(alternate key given as the sysin)
//SYSIN DD *
LI
/*
would there be any problem associated with the creation of AIX/
I might be wrong...
but to process a cluster thru an alternate index You need to define a path
which is the link between the AIX and the original cluster...
to exercise just modify Your program to read all the records ( or a significant number ) sequentially..
if all the steps were done in the right way the same program will process
both the base cluster and the PATH which as the name suggests is
the logical connection of the AIX to the base cluster
to exercise just modify Your program to read all the records ( or a significant number ) sequentially..
--will you pls make me clear , whatyour asking me to do.if it was to read the whole records,i tried to do it.i did it DYNAMICALLY.do you mean to say there was some mistake in READING the file. ya.i had the read in an infinite loop.but,this very well worked with the primary key,for the same file. i have tried it out yeasterday.so there is something wrong with handling the alternate key.
if all the steps were done in the right way the same program will process
both the base cluster and the PATH which as the name suggests is
the logical connection of the AIX to the base cluster
--i have tried mentioning the corresponding path also.still it dint work.though max cc =0. would there be any problem with the creation of the aix and the path?
Joined: 11 Jun 2007 Posts: 80 Location: Columbus, Ohio
The loop ... Is most likely caused by a failure to check the file status after your read statement. After the open statement you should check the file status.
Code:
IF KSDS-FILE-STATUS = '00' OR '97'
CONTINUE
ELSE
DISPLAY pertinent info
PERFORM STOP-PARA
END-IF.
A '97' is the result of a verification performed on the KSDS dataset prior to the open and is ok.
You are only checking for an "AT END" condition on your read statement. If you check your file status after your read, you have better control over your program, ie
Code:
EVALUATE KSDS-FILE-STATUS
WHEN '00'
CONTINUE
WHEN '10' (end of file)
PERFORM normal end of file process
PERFORM STOP-PARA
WHEN '23' (record not found -- also indicates file not
found, but you would not get to this point without
a successful open)
PERFORM record not found process (which may or may not include ending the program)
WHEN OTHER
DISPLAY pertinent info
PERFORM STOP-PARA
END-EVALUATE.