This routine is used to parse XFD files and retrieve information about them, giving you a way to map field description information to file record areas. Similar functionality allows the alfred utility to display data in a logical way (rather than displaying full records).
A detailed description of the use and structure of XFD files can be found in the topic XFD Files of the ACUCOBOL-GT User's Guide.
CALL "C$PARSEXFD"
    USING OP-CODE, parameters
    GIVING return-value. 
               	 OP-CODE (Numeric value)
The op-codes, which are defined in parsexfd.def, select which C$PARSEXFD function to perform. This table shows which operation corresponds to each operation code.
| Code | Operation | 
|---|---|
| 0 | parse XFD file | 
| 1 | retrieve key information | 
| 2 | retrieve condition information | 
| 3 | retrieve field information | 
| 4 | test record conditions | 
| 9 | release XFD file from memory | 
Detailed information about the operations is given in the description below.
| parameters | Op-code parameters vary depending on the operation code chosen. They provide information and hold results for the operations specified. The parameters that apply to C$PARSEXFD op-codes are all defined in parsexfd.def. | 
| return-value (Numeric data item) | This item returns information relevant to the operation. The type of return value varies by op-code. | 
C$PARSEXFD performs a variety of operations depending on the specified op-code. These operations are as follows:
This operation parses a specified XFD file. The syntax is:
CALL "C$PARSEXFD" 
    USING PARSEXFD-PARSE, xfd-name, filename, flags,
         xfd-description. 
               		PARSEXFD-PARSE takes the following parameters:
| xfd-name (PIC X(n)) | Specifies the name of the XFD file to parse, with or without path information. If there is no path information, the configuration variables XFD_PREFIX or XFD_DIRECTORY are used to find the XFD file. You may omit the .xfd extension. | ||||||||||||||||||||||||||||
| filename (PIC X(n) or NULL) | Specifies an indexed data file to be compared against the parsed XFD file. If the characteristics of the specified data file do not match the XFD, the parsed XFD is freed and the return-value is set to NULL. If this parameter is NULL or empty, the XFD file is not compared to any file. | ||||||||||||||||||||||||||||
| flags (Numeric parameter) | Flags modify the type of information returned from other op-codes. This parameter can be 
                                 					 0 (if no flags are set), or the sum of any of the following values: 
 Normally this is returned as elem-1(1), elem-1(2), elem-1(3), elem-1(4), elem-1(5), elem-2(1), elem-2(2), elem-2(3), elem-2(4), elem-2(5), elem-3(1), elem-3(2), elem-3(3), elem-3(4), elem-3(5). If PARSEXFD-FLAG-DEEP-FIRST is specified, the items are instead returned as elem-1(1), elem-2(1), elem-3(1), elem-1(2), elem-2(2), and so on. The same data is returned, but in a different order. | ||||||||||||||||||||||||||||
