List Directory (LD)

Command title

List Directory

Description

This command creates a library directory in a table identified by the TABLE field in xxxx-COMMAND-AREA.

COBOL syntax

MOVE 'LD'                   TO xxxx-COMMAND.
CALL 'TBLBASE' USING        TB-PARM
                            xxxx-COMMAND-AREA
                            [DDNAME
                            [DIR-SPEC]].

C syntax

memcpy( tbCommArea.tbCommand, "LD", 2 );
TBLBASE( &tbParm, &tbCommArea, pDDName, &tbDirSpec );

Parameters

DDNAME (optional)—the name of the library. If DDNAME is spaces or low values, or the parameter is not provided, then all libraries in the tableBASE Library List (LIB-LIST) are included in the directory.

DIR-SPEC (optional)—specifies which tables are to be selected and which information format is to be used for the directory list.

The TABLE-NAME-MASK field of the DIR-SPEC parameter specifies the tables to be selected. A wild-card character can be used to identify the tables to be selected.

The DIRTYPE field of the DIR-SPEC parameter can be:

  • T = All generations of all tables (default)
  • V = View tables (based on tablesONLINE definition); all table names beginning with x’80’ to x’BF’, including lower-case characters
  • D = Latest generation of the Data Tables; all table names beginning with x’C0′ to x’FF’, including lower-case characters, including all upper-case characters and numbers. tablesONLINE Views are not returned for DIRTYPE=D.

Explanation

DIRTYPE = D. The directory table has a row size of 74 and a key size of 16 beginning at location 1. The format of a data directory entry (row) is:

      01  DATA-DIRECTORY-ENTRY.
          05  DATA-NAME          PIC X(8).
          05  DATA-DDNAME        PIC X(8).
          05  DATA-ORG           PIC X.
          05  DATA-METHOD        PIC X.
          05  DATA-TYPE          PIC X.
          05  DATA-SMC           PIC X.
          05  DATA-RSZ           PIC S9(9) COMP.
          05  DATA-KSZ           PIC S9(9) COMP.
          05  DATA-KLOC          PIC S9(9) COMP.
          05  DATA-ROWS          PIC S9(9) COMP.
          05  DATA-GENERATIONS   PIC S9(4) COMP.
          05  DATA-DATE-TIME     PIC X(12).
          05  DATA-DATA-TABLE    PIC X(8).
          05  DATA-VIEW-NAME     PIC X(8).
          05  DATA-USERID        PIC X(8).
DIRTYPE = V. The directory table has a row size of 44 and a key size of 16 beginning at location 1. The format of a view directory entry (row) is:

      01  VIEW-DIRECTORY-ENTRY.
          05  VIEWDE-NAME        PIC X(8).
          05  VIEWDE-DDNAME      PIC X(8).
          05  VIEWDE-DATE-TIME   PIC X(12).
          05  VIEWDE-DATA-TABLE  PIC X(8).
          05  VIEWDE-USERID      PIC X(8).
DIRTYPE = T. The directory table has a row size of 70 and a key size of 18 beginning at location 1. The format of a total directory entry (row) is:

      01  TOTAL-DIRECTORY-ENTRY.
          05  TOTAL-NAME         PIC X(8).
          05  TOTAL-DDNAME       PIC X(8).
          05  TOTAL-ABS-GEN-NO   PIC S9(4) COMP.
          05  TOTAL-MAX-GEN-NO   PIC S9(4) COMP.
          05  TOTAL-ORG          PIC X.
          05  TOTAL-METHOD       PIC X.
          05  TOTAL-TYPE         PIC X.
          05  TOTAL-SMC          PIC X.
          05  TOTAL-RSZ          PIC S9(9) COMP.
          05  TOTAL-KSZ          PIC S9(9) COMP.
          05  TOTAL-KLOC         PIC S9(9) COMP.
          05  TOTAL-ROWS         PIC S9(9) COMP.
          05  TOTAL-GENERATIONS  PIC S9(4) COMP.
          05  TOTAL-DATE-TIME    PIC X(12).
          05  TOTAL-DATA-TABLE   PIC X(8).
          05  TOTAL-USERID       PIC X(8).

Return value

The COUNT field contains the number of directory entries placed into the table.

Errors 0003 subcodes 2-5 can occur when reusing an existing table.

Error 0050 occurs if you specify an invalid directory type.

Error 0006 can occur if the LD uses an invalid VTS redirect.

Notes

LD does not store the directory list table on any library; if the table is to be stored, an ST command must be issued.

The directory list table is built in the local TSR unless the TBPARM subsystem name field associated with the tableBASE call designates a VTS-TSR.

If TABLE is already open and has the same format as the current request, then the new information will be appended to the end of the table and the COUNT field will be updated to reflect the total number of directory entries in the table.

Exceptions

None

See also

DIR-SPEC (9 bytes)