MainframeMaster

COBOL String Processing Concepts

String processing in COBOL involves manipulating character strings, including concatenation, substring extraction, string comparison, and text formatting operations. Understanding string processing concepts is essential for COBOL programming as most business applications require text manipulation and data formatting. Proper string processing ensures data integrity, efficient text handling, and reliable string operations.

Understanding String Processing

String processing in COBOL encompasses all methods of manipulating character strings including concatenation, parsing, formatting, and validation. Strings are fundamental data types in COBOL programs, and proper string processing ensures data integrity and efficient text handling. Different string processing techniques are appropriate for different text manipulation requirements.

String Concatenation

1. STRING Statement

The STRING statement concatenates multiple strings into a single result string. It provides flexible string combination with optional delimiters and overflow handling.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
DATA DIVISION. WORKING-STORAGE SECTION. 01 STRING-VARIABLES. 05 FIRST-NAME PIC X(15) VALUE 'JOHN'. 05 LAST-NAME PIC X(20) VALUE 'SMITH'. 05 MIDDLE-INITIAL PIC X(1) VALUE 'A'. 05 FULL-NAME PIC X(50) VALUE SPACES. 05 ADDRESS-LINE PIC X(50) VALUE SPACES. 05 STREET PIC X(30) VALUE '123 MAIN ST'. 05 CITY PIC X(20) VALUE 'NEW YORK'. 05 STATE PIC X(2) VALUE 'NY'. 05 ZIP-CODE PIC X(10) VALUE '10001'. 01 STRING-CONTROLS. 05 STRING-POINTER PIC 9(2) VALUE 1. 05 OVERFLOW-FLAG PIC X(1) VALUE 'N'. 88 OVERFLOW-OCCURRED VALUE 'Y'. 88 NO-OVERFLOW VALUE 'N'. PROCEDURE DIVISION. STRING-CONCATENATION-EXAMPLE. DISPLAY 'STRING Statement Example' *> Concatenate first and last name PERFORM CONCATENATE-NAMES *> Concatenate address components PERFORM CONCATENATE-ADDRESS *> Display results PERFORM DISPLAY-STRING-RESULTS STOP RUN. CONCATENATE-NAMES. DISPLAY 'Concatenating names' STRING FIRST-NAME DELIMITED BY SPACE ' ' DELIMITED BY SIZE MIDDLE-INITIAL DELIMITED BY SPACE '. ' DELIMITED BY SIZE LAST-NAME DELIMITED BY SPACE INTO FULL-NAME WITH POINTER STRING-POINTER ON OVERFLOW SET OVERFLOW-OCCURRED TO TRUE DISPLAY 'OVERFLOW: Name too long for target field' END-STRING DISPLAY 'Full name: ' FULL-NAME. CONCATENATE-ADDRESS. DISPLAY 'Concatenating address' STRING STREET DELIMITED BY SPACE ', ' DELIMITED BY SIZE CITY DELIMITED BY SPACE ', ' DELIMITED BY SIZE STATE DELIMITED BY SPACE ' ' DELIMITED BY SIZE ZIP-CODE DELIMITED BY SPACE INTO ADDRESS-LINE WITH POINTER STRING-POINTER ON OVERFLOW SET OVERFLOW-OCCURRED TO TRUE DISPLAY 'OVERFLOW: Address too long for target field' END-STRING DISPLAY 'Address: ' ADDRESS-LINE

The STRING statement concatenates multiple strings with optional delimiters. The WITH POINTER clause tracks the current position, and ON OVERFLOW handles cases where the result exceeds the target field size.

2. Advanced STRING Operations

