├── index.html
├── config.cpy
├── file-structs.cpy
├── http-structs.cpy
├── Makefile
├── socket-defs.cpy
├── mime-types.cbl
├── path-utils.cbl
├── README.md
├── file-ops.cbl
├── url-decode.cbl
├── webserver.cbl
└── http-handler.cbl
/index.html:
--------------------------------------------------------------------------------
1 |
Hello from COBOL!
2 |
--------------------------------------------------------------------------------
/config.cpy:
--------------------------------------------------------------------------------
1 | *> Server configuration constants (copybook for reuse across modules)
2 | *> TCP port number for HTTP server (standard development port)
3 | 01 SERVER-PORT PIC 9(5) VALUE 8080.
4 | *> Maximum pending connections in listen queue
5 | 01 MAX-CONNECTIONS PIC 9(3) VALUE 10.
6 | *> Maximum size for file content and HTTP responses (64KB)
7 | 01 BUFFER-SIZE PIC 9(8) VALUE 65536.
8 | *> Maximum length for file paths (prevents buffer overflow)
9 | 01 MAX-PATH-LEN PIC 9(4) VALUE 512.
10 |
--------------------------------------------------------------------------------
/file-structs.cpy:
--------------------------------------------------------------------------------
1 | *> File handling data structures and flags
2 | *> Buffer to store entire file content (64KB maximum)
3 | 01 FILE-BUFFER PIC X(65536).
4 | *> Actual size of file in bytes (binary for system compatibility)
5 | 01 FILE-SIZE PIC 9(8) COMP-5.
6 | *> Original file path from HTTP request
7 | 01 FILE-PATH PIC X(512).
8 | *> Security-validated path safe for file system access
9 | 01 SANITIZED-PATH PIC X(512).
10 | *> MIME content type determined from file extension
11 | 01 MIME-TYPE PIC X(64).
12 | *> File extension extracted for MIME type lookup
13 | 01 FILE-EXTENSION PIC X(10).
14 | *> Flag indicating whether requested file exists
15 | 01 FILE-EXISTS-FLAG PIC 9 VALUE 0.
16 | *> Condition names for readable file existence checking
17 | 88 FILE-EXISTS VALUE 1.
18 | 88 FILE-NOT-FOUND VALUE 0.
19 |
--------------------------------------------------------------------------------
/http-structs.cpy:
--------------------------------------------------------------------------------
1 | *> HTTP request and response data structures
2 | *> Structure for parsing HTTP requests
3 | 01 HTTP-REQUEST.
4 | *> HTTP method (GET, POST, PUT, etc.) - up to 10 characters
5 | 05 REQUEST-METHOD PIC X(10).
6 | *> Requested URL path - up to 512 characters
7 | 05 REQUEST-PATH PIC X(512).
8 | *> Raw HTTP request data from client - 8KB maximum
9 | 05 REQUEST-BUFFER PIC X(8192).
10 |
11 | *> Structure for building HTTP responses
12 | 01 HTTP-RESPONSE.
13 | *> Complete HTTP response (headers + content) - 64KB maximum
14 | 05 RESPONSE-BUFFER PIC X(65536).
15 | *> Actual length of response data (binary for efficiency)
16 | 05 RESPONSE-LEN PIC 9(8) COMP-5.
17 |
18 | *> Utility fields for HTTP header construction
19 | *> HTTP status line (e.g., "HTTP/1.1 200 OK")
20 | 01 STATUS-LINE PIC X(50).
21 | *> Content-Type header value (e.g., "text/html")
22 | 01 CONTENT-TYPE-HDR PIC X(100).
23 | *> Content-Length header value (e.g., "1024")
24 | 01 CONTENT-LENGTH-HDR PIC X(50).
25 |
--------------------------------------------------------------------------------
/Makefile:
--------------------------------------------------------------------------------
1 | # Makefile for COBOL Web Server
2 | # Uses GnuCOBOL compiler
3 |
4 | CC = cobc
5 | CFLAGS = -free -x
6 | CFLAGS_OBJ = -free -c
7 |
8 | # Copybook directory
9 | COPYPATH = -I.
10 |
11 | # Target executable
12 | TARGET = webserver
13 |
14 | # Module object files
15 | MODULES = path-utils.o mime-types.o file-ops.o http-handler.o url-decode.o
16 |
17 | # Default target
18 | all: $(TARGET)
19 |
20 | # Compile modules to object files
21 | path-utils.o: path-utils.cbl
22 | $(CC) $(CFLAGS_OBJ) $(COPYPATH) path-utils.cbl
23 |
24 | mime-types.o: mime-types.cbl
25 | $(CC) $(CFLAGS_OBJ) $(COPYPATH) mime-types.cbl
26 |
27 | file-ops.o: file-ops.cbl
28 | $(CC) $(CFLAGS_OBJ) $(COPYPATH) file-ops.cbl
29 |
30 | http-handler.o: http-handler.cbl http-structs.cpy file-structs.cpy
31 | $(CC) $(CFLAGS_OBJ) $(COPYPATH) http-handler.cbl
32 |
33 | url-decode.o: url-decode.cbl
34 | $(CC) $(CFLAGS_OBJ) $(COPYPATH) url-decode.cbl
35 |
36 | # Compile main program and link with modules
37 | $(TARGET): webserver.cbl $(MODULES) config.cpy socket-defs.cpy http-structs.cpy
38 | $(CC) $(CFLAGS) $(COPYPATH) webserver.cbl $(MODULES) -o $(TARGET)
39 |
40 | # Clean build artifacts
41 | clean:
42 | rm -f $(TARGET) *.so *.dylib *.o *.c *.c.l.h *.c.h
43 |
44 | # Run the server
45 | run: $(TARGET)
46 | ./$(TARGET)
47 |
48 | .PHONY: all clean run
49 |
--------------------------------------------------------------------------------
/socket-defs.cpy:
--------------------------------------------------------------------------------
1 | *> Socket system call definitions and data structures
2 | *> Server socket file descriptor (signed binary for system calls)
3 | 01 SOCKET-HANDLE PIC S9(9) COMP-5.
4 | *> Client connection socket file descriptor
5 | 01 CLIENT-SOCKET PIC S9(9) COMP-5.
6 | *> Return value from socket system calls (negative = error)
7 | 01 SOCKET-RESULT PIC S9(9) COMP-5.
8 | *> Number of bytes received from client
9 | 01 BYTES-READ PIC S9(9) COMP-5.
10 | *> Number of bytes sent to client
11 | 01 BYTES-SENT PIC S9(9) COMP-5.
12 |
13 | *> Internet socket address structure (matches C struct sockaddr_in)
14 | 01 SERVER-ADDRESS.
15 | *> Address family: AF_INET (2) for IPv4
16 | 05 SA-FAMILY PIC 9(4) COMP-5 VALUE 2.
17 | *> Port number in network byte order
18 | 05 SA-PORT PIC 9(4) COMP-5.
19 | *> IP address (0 = INADDR_ANY, bind to all interfaces)
20 | 05 SA-ADDR PIC 9(8) COMP-5 VALUE 0.
21 | *> Padding to match C struct size (8 bytes)
22 | 05 FILLER PIC X(8) VALUE SPACES.
23 |
24 | *> Size of socket address structure (16 bytes for IPv4)
25 | 01 ADDR-LEN PIC 9(9) COMP-5 VALUE 16.
26 | *> Maximum pending connections for listen() system call
27 | 01 BACKLOG PIC 9(9) COMP-5 VALUE 10.
28 | *> Socket option value for SO_REUSEADDR (1 = enable)
29 | 01 SOCKET-OPT PIC 9(9) COMP-5 VALUE 1.
30 |
--------------------------------------------------------------------------------
/mime-types.cbl:
--------------------------------------------------------------------------------
1 | *> MIME type detection based on file extensions
2 | IDENTIFICATION DIVISION.
3 | PROGRAM-ID. MIME-TYPES.
4 |
5 | DATA DIVISION.
6 | WORKING-STORAGE SECTION.
7 | *> Index for scanning filename backwards to find extension
8 | 01 WS-INDEX PIC 9(4) COMP.
9 | *> Length of filename string
10 | 01 WS-LENGTH PIC 9(4) COMP.
11 | *> Starting position of file extension after the dot
12 | 01 WS-EXT-START PIC 9(4) COMP.
13 |
14 | *> Parameters from calling program
15 | LINKAGE SECTION.
16 | *> Full file path to analyze for extension
17 | 01 LS-FILE-PATH PIC X(512).
18 | *> Output MIME type string (e.g., "text/html")
19 | 01 LS-MIME-TYPE PIC X(64).
20 |
21 | PROCEDURE DIVISION USING LS-FILE-PATH LS-MIME-TYPE.
22 |
23 | *> Main MIME type detection logic
24 | MAIN-LOGIC.
25 | *> Default MIME type for unknown extensions (binary data)
26 | MOVE "application/octet-stream" TO LS-MIME-TYPE
27 |
28 | *> Find the file extension by locating the last dot in filename
29 | MOVE 0 TO WS-EXT-START
30 | *> Calculate filename length (excluding trailing spaces)
31 | INSPECT LS-FILE-PATH TALLYING WS-LENGTH
32 | FOR CHARACTERS BEFORE INITIAL SPACE
33 |
34 | *> Scan backwards from end of filename to find last dot
35 | PERFORM VARYING WS-INDEX FROM WS-LENGTH BY -1
36 | UNTIL WS-INDEX < 1
37 | IF LS-FILE-PATH(WS-INDEX:1) = "."
38 | COMPUTE WS-EXT-START = WS-INDEX + 1
39 | EXIT PERFORM
40 | END-IF
41 | END-PERFORM
42 |
43 | *> If no extension found, return default MIME type
44 | IF WS-EXT-START = 0
45 | GOBACK
46 | END-IF
47 |
48 | *> Map file extensions to MIME types for HTTP Content-Type header
49 | *> EVALUATE compares first 4 characters of extension
50 | EVALUATE LS-FILE-PATH(WS-EXT-START:4)
51 | WHEN "html"
52 | MOVE "text/html" TO LS-MIME-TYPE
53 | WHEN "htm "
54 | MOVE "text/html" TO LS-MIME-TYPE
55 | WHEN "css "
56 | MOVE "text/css" TO LS-MIME-TYPE
57 | WHEN "js "
58 | MOVE "application/javascript" TO LS-MIME-TYPE
59 | WHEN "json"
60 | MOVE "application/json" TO LS-MIME-TYPE
61 | WHEN "xml "
62 | MOVE "application/xml" TO LS-MIME-TYPE
63 | WHEN "txt "
64 | MOVE "text/plain" TO LS-MIME-TYPE
65 | WHEN "png "
66 | MOVE "image/png" TO LS-MIME-TYPE
67 | WHEN "jpg "
68 | MOVE "image/jpeg" TO LS-MIME-TYPE
69 | WHEN "jpeg"
70 | MOVE "image/jpeg" TO LS-MIME-TYPE
71 | WHEN "gif "
72 | MOVE "image/gif" TO LS-MIME-TYPE
73 | WHEN "svg "
74 | MOVE "image/svg+xml" TO LS-MIME-TYPE
75 | WHEN "ico "
76 | MOVE "image/x-icon" TO LS-MIME-TYPE
77 | WHEN "pdf "
78 | MOVE "application/pdf" TO LS-MIME-TYPE
79 | END-EVALUATE
80 |
81 | GOBACK.
82 |
--------------------------------------------------------------------------------
/path-utils.cbl:
--------------------------------------------------------------------------------
1 | *> Path validation and sanitization module for security
2 | IDENTIFICATION DIVISION.
3 | PROGRAM-ID. PATH-UTILS.
4 |
5 | DATA DIVISION.
6 | WORKING-STORAGE SECTION.
7 | *> Index for character-by-character path scanning
8 | 01 WS-INDEX PIC 9(4) COMP.
9 | *> Length of input path string
10 | 01 WS-LENGTH PIC 9(4) COMP.
11 | *> Current character being examined
12 | 01 WS-CHAR PIC X.
13 | *> Previous character (for detecting ".." sequences)
14 | 01 WS-PREV-CHAR PIC X VALUE SPACE.
15 |
16 | *> Parameters passed from calling program
17 | LINKAGE SECTION.
18 | *> Original path from HTTP request
19 | 01 LS-INPUT-PATH PIC X(512).
20 | *> Sanitized path safe for file system access
21 | 01 LS-OUTPUT-PATH PIC X(512).
22 | *> Return code indicating validation result
23 | 01 LS-RETURN-CODE PIC 9.
24 | *> Condition names for readable code (88-level items)
25 | 88 PATH-VALID VALUE 0.
26 | 88 PATH-INVALID VALUE 1.
27 |
28 | PROCEDURE DIVISION USING LS-INPUT-PATH LS-OUTPUT-PATH
29 | LS-RETURN-CODE.
30 |
31 | *> Main path validation and sanitization logic
32 | MAIN-LOGIC.
33 | *> Initialize output path and assume path is valid
34 | MOVE SPACES TO LS-OUTPUT-PATH
35 | MOVE 0 TO LS-RETURN-CODE
36 |
37 | *> Calculate actual length of input path (excluding trailing spaces)
38 | INSPECT LS-INPUT-PATH TALLYING WS-LENGTH
39 | FOR CHARACTERS BEFORE INITIAL SPACE
40 |
41 | *> DISPLAY "PATH-UTILS: Input length=" WS-LENGTH
42 | *> DISPLAY "PATH-UTILS: Input path='" LS-INPUT-PATH(1:50) "'"
43 |
44 | *> Reject empty paths as invalid
45 | IF WS-LENGTH = 0
46 | *> DISPLAY "PATH-UTILS: Empty path, rejecting"
47 | MOVE 1 TO LS-RETURN-CODE
48 | GOBACK
49 | END-IF
50 |
51 | *> Handle root path (/) by serving default index.html
52 | IF LS-INPUT-PATH = "/" OR LS-INPUT-PATH(1:2) = "/ "
53 | *> DISPLAY "PATH-UTILS: Root path, using index.html"
54 | MOVE "index.html" TO LS-OUTPUT-PATH
55 | GOBACK
56 | END-IF
57 |
58 | *> Remove leading slash to create relative path
59 | *> Web paths start with / but file system needs relative paths
60 | IF LS-INPUT-PATH(1:1) = "/"
61 | MOVE LS-INPUT-PATH(2:) TO LS-OUTPUT-PATH
62 | ELSE
63 | MOVE LS-INPUT-PATH TO LS-OUTPUT-PATH
64 | END-IF
65 |
66 | *> DISPLAY "PATH-UTILS: Output path='" LS-OUTPUT-PATH(1:50) "'"
67 |
68 | *> Reject absolute paths as security risk
69 | *> Prevents access outside current directory
70 | IF LS-OUTPUT-PATH(1:1) = "/"
71 | *> DISPLAY "PATH-UTILS: Absolute path detected"
72 | MOVE 1 TO LS-RETURN-CODE
73 | GOBACK
74 | END-IF
75 |
76 | *> Scan path character by character for security threats
77 | *> Look for ".." sequences that could access parent directories
78 | PERFORM VARYING WS-INDEX FROM 1 BY 1
79 | UNTIL WS-INDEX > 510
80 | MOVE LS-OUTPUT-PATH(WS-INDEX:1) TO WS-CHAR
81 | *> Stop at end of string
82 | IF WS-CHAR = SPACE OR WS-CHAR = LOW-VALUE
83 | EXIT PERFORM
84 | END-IF
85 | *> Detect ".." pattern (directory traversal attack)
86 | IF WS-CHAR = "." AND WS-PREV-CHAR = "."
87 | MOVE 1 TO LS-RETURN-CODE
88 | GOBACK
89 | END-IF
90 | MOVE WS-CHAR TO WS-PREV-CHAR
91 | END-PERFORM
92 |
93 | *> Additional check for paths starting with "../" or exactly ".."
94 | *> These are classic directory traversal patterns
95 | IF LS-OUTPUT-PATH(1:3) = "../" OR
96 | LS-OUTPUT-PATH = ".."
97 | *> DISPLAY "PATH-UTILS: Directory traversal detected"
98 | MOVE 1 TO LS-RETURN-CODE
99 | END-IF
100 |
101 | *> DISPLAY "PATH-UTILS: Final return code=" LS-RETURN-CODE
102 |
103 | GOBACK.
104 |
--------------------------------------------------------------------------------
/README.md:
--------------------------------------------------------------------------------
1 | # Webbol
2 |
3 | A minimal static web server written in COBOL using GnuCOBOL.
4 |
5 | ## Features
6 |
7 | - Serves static files from the current directory
8 | - Automatic MIME type detection for common file types
9 | - HTTP status codes: 200 (OK), 403 (Forbidden), 404 (Not Found), 413 (Payload Too Large)
10 | - Path traversal attack prevention
11 | - Clean request logging with full HTTP headers
12 | - Defaults to `index.html` for root path requests
13 |
14 | ## Requirements
15 |
16 | - GnuCOBOL (cobc) compiler
17 | - POSIX-compatible operating system (Linux, macOS, BSD)
18 | - make
19 |
20 | ### Installing GnuCOBOL
21 |
22 | **macOS:**
23 | ```bash
24 | brew install gnucobol
25 | ```
26 |
27 | **Ubuntu/Debian:**
28 | ```bash
29 | sudo apt-get install gnucobol
30 | ```
31 |
32 | **Fedora/RHEL:**
33 | ```bash
34 | sudo dnf install gnucobol
35 | ```
36 |
37 | ## Building
38 |
39 | Clone or download the repository, then compile:
40 |
41 | ```bash
42 | make
43 | ```
44 |
45 | This will compile all modules and create the `webserver` executable.
46 |
47 | To clean build artifacts:
48 |
49 | ```bash
50 | make clean
51 | ```
52 |
53 | ## Usage
54 |
55 | Start the server from the directory you want to serve:
56 |
57 | ```bash
58 | ./webserver
59 | ```
60 |
61 | The server will start on port 8080 and serve files from the current directory.
62 |
63 | ### Example
64 |
65 | ```bash
66 | # Create a test HTML file
67 | echo "Hello from COBOL!
" > index.html
68 |
69 | # Start the server
70 | ./webserver
71 |
72 | # In another terminal, test it
73 | curl http://localhost:8080/
74 | ```
75 |
76 | ### Accessing the Server
77 |
78 | Once running, you can access files via:
79 |
80 | - `http://localhost:8080/` - serves `index.html` from the current directory
81 | - `http://localhost:8080/filename.html` - serves the specified file
82 | - `http://localhost:8080/path/to/file.txt` - serves files from subdirectories
83 |
84 | Press `Ctrl+C` to stop the server.
85 |
86 | ## Configuration
87 |
88 | To change the server port, edit `config.cpy` and modify the `SERVER-PORT` value:
89 |
90 | ```cobol
91 | 01 SERVER-PORT PIC 9(5) VALUE 8080.
92 | ```
93 |
94 | Then recompile with `make`.
95 |
96 | ## Project Structure
97 |
98 | ```
99 | webbol/
100 | ├── Makefile # Build configuration
101 | ├── README.md # This file
102 | ├── config.cpy # Server configuration
103 | ├── socket-defs.cpy # Socket structure definitions
104 | ├── http-structs.cpy # HTTP data structures
105 | ├── file-structs.cpy # File handling structures
106 | ├── path-utils.cbl # Path validation and sanitization
107 | ├── mime-types.cbl # MIME type detection
108 | ├── file-ops.cbl # File reading operations
109 | ├── http-handler.cbl # HTTP request/response handling
110 | └── webserver.cbl # Main server program
111 | ```
112 |
113 | ## Supported MIME Types
114 |
115 | - HTML: `text/html`
116 | - CSS: `text/css`
117 | - JavaScript: `application/javascript`
118 | - JSON: `application/json`
119 | - XML: `application/xml`
120 | - Plain text: `text/plain`
121 | - PNG: `image/png`
122 | - JPEG: `image/jpeg`
123 | - GIF: `image/gif`
124 | - SVG: `image/svg+xml`
125 | - ICO: `image/x-icon`
126 | - PDF: `application/pdf`
127 |
128 | Additional MIME types can be added by editing `mime-types.cbl`.
129 |
130 | ## Security Features
131 |
132 | - Path traversal prevention: Blocks requests containing `..` sequences
133 | - Directory access restriction: Only serves files from the current directory and subdirectories
134 | - Safe file handling: Validates all paths before file system access
135 |
136 | ## Limitations
137 |
138 | - Single-threaded: Handles one request at a time
139 | - No SSL/TLS support
140 | - Maximum file size: 64KB
141 | - Line sequential file organization only (text files)
142 | - No caching or compression
143 | - No range requests or partial content support
144 |
145 | ## Troubleshooting
146 |
147 | **Port already in use:**
148 | ```
149 | Bind failed - check if port is in use
150 | ```
151 | Another process is using port 8080. Either stop that process or change the port in `config.cpy`.
152 |
153 | **Permission denied:**
154 | Ensure the files you're trying to serve have read permissions and the current user can access them.
155 |
156 | **File not found (404):**
157 | Verify the file exists in the current directory where the server is running. File paths are case-sensitive.
158 |
159 | ## License
160 |
161 | This project is released into the public domain. Use it however you'd like.
162 |
163 | ## Acknowledgments
164 |
165 | Built with GnuCOBOL, demonstrating that COBOL can still be used for modern systems programming tasks.
166 |
--------------------------------------------------------------------------------
/file-ops.cbl:
--------------------------------------------------------------------------------
1 | IDENTIFICATION DIVISION.
2 | PROGRAM-ID. FILE-OPS.
3 |
4 | ENVIRONMENT DIVISION.
5 | INPUT-OUTPUT SECTION.
6 | FILE-CONTROL.
7 | SELECT DISK-FILE ASSIGN TO WS-FILE-NAME
8 | ORGANIZATION IS LINE SEQUENTIAL
9 | FILE STATUS IS WS-FILE-STATUS.
10 |
11 | DATA DIVISION.
12 | FILE SECTION.
13 | FD DISK-FILE.
14 | 01 FILE-RECORD PIC X(1024).
15 |
16 | WORKING-STORAGE SECTION.
17 | 01 WS-FILE-NAME PIC X(512).
18 | 01 WS-FILE-STATUS PIC XX.
19 | 01 WS-BUFFER-POS PIC 9(8) COMP-5.
20 | 01 WS-LINE-LEN PIC 9(4) COMP-5.
21 | 01 WS-EOF-FLAG PIC 9 VALUE 0.
22 | 01 WS-OVERFLOW-FLAG PIC 9 VALUE 0.
23 |
24 | LINKAGE SECTION.
25 | 01 LS-FILE-PATH PIC X(512).
26 | 01 LS-FILE-BUFFER PIC X(65536).
27 | 01 LS-FILE-SIZE PIC 9(8) COMP-5.
28 | 01 LS-RETURN-CODE PIC 9.
29 | 88 FILE-READ-OK VALUE 0.
30 | 88 FILE-READ-ERROR VALUE 1.
31 | 88 FILE-TOO-LARGE VALUE 2.
32 |
33 | PROCEDURE DIVISION USING LS-FILE-PATH LS-FILE-BUFFER
34 | LS-FILE-SIZE LS-RETURN-CODE.
35 |
36 | MAIN-LOGIC.
37 | MOVE SPACES TO LS-FILE-BUFFER
38 | MOVE 0 TO LS-FILE-SIZE
39 | MOVE 0 TO LS-RETURN-CODE
40 | MOVE 1 TO WS-BUFFER-POS
41 | MOVE 0 TO WS-OVERFLOW-FLAG
42 |
43 | MOVE SPACES TO WS-FILE-NAME
44 | *> Find actual length of file path including embedded spaces
45 | *> Scan backwards from end to find last non-space, non-null character
46 | *> This allows filenames with spaces (e.g. "test file.html")
47 | MOVE 0 TO WS-LINE-LEN
48 | PERFORM VARYING WS-LINE-LEN FROM 512 BY -1
49 | UNTIL WS-LINE-LEN < 1
50 | IF LS-FILE-PATH(WS-LINE-LEN:1) NOT = SPACE AND
51 | LS-FILE-PATH(WS-LINE-LEN:1) NOT = LOW-VALUE
52 | EXIT PERFORM
53 | END-IF
54 | END-PERFORM
55 | *> Copy the trimmed path to file name variable
56 | IF WS-LINE-LEN > 0
57 | MOVE LS-FILE-PATH(1:WS-LINE-LEN) TO WS-FILE-NAME
58 | ELSE
59 | MOVE LS-FILE-PATH TO WS-FILE-NAME
60 | END-IF
61 |
62 | *> DISPLAY "FILE-OPS: Opening file: '" WS-FILE-NAME(1:50) "'"
63 |
64 | OPEN INPUT DISK-FILE
65 |
66 | IF WS-FILE-STATUS NOT = "00"
67 | *> DISPLAY "FILE-OPS: Open failed, status: " WS-FILE-STATUS
68 | MOVE 1 TO LS-RETURN-CODE
69 | GOBACK
70 | END-IF
71 |
72 | *> DISPLAY "FILE-OPS: File opened successfully"
73 |
74 | MOVE 0 TO WS-EOF-FLAG
75 | PERFORM UNTIL WS-EOF-FLAG = 1
76 | READ DISK-FILE
77 | AT END
78 | MOVE 1 TO WS-EOF-FLAG
79 | NOT AT END
80 | *> Calculate actual line length by trimming trailing whitespace
81 | *> Start from end and work backwards to find last non-space character
82 | MOVE 0 TO WS-LINE-LEN
83 | PERFORM VARYING WS-LINE-LEN FROM 1024 BY -1
84 | UNTIL WS-LINE-LEN < 1
85 | IF FILE-RECORD(WS-LINE-LEN:1) NOT = SPACE AND
86 | FILE-RECORD(WS-LINE-LEN:1) NOT = X"0D" AND
87 | FILE-RECORD(WS-LINE-LEN:1) NOT = LOW-VALUE
88 | EXIT PERFORM
89 | END-IF
90 | END-PERFORM
91 | *> Check if line fits in output buffer (prevent overflow)
92 | IF WS-BUFFER-POS + WS-LINE-LEN + 1 <= 65536
93 | *> Copy line content to output buffer if not empty
94 | IF WS-LINE-LEN > 0
95 | MOVE FILE-RECORD(1:WS-LINE-LEN) TO
96 | LS-FILE-BUFFER(WS-BUFFER-POS:WS-LINE-LEN)
97 | ADD WS-LINE-LEN TO WS-BUFFER-POS
98 | END-IF
99 | *> Add line terminator (LF character) after each line
100 | MOVE X"0A" TO
101 | LS-FILE-BUFFER(WS-BUFFER-POS:1)
102 | ADD 1 TO WS-BUFFER-POS
103 | ELSE
104 | *> Stop reading if buffer would overflow - mark as error
105 | *> DISPLAY "FILE-OPS: Buffer full"
106 | MOVE 1 TO WS-EOF-FLAG
107 | MOVE 1 TO WS-OVERFLOW-FLAG
108 | END-IF
109 | END-READ
110 | END-PERFORM
111 |
112 | *> Calculate final file size (subtract 1 for final LF)
113 | IF WS-BUFFER-POS > 1
114 | COMPUTE LS-FILE-SIZE = WS-BUFFER-POS - 1
115 | ELSE
116 | MOVE 0 TO LS-FILE-SIZE
117 | END-IF
118 |
119 | *> DISPLAY "FILE-OPS: Total bytes read=" LS-FILE-SIZE
120 |
121 | *> Close file to free system resources
122 | CLOSE DISK-FILE
123 |
124 | *> Return error if file was too large for buffer
125 | IF WS-OVERFLOW-FLAG = 1
126 | MOVE 2 TO LS-RETURN-CODE
127 | END-IF
128 |
129 | GOBACK.
130 |
--------------------------------------------------------------------------------
/url-decode.cbl:
--------------------------------------------------------------------------------
1 | *> URL decoding module - converts %XX encoded characters to actual characters
2 | IDENTIFICATION DIVISION.
3 | PROGRAM-ID. URL-DECODE.
4 |
5 | DATA DIVISION.
6 | WORKING-STORAGE SECTION.
7 | *> Index for scanning input string
8 | 01 WS-IN-INDEX PIC 9(4) COMP.
9 | *> Index for building output string
10 | 01 WS-OUT-INDEX PIC 9(4) COMP.
11 | *> Length of input string
12 | 01 WS-LENGTH PIC 9(4) COMP.
13 | *> Current character being examined
14 | 01 WS-CHAR PIC X.
15 | *> Two-character hex code from URL encoding
16 | 01 WS-HEX-CODE PIC XX.
17 | *> Numeric value of hex code
18 | 01 WS-HEX-VALUE PIC 9(4) COMP.
19 | *> Character representation of decoded value
20 | 01 WS-DECODED-CHAR PIC X.
21 |
22 | *> Parameters passed from calling program
23 | LINKAGE SECTION.
24 | *> URL-encoded input path (may contain %20, etc.)
25 | 01 LS-INPUT-PATH PIC X(512).
26 | *> Decoded output path (with actual characters)
27 | 01 LS-OUTPUT-PATH PIC X(512).
28 |
29 | PROCEDURE DIVISION USING LS-INPUT-PATH LS-OUTPUT-PATH.
30 |
31 | *> Main URL decoding logic
32 | MAIN-LOGIC.
33 | *> Initialize output path to spaces and reset position indices
34 | MOVE SPACES TO LS-OUTPUT-PATH
35 | MOVE 1 TO WS-IN-INDEX
36 | MOVE 1 TO WS-OUT-INDEX
37 |
38 | *> Calculate actual length of input path (excluding trailing spaces)
39 | INSPECT LS-INPUT-PATH TALLYING WS-LENGTH
40 | FOR CHARACTERS BEFORE INITIAL SPACE
41 |
42 | *> Handle empty input path by returning immediately
43 | IF WS-LENGTH = 0
44 | GOBACK
45 | END-IF
46 |
47 | *> Process each character in input path one at a time
48 | *> URL encoding uses %XX format where XX is hexadecimal ASCII code
49 | PERFORM UNTIL WS-IN-INDEX > WS-LENGTH
50 | MOVE LS-INPUT-PATH(WS-IN-INDEX:1) TO WS-CHAR
51 |
52 | *> Check if current character is % (start of URL-encoded sequence)
53 | IF WS-CHAR = "%"
54 | *> Ensure we have at least 2 more characters for hex code (e.g. %20)
55 | IF WS-IN-INDEX + 2 <= WS-LENGTH
56 | *> Extract the two-character hex code following the %
57 | MOVE LS-INPUT-PATH(WS-IN-INDEX + 1:2)
58 | TO WS-HEX-CODE
59 | *> Convert hex code to actual character (e.g. "20" becomes space)
60 | PERFORM DECODE-HEX-CHAR
61 | *> Write decoded character to output at current position
62 | MOVE WS-DECODED-CHAR TO
63 | LS-OUTPUT-PATH(WS-OUT-INDEX:1)
64 | ADD 1 TO WS-OUT-INDEX
65 | *> Skip past the % and two hex digits (3 characters total)
66 | ADD 3 TO WS-IN-INDEX
67 | ELSE
68 | *> Invalid encoding (% without two hex digits), copy % as-is
69 | MOVE WS-CHAR TO LS-OUTPUT-PATH(WS-OUT-INDEX:1)
70 | ADD 1 TO WS-OUT-INDEX
71 | ADD 1 TO WS-IN-INDEX
72 | END-IF
73 | ELSE
74 | *> Regular unencoded character, copy directly to output
75 | MOVE WS-CHAR TO LS-OUTPUT-PATH(WS-OUT-INDEX:1)
76 | ADD 1 TO WS-OUT-INDEX
77 | ADD 1 TO WS-IN-INDEX
78 | END-IF
79 | END-PERFORM
80 |
81 | GOBACK.
82 |
83 | *> Convert two-character hex code to actual character
84 | *> Handles common URL-encoded special characters used in web requests
85 | DECODE-HEX-CHAR.
86 | *> Initialize to space as default for unrecognized hex codes
87 | MOVE SPACE TO WS-DECODED-CHAR
88 |
89 | *> Decode common URL encodings explicitly
90 | *> Most common: %20 = space character (used in filenames and URLs)
91 | IF WS-HEX-CODE = "20"
92 | MOVE SPACE TO WS-DECODED-CHAR
93 | *> %21 = ! (exclamation mark)
94 | ELSE IF WS-HEX-CODE = "21"
95 | MOVE "!" TO WS-DECODED-CHAR
96 | *> %22 = " (double quote)
97 | ELSE IF WS-HEX-CODE = "22"
98 | MOVE '"' TO WS-DECODED-CHAR
99 | *> %23 = # (hash/pound sign)
100 | ELSE IF WS-HEX-CODE = "23"
101 | MOVE "#" TO WS-DECODED-CHAR
102 | *> %24 = $ (dollar sign)
103 | ELSE IF WS-HEX-CODE = "24"
104 | MOVE "$" TO WS-DECODED-CHAR
105 | *> %25 = % (percent sign)
106 | ELSE IF WS-HEX-CODE = "25"
107 | MOVE "%" TO WS-DECODED-CHAR
108 | *> %26 = & (ampersand)
109 | ELSE IF WS-HEX-CODE = "26"
110 | MOVE "&" TO WS-DECODED-CHAR
111 | *> %27 = ' (single quote)
112 | ELSE IF WS-HEX-CODE = "27"
113 | MOVE "'" TO WS-DECODED-CHAR
114 | *> %28 = ( (left parenthesis)
115 | ELSE IF WS-HEX-CODE = "28"
116 | MOVE "(" TO WS-DECODED-CHAR
117 | *> %29 = ) (right parenthesis)
118 | ELSE IF WS-HEX-CODE = "29"
119 | MOVE ")" TO WS-DECODED-CHAR
120 | *> %2B = + (plus sign)
121 | ELSE IF WS-HEX-CODE = "2B" OR WS-HEX-CODE = "2b"
122 | MOVE "+" TO WS-DECODED-CHAR
123 | *> %2C = , (comma)
124 | ELSE IF WS-HEX-CODE = "2C" OR WS-HEX-CODE = "2c"
125 | MOVE "," TO WS-DECODED-CHAR
126 | *> %2D = - (hyphen/minus)
127 | ELSE IF WS-HEX-CODE = "2D" OR WS-HEX-CODE = "2d"
128 | MOVE "-" TO WS-DECODED-CHAR
129 | *> %2E = . (period/dot)
130 | ELSE IF WS-HEX-CODE = "2E" OR WS-HEX-CODE = "2e"
131 | MOVE "." TO WS-DECODED-CHAR
132 | *> %2F = / (forward slash)
133 | ELSE IF WS-HEX-CODE = "2F" OR WS-HEX-CODE = "2f"
134 | MOVE "/" TO WS-DECODED-CHAR
135 | *> %3A = : (colon)
136 | ELSE IF WS-HEX-CODE = "3A" OR WS-HEX-CODE = "3a"
137 | MOVE ":" TO WS-DECODED-CHAR
138 | *> %3B = ; (semicolon)
139 | ELSE IF WS-HEX-CODE = "3B" OR WS-HEX-CODE = "3b"
140 | MOVE ";" TO WS-DECODED-CHAR
141 | *> %3D = = (equals sign)
142 | ELSE IF WS-HEX-CODE = "3D" OR WS-HEX-CODE = "3d"
143 | MOVE "=" TO WS-DECODED-CHAR
144 | *> %3F = ? (question mark)
145 | ELSE IF WS-HEX-CODE = "3F" OR WS-HEX-CODE = "3f"
146 | MOVE "?" TO WS-DECODED-CHAR
147 | *> %40 = @ (at sign)
148 | ELSE IF WS-HEX-CODE = "40"
149 | MOVE "@" TO WS-DECODED-CHAR
150 | *> %5B = [ (left square bracket)
151 | ELSE IF WS-HEX-CODE = "5B" OR WS-HEX-CODE = "5b"
152 | MOVE "[" TO WS-DECODED-CHAR
153 | *> %5D = ] (right square bracket)
154 | ELSE IF WS-HEX-CODE = "5D" OR WS-HEX-CODE = "5d"
155 | MOVE "]" TO WS-DECODED-CHAR
156 | ELSE
157 | *> Unrecognized hex code - default to space for safety
158 | MOVE SPACE TO WS-DECODED-CHAR
159 | END-IF
160 | .
161 |
--------------------------------------------------------------------------------
/webserver.cbl:
--------------------------------------------------------------------------------
1 | *> Program identification - required in every COBOL program
2 | IDENTIFICATION DIVISION.
3 | PROGRAM-ID. WEBSERVER.
4 |
5 | *> Data definitions section - defines all variables and structures
6 | DATA DIVISION.
7 | WORKING-STORAGE SECTION.
8 | *> Include shared configuration values (port, buffer sizes)
9 | COPY "config.cpy".
10 | *> Include socket system call definitions and data structures
11 | COPY "socket-defs.cpy".
12 | *> Include HTTP request/response data structures
13 | COPY "http-structs.cpy".
14 |
15 | *> Counter for tracking total requests served (8-digit number)
16 | 01 WS-REQUEST-COUNT PIC 9(8) VALUE 0.
17 | *> String representation of port number (5 characters max)
18 | 01 WS-PORT-STR PIC X(5).
19 | *> Port number in network byte order (binary format for system calls)
20 | 01 WS-PORT-NETWORK PIC 9(4) COMP-5.
21 | *> Position where HTTP headers end in request buffer
22 | 01 WS-HEADER-END PIC 9(4) COMP-5.
23 |
24 | *> Executable code section - contains the program's logic
25 | PROCEDURE DIVISION.
26 |
27 | *> Main program entry point
28 | MAIN-LOGIC.
29 | DISPLAY "COBOL Web Server Starting..."
30 | DISPLAY "Press Ctrl+C to stop"
31 | DISPLAY " "
32 |
33 | *> Initialize socket for accepting connections
34 | PERFORM INIT-SOCKET
35 |
36 | *> Check if socket creation failed (negative handle indicates error)
37 | IF SOCKET-HANDLE < 0
38 | DISPLAY "Failed to initialize socket"
39 | STOP RUN
40 | END-IF
41 |
42 | *> Infinite loop to accept and handle client connections
43 | *> UNTIL 1 = 0 creates a loop that never ends naturally
44 | PERFORM ACCEPT-LOOP UNTIL 1 = 0
45 |
46 | STOP RUN.
47 |
48 | *> Create and configure a TCP socket for the web server
49 | INIT-SOCKET.
50 | *> Create socket: AF_INET(2), SOCK_STREAM(1), IPPROTO_TCP(0)
51 | CALL "socket" USING BY VALUE 2 BY VALUE 1 BY VALUE 0
52 | RETURNING SOCKET-HANDLE
53 | END-CALL
54 |
55 | IF SOCKET-HANDLE < 0
56 | DISPLAY "Socket creation failed"
57 | GOBACK
58 | END-IF
59 |
60 | *> Set SO_REUSEADDR option to allow immediate port reuse after restart
61 | *> Parameters: socket, SOL_SOCKET(1), SO_REUSEADDR(2), option_value, size
62 | CALL "setsockopt" USING
63 | BY VALUE SOCKET-HANDLE
64 | BY VALUE 1
65 | BY VALUE 2
66 | BY REFERENCE SOCKET-OPT
67 | BY VALUE 4
68 | RETURNING SOCKET-RESULT
69 | END-CALL
70 |
71 | *> Get size of socket address structure for system calls
72 | MOVE FUNCTION BYTE-LENGTH(SERVER-ADDRESS) TO ADDR-LEN
73 |
74 | *> Convert port to network byte order (big-endian)
75 | *> Split port into low/high bytes and swap them
76 | COMPUTE WS-PORT-NETWORK =
77 | FUNCTION MOD(SERVER-PORT, 256) * 256 +
78 | SERVER-PORT / 256
79 | MOVE WS-PORT-NETWORK TO SA-PORT
80 |
81 | *> Bind socket to address and port (makes it available for connections)
82 | CALL "bind" USING
83 | BY VALUE SOCKET-HANDLE
84 | BY REFERENCE SERVER-ADDRESS
85 | BY VALUE ADDR-LEN
86 | RETURNING SOCKET-RESULT
87 | END-CALL
88 |
89 | IF SOCKET-RESULT < 0
90 | DISPLAY "Bind failed - check if port is in use"
91 | GOBACK
92 | END-IF
93 |
94 | *> Start listening for connections with specified backlog queue size
95 | CALL "listen" USING
96 | BY VALUE SOCKET-HANDLE
97 | BY VALUE BACKLOG
98 | RETURNING SOCKET-RESULT
99 | END-CALL
100 |
101 | IF SOCKET-RESULT < 0
102 | DISPLAY "Listen failed"
103 | GOBACK
104 | END-IF
105 |
106 | DISPLAY "Server listening on port " SERVER-PORT
107 | .
108 |
109 | *> Main server loop - accept and handle client connections
110 | ACCEPT-LOOP.
111 | *> Reset address length for each accept call
112 | MOVE FUNCTION BYTE-LENGTH(SERVER-ADDRESS) TO ADDR-LEN
113 |
114 | *> Wait for and accept incoming client connection
115 | *> This blocks until a client connects
116 | CALL "accept" USING
117 | BY VALUE SOCKET-HANDLE
118 | BY REFERENCE SERVER-ADDRESS
119 | BY REFERENCE ADDR-LEN
120 | RETURNING CLIENT-SOCKET
121 | END-CALL
122 |
123 | IF CLIENT-SOCKET < 0
124 | DISPLAY "Accept failed"
125 | GOBACK
126 | END-IF
127 |
128 | *> Increment request counter for logging
129 | ADD 1 TO WS-REQUEST-COUNT
130 |
131 | *> Process the HTTP request and send response
132 | PERFORM HANDLE-REQUEST
133 |
134 | *> Close client connection (one request per connection)
135 | CALL "close" USING BY VALUE CLIENT-SOCKET
136 | END-CALL
137 | .
138 |
139 | *> Read HTTP request from client and generate response
140 | HANDLE-REQUEST.
141 | *> Clear buffers before processing new request
142 | MOVE SPACES TO REQUEST-BUFFER
143 | MOVE SPACES TO RESPONSE-BUFFER
144 |
145 | *> Read HTTP request data from client socket
146 | *> Parameters: socket, buffer, max_bytes, flags
147 | CALL "recv" USING
148 | BY VALUE CLIENT-SOCKET
149 | BY REFERENCE REQUEST-BUFFER
150 | BY VALUE 8192
151 | BY VALUE 0
152 | RETURNING BYTES-READ
153 | END-CALL
154 |
155 | *> Exit if no data received or connection closed
156 | IF BYTES-READ <= 0
157 | GOBACK
158 | END-IF
159 |
160 | *> Increment request counter for this specific request
161 | ADD 1 TO WS-REQUEST-COUNT
162 |
163 | *> Find end of HTTP headers (marked by CRLF CRLF sequence)
164 | *> X"0D0A0D0A" represents carriage return + line feed twice
165 | MOVE 0 TO WS-HEADER-END
166 | PERFORM VARYING WS-HEADER-END FROM 4 BY 1
167 | UNTIL WS-HEADER-END > BYTES-READ OR WS-HEADER-END > 8188
168 | IF REQUEST-BUFFER(WS-HEADER-END - 3:4) = X"0D0A0D0A"
169 | SUBTRACT 3 FROM WS-HEADER-END
170 | EXIT PERFORM
171 | END-IF
172 | END-PERFORM
173 |
174 | *> Log the HTTP request headers to console
175 | IF WS-HEADER-END > 0 AND WS-HEADER-END <= BYTES-READ
176 | DISPLAY "Request #" WS-REQUEST-COUNT ":"
177 | DISPLAY REQUEST-BUFFER(1:WS-HEADER-END)
178 | ELSE
179 | DISPLAY "Request #" WS-REQUEST-COUNT ": "
180 | REQUEST-BUFFER(1:200)
181 | END-IF
182 |
183 | *> Call HTTP handler to parse request and build response
184 | CALL "HTTP-HANDLER" USING
185 | REQUEST-BUFFER
186 | RESPONSE-BUFFER
187 | RESPONSE-LEN
188 |
189 | *> Send HTTP response back to client if response was generated
190 | IF RESPONSE-LEN > 0
191 | CALL "send" USING
192 | BY VALUE CLIENT-SOCKET
193 | BY REFERENCE RESPONSE-BUFFER
194 | BY VALUE RESPONSE-LEN
195 | BY VALUE 0
196 | RETURNING BYTES-SENT
197 | END-CALL
198 | END-IF
199 | .
200 |
--------------------------------------------------------------------------------
/http-handler.cbl:
--------------------------------------------------------------------------------
1 | *> HTTP request parser and response generator module
2 | IDENTIFICATION DIVISION.
3 | PROGRAM-ID. HTTP-HANDLER.
4 |
5 | DATA DIVISION.
6 | WORKING-STORAGE SECTION.
7 | *> Include HTTP request/response data structures
8 | COPY "http-structs.cpy".
9 | *> Include file handling data structures
10 | COPY "file-structs.cpy".
11 |
12 | *> General purpose index for string operations (binary for efficiency)
13 | 01 WS-INDEX PIC 9(4) COMP.
14 | *> Position of space character in HTTP request parsing
15 | 01 WS-SPACE-POS PIC 9(4) COMP.
16 | *> Length of extracted path from HTTP request
17 | 01 WS-PATH-LEN PIC 9(4) COMP.
18 | *> Return code from called modules (0=success, 1=error)
19 | 01 WS-RETURN-CODE PIC 9.
20 | *> String representation of file size for Content-Length header
21 | 01 WS-SIZE-STR PIC X(10).
22 | *> HTTP line terminator sequence (carriage return + line feed)
23 | 01 WS-CRLF PIC XX VALUE X"0D0A".
24 | *> Decoded path after URL decoding (converts %20 to space, etc.)
25 | 01 WS-DECODED-PATH PIC X(512).
26 |
27 | *> Parameters passed from calling program
28 | LINKAGE SECTION.
29 | *> HTTP request data received from client (8KB max)
30 | 01 LS-REQUEST-BUF PIC X(8192).
31 | *> Buffer for building HTTP response (64KB max)
32 | 01 LS-RESPONSE-BUF PIC X(65536).
33 | *> Actual length of generated response
34 | 01 LS-RESPONSE-LEN PIC 9(8) COMP-5.
35 |
36 | *> Program entry point with parameters
37 | PROCEDURE DIVISION USING LS-REQUEST-BUF LS-RESPONSE-BUF
38 | LS-RESPONSE-LEN.
39 |
40 | *> Main HTTP request processing logic
41 | MAIN-LOGIC.
42 | *> Initialize HTTP request fields
43 | MOVE SPACES TO REQUEST-METHOD
44 | MOVE SPACES TO REQUEST-PATH
45 | MOVE 0 TO LS-RESPONSE-LEN
46 |
47 | *> DISPLAY "Raw request: '" LS-REQUEST-BUF(1:80) "'"
48 |
49 | *> Find first space in request to separate HTTP method
50 | *> HTTP format: "GET /path HTTP/1.1"
51 | MOVE 0 TO WS-SPACE-POS
52 | INSPECT LS-REQUEST-BUF TALLYING WS-SPACE-POS
53 | FOR CHARACTERS BEFORE INITIAL SPACE
54 |
55 | *> DISPLAY "First space at position: " WS-SPACE-POS
56 | *> DISPLAY "Character at pos 4: '" LS-REQUEST-BUF(4:1) "' = "
57 | *> FUNCTION ORD(LS-REQUEST-BUF(4:1))
58 | *> DISPLAY "Character at pos 5: '" LS-REQUEST-BUF(5:1) "' = "
59 | *> FUNCTION ORD(LS-REQUEST-BUF(5:1))
60 |
61 | *> Extract HTTP method (GET, POST, etc.) from first part of request
62 | IF WS-SPACE-POS > 0 AND WS-SPACE-POS <= 10
63 | MOVE LS-REQUEST-BUF(1:WS-SPACE-POS) TO REQUEST-METHOD
64 | *> DISPLAY "Method: '" REQUEST-METHOD "'"
65 | END-IF
66 |
67 | *> Skip space after method to find start of path
68 | COMPUTE WS-INDEX = WS-SPACE-POS + 2
69 | *> DISPLAY "Starting path search at position: " WS-INDEX
70 | *> Find end of path (next space or line ending)
71 | MOVE 0 TO WS-PATH-LEN
72 | PERFORM VARYING WS-SPACE-POS FROM WS-INDEX BY 1
73 | UNTIL WS-SPACE-POS > 8192
74 | IF LS-REQUEST-BUF(WS-SPACE-POS:1) = SPACE OR
75 | LS-REQUEST-BUF(WS-SPACE-POS:1) = X"0D" OR
76 | LS-REQUEST-BUF(WS-SPACE-POS:1) = X"0A"
77 | COMPUTE WS-PATH-LEN = WS-SPACE-POS - WS-INDEX
78 | *> DISPLAY "Found delimiter at position: " WS-SPACE-POS
79 | *> DISPLAY "Delimiter is: "
80 | *> FUNCTION ORD(LS-REQUEST-BUF(WS-SPACE-POS:1))
81 | EXIT PERFORM
82 | END-IF
83 | END-PERFORM
84 |
85 | *> DISPLAY "Path starts at: " WS-INDEX
86 | *> DISPLAY "Path length: " WS-PATH-LEN
87 |
88 | *> Extract the URL path from the HTTP request
89 | IF WS-PATH-LEN > 0 AND WS-PATH-LEN <= 512
90 | MOVE LS-REQUEST-BUF(WS-INDEX:WS-PATH-LEN)
91 | TO REQUEST-PATH
92 | *> DISPLAY "Extracted path: '" REQUEST-PATH(1:50) "'"
93 | END-IF
94 |
95 | *> Decode URL-encoded characters (e.g., %20 -> space)
96 | CALL "URL-DECODE" USING REQUEST-PATH WS-DECODED-PATH
97 |
98 | *> Validate and sanitize the requested path for security
99 | CALL "PATH-UTILS" USING WS-DECODED-PATH SANITIZED-PATH
100 | WS-RETURN-CODE
101 |
102 | *> DISPLAY "Requested path: '" REQUEST-PATH "'"
103 | *> DISPLAY "Decoded path: '" WS-DECODED-PATH "'"
104 | *> DISPLAY "Sanitized path: '" SANITIZED-PATH "'"
105 | *> DISPLAY "Path validation result: " WS-RETURN-CODE
106 |
107 | *> If path validation failed, return 403 Forbidden
108 | IF WS-RETURN-CODE NOT = 0
109 | PERFORM BUILD-403-RESPONSE
110 | GOBACK
111 | END-IF
112 |
113 | *> Attempt to read the requested file
114 | CALL "FILE-OPS" USING SANITIZED-PATH FILE-BUFFER
115 | FILE-SIZE WS-RETURN-CODE
116 |
117 | *> DISPLAY "File read result: " WS-RETURN-CODE
118 | *> DISPLAY "File size: " FILE-SIZE
119 |
120 | *> If file is too large, return 413 Payload Too Large
121 | IF WS-RETURN-CODE = 2
122 | PERFORM BUILD-413-RESPONSE
123 | GOBACK
124 | END-IF
125 |
126 | *> If file read failed, return 404 Not Found
127 | IF WS-RETURN-CODE NOT = 0
128 | *> DISPLAY "File not found: '" SANITIZED-PATH "'"
129 | PERFORM BUILD-404-RESPONSE
130 | GOBACK
131 | END-IF
132 |
133 | *> Determine MIME type based on file extension
134 | CALL "MIME-TYPES" USING SANITIZED-PATH MIME-TYPE
135 |
136 | *> Build successful HTTP response with file content
137 | PERFORM BUILD-200-RESPONSE
138 |
139 | GOBACK.
140 |
141 | *> Build HTTP 200 OK response with file content
142 | BUILD-200-RESPONSE.
143 | *> Convert file size to string for Content-Length header
144 | MOVE FILE-SIZE TO WS-SIZE-STR
145 | *> Initialize response buffer with LOW-VALUE for string termination
146 | MOVE LOW-VALUE TO LS-RESPONSE-BUF
147 |
148 | *> Build HTTP response headers using STRING statement
149 | *> STRING concatenates multiple values into one field
150 | STRING "HTTP/1.1 200 OK" DELIMITED BY SIZE
151 | WS-CRLF DELIMITED BY SIZE
152 | "Content-Type: " DELIMITED BY SIZE
153 | MIME-TYPE DELIMITED BY SPACE
154 | WS-CRLF DELIMITED BY SIZE
155 | "Content-Length: " DELIMITED BY SIZE
156 | WS-SIZE-STR DELIMITED BY SPACE
157 | WS-CRLF DELIMITED BY SIZE
158 | WS-CRLF DELIMITED BY SIZE
159 | INTO LS-RESPONSE-BUF
160 | END-STRING
161 |
162 | *> Calculate length of HTTP headers
163 | MOVE 0 TO LS-RESPONSE-LEN
164 | INSPECT LS-RESPONSE-BUF TALLYING LS-RESPONSE-LEN
165 | FOR CHARACTERS BEFORE INITIAL LOW-VALUE
166 |
167 | *> DISPLAY "Header length: " LS-RESPONSE-LEN
168 |
169 | *> Append file content after headers if file was read successfully
170 | IF LS-RESPONSE-LEN > 0 AND FILE-SIZE > 0
171 | MOVE FILE-BUFFER(1:FILE-SIZE) TO
172 | LS-RESPONSE-BUF(LS-RESPONSE-LEN + 1:FILE-SIZE)
173 | ADD FILE-SIZE TO LS-RESPONSE-LEN
174 | END-IF
175 |
176 | *> DISPLAY "Total response length: " LS-RESPONSE-LEN
177 | *> DISPLAY "File size: " FILE-SIZE
178 | .
179 |
180 | *> Build HTTP 404 Not Found response
181 | BUILD-404-RESPONSE.
182 | *> Create complete HTTP response with headers and HTML body
183 | STRING "HTTP/1.1 404 Not Found" DELIMITED BY SIZE
184 | WS-CRLF DELIMITED BY SIZE
185 | "Content-Type: text/html" DELIMITED BY SIZE
186 | WS-CRLF DELIMITED BY SIZE
187 | "Content-Length: 47" DELIMITED BY SIZE
188 | WS-CRLF DELIMITED BY SIZE
189 | WS-CRLF DELIMITED BY SIZE
190 | "404 Not Found
"
191 | DELIMITED BY SIZE
192 | INTO LS-RESPONSE-BUF
193 | END-STRING
194 |
195 | *> Calculate total response length for sending
196 | INSPECT LS-RESPONSE-BUF TALLYING LS-RESPONSE-LEN
197 | FOR CHARACTERS BEFORE INITIAL LOW-VALUE
198 | .
199 |
200 | *> Build HTTP 403 Forbidden response (for security violations)
201 | BUILD-403-RESPONSE.
202 | *> Create complete HTTP response for path traversal attempts
203 | STRING "HTTP/1.1 403 Forbidden" DELIMITED BY SIZE
204 | WS-CRLF DELIMITED BY SIZE
205 | "Content-Type: text/html" DELIMITED BY SIZE
206 | WS-CRLF DELIMITED BY SIZE
207 | "Content-Length: 47" DELIMITED BY SIZE
208 | WS-CRLF DELIMITED BY SIZE
209 | WS-CRLF DELIMITED BY SIZE
210 | "403 Forbidden
"
211 | DELIMITED BY SIZE
212 | INTO LS-RESPONSE-BUF
213 | END-STRING
214 |
215 | *> Calculate total response length for sending
216 | INSPECT LS-RESPONSE-BUF TALLYING LS-RESPONSE-LEN
217 | FOR CHARACTERS BEFORE INITIAL LOW-VALUE
218 | .
219 |
220 | *> Build HTTP 413 Payload Too Large response (for oversized files)
221 | BUILD-413-RESPONSE.
222 | *> Create complete HTTP response for files exceeding buffer size
223 | STRING "HTTP/1.1 413 Payload Too Large" DELIMITED BY SIZE
224 | WS-CRLF DELIMITED BY SIZE
225 | "Content-Type: text/html" DELIMITED BY SIZE
226 | WS-CRLF DELIMITED BY SIZE
227 | "Content-Length: 59" DELIMITED BY SIZE
228 | WS-CRLF DELIMITED BY SIZE
229 | WS-CRLF DELIMITED BY SIZE
230 | "413 Payload Too Large
"
231 | DELIMITED BY SIZE
232 | INTO LS-RESPONSE-BUF
233 | END-STRING
234 |
235 | *> Calculate total response length for sending
236 | INSPECT LS-RESPONSE-BUF TALLYING LS-RESPONSE-LEN
237 | FOR CHARACTERS BEFORE INITIAL LOW-VALUE
238 | .
239 |
--------------------------------------------------------------------------------