Get member information (metadata)

The two calls associated with getting member metadata are GetFirstMemberInfo and GetNextMemberInfo. As in the case of getting member records, the normal return codes are 0 when member metadata is being returned, and 180 at end of file.

The argument required is not exactly the same as a member name. Instead, a filter is expected. The filter may be a member name, or it may contain characters and wildcard characters.

The wildcard characters supported by File Manager are * matching zero or more characters, and % matching exactly one character.

Here is how a filter argument is passed:

01 SIMPLE-FILTER-SPEC.
    05 SOFTWARE-VERSION PIC 9(4) BINARY.
    05 SIMPLE-FILTER-FIELD-ID PIC 9(4) BINARY.
       88 SIMPLE-FILTER-IS-MEMBER-NAME VALUE 210.
    05 SIMPLE-FILTER-LENGTH PIC 9(4) BINARY.
    05 SIMPLE-FILTER-MASK PIC X(64). GET-RAM-PARM3-FILTER.
     IF RAM-PARM3 = NULL THEN
        MOVE 1 TO PATTERN-LENGTH
        MOVE "*" TO PATTERN-CHARS
     ELSE
        SET ADDRESS OF SIMPLE-FILTER-SPEC TO RAM-PARM3
        IF SIMPLE-FILTER-LENGTH < 0
              OR SIMPLE-FILTER-LENGTH > 10 THEN
           SET RAM-RC-BAD-FILTER TO TRUE
        ELSE
           MOVE SIMPLE-FILTER-LENGTH TO PATTERN-LENGTH
           MOVE SIMPLE-FILTER-MASK(1:PATTERN-LENGTH)
             TO PATTERN-CHARS
        END-IF
     END-IF.

A COBOL nested program called MATCH is provided in the sample COBOL exit to provide function to match a filter (pattern) to a member name.

Note: File Manager strips any leading blanks prior to passing the filter (pattern), so you do not need to remove leading blanks from the filter yourself.
Note: Blanks are treated like any other character in the MATCH program, and if found, must be matched. Therefore, if the LMS returns leading blanks in member names you should strip them. If the member name includes trailing blanks, eliminate them from comparison by setting the length of the member name appropriately.

The metadata returned to File Manager has the following structure. Note that the sample COBOL exit has given some structure to the RHS, which you may want to change:

01 DIR-DATA-RETURN-AREA.
    05 DIR-DATA-RETURN-ATTR1 PIC 9(4) COMP-5 VALUE 20000.
    05 DIR-DATA-RETURN-LEN1  PIC 9(4) BINARY VALUE 10.
    05 DIR-DATA-RETURN-LHS   PIC X(10) VALUE " ".
    05 DIR-DATA-RETURN-ATTR2 PIC 9(4) COMP-5 VALUE 20001.
    05 DIR-DATA-RETURN-LEN2  PIC 9(4) BINARY VALUE 51.
    05 DIR-DATA-RETURN-RHS.       10 RHS-USERID PIC X(7).
       10 FILLER PIC XX VALUE " ".
       10 RHS-MOD-DATE PIC X(10).
       10 FILLER PIC X VALUE " ".
       10 RHS-MOD-TIME PIC X(8).
       10 FILLER PIC XX VALUE " ".
       10 RHS-NLINES PIC ZZZZ9 DISPLAY.
       10 FILLER PIC XX VALUE " ".
       10 RHS-CRE8-DATE PIC X(10).
       10 FILLER PIC X(4).
    05 DIR-DATA-RETURN-END   PIC X(2)        VALUE X"FFFF".

The member name should go into DISP-INFO-RETURN-LHS, padded with trailing blanks. The attribute information should go into DISP-INFO-RETURN-RHS. There is space for 8 to 10 characters for the member name (LHS) and the total line is limited to 80 characters. The RHS can contain the remaining characters. The size of the prompt field is variable. See Get display information for more information on the layout.