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

Query regarding reading an ESDS/KSDS AIX Cluster.


IBM Mainframe Forums -> COBOL Programming
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
yuvrajdutta

New User


Joined: 13 Jul 2009
Posts: 40
Location: India

PostPosted: Tue Apr 12, 2011 10:59 am
Reply with quote

Hello,

I understand that the below requirement is purely for learning purposes but I am hell-bent on resolving this.. so need help on this.

From what I understood from gsf-soft.com/Documents/VSAM-AIX.shtml

Quote:

00 Flag Byte Contains X'00' if the base cluster is an ESDS, X'01' if it is a KSDS
01 Length of Pointer If the base cluster is an ESDS, this field contains X'04'. If the base cluster is a KSDS, this field contains the 8-bit length of the primary key
02 Count of number of pointers Always X'0001' if the AIX is DEFINE'd with the UNIQUEKEY attribute. If the AIX is DEFINE'd with the NONUNIQUEKEY attribute and duplicate keys are present, the count may have a value greater than 1, up to 32767
04 Length of alternate key Key length of the alternate index
05 Alternate key Alternate index key
** Pointer(s) to base record(s) 4-byte RBA (ESDS) or primary key (KSDS); if the AIX is DEFINE'd with the NONUNIQUEKEY attribute, multiple pointers may be present, as specified in the count field at offset 02 in the AIX record.


I understand that reading an AIX CLuster isn't commonplace, rather a PATH is the only portion ever used w.r.t. an AIX but I want to read an AIX CLuster none-the-less.

I am currently reading a KSDS/ESDS AIX CLuster with the following FD:

Code:

FD INPUT-FILE.                       
01 INPUT-REC.                       
    88 END-OF-FILE VALUE HIGH-VALUES.
    05 CONTROL-INFO.                       
       10 CONTROL-INFO-FLAG PIC X.         
       10 CONTROL-INFO-PTRL PIC X.         
       10 CONTROL-INFO-PTRC PIC S9(4) COMP.
       10 CONTROL-INFO-KEYL PIC X.         
    05 MIDDLE-NAME PIC X(20).             
    05 STRING-IN OCCURS 4 TIMES.           
        10 STRING-IN-DATA PIC X(6).       


My KSDS AIX key is the MIDDLE-NAME field while the Base CLuster KEY is of X(6) and the maximum number of repeat occurrences of the AIX NONUNIQUEKEY is 4.

In case of an ESDS the AIX CLUSTER FD is:

Code:

FD INPUT-FILE.                       
01 INPUT-REC.                       
    88 END-OF-FILE VALUE HIGH-VALUES.
    05 CONTROL-INFO.                       
       10 CONTROL-INFO-FLAG PIC X.         
       10 CONTROL-INFO-PTRL PIC X.         
       10 CONTROL-INFO-PTRC PIC S9(4) COMP.
       10 CONTROL-INFO-KEYL PIC X.         
    05 MIDDLE-NAME PIC X(20).             
    05 STRING-IN OCCURS 4 TIMES.           
       10 STRING-IN-DATA.                 
          15 STRING-IN-DATA-1 PIC X.       
          15 STRING-IN-DATA-2 PIC X.       
          15 STRING-IN-DATA-3 PIC X.       
          15 STRING-IN-DATA-4 PIC X.       


In case of an ESDS AIX the actual PRIMARY-KEY DATA is replaced with the relevant Base cluster PRIMARY-KEY RBA.

But herein lies the problem.. I am unable to comprehend as to how to deal with the HEX Values in the CONTROL-INFORMATION portion of the AIX CLUSTER.

For example in case of my KSDS AIX CLuster the field CONTROL-INFO-KEYL when read is giving me a VALUE of x'14' which is correct as the AIX Key length is indeed Decimal 20.. but when I am simply trying to display CONTROL-INFO-KEYL I am getting nothing(to be precise x'14' is a non-displayable character and I can see this x'14' only with HEX ON).

I want the value 20 to be displayed for this field.. and similarly for the other ones too.

I have tried to employ www.ibmmainframes.com/viewtopic.php?t=18366&highlight=displaying+hex+value and www.ibmmainframes.com/post-71091.html and www.mail-archive.com/ibm-main@bama.ua.edu/msg63757.html and www.mail-archive.com/ibm-main@bama.ua.edu/msg63674.html but to no avail.
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Tue Apr 12, 2011 11:52 am
Reply with quote

After all that explanation, you only want to be able to display the fields? I suppose better to have more information than less.

Code:

01  DISPLAY-CONTROL-INFO VALUE LOW-VALUES.
      05  DISPLAY-CONTROL-INFO-FLAG COMP PIC S9(4).
      05  FILLER REDEFINES DISPLAY-INFO-FLAG
            10  FILLER PIC X.
            10  DIPLAY-CONTROL-INFO-FLAG-BYTE PIC X.         