Advanced STRING operations include conditional concatenation, multiple delimiter handling, and complex string building for sophisticated text processing requirements.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
PROCEDURE DIVISION. ADVANCED-STRING-OPERATIONS. DISPLAY 'Advanced STRING Operations Example' *> Conditional string concatenation PERFORM CONDITIONAL-STRING-CONCATENATION *> Multiple delimiter handling PERFORM MULTIPLE-DELIMITER-HANDLING *> Complex string building PERFORM COMPLEX-STRING-BUILDING. CONDITIONAL-STRING-CONCATENATION. DISPLAY 'Conditional string concatenation' *> Build name with optional middle initial IF MIDDLE-INITIAL NOT = SPACES STRING FIRST-NAME DELIMITED BY SPACE ' ' DELIMITED BY SIZE MIDDLE-INITIAL DELIMITED BY SPACE '. ' DELIMITED BY SIZE LAST-NAME DELIMITED BY SPACE INTO FULL-NAME END-STRING ELSE STRING FIRST-NAME DELIMITED BY SPACE ' ' DELIMITED BY SIZE LAST-NAME DELIMITED BY SPACE INTO FULL-NAME END-STRING END-IF DISPLAY 'Conditional name: ' FULL-NAME. MULTIPLE-DELIMITER-HANDLING. DISPLAY 'Multiple delimiter handling' *> Build formatted phone number STRING '(' DELIMITED BY SIZE PHONE-AREA DELIMITED BY SPACE ') ' DELIMITED BY SIZE PHONE-PREFIX DELIMITED BY SPACE '-' DELIMITED BY SIZE PHONE-NUMBER DELIMITED BY SPACE INTO FORMATTED-PHONE END-STRING DISPLAY 'Formatted phone: ' FORMATTED-PHONE. COMPLEX-STRING-BUILDING. DISPLAY 'Complex string building' *> Build customer information string STRING 'Customer ID: ' DELIMITED BY SIZE CUSTOMER-ID DELIMITED BY SPACE ' | Name: ' DELIMITED BY SIZE FULL-NAME DELIMITED BY SPACE ' | Balance: $' DELIMITED BY SIZE CUSTOMER-BALANCE DELIMITED BY SPACE INTO CUSTOMER-INFO-STRING END-STRING DISPLAY 'Customer info: ' CUSTOMER-INFO-STRING

Advanced STRING operations provide sophisticated text processing capabilities including conditional concatenation, multiple delimiters, and complex string building for various business requirements.

String Parsing

1. UNSTRING Statement

The UNSTRING statement breaks down a string into multiple parts based on delimiters. It provides flexible parsing capabilities for extracting specific portions of text data.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
DATA DIVISION. WORKING-STORAGE SECTION. 01 INPUT-STRING PIC X(100) VALUE 'JOHN,A,SMITH,123 MAIN ST,NEW YORK,NY,10001'. 01 PARSED-FIELDS. 05 FIRST-NAME PIC X(15). 05 MIDDLE-INITIAL PIC X(1). 05 LAST-NAME PIC X(20). 05 STREET PIC X(30). 05 CITY PIC X(20). 05 STATE PIC X(2). 05 ZIP-CODE PIC X(10). 01 UNSTRING-CONTROLS. 05 UNSTRING-POINTER PIC 9(3) VALUE 1. 05 FIELD-COUNT PIC 9(2) VALUE 0. 05 DELIMITER-COUNT PIC 9(2) VALUE 0. PROCEDURE DIVISION. UNSTRING-PARSING-EXAMPLE. DISPLAY 'UNSTRING Statement Example' *> Parse comma-delimited string PERFORM PARSE-COMMA-DELIMITED-STRING *> Parse space-delimited string PERFORM PARSE-SPACE-DELIMITED-STRING *> Display parsed results PERFORM DISPLAY-PARSED-RESULTS STOP RUN. PARSE-COMMA-DELIMITED-STRING. DISPLAY 'Parsing comma-delimited string' UNSTRING INPUT-STRING DELIMITED BY ',' INTO FIRST-NAME MIDDLE-INITIAL LAST-NAME STREET CITY STATE ZIP-CODE WITH POINTER UNSTRING-POINTER TALLYING IN FIELD-COUNT ON OVERFLOW DISPLAY 'OVERFLOW: Too many fields to parse' END-UNSTRING DISPLAY 'Parsed ' FIELD-COUNT ' fields'. PARSE-SPACE-DELIMITED-STRING. DISPLAY 'Parsing space-delimited string' MOVE 'JOHN A SMITH 123 MAIN ST NEW YORK NY 10001' TO INPUT-STRING UNSTRING INPUT-STRING DELIMITED BY SPACE INTO FIRST-NAME MIDDLE-INITIAL LAST-NAME STREET CITY STATE ZIP-CODE WITH POINTER UNSTRING-POINTER TALLYING IN FIELD-COUNT END-UNSTRING DISPLAY 'Parsed ' FIELD-COUNT ' space-delimited fields'. DISPLAY-PARSED-RESULTS. DISPLAY 'Parsed Results:' DISPLAY 'First Name: ' FIRST-NAME DISPLAY 'Middle Initial: ' MIDDLE-INITIAL DISPLAY 'Last Name: ' LAST-NAME DISPLAY 'Street: ' STREET DISPLAY 'City: ' CITY DISPLAY 'State: ' STATE DISPLAY 'ZIP Code: ' ZIP-CODE

