CALL "CBL_SPLIT_FILENAME" USING cbltSplitjoinBuf splitBuffer GIVING returnCode |
cbltSplitjoinBuf | Group Item | Group item defined as follows: 01 cblt-splitjoin-buf. 03 param-length pic x(2) comp-x. 03 split-join-flag1 pic x comp-x. 03 split-join-flag2 pic x comp-x. 03 device-offset pic x(2) comp-x. 03 device-length pic x(2) comp-x. 03 basename-offset pic x(2) comp-x. 03 basename-length pic x(2) comp-x. 03 extension-offset pic x(2) comp-x. 03 extension-length pic x(2) comp-x. 03 total-length pic x(2) comp-x. 03 split-buf-len pic x(2) comp-x. 03 join-buf-len pic x(2) comp-x. 03 first-component-length pic x(2) comp-x. On entry: param-lenght is the length of the structure in bytes. It should be set to 24. The value 0 is treated as if it were the structure dimension. splitjoin-flag1’s bit 1 says that the strings are null-terminated if set to 1, while they are space-terminated if set to 0. splitjoin-flag1’s bit 2 says that the filename is folded to upper case if set to 1, while the original case is preserved if set to 0. split-buf-len specifies the length in bytes of splitBuffer. On exit: splitjoin-flag2’s bit 2 is set if there is a significant space in the filename. splitjoin-flag2’s bit 1 is set if there is a wildcard in the path. splitjoin-flag2’s bit 0 is set if there is a wildcard in basename or extension. device-offset returns the start of pathname in splitBuffer, from one. device-length returns the length of the pathname. basename-offset returns the start of basename in splitBuffer, from one. basename-length returns the length of the basename. extension-offset returns the start of extension in splitBuffer, from one. extension-length returns the length of the extension. total-length returns the total number of characters in splitBuffer. first-component-length returns the number of characters up to and including the first backslash or slash or colon in splitBuffer. |
splitBuffer | PIC X(n) | It specifies the string to split. |
0 | Operation successful. |
4 | Invalid filename. |
move "C:\temp\print_01.pdf" to the-path. |the-path is a pic x(n) data-item call "CBL_SPLIT_FILENAME" using cblt-splitjoin-buf, the-path. display the-path(extension-offset:extension-length)|it will display ‘pdf’ |