Directories in COBOL
Here’s the translation of the Go code to COBOL, with explanations in Markdown format suitable for Hugo:
Our program demonstrates working with directories in COBOL. Here’s the full source code:
IDENTIFICATION DIVISION.
PROGRAM-ID. DIRECTORIES.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT WORKFILE ASSIGN TO "subdir/file1"
ORGANIZATION IS LINE SEQUENTIAL.
SELECT PARENTFILE ASSIGN TO "subdir/parent/file2"
ORGANIZATION IS LINE SEQUENTIAL.
SELECT CHILDFILE ASSIGN TO "subdir/parent/child/file4"
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD WORKFILE.
FD PARENTFILE.
FD CHILDFILE.
WORKING-STORAGE SECTION.
01 WS-DIRECTORY-NAME PIC X(50).
01 WS-FILE-NAME PIC X(50).
01 WS-RETURN-CODE PIC 9(4).
PROCEDURE DIVISION.
MAIN-PROCEDURE.
DISPLAY "Creating directories and files..."
*> Create a new sub-directory
MOVE "subdir" TO WS-DIRECTORY-NAME
CALL "CBL_CREATE_DIR" USING WS-DIRECTORY-NAME
RETURNING WS-RETURN-CODE
IF WS-RETURN-CODE NOT = 0
DISPLAY "Error creating directory: " WS-DIRECTORY-NAME
END-IF
*> Create an empty file in the sub-directory
OPEN OUTPUT WORKFILE
CLOSE WORKFILE
*> Create a hierarchy of directories
MOVE "subdir/parent/child" TO WS-DIRECTORY-NAME
CALL "CBL_CREATE_DIR" USING WS-DIRECTORY-NAME
RETURNING WS-RETURN-CODE
IF WS-RETURN-CODE NOT = 0
DISPLAY "Error creating directory: " WS-DIRECTORY-NAME
END-IF
*> Create empty files in the hierarchy
OPEN OUTPUT PARENTFILE
CLOSE PARENTFILE
OPEN OUTPUT CHILDFILE
CLOSE CHILDFILE
*> List directory contents
DISPLAY "Listing subdir/parent"
MOVE "subdir/parent" TO WS-DIRECTORY-NAME
CALL "C$LIST-DIRECTORY" USING WS-DIRECTORY-NAME
WS-FILE-NAME
PERFORM UNTIL WS-FILE-NAME = SPACES
DISPLAY " " WS-FILE-NAME
CALL "C$LIST-DIRECTORY" USING WS-DIRECTORY-NAME
WS-FILE-NAME
END-PERFORM
*> Change current working directory
MOVE "subdir/parent/child" TO WS-DIRECTORY-NAME
CALL "CBL_CHANGE_DIR" USING WS-DIRECTORY-NAME
RETURNING WS-RETURN-CODE
IF WS-RETURN-CODE NOT = 0
DISPLAY "Error changing directory: " WS-DIRECTORY-NAME
END-IF
*> List contents of current directory
DISPLAY "Listing current directory (subdir/parent/child)"
MOVE SPACES TO WS-DIRECTORY-NAME
CALL "C$LIST-DIRECTORY" USING WS-DIRECTORY-NAME
WS-FILE-NAME
PERFORM UNTIL WS-FILE-NAME = SPACES
DISPLAY " " WS-FILE-NAME
CALL "C$LIST-DIRECTORY" USING WS-DIRECTORY-NAME
WS-FILE-NAME
END-PERFORM
*> Change back to original directory
MOVE "../../.." TO WS-DIRECTORY-NAME
CALL "CBL_CHANGE_DIR" USING WS-DIRECTORY-NAME
RETURNING WS-RETURN-CODE
IF WS-RETURN-CODE NOT = 0
DISPLAY "Error changing directory: " WS-DIRECTORY-NAME
END-IF
STOP RUN.
This COBOL program demonstrates various operations with directories:
We start by creating a new sub-directory using the
CBL_CREATE_DIR
system routine.We create empty files in the directories using standard COBOL file handling.
We use
CBL_CREATE_DIR
again to create a hierarchy of directories.To list directory contents, we use the
C$LIST-DIRECTORY
routine, which is similar toReadDir
in the Go example.We change the current working directory using
CBL_CHANGE_DIR
, which is equivalent toChdir
in Go.We demonstrate listing the contents of the current directory after changing to it.
Finally, we change back to the original directory.
Note that COBOL doesn’t have a direct equivalent to Go’s filepath.WalkDir
for recursively visiting directories. To achieve similar functionality, you would need to implement a recursive routine using the directory listing capabilities shown here.
To run the program, compile it with your COBOL compiler and execute the resulting program. The exact commands will depend on your COBOL environment.
$ cobc -x directories.cob
$ ./directories
This will create the directory structure, create empty files, and display the directory contents as specified in the program.
Remember that COBOL file and directory operations can be highly dependent on the specific COBOL implementation and operating system. The routines used here (like CBL_CREATE_DIR
and C$LIST-DIRECTORY
) are common extensions but may not be available in all COBOL environments.