...


The field which is orginally COMP will show "20" if you display it individually rather than display the group item. For the one-byte fields, define something like the above to include all of them, move the one byte to the right-hand byte of the redefined comp field (ie the obvious one) and then display the 05-level.
Back to top
View user's profile Send private message
yuvrajdutta

New User


Joined: 13 Jul 2009
Posts: 40
Location: India

PostPosted: Tue Apr 12, 2011 7:24 pm
Reply with quote

Perfect Bill!!!!

It worked like a charm.

Further I sent the ESDS AIX Cluster RBA field into a S9(8) COMP field and it's displaying fine and I have verified the RBA displayed with a DITTO output and its absolutely correct.

Just for reference.. If someone else needs the code to READ an ESDS AIX cluster let me put the code in here.

Code:

000100*READS ESDS AIX CLUSTER AND ANALYZES IT                           00010092
000200 IDENTIFICATION DIVISION.                                         00020045
000300 PROGRAM-ID. CBLKSDS7.                                            00030074
000400 ENVIRONMENT DIVISION.                                            00040045
000500 INPUT-OUTPUT SECTION.                                            00050045
000600 FILE-CONTROL.                                                    00060045
000700     SELECT INPUT-FILE ASSIGN TO READER                           00070047
000800     ORGANIZATION IS INDEXED                                      00080053
000900     ACCESS MODE IS SEQUENTIAL                                    00090099
001000     RECORD KEY IS MIDDLE-NAME                                    00100074
001100     FILE STATUS IS FILE-STATUS.                                  00110071
001200 DATA DIVISION.                                                   00120045
001300 FILE SECTION.                                                    00130045
001400 FD INPUT-FILE.                                                   00140045
001500 01 INPUT-REC.                                                    00150045
001600     88 END-OF-FILE VALUE HIGH-VALUES.                            00160074
001700*00  FLAG BYTE  CONTAINS X'00' IF THE BASE CLUSTER IS AN ESDS,    00170091
001800*                        X'01' IF IT IS A KSDS                    00180091
001900*                                                                 00190091
002000*01  LENGTH OF POINTER  IF THE BASE CLUSTER IS AN ESDS, THIS      00200091
002100*    FIELD CONTAINS X'04'. IF THE BASE CLUSTER IS A KSDS,         00210091
002200*    THIS FIELD CONTAINS THE 8-BIT LENGTH OF THE PRIMARY KEY      00220091
002300*                                                                 00230091
002400*02  COUNT OF NUMBER OF POINTERS  ALWAYS X'0001' IF THE AIX IS    00240091
002500*    DEFINED WITH THE UNIQUEKEY ATTRIBUTE. IF THE AIX IS DEFINED  00250091
002600*    WITH THE NONUNIQUEKEY ATTRIBUTE AND DUPLICATE KEYS ARE       00260091
002700*    PRESENT, THE COUNT MAY HAVE A VALUE GREATER THAN 1, UP TO    00270091
002800*    32767                                                        00280091
002900*                                                                 00290091
003000*04  LENGTH OF ALTERNATE KEY  KEY LENGTH OF THE ALTERNATE INDEX   00300091
003100*                                                                 00310091
003200*05  ALTERNATE KEY  ALTERNATE INDEX KEY                           00320091
003300*                                                                 00330091
003400***  POINTER(S) TO BASE                                           00340091
003500*    RECORD(S)  4-BYTE RBA (ESDS) OR PRIMARY KEY (KSDS);          00350091
003600*    IF THE AIX IS DEFINE'D WITH THE NONUNIQUEKEY *ATTRIBUTE,     00360091
003700*    MULTIPLE POINTERS MAY BE PRESENT, AS SPECIFIED IN THE *COUNT 00370091
003800*    FIELD AT OFFSET 02 IN THE AIX RECORD.                        00380091
003900     05 CONTROL-INFO.                                             00390085
004000        10 CONTROL-INFO-FLAG PIC X.                               00400087
004100        10 CONTROL-INFO-PTRL PIC X.                               00410087
004200        10 CONTROL-INFO-PTRC PIC S9(4) COMP.                      00420087
004300        10 CONTROL-INFO-KEYL PIC X.                               00430087
004400     05 MIDDLE-NAME PIC X(20).                                    00440074
004500     05 STRING-IN OCCURS 4 TIMES.                                 00450090
004600        10 STRING-IN-DATA PIC S9(8) COMP.                         00460099
004700 WORKING-STORAGE SECTION.                                         00470099
004800 01 FILE-STATUS PIC X(2).                                         00480099
004900     88  RECORDFOUND VALUE '00'.                                  00490099
005000 01 COUNTER   PIC 9(2).                                           00500099
005100 01 DISPLAY-CONTROL-INFO.                                         00510099
005200    05 DISPLAY-CONTROL-INFO-FLAG COMP PIC S9(4).                  00520099
005300    05 FILLER REDEFINES DISPLAY-CONTROL-INFO-FLAG.                00530099
005400       10  FILLER PIC X.                                          00540099
005500       10  DIPLAY-CONTROL-INFO-FLAG-BYTE PIC X.                   00550099
005600 01 DISPLAY-RBA COMP PIC S9(8).                                   00560099
005700 PROCEDURE DIVISION.                                              00570086
005800 DECLARATIVES.                                                    00580071
005900 USE-PROCEDURE SECTION.                                           00590071
006000     USE AFTER EXCEPTION PROCEDURE ON INPUT-FILE.                 00600071
006100 COPY-PROCEDURE.                                                  00610071
006200     COPY FILESTAT.                                               00620071
006300 END DECLARATIVES.                                                00630071
006400 MAINLINE SECTION.                                                00640071
006500 100-MAIN-PARA.                                                   00650071
006600     OPEN INPUT INPUT-FILE                                        00660076
006700     READ INPUT-FILE NEXT RECORD                                  00670053
006800         AT END SET END-OF-FILE TO TRUE                           00680054
006900     END-READ                                                     00690076
007000     PERFORM UNTIL END-OF-FILE                                    00700045
007100         MOVE CONTROL-INFO-FLAG TO DIPLAY-CONTROL-INFO-FLAG-BYTE  00710099
007200         IF DISPLAY-CONTROL-INFO-FLAG EQUAL TO ZERO THEN          00720099
007300             DISPLAY 'FILE TYPE IS ESDS'                          00730099
007400         END-IF                                                   00740099
007500         MOVE CONTROL-INFO-PTRL TO DIPLAY-CONTROL-INFO-FLAG-BYTE  00750099
007600         DISPLAY 'LENGTH OF RBA: ' DISPLAY-CONTROL-INFO-FLAG      00760099
007700         DISPLAY 'NUMBER OF POINTERS: ' CONTROL-INFO-PTRC         00770088
007800         MOVE CONTROL-INFO-KEYL TO DIPLAY-CONTROL-INFO-FLAG-BYTE  00780099
007900         DISPLAY 'KEY-LENGTH OF AIX: ' DISPLAY-CONTROL-INFO-FLAG  00790099
008000         DISPLAY 'ALTERNATE KEY FIELD: ' MIDDLE-NAME              00800088
008100         PERFORM VARYING COUNTER FROM 1 BY 1 UNTIL COUNTER >      00810077
008200         CONTROL-INFO-PTRC                                        00820088
008300             DISPLAY 'RBA: ' STRING-IN-DATA(COUNTER)              00830099
008400         END-PERFORM                                              00840077
008500         DISPLAY ' '                                              00850064
008600         READ INPUT-FILE NEXT RECORD                              00860054
008700             AT END SET END-OF-FILE TO TRUE                       00870054
008800         END-READ                                                 00880054
008900     END-PERFORM                                                  00890076
009000     CLOSE INPUT-FILE                                             00900076
009100     STOP RUN.                                                    00910054


