MVSFORUMS.com Forum Index MVSFORUMS.com
A Community of and for MVS Professionals
 
 FAQFAQ   SearchSearch   Quick Manuals   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

Read PDS directory including "last modified" data

 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Application Programming
View previous topic :: View next topic  
Author Message
bauer
Intermediate


Joined: 10 Oct 2003
Posts: 315
Topics: 49
Location: Germany

PostPosted: Thu Jun 05, 2014 7:58 am    Post subject: Read PDS directory including "last modified" data Reply with quote

Hi *,

I'm trying to read the directory of a PDS (or PDSE) dataset using PL/1 (or Cobol).

This works for membernames, the structure for a PDS directory is documented for exemple here: OSDFSMS: Using Data Sets, SC26-7410-05.

My problem is now the "last modified" date (like ISPF output). Which bytes are the relevant bytes in the PDS directory records ? How to interpret this bytes?

There are some solutions in the internet available using REXX and the LMMFIND and ZLM4DATE command. But this doesn't help.

I need to do this task in a PL/1 and/or Cobol program.

So can anybody give me some advise, about the relevant bytes and the interpretation of the bytes ?

kind regards,
bauer
Back to top
View user's profile Send private message
William Collins
Supermod


Joined: 03 Jun 2012
Posts: 437
Topics: 0

PostPosted: Thu Jun 05, 2014 8:04 am    Post subject: Reply with quote

http://publibz.boulder.ibm.com/cgi-bin/bookmgr_OS390/BOOKS/ispzdg90/C.4.4
Back to top
View user's profile Send private message
bauer
Intermediate


Joined: 10 Oct 2003
Posts: 315
Topics: 49
Location: Germany

PostPosted: Thu Jun 05, 2014 8:12 am    Post subject: Reply with quote

William Collins,

YES, this looks really pretty good and helpful.

Thank you very much for your very fast answer.

Now, let's do the coding.

Kind regards,
bauer
Back to top
View user's profile Send private message
bauer
Intermediate


Joined: 10 Oct 2003
Posts: 315
Topics: 49
Location: Germany

PostPosted: Thu Jun 05, 2014 8:23 am    Post subject: Reply with quote

Ok, I did the coding. It works, thank you again.
Back to top
View user's profile Send private message
ironponygrl
Beginner


Joined: 22 Mar 2013
Posts: 21
Topics: 7
Location: Fort Worth, TX

PostPosted: Mon Jun 09, 2014 8:12 am    Post subject: example? Reply with quote

bauer wrote:
Ok, I did the coding. It works, thank you again.



would you be inclined to post your COBOL solution? perhaps just the pertinent snippets.
Back to top
View user's profile Send private message
bauer
Intermediate


Joined: 10 Oct 2003
Posts: 315
Topics: 49
Location: Germany

PostPosted: Tue Jun 10, 2014 3:03 am    Post subject: Reply with quote

ironponygrl,

well I'm, sorry. It is a PL/1 solution, not COBOL.

But here is the coding (only the main parts of it ....), may be, it's helpful for anybody.

The complete routine "ReadPDSDirectory" is a submodule with a callback option to provide each entry of the PDS Directory to the calling (main-) routine.

This is the datastructure which provides information for each entry.


Code:


DEFINE STRUCTURE
   1 tPDSEntry
    , 2 Name      UNAL    CHAR(8)    /* Name of Member */
    , 2 Modified  UNAL    CHAR(26)   /* YYYY-MM-DD-SS.MM.SS.NNNNN */
    , 2 User      UNAL    CHAR(8)    /* User       */
    ;



In the JCL of the calling main program the PDS files is defined as follows (or do a dynamic definition of the DD Name).

Code:


//RUN.X     DD DSN=MY.PDS.FILE,DISP=SHR,
//       DCB=(RECFM=F,LRECL=256,BLKSIZE=256)



The coding in the main program calls the ReadPDSDirectory module and provides the callback entry which should be called for each PDS Directory entry from the ReadPDSDirectory submodule.

Code:



CALL ReadPDSDirectory('X',MyCallBack,NULL());