| xfd-description (Group item) | This parameter is structured as follows: 01  PARSEXFD-DESCRIPTION. 
           03  PARSEXFD-HEADER-LINE. 
               05  PARSEXFD-VERSION            PIC X COMP-N. 
               05  PARSEXFD-SELECT-NAME        PIC X(30). 
               05  PARSEXFD-FILENAME           PIC X(30). 
               05  PARSEXFD-FILETYPE           PIC X COMP-N. 
                   88  PARSEXFD-SEQUENTIAL-FILE    VALUE 4. 
                   88  PARSEXFD-RELATIVE-FILE      VALUE 8. 
                   88  PARSEXFD-INDEXED-FILE       VALUE 12. 
           03  PARSEXFD-RECORD-LINE. 
               05  PARSEXFD-MAX-REC-SIZE       PIC X(4) COMP-N. 
               05  PARSEXFD-MIN-REC-SIZE       PIC X(4) COMP-N. 
               05  PARSEXFD-NUM-KEYS           PIC X COMP-N. 
           03  PARSEXFD-CONDITION-LINE. 
               05  PARSEXFD-NUMBER-CONDITIONS  PIC XX COMP-N. 
           03  PARSEXFD-FIELDS-LINE. 
               05  PARSEXFD-NUMBER-FIELDS      PIC X(4) COMP-N. 
           03  PARSEXFD-V6-INFORMATION. 
               05  PARSEXFD-COBOL-TRIGGER      PIC X(100). 
               05  PARSEXFD-COMPILE-LINE. 
                   07  PARSEXFD-SIGN-FLAG      PIC X(2) COMP-N. 
                       88  PARSEXFD-SIGN-ACU   VALUE 0. 
                       88  PARSEXFD-SIGN-IBM   VALUE 4. 
                       88  PARSEXFD-SIGN-MF    VALUE 8. 
                       88  PARSEXFD-SIGN-NCR   VALUE 20. 
                       88  PARSEXFD-SIGN-VAX   VALUE 36. 
                       88  PARSEXFD-SIGN-MBP   VALUE 72. 
                       88  PARSEXFD-SIGN-REA   VALUE 128. 
                   07  PARSEXFD-MAX-DIGITS     PIC X(2) COMP-N. 
                       88  PARSEXFD-18-DIGITS  VALUE 40. 
                       88  PARSEXFD-31-DIGITS  VALUE 68. 
                   07  PARSEXFD-PGM-PERIOD     PIC X. 
                   07  PARSEXFD-PGM-COMMA      PIC X. 
                   07  PARSEXFD-ENCODING       PIC X(2) COMP-N. 
                       88  PARSEXFD_ASCII      VALUE 0. 
                       88  PARSEXFD_WIDE       VALUE 1. 
                       88  PARSEXFD_UTF-8      VALUE 2. 
                       88  PARSEXFD_UTF-16-LE  VALUE 3. 
                       88  PARSEXFD_UTF-16-BE  VALUE 5. 
                       88  PARSEXFD_UTF-32-LE  VALUE 4. 
                       88  PARSEXFD_UTF-32-BE  VALUE 6. 
The values of the xfd-description parameter are defined as follows: 
 | ||||||||||||||||||||||||||||
| return-value | For this op-code, the return value is the handle to the XFD. This handle must be used in future calls to C$PARSEXFD to get
                                 more information about the XFD, and to free the XFD when you are finished. If the return-value is 0, an error occurred. You can get information about errors by examining f-errno and f-int-errno, which are defined in the filesys.def COPY file. | 
This operation retrieves information about the specified (single) key. It uses the following syntax:
CALL "C$PARSEXFD" 
    USING PARSEXFD-GET-KEY-INFO, xfd-handle, keynum,
          key-description 
               		The operation takes the following parameters:
| xfd-handle | A valid handle returned by C$PARSEXFD PARSEXFD-PARSE. | ||||||||||||
| keynum (Numeric parameter between 0 and PARSEXFD-NUM-KEYS) | Used to specify which key to parse. Takes a value between 0 and PARSEXFD-NUM-KEYS. Both 0 and PARSEXFD-NUM-KEYS - 1 are valid key numbers, but PARSEXFD-NUM-KEYS is not valid. In other words, key numbers are a zero-based array. | ||||||||||||
| Key-description (Group item) | This parameter is structured as follows: 01 PARSEXFD-KEY-DESCRIPTION.
   03 PARSEXFD-NUMBER-SEGMENTS        PIC X COMP-N.
   03 PARSEXFD-DUP-FLAG               PIC X COMP-N.
      88 PARSEXFD-ALLOW-DUPLICATES    VALUE 1 FALSE 0.
   03 PARSEXFD-SEGMENT-DESCRIPTION
        OCCURS MAX-SEGS TIMES
        INDEXED BY PARSEXFD-SEG-IDX.
      05 PARSEXFD-SEGMENT-LENGTH      PIC X COMP-N.
      05 PARSEXFD-SEGMENT-OFFESET     PIC X(4) COMP-N.
      05 PARSEXFD-SEGMENT-OFFSET      PIC X(4) COMP-N.
   03 PARSEXFD-NUMBER-KEY-FIELDS      PIC X COMP-N.
   03 PARSEXFD-KEY-FIELDS
        OCCURS MAXNUMKEYFIELDS TIMES
        INDEXED BY PARSEXFD-KEY-FIELD-IDX.
      05 PARSEXFD-KEY-FIELD-NUM       PIC XX COMP-N.The values of the key-description parameter are defined as follows: 
 | ||||||||||||