The UNSTRING statement parses strings based on delimiters, extracting multiple fields into separate variables. The TALLYING clause counts parsed fields, and WITH POINTER tracks the current parsing position.

2. Advanced UNSTRING Operations

Advanced UNSTRING operations include multiple delimiter handling, conditional parsing, and complex string extraction for sophisticated text processing requirements.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
PROCEDURE DIVISION. ADVANCED-UNSTRING-OPERATIONS. DISPLAY 'Advanced UNSTRING Operations Example' *> Multiple delimiter parsing PERFORM MULTIPLE-DELIMITER-PARSING *> Conditional parsing PERFORM CONDITIONAL-PARSING *> Complex string extraction PERFORM COMPLEX-STRING-EXTRACTION. MULTIPLE-DELIMITER-PARSING. DISPLAY 'Multiple delimiter parsing' MOVE 'JOHN,A SMITH|123 MAIN ST,NEW YORK|NY,10001' TO INPUT-STRING UNSTRING INPUT-STRING DELIMITED BY ',' OR '|' INTO FIRST-NAME LAST-NAME STREET CITY STATE ZIP-CODE WITH POINTER UNSTRING-POINTER TALLYING IN FIELD-COUNT END-UNSTRING DISPLAY 'Parsed with multiple delimiters: ' FIELD-COUNT ' fields'. CONDITIONAL-PARSING. DISPLAY 'Conditional parsing' *> Parse based on string format IF INPUT-STRING(1:1) = '(' *> Parse phone number format: (123) 456-7890 UNSTRING INPUT-STRING DELIMITED BY '(' OR ')' OR ' ' OR '-' INTO PHONE-AREA PHONE-PREFIX PHONE-NUMBER WITH POINTER UNSTRING-POINTER END-UNSTRING ELSE *> Parse simple format: 123-456-7890 UNSTRING INPUT-STRING DELIMITED BY '-' INTO PHONE-AREA PHONE-PREFIX PHONE-NUMBER WITH POINTER UNSTRING-POINTER END-UNSTRING END-IF DISPLAY 'Parsed phone: ' PHONE-AREA '-' PHONE-PREFIX '-' PHONE-NUMBER. COMPLEX-STRING-EXTRACTION. DISPLAY 'Complex string extraction' *> Extract specific portions of a complex string MOVE 'CUSTOMER:12345|NAME:JOHN SMITH|BALANCE:1000.50' TO INPUT-STRING *> Extract customer ID UNSTRING INPUT-STRING DELIMITED BY 'CUSTOMER:' OR '|' INTO CUSTOMER-ID WITH POINTER UNSTRING-POINTER END-UNSTRING *> Extract customer name UNSTRING INPUT-STRING DELIMITED BY 'NAME:' OR '|' INTO CUSTOMER-NAME WITH POINTER UNSTRING-POINTER END-UNSTRING *> Extract balance UNSTRING INPUT-STRING DELIMITED BY 'BALANCE:' OR '|' INTO CUSTOMER-BALANCE WITH POINTER UNSTRING-POINTER END-UNSTRING DISPLAY 'Extracted - ID: ' CUSTOMER-ID ' Name: ' CUSTOMER-NAME ' Balance: ' CUSTOMER-BALANCE

Advanced UNSTRING operations provide sophisticated parsing capabilities including multiple delimiters, conditional parsing, and complex string extraction for various text processing requirements.

Reference Modification

1. Substring Extraction