MyCallBack:
   PROC(pPDSEntry,pUserData);
   DCL pPDSEntry   PTR ;
   DCL pUserData   PTR ;

   DCL PDSEntry UNAL TYPE tPDSEntry BASED(pPDSEntry);

   PUT SKIP EDIT( PDSEntry.Name
                 ,' '
                 ,PDSEntry.Modified
                 ,' '
                 ,PDSEntry.User
                )(A,A,A,A,A);
   END;




This is the ReadPDSDirectory routine (hopefully I missed nothing during cut / paste ....)

Code:

ReadPDSDirectory:
   PROC(DDName,CallBack,UserData);

   DCL DDName CHAR(8);                /* DD Name of PDS */

   DCL CallBack VARIABLE ENTRY (PTR,PTR);

   DCL UserData PTR ;

   DCL EOF  BIT(1) AUTO INIT('0');    /* End Of File    */
   DCL EOB  BIT(1) AUTO INIT('0');    /* End of Block   */

   DCL PDS FILE RECORD SEQUENTIAL INPUT ENV(U) ;

   DCL 1 DirBlock    UNAL ,
         2 Count     BIN FIXED(15)
        ,2 Entries   CHAR(254)
        ;

   DCL   pEntry     UNAL POINTER ;
   DCL 1 Entry      UNAL BASED (pEntry),
          2 NAME      CHAR(8)
         ,2 TTR       CHAR(3)
         ,2 INDIC,
            3 ALIAS   BIT(1)
           ,3 TTRS    BIT(2)
           ,3 USERCT  BIT(5)

         ,2 USERDATA  CHAR(62)
         ;

   DCL 1 ISPFStatisticsEntry UNAL BASED(ADDR(Entry.UserData))
        ,2 Level1          CHAR(1)
        ,2 Level2          CHAR(1)
        ,2 Flags           CHAR(1)
        ,2 ModifSeconds    CHAR(1)
        ,2 CreaCentury     CHAR(1)
        ,2 CreaDate        CHAR(3)
        ,2 ModifCentury    CHAR(1)
        ,2 ModifDate       CHAR(3)
        ,2 ModifHours      CHAR(1)
        ,2 ModifMinutes    CHAR(1)
        ,2 CurrentLines    CHAR(2)
        ,2 InitialLines    CHAR(2)
        ,2 ModifLines      CHAR(2)
        ,2 User            CHAR(7)
        ,2 Misc            CHAR(13)
       ;


   DCL PDSEntry UNAL TYPE tPDSEntry ;

   DCL Offset BIN FIXED(15) AUTO INIT(0);
 
   ON ENDFILE(PDS) EOF   = '1'B;

   OPEN FILE(PDS) TITLE(DDName);
   READ FILE(PDS) INTO (DirBlock);

   DO WHILE(EOF = '0'B) ;

      DO WHILE(EOB = '0'B);

         pEntry = ADDR(DirBlock.Entries ) + Offset ;

         IF   (SUBSTR( Entry.NAME,1,1 ) = LOW(1))
            | (SUBSTR( Entry.NAME,1,1 ) = HIGH(1)) THEN DO ;
            EOB = '1'B;
         END;
         ELSE DO;

            CALL PLIFILL(ADDR(PDSEntry),'00'X,CSTG(PDSEntry));

            PDSEntry.Name = Entry.NAME ;

            IF SUBSTR(ISPFStatisticsEntry.Misc,1,3) = '404040'X
            THEN DO ;
               PDSEntry.User = ISPFStatisticsEntry.User ;
               PDSEntry.Modified =
                      UnpackDate (
                          ISPFStatisticsEntry.ModifDate
                       || ISPFStatisticsEntry.ModifCentury
                                  )
                       || '-'
                       || HEX(ISPFStatisticsEntry.ModifHours)
                       || '.'
                       || HEX(ISPFStatisticsEntry.ModifMinutes)
                       || '.'
                       || HEX(ISPFStatisticsEntry.ModifSeconds)
                       || '.'
                       || '000000'
                       ;
            END;
            ELSE DO;
            END;

            CALL Callback(ADDR(PDSEntry),UserData);

            Offset = Offset + 12 + (2 * Entry.INDIC.USERCT);

         END;

       END;

       READ FILE(PDS) INTO (DirBlock);
       Offset = 0;
       EOB    = '0'B;

    END;

    CLOSE FILE(PDS);

    END;




The here not provided function UnpackDate converts the date format from the PDS directory just to the format YYYY-MM-DD.

