ContentsIndexPreviousNext

C$OPENSAVEBOX Routine

C$OPENSAVEBOX provides a facility for creating an Open or Save As dialog box. These dialogs allow the user to browse the system's file directories and select a file. Not all systems support C$OPENSAVEBOX. However, you can determine at runtime whether the host system supports it.

Usage

CALL "C$OPENSAVEBOX"
   USING OP-CODE, OPENSAVE-DATA
   GIVING OPENSAVE-STATUS

Parameters

OP-CODE Numeric value

Selects which C$OPENSAVEBOX function to perform. The values are described below.

OPENSAVE-DATA :

01  OPENSAVE-DATA.
    03  OPNSAV-FILENAME         PIC X(256).
    03  OPNSAV-FLAGS            PIC 9(4) COMP-X.
    03  OPNSAV-DEFAULT-EXT      PIC X(12).
    03  OPNSAV-TITLE            PIC X(80).
    03  OPNSAV-FILTERS          PIC X(512).
    03  OPNSAV-DEFAULT-FILTER   PIC 9(4) COMP-X.
    03  OPNSAV-DEFAULT-DIR      PIC X(128).
    03  OPNSAV-BASENAME         PIC X(128).

OPENSAVE-DATA is described below.

OPENSAVE-STATUS Signed numeric data item

This item returns the status of the operation. A value of "1" indicates that the operation completed successfully. A zero or negative value indicates that the operation failed.


Note that all of the data items and definitions required by this routine can be found in the COPY library "opensave.def".
Description

C$OPENSAVEBOX performs a variety of operations depending on the passed OP-CODE. The operations are as follows:

OP-CODES:

OPENSAVE-SUPPORTED (OP-CODE value "1")

This operation returns a value that indicates whether the host system supports C$OPENSAVEBOX. If the system supports it, OPENSAVE-STATUS is set to "1". Otherwise, it is set to OPNSAVERR-UNSUPPORTED (value "0"). The OPENSAVE-DATA parameter is not used with this OP-CODE and should be omitted. (Note that Microsoft Windows hosts support C$OPENSAVEBOX.)

OPENSAVE-OPEN-BOX (OP-CODE value "2")

This operation initiates an Open File dialog with the user. The OPENSAVE-DATA structure initializes the dialog box and returns the results. Each field is described below.

OPENSAVE-SAVE-BOX (OP-CODE value "3")

This operation initiates a Save As dialog with the user. The OPENSAVE-DATA structure initializes the dialog box and returns the results. Each field is described below. On some systems, there is no difference between an Open and Save As dialog box. On other systems, there are some differences.

OPENSAVE-DATA

The fields contained in the OPENSAVE-DATA structure are used as follows:

OPNSAV-FILENAME: On input to the routine, this item contains the default file name to use as the initial prompt. Set OPNSAV-FILENAME to spaces if there should be no default name. When the routine returns, this item contains the name of the file selected by the user.

OPNSAV-FLAGS: This item is reserved for future use. It must be set to zero ("0").

OPNSAV-DEFAULT-EXT: This item holds the default file name extension. The extension is the string of characters that appear after the "." in the file name. The value of OPNSAV-DEFAULT-EXT is added to the file name typed by the user, if the user does not type an extension. The default extension should not include the period ".". Set this item to spaces to avoid having a default extension.

OPNSAV-TITLE: This item holds the title of the dialog box. If it is set to spaces, a generic title is applied. The generic title is host-specific.

OPNSAV-FILTERS: The value of OPNSAV-FILTERS describes the set of filters that the dialog box will use to restrict the set of files shown to the user. Filters make it easier for a user to navigate through a large directory by limiting the files shown at once.

Each filter consists of a pair of descriptors. These descriptors are separated by a vertical bar character ("|"). The first descriptor in the pair is displayed in the file type selection box of the Open or Save As dialog box. In Windows, it appears in the List of File Types drop-down box (see the illustration below). The second descriptor is the file name pattern that defines the filter. The file name pattern is formatted as "A [ . B ]" where "A" and "B" are optional text followed by an optional asterisk. An asterisk matches any sequence of characters excluding periods. This descriptor is what the system uses to look for matching files.

Here is a sample OPNSAV-FILTERS setting that contains two filters:

     "COBOL source files (*.cbl)|*.cbl|All files (*.*)|*.*"

