C$LIST-DIRECTORY

The C$LIST-DIRECTORY routine lists the contents of a selected directory. Each operating system has a unique method for performing this task. C$LIST-DIRECTORY provides a single method that will work for all operating systems.
Note: This ACUCOBOL-GT library routine is available in this COBOL version. Any compatibility issues in this COBOL system are in the Compatibility Issues section at the end of the topic.

Usage

CALL "C$LIST-DIRECTORY" 
    USING OP-CODE, parameters 

Parameters

OP-CODE PIC 99 COMP-X

Indicates which C$LIST-DIRECTORY operation to perform. The operations are described below.

Parameters vary depending on the op-code chosen.

Parameters provide information and hold results for the op-code specified. These parameters are described below.

Description

C$LIST-DIRECTORY allows you to get the names of files residing in a given directory. It accomplishes this through three distinct operations. The first operation opens the specified directory. The second operation returns the filenames in the list, one-at-a-time. The third operation closes the directory and deallocates all memory used by the routine. C$LIST-DIRECTORY has the following operation codes (defined in acucobol.def):

LISTDIR-OPEN (VALUE 1)
Opens the specified directory. It has two parameters:
Directoryname PIC X(n)
Contains the name of the directory to open. This directory must exist, and you must have permissions to read the directory. You may use remote name syntax if AcuServer is installed on the remote machine. The "@[DISPLAY]:" for Thin Client support may be used. For example:
C$LIST-DIRECTORY using listdir-open, 
"@[DISPLAY]:C:\path", pattern 
Pattern PIC X(n)
Specifies the type of filename for which to search. This routine supports "wildcards," meaning that the character "*" will match any number of characters, and the character "?" will match any single character. For example, you can search by file suffix (*.def) or by a common part of a file name (acu*).

If the call to LISTDIR-OPEN is successful, RETURN-CODE contains a handle to the list. The value in RETURN-CODE should be moved to a data item that is USAGE HANDLE. That data item should be passed as the directory handle to the other C$LISTDIRECTORY operations. If the call to LISTDIR-OPEN fails (if the directory does not exist, contains no files, or you do not have permission to read the directory), RETURN-CODE is set to a NULL handle.

LISTDIR-NEXT (VALUE 2)
Reads each filename from the open directory. It has two parameters:
Handle USAGE HANDLE
The handle returned in the LISTDIR-OPEN operation.
Filename PIC X(n)
The location of the next filename to be returned. If the directory listing is finished, it is filled with spaces.

The call to LISTDIR-NEXT can include an additional argument, LISTDIR-FILE-INFORMATION (defined in "acucobol.def"), which receives information about the returned file name. This is an optional group item which returns information about the following data items:

LISTDIR-FILE-TYPE
The file type can be one of the following:

B = block device
C = character device
D = directory
F = regular file
P = pipe (FIFO)
S = socket
U = unknown

LISTDIR-FILE-CREATION-TIME
The creation time is the date (and time) that the file was originally created.
LISTDIR-FILE-LAST-ACCESS-TIME
The last access time is the date (and time) that the file was last accessed by some application (usually when the file was queried in some way).
LISTDIR-FILE-LAST-MODIFICATION-TIME
The last modification time is the date (and time) the file was last written to.
LISTDIR-FILE-SIZE
The size of the file is given in bytes.
LISTDIR-CLOSE (VALUE 3)
Releases the resources used by the other operations. It must be called to avoid memory leaks. It has one parameter, handle, which is the same data item used by the LISTDIR-NEXT operation.
Handle USAGE HANDLE
The handle returned in the LISTDIR-OPEN operation.
Note: Because the supported file types vary by operating system, The data items in the above list have slightly different meanings depending on your operating system. Even on operating systems that support these values, some file systems may not. Some versions of the UNIX® operating system may change these values when permissions are changed. Refer to your operating system documentation for specific definitions.

Example

The following example lists the contents of a directory with repeated calls C$LISTDIRECTORY:

WORKING-STORAGE SECTION.
copy "def/acucobol.def".
01  pattern       pic x(5) value "*.vbs".
01  directory     pic x(20) value "/virusscan".
01  filename      pic x(128).
01  mydir         usage handle.
PROCEDURE DIVISION.
MAIN.
* CALL LISTDIR-OPEN to get a directory handle.
    call "C$LIST-DIRECTORY" 
       using listdir-open, directory, pattern.
    move return-code to mydir.
    if mydir = 0
       stop run
    end-if.
* CALL LISTDIR-NEXT to get the names of the files.  
* Repeat this operation until a filename containing only 
* spaces is returned.  The filenames are not necessarily 
* returned in any particular order.  Filenames may be 
* sorted on some machines and not on others.
    perform with test after until filename = spaces
       call "C$LIST-DIRECTORY" 
          using listdir-next, mydir, filename
    end-perform.
* CALL LISTDIR-CLOSE to close the directory and deallocate
* memory. Omitting this call will result in memory leaks.
    call "C$LIST-DIRECTORY" using listdir-close, mydir.
    stop run.

Compatibility Issues

  • You must compile with the DIALECT"ACU" Compiler directive when using this library routine.
  • "@[DISPLAY]" is not supported in this COBOL system.