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

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.

Related

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.

Read a file with three records, only one of expected records output

IDENTIFICATION DIVISION.
PROGRAM-ID. PROGRAM1.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT EMP-GRADE ASSIGN TO 'input.txt'
ORGANIZATION IS SEQUENTIAL
ACCESS MODE IS SEQUENTIAL
FILE STATUS IS WS-STATUS.
DATA DIVISION.
FILE SECTION.
FD EMP-GRADE.
01 NEWFILE.
05 FS-EMPID PIC 9(5).
05 FS-NAME PIC A(5).
05 FS-STREAM PIC X(5).
05 FS-GRADE PIC A(1).
05 FILLER PIC X(64).
WORKING-STORAGE SECTION.
01 WS-EOF PIC A(1) VALUE "N".
01 WS-STATUS PIC X(2).
PROCEDURE DIVISION.
MAIN-PARA.
OPEN INPUT EMP-GRADE.
PERFORM PARA1 THRU PARA1-EXIT UNTIL WS-EOF="Y".
CLOSE EMP-GRADE.
STOP RUN.
MAIN-PARA-EXIT.
EXIT.
PARA1.
READ EMP-GRADE
AT END MOVE "Y" TO WS-EOF
NOT AT END
IF FS-GRADE='A'
DISPLAY FS-EMPID , FS-NAME , FS-STREAM , FS-GRADE
END-IF
END-READ.
PARA1-EXIT.
EXIT.
input provided:
1234 sita comp A
2345 tina main B
5689 riya math A
but the output is coming :
1234 sita comp A
It is reading only the first record.
As Brian Tiffin is hinting at in the comments, it is your data which is the problem.
This:
05 FILLER PIC X(64).
Means that your records should be 64 bytes longer than they are.
If you have a fixed-length record, or only fixed-length records, under an FD, then the data all have to be the same length, and equal to what you have defined in your program.
It means, and behaviour depends on compiler, you only have one record as far as the COBOL program is concerned.
A good way to spot such things is to always count your input records, and count your output records, and records which should not be selected for output. You can then easily tell if anything has fallen between a crack.
Leaving that aside, here's your program with some adjustments:
IDENTIFICATION DIVISION.
PROGRAM-ID. PROGRAM1.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT EMP-GRADE ASSIGN TO 'input.txt'
ORGANIZATION IS SEQUENTIAL
ACCESS MODE IS SEQUENTIAL
FILE STATUS IS WS-STUDENT-GRADE-STATUS.
DATA DIVISION.
FILE SECTION.
FD EMP-GRADE.
01 NEWFILE.
05 FS-EMPID PIC 9(5).
05 FS-NAME PIC X(5).
05 FS-STREAM PIC X(5).
05 FS-GRADE PIC X(1).
05 FILLER PIC X(64).
WORKING-STORAGE SECTION.
01 WS-STUDENT-GRADE-STATUS PIC X(2).
88 END-OF-STUDENT-GRADE-FILE VALUE "10".
88 ERROR-ON-STUDENT-GRADE-FILE VALUE ZERO.
PROCEDURE DIVISION.
OPEN INPUT EMP-GRADE
* perform a paragraph to check FILE STATUS field is zero, using an 88.
PERFORM PRIMING-READ
PERFORM PROCESS-STUDENT-GRADE-FILE
UNTIL END-OF-STUDENT-GRADE-FILE
CLOSE EMP-GRADE
* perform a paragraph to check FILE STATUS field is zero, using an 88.
GOBACK
.
PRIMING-READ.
PERFORM READ-STUDENT-GRADE
.
READ-STUDENT-GRADE.
READ EMP-GRADE
* perform a paragraph to check FILE STATUS field is zero, using an 88.
.
PROCESS-STUDENT-GRADE-FILE.
IF FS-GRADE='A'
* To see the problem with your data, DISPLAY the 01-level
DISPLAY NEWFILE
DISPLAY FS-EMPID
FS-NAME
FS-STREAM FS-GRADE
END-IF
PERFORM READ-STUDENT-GRADE
.
If you use the FILE STATUS field, you should check it. Since you use it, you can use it to check for end-of-file without the AT END. If you use a "priming read" you don't need the AT END/NOT AT END tangle. If you code the minimum of full-stops/periods in the PROCEDURE DIVISION, you won't have a problem with them. Commas are never needed, so don't use them. Format your program for human readability. Use good descriptive names for everything. The THRU on a PERFORM invites the use of GO TO. As a learning, avoid the invitation.
If your class itself enforces particular ways to code COBOL, you'll have to use those ways. If so, I'd suggest you do both. The first couple of times at least, submit both to your tutor. Even if they tell you not to do that, continue doing dual examples when given tasks (just don't submit them any more). There is no reason for you to start off with bad habits.
Keep everything simple. If your code looks bad, make it look good through simplification and formatting.
Remember also that COBOL is all about fixed-length stuff. Get's us back to your original problem.

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
.

Read and jump first line and anothers lines in file

How I can read a .dat file with struct like that: ( A = ALPHANUMERIC && N = NUMERIC )
0AAAAAAAANNNN (233 BLANK SPACES ) 999999 ( SEQUENTIAL NUMBER ONE BY ONE )
1NNNNNNNNNNNNAAAAAAAAAAAAAAAAAAA (194 BLANK SPACES) 999999 (SEQUENTIAL NUMBER ONE BY ONE)
2AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA (194 BLANK SPACES) 999999 (SEQUENTIAL NUMBER ONE BY ONE)
1NNNNNNNNNNNNAAAAAAAAAAAAAAAAAAA (194 BLANK SPACES) 999999 (SEQUENTIAL NUMBER ONE BY ONE)
2AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA (194 BLANK SPACES) 999999 (SEQUENTIAL NUMBER ONE BY ONE)
1NNNNNNNNNNNNAAAAAAAAAAAAAAAAAAA (194 BLANK SPACES) 999999 (SEQUENTIAL NUMBER ONE BY ONE)
2AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA (194 BLANK SPACES) 999999 (SEQUENTIAL NUMBER ONE BY ONE)
1NNNNNNNNNNNNAAAAAAAAAAAAAAAAAAA (194 BLANK SPACES) 999999 (SEQUENTIAL NUMBER ONE BY ONE)
2AAAAAAAAAAAAAAAAAAAAAAAAAAAAAAA (194 BLANK SPACES) 999999 (SEQUENTIAL NUMBER ONE BY ONE)
9 (245 BLANK SPACES) 999999 (SEQUENTIAL NUMBER ONE BY ONE)
So, I know, how I can make a program to read this in C/C++ or in C#, but, I try to make in Cobol, just for study....
But, I don't know what the command I need to use to open the file with this style ( I just know the:
ORGANIZATION IS LINE SEQUENTIAL.
I think, exist a another command to open with custon instructions... i don't know...
So, btw, how I can open the file and read the informations ??
( i just need to read the line 1 on time, and, I need to read the line 2 and 3 always paried ... 4 and 5 && 6 and 7 && 8 and 9 ... )
and, I whant to show that information with DISPLAY ( just for study )
Thanks :)
Something like this below your FD:
01 INPUT-RECORD.
05 IR-RECORD-TYPE PIC X.
88 INPUT-RECORD-IS-HEADER VALUE '0'.
88 INPUT-RECORD-IS-DATA1 VALUE '1'.
88 INPUT-RECORD-IS-DATA2 VALUE '2'.
88 INPUT-RECORD-IS-TRAILER VALUE '9'.
05 FILLER PIC X(whatever).
You may need a "trailing" byte for a record-delimiter, I don't know, and you'll have to sort out the lengths, as they seem to vary.
These in Working-Storage:
01 INPUT-RECORD-HEADER.
05 IRH-RECORD-TYPE PIC X.
05 IRH-ITEM1 PIC X(8).
05 IRH-ITEM2 PIC 9(4).
05 FILLER PIC X(233).
05 IRH-SEQUENCE PIC X(6)
01 INPUT-RECORD-DATA1.
05 IRD1-RECORD-TYPE PIC X.
05 IRD1-ITEM1 PIC 9(14).
05 IRD1-ITEM1 PIC X(19).
05 FILLER PIC X(194).
05 IRD1-SEQUENCE PIC X(6)
01 INPUT-RECORD-DATA2.
05 IRD2-RECORD-TYPE PIC X.
05 IRD2-ITEM1 PIC X(33).
05 FILLER PIC X(194).
05 IRD2-SEQUENCE PIC X(6)
01 INPUT-RECORD-TRAILER.
05 IRT-RECORD-TYPE PIC X.
05 FILLER PIC X(245).
05 IRT-SEQUENCE PIC X(6).
You have to read each record, one at a time. Identify it. Put it in the correct W-S definition. When you read a "2" you can process the "1" you have stored along with the "2".
My datanames aren't very good, as I don't know what your data is. Also I have not "formatted" the definitions, which will make them more readable when you do it.
For OpenCOBOL, here is a sample standard in/standard out filter program:
>>SOURCE FORMAT IS FIXED
*> ***************************************************************
*><* ===========
*><* filter
*><* ===========
*><* :Author: Brian Tiffin
*><* :Date: 20090207
*><* :Purpose: Standard IO filters
*><* :Tectonics: cobc -x filter.cob
*> ***************************************************************
identification division.
program-id. filter.
environment division.
configuration section.
input-output section.
file-control.
select standard-input assign to keyboard.
select standard-output assign to display.
data division.
file section.
fd standard-input.
01 stdin-record pic x(32768).
fd standard-output.
01 stdout-record pic x(32768).
working-storage section.
01 file-status pic x value space.
88 end-of-file value high-value
when set to false is low-value.
*> ***************************************************************
procedure division.
main section.
00-main.
perform 01-open
perform 01-read
perform
until end-of-file
perform 01-transform
perform 01-write
perform 01-read
end-perform
.
00-leave.
perform 01-close
.
goback.
*> end main
support section.
01-open.
open input standard-input
open output standard-output
.
01-read.
read standard-input
at end set end-of-file to true
end-read
.
*> All changes here
01-transform.
move stdin-record to stdout-record
.
*>
01-write.
write stdout-record end-write
.
01-close.
close standard-input
close standard-output
.
end program filter.
*><*
*><* Last Update: dd-Mmm-yyyy
and here is a demonstration of using LINAGE that just happens to read in a text file.
*****************************************************************
* Example of LINAGE File Descriptor
* Author: Brian Tiffin
* Date: 10-July-2008
* Tectonics: $ cocb -x linage-demo.cob
* $ ./linage-demo <filename ["linage-demo.cob"]>
* $ cat -n mini-report
*****************************************************************
IDENTIFICATION DIVISION.
PROGRAM-ID. linage-demo.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
select optional data-file assign to file-name
organization is line sequential
file status is data-file-status.
select mini-report assign to "mini-report".
DATA DIVISION.
FILE SECTION.
FD data-file.
01 data-record.
88 endofdata value high-values.
02 data-line pic x(80).
FD mini-report
linage is 16 lines
with footing at 15
lines at top 2
lines at bottom 2.
01 report-line pic x(80).
WORKING-STORAGE SECTION.
01 command-arguments pic x(1024).
01 file-name pic x(160).
01 data-file-status pic 99.
01 lc pic 99.
01 report-line-blank.
02 filler pic x(18) value all "*".
02 filler pic x(05) value spaces.
02 filler pic x(34)
VALUE "THIS PAGE INTENTIONALLY LEFT BLANK".
02 filler pic x(05) value spaces.
02 filler pic x(18) value all "*".
01 report-line-data.
02 body-tag pic 9(6).
02 line-3 pic x(74).
01 report-line-header.
02 filler pic x(6) VALUE "PAGE: ".
02 page-no pic 9999.
02 filler pic x(24).
02 filler pic x(5) VALUE " LC: ".
02 header-tag pic 9(6).
02 filler pic x(23).
02 filler pic x(6) VALUE "DATE: ".
02 page-date pic x(6).
01 page-count pic 9999.
PROCEDURE DIVISION.
accept command-arguments from command-line end-accept.
string
command-arguments delimited by space
into file-name
end-string.
if file-name equal spaces
move "linage-demo.cob" to file-name
end-if.
open input data-file.
read data-file
at end
display
"File: " function trim(file-name) " open error"
end-display
go to early-exit
end-read.
open output mini-report.
write report-line
from report-line-blank
end-write.
move 1 to page-count.
accept page-date from date end-accept.
move page-count to page-no.
write report-line
from report-line-header
after advancing page
end-write.
perform readwrite-loop until endofdata.
display
"Normal termination, file name: "
function trim(file-name)
" ending status: "
data-file-status
end-display.
close mini-report.
* Goto considered harmful? Bah! :)
early-exit.
close data-file.
exit program.
stop run.
****************************************************************
readwrite-loop.
move data-record to report-line-data
move linage-counter to body-tag
write report-line from report-line-data
end-of-page
add 1 to page-count end-add
move page-count to page-no
move linage-counter to header-tag
write report-line from report-line-header
after advancing page
end-write
end-write
read data-file
at end set endofdata to true
end-read
.
*****************************************************************
* Commentary
* LINAGE is set at a 20 line logical page
* 16 body lines
* 2 top lines
* A footer line at 15 (inside the body count)
* 2 bottom lines
* Build with:
* $ cobc -x -Wall -Wtruncate linage-demo.cob
* Evaluate with:
* $ ./linage-demo
* This will read in linage-demo.cob and produce mini-report
* $ cat -n mini-report
*****************************************************************
END PROGRAM linage-demo.
With those samples, along with Gilbert's answer, you should have enough to tackle your problem, with the caveat that these examples are shy on proper error handling, so be careful is this is homework or a paid assignment. For an example of standard input/output or by filename depending on command line arguments (or lack thereof), see the ocdoc.cob program in the OpenCOBOL FAQ.
Offtopic: Output of an ocdoc pass over ocdoc.cob itself can be seen at http://opencobol.add1tocobol.com/ocdoc.html (Why mention it? The COBOL lexicon highlighter for Pygments has just been accepted into main. Any Pygments pulled after version 1.6 will allow for COBOL (context free) lexical highlighting.)
You write an ordinary Cobol program that reads a file.
The first byte (character) of the record is either 0, 1, 2, or 9.
Define a Working-Storage area (01 level) for each of the 4 record types. Then, after you read the record, you move it from the input area to the appropriate Working-Storage area for the record.
Then you process the record how you wish from one of the 4 Working-Storage areas.

Standard way to remove spaces from input in 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.

Resources