Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

NLMOD - Modify local FT file attribute

The macro CALL "NLMOD"... can be used to modify the FTAM attributes of a file in the local system and adapt the attributes to make them available for file transfer or file management request with an FTAM partner. The functionality corresponds to that of the command MODIFY-FILE-FT-ATTRIBUTES.

In addition to the options offered by the openFT (BS2000) command interface, the filenames can also be addressed via their linknames.

Macro

The function can be called as follows:

CALL "NLMOD" USING FT-NLMOD-LIST FT-RETURN-INFO.

FT-NLMOD-LIST

The range FT-NLMOD-LIST describes the parameter list for the NLMOD macro. FT-NLMOD-LIST must be defined in the WORKING-STORAGE SECTION and can be copied to there with the statement

COPY FTNLMOD OF linkname.

Before the first NLMOD macro, the parameter fields should be deleted with the statement

MOVE LOW-VALUE TO USER-PARAMETERS IN FT-NLMOD-LIST.

Before executing another NLMOD macro, you must fill the desired fields. If a parameter is not specified or the default value is to be used, this field must be assigned the value LOW-VALUE.

FT-NLMOD-LIST is defined as follows:

 01  FT-NLMOD-LIST.
*
   02 FILLER                   PIC X(4)  VALUE "V520".
*
   02 USER-PARAMETERS.
*
     05 FILE-NAME              PIC X(54).
         88 NOT-SPECIFIED                 VALUE LOW-VALUE.
     05 LINK-NAME              PIC X(8).
         88 NOT-SPECIFIED                 VALUE LOW-VALUE.
*
     05 FILE-PASSWORD          PIC X(4).
         88 NONE                          VALUE LOW-VALUE.
     05 FILE-PASSWD-ATTR       PIC X(1).
         88 GRAPHIC                       VALUE LOW-VALUE.
         88 OCTET                         VALUE "O".
*
     05 PERMITTED-ACTIONS      PIC X(1).
         88 UNCHANGED                     VALUE LOW-VALUE.
         88 PARAMETER                     VALUE "P".
     05 READ-FILE              PIC X(1).
         88 NO-VALUE                      VALUE LOW-VALUE.
         88 NO-PAR                        VALUE "N".
         88 YES                           VALUE "Y".
     05 INSERT-DATA-UNIT       PIC X(1).
         88 NO-VALUE                      VALUE LOW-VALUE.
         88 NO-PAR                        VALUE "N".
         88 YES                           VALUE "Y".
     05 REPLACE-FILE           PIC X(1).
         88 NO-VALUE                      VALUE LOW-VALUE.
         88 NO-PAR                        VALUE "N".
         88 YES                           VALUE "Y".
     05 EXTEND-FILE            PIC X(1).
         88 NO-VALUE                      VALUE LOW-VALUE.
         88 NO-PAR                        VALUE "N".
         88 YES                           VALUE "Y".
     05 ERASE-DATA-UNIT        PIC X(1).
         88 NO-VALUE                      VALUE LOW-VALUE.
         88 NO-PAR                        VALUE "N".
         88 YES                           VALUE "Y".
     05 READ-ATTRIBUTES        PIC X(1).
         88 NO-VALUE                      VALUE LOW-VALUE.
         88 NO-PAR                        VALUE "N".
         88 YES                           VALUE "Y".
     05 CHANGE-ATTRIBUTES      PIC X(1).
         88 NO-VALUE                      VALUE LOW-VALUE.
         88 NO-PAR                        VALUE "N".
         88 YES                           VALUE "Y".
     05 DELETE-FILE            PIC X(1).
         88 NO-VALUE                      VALUE LOW-VALUE.
         88 NO-PAR                        VALUE "N".
         88 YES                           VALUE "Y".
