CALL "CBL_OPEN_FILE" USING fileName accessMode denyMode device fileHandle GIVING returnCode |
fileName | PIC X(n) | Specifies the name of the file to open. The name can be partially or entirely changed through configuration properties if iscobol.file.env_naming (boolean) is set to true. If the name is a relative path and iscobol.file.prefix is set, then the first FILE-PREFIX path is used to locate the file. The ISF protocol is not supported, it will invalidate the file path, if used. |
accessMode | PIC X COMP-X | Specifies the access mode. Possible values are: 1... Read only 2... Write only (denyMode must be 0) 3... Read/write 64... Read/write files greater than 4Gb |
denyMode | PIC X COMP-X | Specifies the deny mode. Possible values are: 0... Deny both read and write (exclusive) 1... Deny write 2... Deny read 3... Deny neither read nor write |
device | PIC X COMP-X | This item must be set to zero. |
fileHandle | PIC X(4) COMP-X | Returns an handle to the opened file unless an error occurs. |
0 | Operation successful. |
>0 | Operation failed. See Interpreting the return code as a file status code. |
working-storage section. ... 01 file-status-group. 03 file-status pic xx comp-x. 03 redefines file-status. 05 fs-byte-1 pic x. 05 fs-byte-2 pic x comp-x. 01 file-name pic x(32) value "test". 01 access-mode pic x comp-x value 3. 01 deny-mode pic x comp-x value 3. 01 device pic x comp-x value 0. 01 file-handle pic x(4) comp-x. ... procedure division. ... call "cbl_open_file" using file-name, access-mode, deny-mode, device, file-handle. if return-code not = 0 move return-code to file-status ... |