Thanks again.. Bill icon_smile.gif
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Tue Apr 12, 2011 9:47 pm
Reply with quote

And now, since you've put it here for all to see, you have to do everything to it to "bullteproof" it, as you would with any program you write.

You even left off the "VALUE LOW-VALUES" I put on my suggestion. How is your FILLER getting initialised?

I always find it horrible to see something called COUNTER (asking to be made a RESERVED WORD in the future). Also, PIC 99 for any math makes me shudder.

Put those things right please.

I like to highlight what is being displayed. Personal thing, but like this:

Code:

DISPLAY "THIS IS THE VALUE>" W-VALUE-TO-DISPLAY "<"


Then you never have to wonder whether your whole field is displayed or not. I assure you, one time this will get you otherwise. Spend six hours of your life looking for the solution when it happens, or always code to avoid it.

A nice thing to display is the program name and date/time compiled. See if you can get to that.
Back to top
View user's profile Send private message
yuvrajdutta

New User


Joined: 13 Jul 2009
Posts: 40
Location: India

PostPosted: Wed Apr 13, 2011 12:13 pm
Reply with quote

Bill,

FILLER initialization is something I missed out icon_sad.gif

COUNTER and its PIC are a BAD HABIT icon_razz.gif.. COMP/COMP-3 is mandatory..

Highlighting the bounds of displayed data is definitely adoptable.
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 -> COBOL Programming

 


Similar Topics
Topic Forum Replies
No new posts RC query -Time column CA Products 3
No new posts Merge two VSAM KSDS files into third ... JCL & VSAM 6
No new posts Random read in ESDS file by using RBA JCL & VSAM 6
No new posts Dynamically pass table name to a sele... DB2 2
No new posts Reading dataset in Python - New Line ... All Other Mainframe Topics 22
Search our Forums:

Back to Top