kind regards,
bauer
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12370
Topics: 75
Location: San Jose

PostPosted: Tue Jun 10, 2014 6:33 pm    Post subject: Re: example? Reply with quote

ironponygrl wrote:

would you be inclined to post your COBOL solution? perhaps just the pertinent snippets.


I had an old cobol program to read the directory and get the member names, so I just added the functionality to get the stats too. Here is the code

Code:

       IDENTIFICATION DIVISION.
       PROGRAM-ID. PDSATTR.
      *****************************************************************
      * PROGRAM : PDSATTR                                             *
      *                                                               *
      * PURPOSE: THIS COBOL PROGRAM READS THE PDS DIRECTORY AND GET   *
      * THE MEMBER STATISTICS                                         *
      *                                                               *
      * INPUT FILES: PDS-DATASET                                      *
      *                                                               *
      *****************************************************************
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.

             SELECT PDS-DATASET ASSIGN TO PDS.

       DATA DIVISION.

       FILE SECTION.

         FD  PDS-DATASET
             RECORDING MODE IS U
             RECORD CONTAINS 256 CHARACTERS
             LABEL RECORDS ARE STANDARD.

         01  PDS-DIRECTORY.
             05 PDS-DIR-LEN             PIC S9(4) COMP.
             05 PDS-DIR-REC             PIC X(254).

       WORKING-STORAGE SECTION.

       01 WS-PDS-DIRECTORY.
          05 WS-PDS-MEMBER-NAME         PIC X(8).
          05 FILLER                     PIC X(3).
          05 WS-PDS-INDC                PIC X.
          05 WS-PDS-USER-DATA.
             10 WS-PDS-LEVEL-1          PIC X(01).
             10 WS-PDS-LEVEL-2          PIC X(01).
             10 WS-PDS-FLAGS            PIC X(01).
             10 WS-PDS-MODIFIED-SECONDS PIC X(01).
             10 WS-PDS-CREATE-CENTURY   PIC X(01).
             10 WS-PDS-CREATE-JDATE     PIC S9(05) COMP-3.
             10 WS-PDS-MODIFIED-CENTURY PIC X(01).
             10 WS-PDS-MODIFIED-JDATE   PIC S9(05) COMP-3.
             10 WS-PDS-MODIFIED-HOURS   PIC X(01).
             10 WS-PDS-MODIFIED-MINUTES PIC X(01).
             10 WS-PDS-CURRENT-LINES    PIC S9(04) COMP.
             10 WS-PDS-INITIAL-LINES    PIC S9(04) COMP.
             10 WS-PDS-MODIFIED-LINES   PIC S9(04) COMP.
             10 WS-PDS-USERID           PIC X(07).

       01 WS-TTR.
          05 WS-TTR-NUMERIC             PIC S9(4) COMP.

       01 WS-TEMP-DATE.
          05 WS-CENTURY                 PIC 9(02).
          05 WS-PACKED-DATE             PIC 9(05).

       01 WS-JULIAN-DATE                REDEFINES WS-TEMP-DATE
                                        PIC 9(07).
       01 WS-GREGORIAN-DATE             PIC 9(08).

       01 WS-MODIFIED-TIME.
          05 WS-MODIFIED-HH             PIC 9(02).
          05 FILLER                     PIC X(01) VALUE ':'.
          05 WS-MODIFIED-MM             PIC 9(02).
          05 FILLER                     PIC X(01) VALUE ':'.
          05 WS-MODIFIED-SS             PIC 9(02).

       01  WS-OFFSET                    PIC S9(4) COMP.
       01  WS-TRASH                     PIC S9(4) COMP.
       01  WS-HALF-WORDS                PIC S9(4) COMP.

       01  WS-CHAR-PACKED.
           05 WS-CHAR-PACKED-BYTE1      PIC X.
           05 WS-CHAR-PACKED-BYTE2      PIC X.
       01  WS-PACKED                    REDEFINES WS-CHAR-PACKED
                                        PIC S9(3) COMP-3.

       01  S-EOF-DIRECTORY              PIC X(01)  VALUE 'N'.

       PROCEDURE DIVISION.

             PERFORM 1000-INITIALIZATION

             PERFORM 2000-MAIN-PROCESS UNTIL S-EOF-DIRECTORY = 'Y'

             PERFORM 3000-WRAPUP

             GOBACK
             .

       1000-INITIALIZATION.
      **************************************************************
      * THIS PARAGRAPH OPENS INPUT AND OUTPUT FILES AND DOES THE   *
      * PRIME READ.                                                *
      **************************************************************

             OPEN INPUT PDS-DATASET.
             PERFORM 2500-READ-DIRECTORY
             .

       2000-MAIN-PROCESS.
      *************************************************************
      * THIS PARAGRAPH PERFORMS THE MAIN LOGIC OF READING THE PDS *
      * DIRECTORY AND EXTRACTING THE USER DATA.                   *
      *************************************************************

             MOVE 1                    TO WS-OFFSET
             PERFORM UNTIL PDS-DIR-LEN - WS-OFFSET < 11
                  OR PDS-DIR-REC(WS-OFFSET:1) = HIGH-VALUES
                     PERFORM 2100-PROCESS-MEMBER-DATA
                     INITIALIZE WS-TTR
                     MOVE WS-PDS-INDC  TO WS-TTR (2:1)
                     DIVIDE WS-TTR-NUMERIC BY 32 GIVING WS-TRASH
                            REMAINDER WS-HALF-WORDS
                     COMPUTE WS-OFFSET = WS-OFFSET + 12 +
                                         WS-HALF-WORDS * 2
             END-PERFORM
             PERFORM 2500-READ-DIRECTORY
             .

       2100-PROCESS-MEMBER-DATA.
      *************************************************************
      * THIS PARAGRAPH PROCESS THE MEMBER DATA.                   *
      *************************************************************

             MOVE SPACES                  TO WS-PDS-DIRECTORY
             MOVE PDS-DIR-REC (WS-OFFSET:39)
                                          TO WS-PDS-DIRECTORY
             DISPLAY 'MEMBER NAME       :  ' WS-PDS-MEMBER-NAME
             IF WS-PDS-INDC = X'00'
                DISPLAY 'NO STATS EXIST FOR MEMBER : '
                        WS-PDS-MEMBER-NAME
             ELSE
                PERFORM 2200-CONVERT-DATES
                PERFORM 2400-CONVERT-MODIFIED-TIME
                DISPLAY 'INITIAL LINES     :  ' WS-PDS-INITIAL-LINES
                DISPLAY 'CURRENT LINES     :  ' WS-PDS-CURRENT-LINES
                DISPLAY 'MODIFIED LINES    :  ' WS-PDS-MODIFIED-LINES
                DISPLAY 'USER ID           :  ' WS-PDS-USERID
             END-IF
             DISPLAY '*****************************************'
             .

       2200-CONVERT-DATES.
      *************************************************************
      * THIS PARAGRAPH CONVERTS THE CREATE AND MODIFIED DATES TO  *
      * READABLE FORMAT.                                          *
      *************************************************************

             MOVE X'000C'                 TO WS-CHAR-PACKED
             MOVE WS-PDS-CREATE-CENTURY   TO WS-CHAR-PACKED-BYTE1
             MOVE WS-PDS-CREATE-JDATE     TO WS-PACKED-DATE
             PERFORM 2300-CONV-JDATE-TO-GREGDATE
             DISPLAY 'CREATE DATE       :  '
                     WS-GREGORIAN-DATE(1:4)
                     '-'
                     WS-GREGORIAN-DATE(5:2)
                     '-'
                     WS-GREGORIAN-DATE(7:2)

             MOVE X'000C'                 TO WS-CHAR-PACKED
             MOVE WS-PDS-MODIFIED-CENTURY TO WS-CHAR-PACKED-BYTE1
             MOVE WS-PDS-MODIFIED-JDATE   TO WS-PACKED-DATE
             PERFORM 2300-CONV-JDATE-TO-GREGDATE
             DISPLAY 'MODIFIED DATE     :  '
                     WS-GREGORIAN-DATE(1:4)
                     '-'
                     WS-GREGORIAN-DATE(5:2)
                     '-'
                     WS-GREGORIAN-DATE(7:2)
             .

       2300-CONV-JDATE-TO-GREGDATE.
      *************************************************************
      * THIS PARAGRAPH CONVERTS THE INPUT JULIAN DATE TO GREGORIAN*
      * DATE.                                                     *
      *************************************************************

             COMPUTE WS-CENTURY            = WS-PACKED / 10  + 19

             COMPUTE WS-GREGORIAN-DATE = FUNCTION DATE-OF-INTEGER
                                         (FUNCTION INTEGER-OF-DAY
                                         (WS-JULIAN-DATE))

             .
       2400-CONVERT-MODIFIED-TIME.
      *************************************************************
      * THIS PARAGRAPH CONVERTS THE MODIFIED TIME TO READABLE     *
      * FORMAT.                                                   *
      *************************************************************

             MOVE X'000C'                 TO WS-CHAR-PACKED
             MOVE WS-PDS-MODIFIED-HOURS   TO WS-CHAR-PACKED-BYTE1
             COMPUTE WS-MODIFIED-HH        = WS-PACKED / 10

             MOVE X'000C'                 TO WS-CHAR-PACKED
             MOVE WS-PDS-MODIFIED-MINUTES TO WS-CHAR-PACKED-BYTE1
             COMPUTE WS-MODIFIED-MM        = WS-PACKED / 10

             MOVE X'000C'                 TO WS-CHAR-PACKED
             MOVE WS-PDS-MODIFIED-SECONDS TO WS-CHAR-PACKED-BYTE1
             COMPUTE WS-MODIFIED-SS        = WS-PACKED / 10
             DISPLAY 'MODIFIED TIME     :  ' WS-MODIFIED-TIME

             .
       2500-READ-DIRECTORY.
      *************************************************************
      * THIS PARAGRAPH READS THE PDS DIRECTORY                    *
      *************************************************************

             READ PDS-DATASET
               AT END
                  MOVE 'Y'           TO S-EOF-DIRECTORY
             END-READ
             .

       3000-WRAPUP.
      *************************************************************
      * THIS PARAGRAPH CLOSES THE INPUT & OUTPUT FILES            *
      ***************************************************************
             CLOSE PDS-DATASET
             .