Reference modification allows programs to access specific portions of a string by specifying starting position and length. This provides efficient substring extraction and manipulation capabilities.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
DATA DIVISION. WORKING-STORAGE SECTION. 01 SOURCE-STRING PIC X(50) VALUE 'JOHN A SMITH 123 MAIN ST NEW YORK NY'. 01 EXTRACTED-FIELDS. 05 FIRST-NAME PIC X(10). 05 MIDDLE-INITIAL PIC X(1). 05 LAST-NAME PIC X(10). 05 STREET-NUMBER PIC X(5). 05 STREET-NAME PIC X(15). 05 CITY-NAME PIC X(10). 05 STATE-CODE PIC X(2). 01 REFERENCE-CONTROLS. 05 START-POSITION PIC 9(2) VALUE 1. 05 FIELD-LENGTH PIC 9(2) VALUE 0. PROCEDURE DIVISION. REFERENCE-MODIFICATION-EXAMPLE. DISPLAY 'Reference Modification Example' *> Extract substrings using reference modification PERFORM EXTRACT-SUBSTRINGS *> Modify substrings PERFORM MODIFY-SUBSTRINGS *> Display results PERFORM DISPLAY-REFERENCE-RESULTS STOP RUN. EXTRACT-SUBSTRINGS. DISPLAY 'Extracting substrings' *> Extract first name (positions 1-4) MOVE SOURCE-STRING(1:4) TO FIRST-NAME *> Extract middle initial (position 6) MOVE SOURCE-STRING(6:1) TO MIDDLE-INITIAL *> Extract last name (positions 8-12) MOVE SOURCE-STRING(8:5) TO LAST-NAME *> Extract street number (positions 14-16) MOVE SOURCE-STRING(14:3) TO STREET-NUMBER *> Extract street name (positions 18-26) MOVE SOURCE-STRING(18:9) TO STREET-NAME *> Extract city (positions 28-35) MOVE SOURCE-STRING(28:8) TO CITY-NAME *> Extract state (positions 37-38) MOVE SOURCE-STRING(37:2) TO STATE-CODE DISPLAY 'Extracted substrings successfully'. MODIFY-SUBSTRINGS. DISPLAY 'Modifying substrings' *> Convert first name to uppercase MOVE FUNCTION UPPER-CASE(FIRST-NAME) TO FIRST-NAME *> Convert last name to uppercase MOVE FUNCTION UPPER-CASE(LAST-NAME) TO LAST-NAME *> Convert city to uppercase MOVE FUNCTION UPPER-CASE(CITY-NAME) TO CITY-NAME DISPLAY 'Modified substrings successfully'. DISPLAY-REFERENCE-RESULTS. DISPLAY 'Reference Modification Results:' DISPLAY 'First Name: ' FIRST-NAME DISPLAY 'Middle Initial: ' MIDDLE-INITIAL DISPLAY 'Last Name: ' LAST-NAME DISPLAY 'Street Number: ' STREET-NUMBER DISPLAY 'Street Name: ' STREET-NAME DISPLAY 'City: ' CITY-NAME DISPLAY 'State: ' STATE-CODE

Reference modification provides efficient substring extraction and manipulation by specifying starting position and length. This method is ideal for accessing specific portions of strings without complex parsing operations.

2. Dynamic Reference Modification

