Skip to main content

From within my native Visual COBOL code, I want to specify the name of a folder (e.g., "c:\\surveys\\finance\\2018") and then populate a working storage table with as many as 500 names of *.xlsx files in that folder.   All the filenames will be 13 characters in length: nnnnnnnn.xlsx

01  SURVEY-FILE-TABLE.

      05  SURVEY-FILE   PIC X(13) OCCURS 500.

I've been studying available documentation on CBL_DIR_SCAN_START, CBL_DIR_SCAN_READ, and CBL_DIR_SCAN_END -- but it's all Greek to me.  Are those even the routines that I will need?   And are there any examples out there that actually show getting a list of filenames in a given folder? 

From within my native Visual COBOL code, I want to specify the name of a folder (e.g., "c:\\surveys\\finance\\2018") and then populate a working storage table with as many as 500 names of *.xlsx files in that folder.   All the filenames will be 13 characters in length: nnnnnnnn.xlsx

01  SURVEY-FILE-TABLE.

      05  SURVEY-FILE   PIC X(13) OCCURS 500.

I've been studying available documentation on CBL_DIR_SCAN_START, CBL_DIR_SCAN_READ, and CBL_DIR_SCAN_END -- but it's all Greek to me.  Are those even the routines that I will need?   And are there any examples out there that actually show getting a list of filenames in a given folder? 

The following is an example that will scan a specified folder for all files with an extension of .txt and then display them to the user.

 

       id division.
       program-id. dirscan.
       working-storage section.
       01 any-key pic x.
       01 f-entry.         
          03 f-attribute        pic x(4) comp-5.
          03 f-date-stamp.  
             05 f-year          pic x(4) comp-5.
             05 f-month         pic x(2) comp-5.
             05 f-day           pic x(2) comp-5.
             05 f-hour          pic x(2) comp-5.
             05 f-minute        pic x(2) comp-5.
             05 f-second        pic x(2) comp-5.
             05 f-millisec      pic x(2) comp-5.
             05 f-dst           pic x    comp-5.
             05 f-size          pic x(8) comp-5.
             05 f-name.     
                07 f-max-len    pic x(2) comp-5 value 256.
                07 f-entry-name pic x(256).
       
       01 scan-pattern.
           05 pattern-len       pic x(2) comp-5  value 0.
           05 pattern-text      pic x(256)       value spaces.
       01 scan-attrib           pic x(4) comp-5  value 1.      
       01 scan-flags            pic x(4) comp-5  value 2.
       01 scan-status           pic x(2) comp-5  value 0.
       01 scan-handle           pointer.
       01 my-field              pic x(256)  value "c:\\temp\\*".
       01 char-count            pic 9(5) value 0.
       procedure division.
           
           move z"c:\\temp\\*.txt" to pattern-text
           move 0 to pattern-len
           move 1 to scan-attrib
           move 2 to scan-flags
           
           call "CBL_DIR_SCAN_START" 
              using by reference scan-handle,
                    by reference scan-pattern,
                    by value scan-attrib,
                    by value scan-flags,
              returning scan-status
           end-call
           
           perform until exit           
              move spaces to f-entry-name
              call "CBL_DIR_SCAN_READ"
                 using  by reference scan-handle
                                     f-entry
                 returning scan-status
              end-call
              if scan-status = 0
                 perform varying char-count from length of f-entry-name by -1 until char-count < 1
                    if f-entry-name(char-count:1) = "\\"
				       add 1 to char-count
                       exit perform
                    end-if
                 end-perform
                 display f-entry-name(char-count:) 
              else
                 call "CBL_DIR_SCAN_END" using scan-handle
                 exit perform
              end-if
           end-perform.
           accept any-key
           goback.