| return-value (0 or 1) | A return value of 1 indicates that the operation was successful; a 0 indicates failure. For this operation, a return code of 0 means that you have entered an invalid key number (for instance, specifying a key number of 3 for a file that only has two keys). Note, however, that if an invalid handle is specified, the results are undefined and may result in a memory violation. | 
This operation retrieves information about conditions that use the WHEN directive within the XFD file. It uses the following syntax:
CALL "C$PARSEXFD"
    USING PARSEXFD-GET-COND-INFO, xfd-handle, cond-index,
          cond-description. 
               		PARSEXFD-GET-COND-INFO takes the following parameters:
| xfd-handle | A valid handle returned by C$PARSEXFD PARSEXFD-PARSE. | 
| cond-index (Numeric parameter) | The condition index determines which condition to evaluate. It takes a value between 0 and PARSEXFD-NUMBER-CONDITIONS. Because conditions are a zero-based array, 0 and PARSEXFD-NUMBER-CONDITIONS - 1 are valid values, but PARSEXFD-NUMBER-CONDITIONS is not. | 
| cond-description (Group item) | The condition description holds information about what condition has been set (EQUAL TO, AND, OR), whether the condition
                                 has been met (is true or false), and how the condition is structured. This parameter is structured as follows: 01  PARSEXFD-CONDITION-DESCRIPTION.
    03  PARSEXFD-CONDITION-TYPE         PIC X COMP-N.
        88  PARSEXFD-EQUAL-CONDITION    VALUE 1.
        88  PARSEXFD-AND-CONDITION      VALUE 2.
        88  PARSEXFD-OTHER-CONDITION    VALUE 3.
        88  PARSEXFD-GT-CONDITION       VALUE 4.
        88  PARSEXFD-GE-CONDITION       VALUE 5.
        88  PARSEXFD-LT-CONDITION       VALUE 6.
        88  PARSEXFD-LE-CONDITION       VALUE 7.
        88  PARSEXFD-NE-CONDITION       VALUE 8.
        88  PARSEXFD-OR-CONDITION       VALUE 9.
        88  PARSEXFD-COMPARISON-COND    VALUES 1, 4 THROUGH 8.
    03  PARSEXFD-CONDITION-FLAG         PIC X.
        88  PARSEXFD-TRUE-CONDITION     VALUE 'Y' FALSE 'N'.
    03  PARSEXFD-COMPARISON-CONDITIONS.
        05  PARSEXFD-COMP-FIELDNUM      PIC XX COMP-N.
        05  PARSEXFD-COMP-FIELDNAME     PIC X(30).
        05  PARSEXFD-COMP-FIELD-VAL     PIC X(50).
    03  PARSEXFD-OTHER-CONDITIONS
         REDEFINES PARSEXFD-COMPARISON-CONDITIONS.
        05  PARSEXFD-OTHER-FIELDNUM     PIC XX COMP-N.
        05  PARSEXFD-OTHER-FIELDNAME    PIC X(30).
    03  PARSEXFD-AND-OR-CONDITIONS
         REDEFINES PARSEXFD-COMPARISON-CONDITIONS.
        05  PARSEXFD-CONDITION-1        PIC XX COMP-N.
        05  PARSEXFD-CONDITION-2        PIC XX COMP-N.
    03  PARSEXFD-CONDITION-TABLENAME    PIC X(30).The values of the cond-description parameter are defined as follows: 
 For OTHER conditions, the following fields are valid: 
 For AND and OR conditions, the following fields are valid: 
 | 
This operation retrieves information about the field. It uses the following syntax:
CALL "C$PARSEXFD"
    USING PARSEXFD-GET-FIELD-INFO, xfd-handle, fieldnum,
          field-description. 
               		The operation takes the following parameters:
| xfd-handle | A valid handle returned by C$PARSEXFD PARSEXFD-PARSE. | ||||||||||||||||||||||||||||||||
| fieldnum (Numeric parameter) | Takes a value between 0 and PARSEXFD-NUMBER-FIELDS. Because fields are a zero-based array, 0 and PARSEXFD-NUMBER-FIELDS - 1 are valid values, but PARSEXFD-NUMBER-FIELDS is not valid. | ||||||||||||||||||||||||||||||||
| field-description (Group item) | This parameter is structured as follows: 01  PARSEXFD-FIELD-DESCRIPTION.
    03  PARSEXFD-FIELD-OFFSET            PIC X(4) COMP-N.
    03  PARSEXFD-FIELD-LENGTH            PIC X(4) COMP-N.
    03  PARSEXFD-FIELD-TYPE              PIC X COMP-N.
        88  PARSEXFD-SIGNED-FIELD   VALUES NumSignSep
                                           NumSigned
                                           NumSepLead
                                           NumLeading
                                           CompSigned
                                           PackedSigned
                                           BinarySigned
                                           NativeSigned.
        88  PARSEXFD-NUM-FIELD      VALUES NumEdited THRU
                                           NativeUnsigned.
        88  PARSEXFD-FLOAT-FIELD    VALUE  Flt.
        88  PARSEXFD-ASCII-FIELD    VALUES Alphanum THRU Group.
        88  PARSEXFD-NAT-FIELD      VALUES Nat-type THRU NatEdited.
        88  PARSEXFD-WIDE-FIELD     VALUES Wide-type THRU
                                           WideEdited.
    03  PARSEXFD-FIELD-DIGITS            PIC X COMP-N.
    03  PARSEXFD-FIELD-SCALE             SIGNED-SHORT.
    03  PARSEXFD-FIELD-USER-TYPE         PIC XX COMP-N.
    03  PARSEXFD-FIELD-CONDITION         PIC XX COMP-N.
    03  PARSEXFD-FIELD-LEVEL             PIC X COMP-N.
    03  PARSEXFD-FIELD-NAME              PIC X(30).
    03  PARSEXFD-FIELD-FORMAT            PIC X(30).
    03  PARSEXFD-FIELD-OCCURS-DEPTH      PIC X COMP-N.
    03  PARSEXFD-FIELD-OCCURS-TABLE
            OCCURS MaxNumKeyFields TIMES
            INDEXED BY PARSEXFD-FIELD-OCCURS-LEVEL.
        05  PARSEXFD-FIELD-OCC-MAX-IDX   PIC XX COMP-N.
        05  PARSEXFD-FIELD-OCC-THIS-IDX  PIC XX COMP-N.
    03  PARSEXFD-FIELD-IN-KEY-FLAG       PIC X.
        88  PARSEXFD-FIELD-IS-IN-KEY     VALUE 'Y' FALSE 'N'.
    03  PARSEXFD-FIELD-SECONDARY-FLAG    PIC X.
        88  PARSEXFD-FIELD-IS-SECONDARY  VALUE 'Y' FALSE 'N'.
    03  PARSEXFD-FIELD-HIDDEN-FLAG       PIC X.
        88  PARSEXFD-FIELD-IS-HIDDEN     VALUE 'Y' FALSE 'N'.
    03  PARSEXFD-FIELD-READ-ONLY-FLAG    PIC X.
        88  PARSEXFD-FIELD-IS-READ-ONLY  VALUE 'Y' FALSE 'N'.The values of the field-description parameter are defined as follows: 
 | ||||||||||||||||||||||||||||||||
| return-value (0 or 1) | A return-value of 1 indicates that the operation was successful; a 0 indicates failure. For this operation, you will only see a return code of 0 if you specify an invalid field number (for example, if you try to retrieve information about field number 17 in a record that only has 15 fields). | 
This operation tests the conditions of a particular record. It uses the following syntax:
CALL "C$PARSEXFD" 
    USING PARSEXFD-TEST-CONDITIONS, xfd-handle, 
          record-pointer. 
               		The operation takes the following parameters:
| xfd-handle | A valid handle returned by C$PARSEXFD PARSEXFD-PARSE. | 
| record-pointer | This is a pointer to the record area on which to test conditions. (Because conditions are true or false depending on the value of particular fields, the values of those fields must be known. The only way to do this is to have a record from a file, specified with the PARSEXFD-PARSE op-code, to test against.) | 
After calling with this op-code, you can get each condition and tell whether fields that depend on that condition should be included in this record.
This operation frees all memory associated with the XFD. It has the following syntax:
CALL "C$PARSEXFD" USING PARSEXFD-RELEASE, xfd-handle
This operation takes a single parameter:
| xfd-handle | A valid handle returned by C$PARSEXFD PARSEXFD-PARSE. | 
After calling this op-code, do not reference the XFD handle. Doing so will result in undefined behavior, and may cause a memory access violation.