Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations Mike Lewis on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

How do I convert comma-delimited records?

Cobol Code Examples

How do I convert comma-delimited records?

by  k5tm  Posted    (Edited  )
Perhaps you have someone supplying data in a comma-separated (CSV) file. This might help.
Code:
       identification division.
       program-id.  unstring-fields.
       data division.
       working-storage section.
       01  binary.
           02  I               PIC S9(4).
           02  J               PIC S9(4).
       01  the-delimiter       PIC X(3).             
       01  INPUT-FIELD  PIC X(123) VALUE 
           'Bill Smith,"444-55-6666",999999999,1234567,"$1,060.46 "'.
       78  INPUT-FIELD-SIZE value LENGTH OF INPUT-FIELD.

       01  .
           02  OCCURS 40.
               03  FIELD-HOLDER PIC X(50).
               03  FIELD-LENGTH PIC 9(4).
       procedure division.
       a.
           MOVE 1 to I.
           MOVE 1 TO J.
           PERFORM UNTIL I > INPUT-FIELD-SIZE
               INSPECT INPUT-FIELD (I:) TALLYING I FOR LEADING SPACE
               IF I NOT > INPUT-FIELD-SIZE
                   EVALUATE INPUT-FIELD (I:1)
                   WHEN '"'
                       ADD 1 TO I
                       IF I NOT > INPUT-FIELD-SIZE
                           UNSTRING INPUT-FIELD 
                               DELIMITED BY '",' OR '"'
                               INTO FIELD-HOLDER (J)
                               DELIMITER IN THE-DELIMITER
                               COUNT IN FIELD-LENGTH (J)
                               POINTER I
                           END-UNSTRING
                           ADD 1 to J
                       END-IF
                   WHEN OTHER
                       UNSTRING INPUT-FIELD DELIMITED BY ","
                           INTO FIELD-HOLDER (J)
                           DELIMITER IN THE-DELIMITER
                           COUNT IN FIELD-LENGTH (J)
                           POINTER I
                       END-UNSTRING
                       ADD 1 to J
                   END-EVALUATE
               END-IF
           END-PERFORM.
           SUBTRACT 1 FROM J.
           stop run.
Note that this code provides the skeleton of scanning comma-delimited records, including detecting fields that are enclosed in quotation marks ([tt]"[/tt]). Subsequent conversion of numeric values, embedded quotation marks, and other anomolies you might find in 'real life' are not addressed.
Register to rate this FAQ  : BAD 1 2 3 4 5 6 7 8 9 10 GOOD
Please Note: 1 is Bad, 10 is Good :-)

Part and Inventory Search

Back
Top