*
     05 TRANSFER-ATTRIBUTES.
         10 TR-ATTRIBUTES      PIC X(1).
             88 UNCHANGED                 VALUE LOW-VALUE.
             88 PARAMETER                 VALUE "P".
         10 DATA-TYPE          PIC X(1).
             88 UNCHANGED                 VALUE LOW-VALUE.
             88 BINARY-DATA               VALUE "B".
             88 CHARACTER-TYPE            VALUE "C".
         10 CHARACTER-SET      PIC X(1).
             88 NO-VALUE                  VALUE LOW-VALUE.
             88 GRAPHIC                   VALUE "R".
             88 GENERAL                   VALUE "E".
             88 IA5                       VALUE "I".
             88 VISIBLE                   VALUE "V".
         10 RECORD-FORMAT      PIC X(1).
             88 UNCHANGED                 VALUE LOW-VALUE.
         10 RECORD-SIZE        PIC X(5).
             88 UNCHANGED                 VALUE LOW-VALUE.

The version specification at the beginning of the structure FT-NCOPY-LIST serves to identify the COPY element and must not be overwritten.

The NLMOD macro does not change any values in the structure FT-NLMOD-LIST.

The fields are to be written with left-justified characters and filled with right-justified blanks (default for the COBOL-MOVE statement for character strings).

Fields which should not contain any specifications are to be assigned LOW-VALUE.

If a parameter is not entered, the default values are generated as in the MODIFY-FILE-FT-ATTRIBUTES command.

All other values which should be set in quotation marks at the command interface do not have these quotation marks in the programming interface.

Passwords with integer values must be entered in binary form.

For the assignment of keywords, e.g. *BINARY, *VISIBLE and *YES, use the values which are set in the corresponding 88 step structure.

Description of the data fields

The parameters for FT-NLMOD-LIST have the same names and functions as the corresponding operands for the command MODIFY-FILE-FT-ATTRIBUTES. Please refer to the command descriptions in the manual "openFT (BS2000) - Command Interface ".

In addition to the options offered at the command interface, the COBOL program allows you to address files and libraries by their linkname This is done using the field LINK-NAME in the FT-NLMOD-LIST.

Only the link name or the filename/library name (not both) may be specified.

A link name which is not assigned at execution time leads to the message

FILE UNKNOWN.

FILE-PASSWORD can be used to enter any necessary file passwords.

Example NLMOD

***************************************************************
*  EXAMPLE:                                                   *
*  /MODIFY-FILE-FT-ATTRIBUTES FILE-NAME=LOCALFILE,-           *
*  /               TRANSFER-ATTRIBUTES=(DATA-TYPE=*BINARY)    *
*  FROM A COBOL PROGRAM                                       *
***************************************************************
 IDENTIFICATION DIVISION.
 PROGRAM-ID. TESTNLMOD.
*
 ENVIRONMENT DIVISION.
*
 CONFIGURATION SECTION.
 SPECIAL-NAMES.
     TERMINAL IS TERM.
*
 DATA DIVISION.
 WORKING-STORAGE SECTION.
 77 MAIN-RCODE-STRING                 PIC -ZZZZ9.
 77 SUB-RCODE-STRING                  PIC -ZZZZ9.
 COPY FTNLMOD OF FTLIB.
 COPY FTRETC OF FTLIB.
*
 PROCEDURE DIVISION.
 STEUER SECTION.
 ST-01.
*
*SPECIFY PARAMETERS.
     MOVE LOW-VALUE TO USER-PARAMETERS.
     MOVE "LOCALFILE" TO FILE-NAME.
     SET BINARY-DATA IN DATA-TYPE TO TRUE.
*
*NLMOD-CALLING.
     CALL "NLMOD" USING FT-NLMOD-LIST FT-RETURN-INFO.
*
*RESULT-HANDLING.
     IF OKAY IN MAIN-RETURN-CODE
     THEN
         DISPLAY "NLMOD OKAY" UPON TERM
    ELSE
        MOVE MAIN-RETURN-CODE TO MAIN-RCODE-STRING
        MOVE SUB-RETURN-CODE TO SUB-RCODE-STRING
        DISPLAY "NLMOD REJECTED" UPON TERM
        DISPLAY "MAIN-RETURN-CODE: " MAIN-RCODE-STRING
                " SUB-RETURN-CODE: " SUB-RCODE-STRING
                UPON TERM.
ST-99.
    STOP RUN.