And the JCL that is used to run this program is
Code:

//STEP0100 EXEC PGM=PDSATTR
//STEPLIB  DD DISP=SHR,DSN=Your Pgm Loadlib
//PDS      DD DISP=SHR,DSN=Your.PDS, 
//            RECFM=U,LRECL=256             
//SYSOUT   DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
//*
Back to top
View user's profile Send private message Send e-mail Visit poster's website
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12370
Topics: 75
Location: San Jose

PostPosted: Tue Jun 10, 2014 6:35 pm    Post subject: Reply with quote

bauer wrote:

The complete routine "ReadPDSDirectory" is a submodule with a callback option to provide each entry of the PDS Directory to the calling (main-) routine.

This is the datastructure which provides information for each entry.


bauer,

I don't have much experience with PLI, so I may be I am missing something.

1. Your PDS directory need to RECFM=U instead of RECFM=F
2. Does your program handle members WITHOUT stats?
_________________
Kolusu - DFSORT Development Team (IBM)
DFSORT is on the Web at:
www.ibm.com/storage/dfsort

www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
ironponygrl
Beginner


Joined: 22 Mar 2013
Posts: 21
Topics: 7
Location: Fort Worth, TX

PostPosted: Tue Jun 10, 2014 7:13 pm    Post subject: Reply with quote

