Standard way to remove spaces from input in cobol? - cobol

I'm just learning COBOL; I'm writing a program that simply echos back user input. I have defined a variable as:
User-Input PIC X(30).
Later when I ACCEPT User-Input, then DISPLAY User-Input " plus some extra text", it has a bunch of spaces to fill the 30 characters. Is there a standard way (like Ruby's str.strip!) to remove the extra spaces?

One would hope for a more elegant way of simply trimming text strings
but this is pretty much the standard solution... The trimming part
is done in the SHOW-TEXT paragraph.
*************************************
* TRIM A STRING... THE HARD WAY...
*************************************
IDENTIFICATION DIVISION.
PROGRAM-ID. TESTX.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 USER-INPUT PIC X(30).
01 I PIC S9(4) BINARY.
PROCEDURE DIVISION.
MOVE SPACES TO USER-INPUT
PERFORM SHOW-TEXT
MOVE ' A B C' TO USER-INPUT
PERFORM SHOW-TEXT
MOVE 'USE ALL 30 CHARACTERS -------X' TO USER-INPUT
PERFORM SHOW-TEXT
GOBACK
.
SHOW-TEXT.
PERFORM VARYING I FROM LENGTH OF USER-INPUT BY -1
UNTIL I LESS THAN 1 OR USER-INPUT(I:1) NOT = ' '
END-PERFORM
IF I > ZERO
DISPLAY USER-INPUT(1:I) '# OTHER STUFF'
ELSE
DISPLAY '# OTHER STUFF'
END-IF
.
Produces the following output:
# OTHER STUFF
A B C# OTHER STUFF
USE ALL 30 CHARACTERS -------X# OTHER STUFF
Note that the PERFORM VARYING statement relies on the left to
right evaluation of the UNTIL clause to avoid out-of-bounds
subscripting on USER-INPUT in the case where it contains only
blank spaces.

Use OpenCOBOL 1.1 or greater.
Identification division.
Program-id. 'trimtest'.
*> Compile:
*> cobc -x -free -ffunctions-all TrimTest.cbl
*>
Data division.
Working-Storage Section.
1 myBigStr Pic X(32768) Value Spaces.
Procedure Division.
Display "Enter Something? " With no advancing.
Accept myBigStr.
Display "[" Trim(myBigStr) "]".
Goback.
The trim function also has the options; Leading or Trailing.
cobc -h formore info.

Here's a solution if you work on OpenVMS:
01 WS-STRING-LENGTH PIC S9(04) COMP.
CALL "STR$TRIM" USING BY DESCRIPTOR user_output,
user_input,
BY REFERENCE WS-STRING-LENGTH.

a more general solution:
01 length pic 99.
perform varying length from 1 by 1
until length > 30 or user-input[length] = space
end-perform.
if length > 30
display user-input 'plus some extra text'
else
display user-input[1:length] 'plus some extra text'
end-if.
untested, I don't have a compiler at hand at the moment

There are three ways you can do this.
Use the COBOL functions to determine the string's "length". This is a mix of a couple functions. This is my preferred method, but requires declaring extra variables.
Write your own function to get the "length".
Use knowledge of a "terminating" string. You have to know what key characters indicates an end-of-string, like three spaces or a low-value character.
This example code demonstrates all three.
IDENTIFICATION DIVISION.
PROGRAM-ID. TESTPROG.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 ONE-A PIC X(20) VALUE 'RALPH WIGGAM'.
01 ONE-A-TLY PIC 9(02) VALUE ZERO.
01 ONE-A-LEN PIC 9(02) VALUE ZERO.
01 ONE-B PIC X(20) VALUE 'LIKES LEARNDING'.
01 ONE-B-TLY PIC 9(02) VALUE ZERO.
01 ONE-B-LEN PIC 9(02) VALUE ZERO.
01 TWO-A PIC X(20) VALUE 'RALPH WIGGAM'.
01 TWO-A-LEN PIC 9(02) VALUE ZERO.
01 TWO-B PIC X(20) VALUE 'LIKES LEARNDING'.
01 TWO-B-LEN PIC 9(02) VALUE ZERO.
01 THREE-A PIC X(20) VALUE 'RALPH WIGGAM'.
01 THREE-B PIC X(20) VALUE 'LIKES LEARNDING'.
01 THREE-C PIC X(80) VALUE SPACES.
PROCEDURE DIVISION.
DISPLAY ' -- METHOD ONE -- '
INSPECT FUNCTION REVERSE(ONE-A)
TALLYING ONE-A-TLY FOR LEADING SPACES.
SUBTRACT ONE-A-TLY FROM LENGTH OF ONE-A GIVING ONE-A-LEN.
INSPECT FUNCTION REVERSE(ONE-B)
TALLYING ONE-B-TLY FOR LEADING SPACES.
SUBTRACT ONE-B-TLY FROM LENGTH OF ONE-A GIVING ONE-B-LEN.
DISPLAY ONE-A(1:ONE-A-LEN)
' ' ONE-B(1:ONE-B-LEN)
'.'.
DISPLAY ' -- METHOD TWO -- '
PERFORM VARYING TWO-A-LEN FROM LENGTH OF TWO-A BY -1
UNTIL TWO-A-LEN < 1 OR TWO-A(TWO-A-LEN:1) > SPACE
END-PERFORM.
PERFORM VARYING TWO-B-LEN FROM LENGTH OF TWO-B BY -1
UNTIL TWO-B-LEN < 1 OR TWO-B(TWO-B-LEN:1) > SPACE
END-PERFORM.
DISPLAY TWO-A(1:TWO-A-LEN)
' ' TWO-B(1:TWO-B-LEN)
'.'.
DISPLAY ' -- METHOD THREE, NAIVE -- '
* DELIMITING BY JUST ANY SPACES ISN'T GOOD ENOUGH.
STRING THREE-A DELIMITED BY SPACES
' ' DELIMITED BY SIZE
THREE-B DELIMITED BY SPACES
'.' DELIMITED BY SIZE
INTO THREE-C.
DISPLAY THREE-C.
DISPLAY ' -- METHOD THREE, OK -- '
STRING THREE-A DELIMITED BY ' '
' ' DELIMITED BY SIZE
THREE-B DELIMITED BY ' '
'.' DELIMITED BY SIZE
INTO THREE-C.
DISPLAY THREE-C.
EXIT-PROG.
STOP RUN.
and the output looks like this:
-- METHOD ONE --
RALPH WIGGAM LIKES LEARNDING.
-- METHOD TWO --
RALPH WIGGAM LIKES LEARNDING.
-- METHOD THREE, NAIVE --
RALPH LIKES.
-- METHOD THREE, OK --
RALPH WIGGAM LIKES LEARNDING.

Related

Counting uppercase and lowercase. A better way to specify the alphabets?

Given this working version
IDENTIFICATION DIVISION.
PROGRAM-ID. HELLO-WORLD.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 UC-COUNTER PIC 99.
01 LC-COUNTER PIC 99.
PROCEDURE DIVISION.
INSPECT "My dog has fleas"
TALLYING UC-COUNTER FOR ALL 'A','B','C','D','E','F',
'G','H','I','J','K','L','M','N','O','P','Q','R','S','T',
'U','V','W','X','Y','Z'
LC-COUNTER FOR ALL 'a','b','c','d','e','f',
'g','h','i','j','k','l','m','n','o','p','q','r','s','t',
'u','v','w','x','y','z'.
DISPLAY UC-COUNTER " UPPER CASE CHARACTERS".
DISPLAY LC-COUNTER " LOWER CASE CHARACTERS".
GOBACK.
Is there a better way of expressing the alphabets? That is, can we have a SPECIAL-NAMES or something like that so that the instruction can be INSPECT TALLYING FOR ALL LATIN-UPPERCASE-LETTERS-ENGLISH or something similar.
LATER
Things like this don't appear to work (and given the GnuCOBOL docs, probably won't)
IDENTIFICATION DIVISION.
PROGRAM-ID. HELLO-WORLD.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SPECIAL-NAMES.
CLASS UPPER-CASE-ENGLISH-LETTERS IS
'A','B','C','D','E','F','G','H','I','J','K','L','M',
'N','O','P','Q','R','S','T','U','V','W','X','Y','Z'.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 UC-COUNTER PIC 99.
PROCEDURE DIVISION.
INSPECT "My dog has fleas"
TALLYING UC-COUNTER FOR ALL UPPER-CASE-ENGLISH-LETTERS.
DISPLAY UC-COUNTER " UPPER CASE CHARACTERS".
STOP RUN.
Is there a better way of expressing the alphabets?
COBOL has the class conditions ALPHABETIC-UPPER and ALPHABETIC-LOWER. Each of these includes space as part of the class condition. Unfortunately, for what you are requesting, class conditions cannot be used in an INSPECT statement.
It is necessary to simulate the INSPECT statement by using a loop to inspect each character to determine if it meets the class conditions while excluding spaces.
Code:
data division.
working-storage section.
01 uc-counter pic 99.
01 lc-counter pic 99.
01 str pic x(50).
01 n comp pic 9(4).
procedure division.
initialize uc-counter lc-counter
string "My dog has fleas" low-value delimited size
into str
perform varying n from 1 by 1
until str(n:1) = low-value
evaluate true
when str(n:1) = space
continue *> ignore space
when str(n:1) is alphabetic-upper
add 1 to uc-counter *> count upper-case letter
when str(n:1) is alphabetic-lower
add 1 to lc-counter *> count lower-case letter
when other
continue
end-evaluate
end-perform
display uc-counter " upper case characters"
display lc-counter " lower case characters"
goback
.
Output:
01 upper case characters
12 lower case characters
Depending on what character set you are using, if the characters are contiguous, then you could suffice with a few comparisons.

