CALL "C$FILEINFO" USING fileName                          fileInfo                   GIVING returnCode  | 
fileName   | PIC X(n)   | Specifies the name of the file. This should either be a full path name or a name relative to the current directory. If the routine can’t find the file specified by fileName as is, the routine tries a second time after appending the file extension. The file extension is the first applicable between: •	the value of iscobol.file.suffix configuration property •	the value of iscobol.file.index.data_suffix * configuration property •	the default data file extension: ".dat"  | 
fileInfo   | Group Item   | Receives the file information. It must have the following structure: 01 fileInfo.    03 fileSize    pic x(8) comp-x.    03 fileDate    pic 9(8) comp-x.    03 fileTime    pic 9(8) comp-x. fileSize Size of the file in bytes. fileDate Last modified date of the file, in YYYYMMDD format. fileTime Last modified time of the file.  | 
0   | Operation successful, file information has been retrieved.  | 
1   | An error occurred, no information retrieved.  | 
working-storage section. 01 file-info.    02 file-size pic x(8) comp-x.    02 file-date pic 9(8) comp-x.    02 file-time pic 9(8) comp-x. 77 file-name    pic x(256). 77 retCode      pic s9(2). ... procedure division. ...    move "c:\myapp\resources\properties1.txt" to file-name    call "c$fileinfo" using file-name, file-info         giving retCode    if retCode = 0       display message "File size   : " file-size x"0d0a"                       "Last update : " file-date " - " file-time    else       display message "File information could not be retrieved"    end-if.  |