thanks fellows, that's awesome. now I can see it clearly and if i ever need to do that, it's here for all perpetuity.
Back to top
View user's profile Send private message
William Collins
Supermod


Joined: 03 Jun 2012
Posts: 437
Topics: 0

PostPosted: Wed Jun 11, 2014 1:55 am    Post subject: Reply with quote

I always thought that RECFM=U was required for reading a PDS directory. I recently discovered that RECFM works equally. Others have always used RECFM=F and were surprised that RECFM=U worked Smile As important is the LRECL, which everyone agrees is 256.
Back to top
View user's profile Send private message
bauer
Intermediate


Joined: 10 Oct 2003
Posts: 315
Topics: 49
Location: Germany

PostPosted: Wed Jun 11, 2014 2:44 am    Post subject: Reply with quote

kolusu,

according your questions:

1) see line DCL PDS FILE RECORD SEQUENTIAL INPUT ENV(U) ; in the PL/1 coding. Here is RECFM = U But, yes you are right, the JCL provides a different RECFM parameter.

2) yes, this is handled. See code line IF SUBSTR(ISPFStatisticsEntry.Misc,1,3) = '404040'X , according the IBM dokumentation: If this bytes are Blank => statistics data available, otherwise not available.

Remark: My here provided coding are only the most important lines. The real coding contains some additional logic for wildcardsearch, descision for reading SSI Data in case of loadmodule libs (type of libaray is evaluated).

