000100 Identification Division. 000200 Program-id. FILECONV. 000300 000400 Environment Division. 000500 Input-Output Section. 000600 File-Control. 000700 Select County-Names Assign to COUNTYDD 000800 Organization is Sequential 000900 . 001000 Select Unsorted-Names Assign to CLIDD 001100 Organization is Sequential 001200 . 001300 Select Work-File Assign to SYSWK1 001400 . 001500 Select Sorted-Names Assign to SCLIDD 001600 Organization is Sequential 001700 . 001800 Select Error-File Assign to ERRDD 001900 Organization is Sequential 002000 . 002100 Data Division. 002200 File Section. 002300 FD County-Names Recording Mode F. 002400 01 County-Rec Pic X(80). 002500 88 End-Of-County-Rec Value High-Value. 002600 002700 FD Unsorted-Names Recording Mode F. 002800 01 Unsorted-Rec Pic X(80). 002900 88 End-Of-Unsorted-Rec Value High-Value. 003000 003100 SD Work-File. 003200 01 Work-Rec. 003300 05 Client-Name Pic X(35). 003400 05 Client-Address Pic X(60). 003500 05 County-No Pic 99. 003600 05 Client-No Pic 9999. 003700 003800 FD Sorted-Names Recording Mode F. 003900 01 Sorted-rec Pic X(101). 004000 004100 FD Error-File Recording Mode F. 004200 01 Error-Rec Pic X(80). 004300 004400 Working-Storage Section. 004500 01 Number-Of-Countys Pic 99 Value 1. 004600 004700 01 County-Table. 004800 05 County-Name Occurs 50 Times 004900 Depending on Number-of-Countys 005000 Ascending Key County-Name 005100 Indexed by County-Num 005200 Pic X(11) 005300 . 005400 005500 01 lower-case PIC X(26) 005600 Value 'abcdefghijklmnopqrstuvwxyz'. 005700 005800 01 UPPER-CASE PIC X(26) 005900 Value 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'. 006000 006400 01 Hold-Items. 006500 05 Hold-Client Pic X(35). 006600 05 Hold-Name Pic X(35). 006700 05 Hold-County Pic X(11). 006800 05 Hold-Client-No Pic X(04). 006900 007000 01 Ptr-Items. 007100 05 Unstr-Ptr Pic 99. 007200 88 End-of-Address Value 61. 007300 88 End-of-Name Value 36. 007400 05 Str-Ptr Pic 99. 007500 05 Name-End Pic 99. 007600 007700 Procedure Division. 007710 Perform Open-All-Files 008100 Perform Fill-County-Table 008200 008300* Sort Work-File on Ascending County-No, Client-Name 008310 Sort Work-File on Ascending Client-Name 008400 Input Procedure is Convert-Records 008500 Giving Sorted-Names 008600 008700 Perform Close-All-Files 008800 009000 GoBack 009100 . 009300 Fill-County-Table. 009400 Perform Until End-Of-County-Rec 009500 Read County-Names 009600 Into County-Name(Number-Of-Countys) 009700 At End 009800 Set End-Of-County-Rec to True 009900 End-Read 010000 Add 1 to Number-Of-Countys 010100 End-Perform 010200 . 010300 Convert-Records. 010400 Read Unsorted-Names 010500 At End 010600 Set End-Of-Unsorted-Rec to True 010700 Not At End 010800 Perform Unpack-Records 010900 Until End-Of-Unsorted-Rec 011000 End-Read 011100 . 011200 Unpack-Records. 011300 Move Space to Work-Rec 011400 Move 1 to Unstr-Ptr 011500 011600 Unstring Unsorted-Rec 011700 Delimited by ',' 011800 Into Hold-Client 011900 Client-Address 012000 Hold-Client-No 012100 Move Hold-Client-No to Client-No 012200 012300 Perform Until End-of-Address 012400 Unstring Client-Address Delimited by All Spaces 012500 Into Hold-County 012600 With Pointer Unstr-Ptr 012700 012800 End-Perform 012900 013000* Move Function Upper-Case(Hold-County) to Hold-County 013100 013200 Inspect Hold-County Converting lower-case to UPPER-CASE 013300 013400 Search All County-Name 013500 At End 013600 Write Error-Rec from Unsorted-Rec 013700 When County-Name(County-Num) = Hold-County 013800 Set County-no to County-Num 013900 Perform Restructure-Name 014000 Release Work-Rec 014100 End-Search 014300 Read Unsorted-Names 014400 At End 014500 Set End-Of-Unsorted-Rec to True 014600 End-Read 014700 . 014800 014900 Restructure-Name. 015000 Move 1 to Unstr-Ptr, Str-Ptr 015100 Perform Until End-Of-Name 015200 Move Unstr-Ptr to Name-End 015300 Unstring Hold-Client Delimited by All Spaces 015400 Into Hold-Name 015500 With Pointer Unstr-Ptr 015600 End-Unstring 015700 End-Perform 015800 015900 String Hold-Name Delimited By Space 016000 Space Delimited By Size 016100 Into Client-Name 016200 With Pointer Str-Ptr 016300 End-String 016400 016500 Move 1 to Unstr-Ptr 016600 Perform Until Unstr-Ptr >= Name-End 016700 Unstring Hold-Client Delimited by Space 016800 Into Hold-Name 016900 With Pointer Unstr-Ptr 017000 End-Unstring 017100 String Hold-Name Delimited by Space 017200 Space Delimited by Size 017300 Into Client-Name 017400 With Pointer Str-Ptr 017500 End-String 017600 End-Perform 017700 . 017800 Open-All-Files. 017900 Open Input County-Names 018000 Open Input Unsorted-Names 018100 Open Output Error-File 018200 . 018300 Close-All-Files. 018400 Close County-Names 018500 Close Unsorted-Names 018600 Close Error-File 018700 .