COBOL supress last number while summing two decimal numbers

According to the COBOL code below when I try to sum WS-NUM1 with WS-NUM2, COBOL seems to supress the last number. For example: variable WS-NUM1 and WS-NUM2 are 10.15, I get 20.20 as result but expected 20.30. What's wrong?
WS-NUM1 PIC 9(2)V99.
WS-NUM2 PIC 9(2)V99.
WS-RESULTADO PIC 9(2)V99.
DISPLAY "Enter the first number:"
ACCEPT WS-NUM1.
DISPLAY "Enter the second number:"
ACCEPT WS-NUM2.
COMPUTE WS-RESULTADO = WS-NUM1 + WS-NUM2.
Thanks in advance.
PIC 9(2)v99 defines a variable with an implied decimal place not a real one. You're trying to enter data containing a decimal point and it's not working because you have to strip out the '.' to get the numeric part of your data to properly fit in the 4 bytes that your working storage area occupies.
PROGRAM-ID. ADD2.
data division.
working-storage section.
01 ws-num-input pic x(5).
01 WS-NUM1 PIC 9(2)V99 value 0.
01 redefines ws-num1.
05 ws-high-num pic 99.
05 ws-low-num pic 99.
01 WS-NUM2 PIC 9(2)V99 value 0.
01 redefines ws-num2.
05 ws-high-num2 pic 99.
05 ws-low-num2 pic 99.
01 WS-RESULTADO PIC 9(2)V99.
PROCEDURE DIVISION.
DISPLAY "Enter the first number:"
*
accept ws-num-input
unstring ws-num-input delimited by '.'
into ws-high-num, ws-low-num
DISPLAY "Enter the second number:"
accept ws-num-input
unstring ws-num-input delimited by '.'
into ws-high-num2, ws-low-num2
*
COMPUTE WS-RESULTADO = WS-NUM1 + WS-NUM2.
DISPLAY WS-RESULTADO
STOP RUN
.
This is just a simple demonstration. In a real world application you would have to insure much more robust edits to ensure that valid numeric data was entered.
If I declare it like this
01 WS-NUM1 PIC 9(2)V99.
01 WS-NUM2 PIC 9(2)V99.
01 WS-RESULTADO PIC 9(2)V99.
and define and sum them up like this
SET WS-NUM1 TO 10.15.
SET WS-NUM2 TO 10.15.
COMPUTE WS-RESULTADO = WS-NUM1 + WS-NUM2.
DISPLAY WS-RESULTADO.
I get the expected result of 20.30.
This looks like a job for a special type of PICture : Edited picture
Indeed you seem to know about the vanilla PICture clause (I'm writing PICture because as you may know it you can either write PIC or PICTURE).
A vanilla number PIC contains only 4 different symbols (and the parentheses and numbers in order to repeat some of the symbols)
9 : Represents a digit. You can repeat by using a number between parentheses like said before.
S : Means that the number is signed
V : Show the position of the implicit decimal point
P : I've been told that it exists but I honestly never found it in the codebase of my workplace. Its another kind of decimal point used for scaling factors but I don't know much about it.
But there are other symbols.
If you use theses other mysterious symbols the numeric PIC becomes an edited numeric PIC. As its name says, an edited PICture is made to be shown. It will allow you to format your numbers for better presentation or to receive number formatted for human reading.
Once edited, you cannot use it to make computations so you will have to transfer from edited to vanilla to perform computations on the latter. And you move from vanilla to edited in order to display your results.
So now I shall reveal some of these mysterious symbols :
B : Insert a blank at the place it is put
0 : Insert a zero at the place it is put
. : Insert the decimal point at the place it is put
: Insert a + if the number is positive and a - if the number is negative
Z : Acts like a 9 if the digits it represents has a value different than 0. Acts like a blank if the digits has the value of 0.
To my knowledge there are also : / , CR DB * $ -
You can look up for it on the internet. They really show the accountant essence of cobol.
For your problems we are really interested by the "." which will allow us to take into account the decimal point you have the write when you type down your input.
For a bonus I will also use Z which will make your result looks like 2.37 instead of 02.37 if the number is less than ten.
Note that you cannot use the repeating pattern with parenthesis ( 9(03) for instance) when describing an edited picture ! Each digits has to represented explicitly
IDENTIFICATION DIVISION.
PROGRAM-ID. EDITCOMP.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-NUM1-EDITED PIC 99.99.
01 WS-NUM2-EDITED PIC 99.99.
01 WS-NUM1-CALC PIC 9(2)V99.
01 WS-NUM2-CALC PIC 9(2)V99.
01 WS-RESULTADO-EDITED PIC Z9.99.
PROCEDURE DIVISION.
ACCEPT WS-NUM1-EDITED.
ACCEPT WS-NUM2-EDITED.
MOVE WS-NUM1-EDITED TO WS-NUM1-CALC.
MOVE WS-NUM2-EDITED TO WS-NUM2-CALC.
COMPUTE WS-RESULTADO-EDITED = WS-NUM1-CALC + WS-NUM2-CALC.
DISPLAY WS-RESULTADO-EDITED.
STOP RUN.
You should note that there also exist edited alphanumeric picture. You can insert Blank (B), zeroes (0) or / (/) in it.

COBOL: Can a GDG file descriptor (FD) reference multiple generations?

I have a program which reads a GDG file and moves data to working storage. I am interested to know if it can be made to repeat this process for multiple generations of the GDG using a reference to the file definition. Perhaps there is a way to use subscripts on the file definition? My thought is there must be a method to move different file definitions into a reference variable from which to access the files.
Code Sample based on suggested, setenv solution
FILE-CONTROL.
SELECT DATAIN ASSIGN TO UT-S-DATAIN.
DATA DIVISION.
FILE-SECTION.
FD DATAIN
BLOCK CONTAINS 0 RECORDS
RECORD CONTAINS 133 CHARACTERS
LABEL RECORDS ARE STANDARD
DATA RECORD IS DATA-REC.
01 DATA-REC PIC X(133).
WORKING-STORAGE SECTION.
01 ENV-VARS.
02 ENV-NAME PIC X(9).
02 ENV-VALUE PIC X(100).
02 ENV-OVERWRITE PIC S9(8) COMPUTATIONAL VALUE 1.
PROCEDURE DIVISION.
MOVE Z"DATAIN" TO ENV-NAME
MOVE Z"DSN(PROGRAMMER.TEST.GDGFILE(-1)),SHR" TO ENV-VALUE
MOVE 1 TO ENV-OVERWRITE
CALL "setenv" USING ENV-NAME ENV-VALUE ENV-OVERWRITE.
Notes
Pay special attention when moving DSN value to ENV-VALUE. On my first swing I left out the closing parentheses, most likely because of JCL muscle memory.
Be sure to empty out your DD statement in JCL/Step.
In mainframe COBOL, the FD refers to a SELECT which refers to a DD statement attached to the EXEC PGM statement for your program in the invoking JCL. The DD statement may refer to one or many GDGs. This is determined at compile time.
What I think you are asking for is dynamic allocation of a file at runtime. There are a couple of ways to accomplish that, one is BPXWDYN.
Identification Division.
Program-ID. SOMETEST.
Environment Division.
Input-Output Section.
File-Control.
Select MY-FILE Assign SYSUT1A.
Data Division.
File Section.
FD MY-FILE
Record 80
Block 0
Recording F.
01 MY-FILE-REC PIC X(080).
Working-Storage Section.
01 CONSTANTS.
05 BPXWDYN-PGM PIC X(008) VALUE 'BPXWDYN '.
05 ALCT-LIT-PROC PIC X(035)
VALUE 'ALLOC FI(SYSUT1A) SHR MSG(WTP) DSN('.
05 FREE-LIT-PROC PIC X(016)
VALUE 'FREE FI(SYSUT1A)'.
05 A-QUOTE PIC X(001) VALUE "'".
01 WORK-AREAS.
05 WS-DSN PIC X(044) VALUE 'MY.GDG.BASE'.
05 WS-GDG-NB PIC 999 VALUE ZEROS.
05 BPXWDYN-PARM.
10 PIC S9(004) COMP-5 VALUE +100.
10 BPXWDYN-PARM-TXT PIC X(100).
Procedure Division.
* Construct the allocation string for BPXWDYN.
MOVE SPACES TO BPXWDYN-PARM-TXT
STRING
ALCT-LIT-PROC
DELIMITED SIZE
WS-DSN
DELIMITED SPACE
'(-'
DELIMITED SIZE
WS-GDG-NB
DELIMITED SIZE
')'
DELIMITED SIZE
INTO
BPXWDYN-PARM-TXT
END-STRING
CALL BPXWDYN-PGM USING
BPXWDYN-PARM
END-CALL
IF RETURN-CODE = 0
CONTINUE
ELSE
[error handling]
END-IF
[file I/O with MY-FILE]
MOVE SPACES TO BPXWDYN-PARM-TXT
MOVE FREE-LIT-PROC TO BPXWDYN-PARM-TXT
CALL BPXWDYN-PGM USING
BPXWDYN-PARM
END-CALL
IF RETURN-CODE = 0
CONTINUE
ELSE
[error handling]
END-IF
GOBACK.
This is just freehand, so there may be a syntax error, but I hope I've made the idea clear.
There is another technique, using the C RTL function setenv, documented by IBM here. It looks like it might be simpler but I've never done it that way.

Extract records by first letter of name

I am trying to make the program below to pull out records that have customer names beginning with letter the "M" and write the records to a temporary file. The program runs but it won't write records to the output file. I debugged the code, and it seems like the code line "WRITE MAST2-RECORD" never runs. It skips this line of code.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT MAST-FILE ASSIGN TO 'G:\CPSC315-COBOL\COBOLAssignments\P15-1\OVERDUE.IND.TXT'
ORGANIZATION IS INDEXED
ACCESS IS RANDOM
RECORD KEY IS M-ACCT-NUM.
SELECT MAST2-FILE ASSIGN TO 'G:\CPSC315-COBOL\COBOLAssignments\P15-1\OVERDUE2.IND.TXT'
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD MAST-FILE
LABEL RECORDS ARE STANDARD.
01 MAST-RECORD.
05 M-ACCT-NUM PIC X(4).
05 M-CUSTOMER-NAME PIC X(15).
05 M-DAYS-OVERDUE PIC 99.
05 M-BALANCE-DUE PIC 999V99.
FD MAST2-FILE
LABEL RECORDS ARE STANDARD.
01 MAST2-RECORD PIC X(50).
WORKING-STORAGE SECTION.
01 COUNTER PIC 9.
01 PROGRAM-DATA-ITEMS.
05 WRITE-OK PIC X VALUE 'Y'.
PROCEDURE DIVISION.
10-MAINLINE.
OPEN OUTPUT MAST-FILE
OUTPUT MAST2-FILE
PERFORM 20-LOAD-MAST-FILE
CLOSE MAST-FILE
MAST2-FILE
STOP RUN.
20-LOAD-MAST-FILE.
PERFORM 30-INPUT-INDEX
PERFORM UNTIL M-ACCT-NUM = 0 OR WRITE-OK = 'N'
PERFORM 40-WRITE-FILE
PERFORM 50-FIND-CUSTOMER-START-WITH-M
PERFORM 30-INPUT-INDEX
END-PERFORM.
30-INPUT-INDEX.
DISPLAY 'ENTER ACCOUNT NUMBER (0 TO QUIT): ' WITH NO ADVANCING
ACCEPT M-ACCT-NUM.
40-WRITE-FILE.
DISPLAY ' ENTER CUSTOMER NAME: ' WITH NO ADVANCING
ACCEPT M-CUSTOMER-NAME
DISPLAY ' ENTER DAYS OVERDUE: ' WITH NO ADVANCING
ACCEPT M-DAYS-OVERDUE
DISPLAY ' ENTER BALANCE DUE: ' WITH NO ADVANCING
ACCEPT M-BALANCE-DUE
WRITE MAST-RECORD
INVALID KEY
MOVE 'N' TO WRITE-OK
DISPLAY 'ERROR ' MAST-RECORD
END-WRITE.
50-FIND-CUSTOMER-START-WITH-M.
MOVE 0 TO COUNTER
INSPECT MAST-RECORD TALLYING COUNTER FOR ALL ' M '
IF COUNTER > 0
WRITE MAST2-RECORD
END-IF.
end program Program1.
You are looking for blank-M-blank, across the entire record.
What you say you want to do is fine customer-names which begin with M.
05 M-CUSTOMER-NAME.
10 M-CUSTOMER-NAME-FIST-CHARACTER PIC X.
88 M-CUSTOMER-NAME-START-M VALUE "M".
If you use that definition in place of what you have, and use the 88 in the test for your write, you should get what you want.
Eg replace:
50-FIND-CUSTOMER-START-WITH-M.
MOVE 0 TO COUNTER
INSPECT MAST-RECORD TALLYING COUNTER FOR ALL ' M '
IF COUNTER > 0
WRITE MAST2-RECORD
END-IF.
By:
50-FIND-CUSTOMER-START-WITH-M.
IF M-CUSTOMER-NAME-START-M
WRITE MAST2-RECORD
END-IF
.
Simpler, easier to understand, so easier to maintain.
You should consider the possible "validity" of your names. In a good system, there will be no leading blanks. In a poor system there may be.
To deal with that, test the first byte of the customer-name for being space as well, if so, test the customer-name for entirely space. If not entirely space, loop until you find the first non-blank. Test that first non-blank for M. So in this case you have two tests.
You can assess the quality of your data separately by copying and cutting-down this program and reporting/outputting where the first byte of the customer-name is blank.
Once you know that, you go to the analyst (tutor) and ask if you need to deal with possible leading blanks. If you don't, keep the test for blank in your actual program, and crash in that case :-)

How do you grab a string in COBOL from a file when the position is unknown?

I'm new to the site as well as COBOL. I am trying to write a program that reads in an 80 byte file, and finds a certain string and grabs another string that is positioned right after that. The only issue I'm having with this is that the starting position of the string is not always in the same byte throughout the file. For example, the string I am trying to find below is the LENGTH(#####) string that appears twice throughout the file:
LENGTH(14909135) FILEID(DD:EDIREC) MSGDATE(130723) MSGDATELONG(20130723)
MSGTIME(091053) MSGSEQO(001390) MSGNAME(00008557) MSGSEQNO(00001)
SESSIONKEY(XXXXXXXX) DELIMITED(E) SYSNAME(XXXXX-XX) SYSLEVEL(XXXX) TIMEZONE(L)
DATATYPE(E) EDITYPE(XXX) SENDERFILE(#####) RECFM(????) RECLEN(#) RECDLM(E)
UNIQUEID(XXXXXXXX) SYSTYPE(##) SYSVER(#);
RECEIVED ACCOUNT(XXXX) USERID(XXXXXXXX) CLASS(#E2) CHARGE(3) LENGTH(14911043)
FILEID(DD:EDIREC) MSGDATE(130723) MSGDATELONG(20130723) MSGTIME(093045)
MSGSEQO(001392) MSGSEQNO(00000) SESSIONKEY(XXXXXXXX) DELIMITED(C)
SYSNAME(XXXXX-XX) SYSLEVEL(XXXX) TIMEZONE(L) DATATYPE(E) EDITYPE(UNFORMATTED)
SENDERFILE(XXXXXXXXXXXXX) RECFM(????) RECLEN(0) RECDLM(C) UNIQUEID(XXXXXXXX)
SYSTYPE(24) SYSVER(5);
Notice the two LENGTH(#####) strings. The below code manages to count the amount of times the length string appears as well as grab the final length string count (what I really want, the numbers within the length string), but only when they are in these two positions:
WORKING-STORAGE SECTION.
01 WS-INPUT-RECORD PIC X(80).
01 WS-STRINGS.
05 LENGTH-STRING PIC X(7) VALUE 'LENGTH('.
01 WS-COUNTERS.
05 WS-MSG-COUNT PIC 9(11).
01 WS-CHAR-TOTALS.
05 CHAR-TOTAL PIC 9(11) VALUE ZEROS.
05 TMP-TOTAL PIC X(11) VALUE ZEROS.
......
PROCEDURE DIVISION.
2200-GET-MSG-TOTAL.
INSPECT WS-INPUT-RECORD
TALLYING WS-MSG-COUNT FOR ALL LENGTH-STRING.
2300-CHAR-TOTAL.
IF WS-INPUT-RECORD(1:7) = LENGTH-STRING
MOVE WS-INPUT-RECORD(8:9) TO TMP-TOTAL
UNSTRING TMP-TOTAL DELIMITED BY ')'
INTO CHAR-TOTAL
END-IF
IF WS-INPUT-RECORD(61:7) = LENGTH-STRING
MOVE WS-INPUT-RECORD(68:9) TO TMP-TOTAL
UNSTRING TMP-TOTAL DELIMITED BY ')'
INTO CHAR-TOTAL
END-IF
The code works great for the two positions shown in the example input above. But it won't work if LENGTH(####) ends up in any other byte position. Other than coding 80 IF statements to check for every byte in the file for the string, is there an easier way to go about getting those values inside of the length parens? I've checked a lot of other posts and I've thought about using pointers or tables but I can't quite seem to figure it out.
Use INSPECT to establish that LENGTH( is on the current record.
Only if present, do the following:
UNSTRING using LENGTH( as a delimiter with two receiving fields.
UNSTRING second receiving field delimited by ) leaving you with the number.
For example:
01 delimiting-field PIC X(7) VALUE "LENGTH(".
01 desitnation-field-1 PIC X.
01 destination-field-2 PIC X(18) JUST RIGHT.
UNSTRING source-field DELIMITED BY delimiting-field INTO desitnation-field-1
destination-field-2
Abandon destination-field-1. Use destination-field-2 for input to the second UNSTRING.
Use meaningful names, rather than those I have shown to illuminate the example.
So,
01 WS-INPUT-RECORD PIC X(80).
01 NUMBER-OF-LENGTHS BINARY PIC 9(4).
01 DELIMITER-COUNT BINARY PIC 9(4).
88 NO-DELIMITERS VALUE ZERO.
88 ONE-DELIMITER VALUE 1.
01 LENGTH-OPEN-PAREN PIC X(7)
VALUE "LENGTH(".
01 DATA-TO-IGNORE PIC X.
01 DATA-WITH-LENGTH-VALUE PIC X(80).
01 CLOSING-PAREN PIC X VALUE ")".
01 VALUE-OF-LENGTH-AN PIC X(18) JUST RIGHT.
THE-STUFF.
SET NO-DELIMITERS TO TRUE
INSPECT WS-INPUT-RECORD TALLYING DELIMITER-COUNT
FOR ALL LENGTH-OPEN-PAREN
EVALUATE TRUE
WHEN NO-DELIMITERS
CONTINUE
WHEN ONE-DELIMITER
PERFORM GET-THE-DATA
WHEN OTHER
PERFORM OH-DEAR-MORE-THAN-ONE
END-EVALUATE
.
GET-THE-DATA.
UNSTRING WS-INPUT-RECORD DELIMITED BY
LENGTH-OPEN-PAREN
INTO DATA-TO-IGNORE
DATA-WITH-LENGTH-VALUE
UNSTRING DATA-WITH-LENGTH-VALUE
DELIMITED BY CLOSING-PAREN
INTO VALUE-OF-LENGTH-AN
DISPLAY "THIS IS WHAT WE FOUND"
DISPLAY ">"
VALUE-OF-LENGTH-AN
"<"
.
OH-DEAR-MORE-THAN-ONE.
DISPLAY "THE FOLLOWING LINE HAS MORE THAN ONE LENGTH("
DISPLAY ">"
WS-INPUT-RECORD
"<"
.
The technique with the INSPECT to see if the "string" is present can be applied to the other solution accepted so that only if the line contains the value desired is it "searched".
You can use a "perform varying" loop to look at each block of the string within each line, where each block is a string the length of the string you are looking for. Here is an example that works in OpenCobol:
IDENTIFICATION DIVISION.
PROGRAM-ID. FIND-STRING.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT IN-FILE ASSIGN TO 'SAMPLE-LEN.TXT'
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD IN-FILE.
01 IN-RECORD PIC X(80).
WORKING-STORAGE SECTION.
01 END-OF-FILE-SWITCH PIC XXX VALUE 'NO '.
88 END-OF-FILE VALUE 'YES'.
01 STRING-MARKER PIC X(7) VALUE 'LENGTH('.
01 STRING-MARKER-LENGTH PIC 99 VALUE 7.
01 STRING-SOUGHT PIC X(11).
01 STRING-INDEX PIC 99.
01 RECORD-LENGTH PIC 99 VALUE 80.
PROCEDURE DIVISION.
MAIN.
OPEN INPUT IN-FILE
PERFORM UNTIL END-OF-FILE
READ IN-FILE
AT END
SET END-OF-FILE TO TRUE
NOT AT END
PERFORM FIND-STRING
END-READ
END-PERFORM
CLOSE IN-FILE
STOP RUN
.
FIND-STRING.
PERFORM VARYING STRING-INDEX FROM 1 BY 1
UNTIL STRING-INDEX > (RECORD-LENGTH
- STRING-MARKER-LENGTH)
IF IN-RECORD(STRING-INDEX:STRING-MARKER-LENGTH) =
STRING-MARKER
UNSTRING IN-RECORD(STRING-INDEX
+ STRING-MARKER-LENGTH : 10)
DELIMITED BY ')' INTO STRING-SOUGHT
END-UNSTRING
DISPLAY STRING-SOUGHT END-DISPLAY
END-IF
END-PERFORM
.
Based on Bill Woodger's comments, here is a better solution. Thank's Bill, for teaching me not to slouch :) I still like looping through each record as a way to catch multiple matches on one line, so I kept that part.
IDENTIFICATION DIVISION.
PROGRAM-ID. FIND-STRING-2.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT IN-FILE ASSIGN TO 'SAMPLE-LEN.TXT'
ORGANIZATION IS LINE SEQUENTIAL
FILE STATUS IS IN-FILE-STATUS.
DATA DIVISION.
FILE SECTION.
FD IN-FILE.
01 IN-RECORD PIC X(80).
WORKING-STORAGE SECTION.
01 IN-FILE-STATUS PIC XX.
01 END-OF-FILE-SWITCH PIC XXX VALUE 'NO '.
88 END-OF-FILE VALUE 'YES'.
01 STRING-MARKER-LEFT PIC X(7) VALUE 'LENGTH('.
01 STRING-MARKER-RIGHT PIC X VALUE ')'.
01 STRING-MARKER-LENGTH PIC 99 USAGE BINARY.
01 STRING-INDEX PIC 99 USAGE BINARY.
01 START-INDEX PIC 99 USAGE BINARY.
01 END-INDEX PIC 99 USAGE BINARY.
01 RECORD-LENGTH PIC 99 USAGE BINARY.
01 SEARCH-LENGTH PIC 99 USAGE BINARY.
01 IS-END-FOUND PIC XXX VALUE 'NO '.
88 END-FOUND VALUE 'YES'.
88 END-NOT-FOUND VALUE 'NO '.
PROCEDURE DIVISION.
MAIN.
OPEN INPUT IN-FILE
IF IN-FILE-STATUS NOT = '00'
DISPLAY 'FILE READ ERROR ' IN-FILE-STATUS
END-DISPLAY
PERFORM EXIT-PROGRAM
END-IF
PERFORM INITIALIZE-LENGTHS
PERFORM UNTIL END-OF-FILE
READ IN-FILE
AT END
SET END-OF-FILE TO TRUE
NOT AT END
PERFORM FIND-STRING
END-READ
END-PERFORM
PERFORM EXIT-PROGRAM
.
INITIALIZE-LENGTHS.
MOVE FUNCTION LENGTH(IN-RECORD) TO RECORD-LENGTH
COMPUTE STRING-MARKER-LENGTH = FUNCTION LENGTH(
STRING-MARKER-LEFT)
END-COMPUTE
COMPUTE SEARCH-LENGTH = RECORD-LENGTH - STRING-MARKER-LENGTH
END-COMPUTE
.
FIND-STRING.
PERFORM VARYING STRING-INDEX FROM 1 BY 1
UNTIL STRING-INDEX > SEARCH-LENGTH
IF IN-RECORD(STRING-INDEX:STRING-MARKER-LENGTH) =
STRING-MARKER-LEFT
COMPUTE START-INDEX = STRING-INDEX
+ STRING-MARKER-LENGTH
END-COMPUTE
SET END-NOT-FOUND TO TRUE
PERFORM VARYING END-INDEX FROM START-INDEX BY 1
UNTIL END-INDEX > RECORD-LENGTH OR END-FOUND
IF IN-RECORD(END-INDEX:
FUNCTION LENGTH(STRING-MARKER-RIGHT)) =
STRING-MARKER-RIGHT
SET END-FOUND TO TRUE
END-IF
END-PERFORM
COMPUTE END-INDEX = END-INDEX - START-INDEX - 1
END-COMPUTE
DISPLAY IN-RECORD(START-INDEX:END-INDEX)
END-DISPLAY
END-IF
END-PERFORM
.
EXIT-PROGRAM.
CLOSE IN-FILE
STOP RUN
.

Resources