Dynamic reference modification uses variables to specify positions and lengths, providing flexible substring operations based on runtime conditions.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
PROCEDURE DIVISION. DYNAMIC-REFERENCE-MODIFICATION. DISPLAY 'Dynamic Reference Modification Example' *> Dynamic substring extraction PERFORM DYNAMIC-SUBSTRING-EXTRACTION *> Variable-length field extraction PERFORM VARIABLE-LENGTH-EXTRACTION *> Conditional substring operations PERFORM CONDITIONAL-SUBSTRING-OPERATIONS. DYNAMIC-SUBSTRING-EXTRACTION. DISPLAY 'Dynamic substring extraction' *> Find position of delimiter PERFORM FIND-DELIMITER-POSITION *> Extract substring up to delimiter MOVE SOURCE-STRING(START-POSITION:DELIMITER-POSITION - START-POSITION) TO EXTRACTED-SUBSTRING DISPLAY 'Extracted substring: ' EXTRACTED-SUBSTRING. FIND-DELIMITER-POSITION. MOVE 1 TO DELIMITER-POSITION PERFORM UNTIL DELIMITER-POSITION > FUNCTION LENGTH(SOURCE-STRING) IF SOURCE-STRING(DELIMITER-POSITION:1) = ',' EXIT PERFORM ELSE ADD 1 TO DELIMITER-POSITION END-IF END-PERFORM. VARIABLE-LENGTH-EXTRACTION. DISPLAY 'Variable-length field extraction' *> Extract fields of variable length PERFORM VARYING FIELD-INDEX FROM 1 BY 1 UNTIL FIELD-INDEX > 5 PERFORM CALCULATE-FIELD-POSITION-AND-LENGTH MOVE SOURCE-STRING(FIELD-START-POSITION:FIELD-LENGTH) TO EXTRACTED-FIELD(FIELD-INDEX) DISPLAY 'Field ' FIELD-INDEX ': ' EXTRACTED-FIELD(FIELD-INDEX) END-PERFORM. CONDITIONAL-SUBSTRING-OPERATIONS. DISPLAY 'Conditional substring operations' *> Extract based on conditions IF FUNCTION LENGTH(SOURCE-STRING) > 20 MOVE SOURCE-STRING(1:20) TO SHORT-STRING DISPLAY 'Shortened string: ' SHORT-STRING ELSE MOVE SOURCE-STRING TO SHORT-STRING DISPLAY 'Original string: ' SHORT-STRING END-IF

Dynamic reference modification provides flexible substring operations using variables for positions and lengths. This approach enables sophisticated string manipulation based on runtime conditions and data characteristics.

String Functions

1. Intrinsic String Functions

COBOL provides intrinsic string functions for common string operations including LENGTH, UPPER-CASE, LOWER-CASE, and REVERSE for efficient string manipulation.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
PROCEDURE DIVISION. INTRINSIC-STRING-FUNCTIONS. DISPLAY 'Intrinsic String Functions Example' *> String length function PERFORM STRING-LENGTH-OPERATIONS *> Case conversion functions PERFORM CASE-CONVERSION-OPERATIONS *> String reversal function PERFORM STRING-REVERSAL-OPERATIONS *> String comparison functions PERFORM STRING-COMPARISON-OPERATIONS. STRING-LENGTH-OPERATIONS. DISPLAY 'String length operations' MOVE FUNCTION LENGTH(SOURCE-STRING) TO STRING-LENGTH DISPLAY 'Source string length: ' STRING-LENGTH *> Validate string length IF FUNCTION LENGTH(INPUT-STRING) > MAX-STRING-LENGTH DISPLAY 'ERROR: String too long' ELSE DISPLAY 'String length is acceptable' END-IF. CASE-CONVERSION-OPERATIONS. DISPLAY 'Case conversion operations' *> Convert to uppercase MOVE FUNCTION UPPER-CASE(SOURCE-STRING) TO UPPERCASE-STRING DISPLAY 'Uppercase: ' UPPERCASE-STRING *> Convert to lowercase MOVE FUNCTION LOWER-CASE(SOURCE-STRING) TO LOWERCASE-STRING DISPLAY 'Lowercase: ' LOWERCASE-STRING *> Convert mixed case MOVE FUNCTION UPPER-CASE(FIRST-NAME) TO FIRST-NAME MOVE FUNCTION LOWER-CASE(LAST-NAME) TO LAST-NAME DISPLAY 'Mixed case: ' FIRST-NAME ' ' LAST-NAME. STRING-REVERSAL-OPERATIONS. DISPLAY 'String reversal operations' *> Reverse string MOVE FUNCTION REVERSE(SOURCE-STRING) TO REVERSED-STRING DISPLAY 'Reversed: ' REVERSED-STRING *> Check if string is palindrome IF FUNCTION REVERSE(SOURCE-STRING) = SOURCE-STRING DISPLAY 'String is a palindrome' ELSE DISPLAY 'String is not a palindrome' END-IF. STRING-COMPARISON-OPERATIONS. DISPLAY 'String comparison operations' *> Case-insensitive comparison IF FUNCTION UPPER-CASE(STRING-1) = FUNCTION UPPER-CASE(STRING-2) DISPLAY 'Strings are equal (case-insensitive)' ELSE DISPLAY 'Strings are different' END-IF *> Length comparison IF FUNCTION LENGTH(STRING-1) > FUNCTION LENGTH(STRING-2) DISPLAY 'String 1 is longer than String 2' ELSE IF FUNCTION LENGTH(STRING-1) < FUNCTION LENGTH(STRING-2) DISPLAY 'String 1 is shorter than String 2' ELSE DISPLAY 'Strings have equal length' END-IF END-IF