kind regards,
bauer
Back to top
View user's profile Send private message
bauer
Intermediate


Joined: 10 Oct 2003
Posts: 315
Topics: 49
Location: Germany

PostPosted: Wed Jun 11, 2014 3:28 am    Post subject: Reply with quote

kolusu,

add 2),

In your coding you evaluate this:

IF WS-PDS-INDC = X'00'
DISPLAY 'NO STATS EXIST FOR MEMBER : '
WS-PDS-MEMBER-NAME

This is not handled in my provided coding. Thank you for asking.

My check IF SUBSTR(ISPFStatisticsEntry.Misc,1,3) = '404040'X checks, if the available statistics bytes are filled, content is set.

In our environment we have PDS datasets with available statistics bytes (your checked byte not equal zero) but without a useful content of this bytes.

So my understanding:

I should add your evaluation of the single byte (your field WS-PDS-INDC, my field Entry.INDIC), if statistics data bytes are in general available.

You should add my evaluation, if the statistics bytes have a really filled content.

kind regards,
bauer
Back to top
View user's profile Send private message
William Collins
Supermod


Joined: 03 Jun 2012
Posts: 437
Topics: 0

PostPosted: Wed Jun 11, 2014 5:31 am    Post subject: Reply with quote

I'm pretty sure that it makes no difference whether RECFM=F or RECFM=U in the JCL or records are Fixed or Undefined in the program. They can even be mixed.

The index consists of individual records each of 256 bytes. Whether F or U, the results (256 bytes of data for every read) are the same. Both F and U work, even in a mixture.

If the index records were blocked, it would be a different thing.
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12370
Topics: 75
Location: San Jose

PostPosted: Wed Jun 11, 2014 11:04 am    Post subject: Reply with quote

ironponygrl wrote:
thanks fellows, that's awesome. now I can see it clearly and if i ever need to do that, it's here for all perpetuity.


It doesn't hurt to have a copy of it now as I lost a good part of my solutions due to server crash and I had to use a backup which was more than a year old.

William Collins wrote:
I always thought that RECFM=U was required for reading a PDS directory. I recently discovered that RECFM works equally. Others have always used RECFM=F and were surprised that RECFM=U worked Smile As important is the LRECL, which everyone agrees is 256.


William,

There are 2 things

1. JCL override of RECFM=U
2. RECORDING MODE in the Program in FILE SECTION.

It works only if you had

1.If your JCL has RECFM=U and if your Program had RECORDING MODE IS F
2.If your JCL has RECFM=F and if your Program had RECORDING MODE IS U

It fails if you had RECFM=F and the Program ALSO had RECORDING MODE IS F

So if you have in the program defined as
Code:

FD  PDS-DATASET                         
    RECORDING MODE IS U                 
    RECORD CONTAINS 256 CHARACTERS     
    LABEL RECORDS ARE STANDARD.         
                                       


It doesn't matter what RECFM you use in the JCL

bauer wrote:

So my understanding:

I should add your evaluation of the single byte (your field WS-PDS-INDC, my field Entry.INDIC), if statistics data bytes are in general available.

You should add my evaluation, if the statistics bytes have a really filled content.

bauer


bauer,

Unless I am gravely mistaken, the SUBSTR(ISPFStatisticsEntry.Misc,1,3) check is for EXTENDED statistics and NOT for the regular stats. With extended member statistics ISPF allows to store more than 65,535 lines. That is the reason as to why the field in extended stats are of 4 bytes instead of 2 bytes.
_________________
Kolusu - DFSORT Development Team (IBM)
DFSORT is on the Web at:
www.ibm.com/storage/dfsort

www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
Display posts from previous:   
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Application Programming All times are GMT - 5 Hours
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


MVSFORUMS
Powered by phpBB © 2001, 2005 phpBB Group