The first filter in the example shows only ".cbl" files to the user. The second filter shows all files. The user selects which filter to use based on the descriptions supplied.


Note that filters do not restrict the user from entering names that do not match the supplied pattern. Filters do not limit the user's choices, they only simplify the process of choosing.
Set OPNSAV-FILTERS to spaces if you don't want any filters.

Some systems do not support multiple filters. In this case, only the initial filter will be used. See OPNSAV-DEFAULT-FILTER to determine how to select the initial filter.

OPNSAV-DEFAULT-FILTER: This item is used in conjunction with OPNSAV-FILTERS. The value of OPNSAV-DEFAULT-FILTER determines which of the given filters to use as the initial filter. A value of "1" selects the first filter pair, "2" selects the second pair, and so on. A value of zero also selects the first pair. This setting is not used if no filters are defined.

OPNSAV-DEFAULT-DIR: This item holds the default directory to use for the selected file. The dialog box initially displays the files found in this directory. If this item is set to spaces, the current directory is used. Note that the value of this item only defines the default directory. It does not prevent the user from selecting files in a different directory.

OPNSAV-BASENAME: When the routine returns, this item contains the base file name of the file chosen by the user. This differs from the value of OPNSAV-FILENAME in that all directory information is removed, leaving only the file name.


Important: You should use the INITIALIZE verb on OPENSAVE-DATA before you fill in the data fields. This ensures that you have set all the fields to the default values and protects you from possible future changes to the OPENSAVE-DATA structure.

Also note that the OPENSAVE-DATA item is fairly large (1120 bytes). You can conserve memory by using C$OPENSAVEBOX from a utility subprogram that you write. This subprogram would include OPENSAVE-DATA. After using the subprogram, you can free the memory with the CANCEL verb. In this way, you need to keep OPENSAVE-DATA in memory only while you are using it. Alternatively, you can use the M$ALLOC library routine to allocate memory to hold OPENSAVE-DATA, and then free that memory after you are done.
Error Handling

C$OPENSAVEBOX returns a value of "1" when successful. Otherwise, it returns one of the following values (found in "opensave.def"):

OPNSAVERR-UNSUPPORTED: This error indicates that the C$OPENSAVEBOX routine is not supported by the current host system.

OPNSAVERR-CANCELLED: This error indicates that the user clicked the "Cancel" button or typed the Escape key while using the dialog box.

OPNSAVERR-NO-MEMORY: This error indicates that not enough memory could be allocated to load the dialog box.

OPNSAVERR-NAME-TOO-LARGE: This error indicates that the name entered by the user does not fit in OPNSAV-FILENAME.

Example

This example uses C$OPENSAVEBOX to prompt for a text file name, and uses M$ALLOC to dynamically allocate OPENSAVE-DATA, freeing it after it is no longer needed.

WORKING-STORAGE SECTION.
77  OPENSAVE-DATA-SIZE  PIC 9(4) BINARY.
77  OPENSAVE-DATA-ADDR  POINTER.
77  OPENSAVE-STATUS  PIC S99.
    88  OPENSAVE-OK  VALUE 1.
77  FILE-NAME   PIC X(256).

LINKAGE SECTION.
COPY "opensave.def".

PROCEDURE DIVISION.
MAIN-LOGIC.
   SET OPENSAVE-DATA-SIZE TO SIZE OF OPENSAVE-DATA.
   CALL "M$ALLOC"
      USING OPENSAVE-DATA-SIZE, OPENSAVE-DATA-ADDR.
   IF OPENSAVE-DATA-ADDR = NULL
      {error handling here}
   ELSE
      SET ADDRESS OF OPENSAVE-DATA
          TO OPENSAVE-DATA-ADDR
      INITIALIZE OPENSAVE-DATA
      MOVE
          "Text files (*.txt)|*.txt|All files (*.*)|*.*"
          TO OPNSAV-FILTERS
      MOVE "txt" TO OPNSAV-DEFAULT-EXT
      CALL "C$OPENSAVEBOX" USING OPENSAVE-SAVE-BOX,
                                 OPENSAVE-DATA
                           GIVING OPENSAVE-STATUS

      IF OPENSAVE-OK
          MOVE OPNSAV-FILENAME TO FILE-NAME
      END-IF
      CALL "M$FREE" USING OPENSAVE-DATA-ADDR
   END-IF.