Intrinsic string functions provide efficient string operations including length calculation, case conversion, string reversal, and comparison operations. These functions simplify common string manipulation tasks.

2. Custom String Functions

Custom string functions can be created to handle specific string processing requirements that are not covered by intrinsic functions.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
PROCEDURE DIVISION. CUSTOM-STRING-FUNCTIONS. DISPLAY 'Custom String Functions Example' *> Custom string validation function PERFORM CUSTOM-STRING-VALIDATION *> Custom string formatting function PERFORM CUSTOM-STRING-FORMATTING *> Custom string parsing function PERFORM CUSTOM-STRING-PARSING. CUSTOM-STRING-VALIDATION. DISPLAY 'Custom string validation' *> Validate email format PERFORM VALIDATE-EMAIL-FORMAT *> Validate phone number format PERFORM VALIDATE-PHONE-FORMAT *> Validate postal code format PERFORM VALIDATE-POSTAL-CODE-FORMAT. VALIDATE-EMAIL-FORMAT. DISPLAY 'Validating email format' *> Check for @ symbol IF FUNCTION LENGTH(EMAIL-STRING) > 0 PERFORM CHECK-EMAIL-SYMBOLS IF EMAIL-VALID DISPLAY 'Email format is valid' ELSE DISPLAY 'Email format is invalid' END-IF ELSE DISPLAY 'Email string is empty' END-IF. CHECK-EMAIL-SYMBOLS. MOVE 'Y' TO EMAIL-VALID-FLAG *> Check for @ symbol PERFORM VARYING EMAIL-INDEX FROM 1 BY 1 UNTIL EMAIL-INDEX > FUNCTION LENGTH(EMAIL-STRING) IF EMAIL-STRING(EMAIL-INDEX:1) = '@' ADD 1 TO AT-SYMBOL-COUNT END-IF END-PERFORM IF AT-SYMBOL-COUNT NOT = 1 MOVE 'N' TO EMAIL-VALID-FLAG END-IF. CUSTOM-STRING-FORMATTING. DISPLAY 'Custom string formatting' *> Format currency string PERFORM FORMAT-CURRENCY-STRING *> Format date string PERFORM FORMAT-DATE-STRING *> Format phone number string PERFORM FORMAT-PHONE-STRING. FORMAT-CURRENCY-STRING. DISPLAY 'Formatting currency string' *> Add currency symbol and formatting STRING '$' DELIMITED BY SIZE CURRENCY-AMOUNT DELIMITED BY SPACE INTO FORMATTED-CURRENCY END-STRING DISPLAY 'Formatted currency: ' FORMATTED-CURRENCY. CUSTOM-STRING-PARSING. DISPLAY 'Custom string parsing' *> Parse complex data string PERFORM PARSE-COMPLEX-DATA-STRING *> Extract specific patterns PERFORM EXTRACT-STRING-PATTERNS. PARSE-COMPLEX-DATA-STRING. DISPLAY 'Parsing complex data string' *> Parse JSON-like string MOVE '{"name":"John","age":"30","city":"New York"}' TO COMPLEX-STRING *> Extract name field PERFORM EXTRACT-JSON-FIELD 'name' NAME-FIELD *> Extract age field PERFORM EXTRACT-JSON-FIELD 'age' AGE-FIELD *> Extract city field PERFORM EXTRACT-JSON-FIELD 'city' CITY-FIELD DISPLAY 'Parsed fields - Name: ' NAME-FIELD ' Age: ' AGE-FIELD ' City: ' CITY-FIELD

Custom string functions provide specialized string processing capabilities for specific business requirements. These functions handle complex validation, formatting, and parsing operations not covered by intrinsic functions.

Best Practices for String Processing

Common String Processing Patterns