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 gkittelson on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

using perform until

Status
Not open for further replies.

Guest_imported

New member
Jan 1, 1970
0
Using the perform varying statement.

perform b0001-read thru b001-exit
varying 1 by 1 until >= 200.

What if I have anywhere from 4 to 200 records and I want to display on the screen the first 11 records, then if there are more than 11 records, I want to display those next 11 records. How would I do that with the perform varying statement???
 
I am still getting the same error, I typed part of my code.

I am reading the sorted masterfile (sort-file) into a table (ws-input-name-table with 1000 occurances), I then ask if the user input last name matches the 1st table last name, if they do, I move the fields I need (last name, first name, id and ssn) to the table with 200 occurances.
01 max-display-ct pic 9(01) value 8.
01 h-idx pic 9(04).
01 i-idx pic 9(04).
01 ws-display-sub pic 9(01).
01 WS-INPUT-NAME-DATA.
03 WS-INT-TABLE OCCURS 1000 TIMES.
05 WS-INT-ID PIC X(09).
05 WS-INT-SS.
10 WS-INT-SS1 PIC 9(03).
10 WS-INT-SS2 PIC 9(02).
10 WS-INT-SS3 PIC 9(04).
05 FILLER PIC X(08).
05 WS-INT-LNAME PIC X(20).
05 WS-INT-FNAME PIC X(14).
05 FILLER PIC X(58).
05 WS-INT-HHSIZE PIC 9(02).
05 FILLER PIC X(160).
05 WS-INT-OTHERDATA PIC X(357).
05 FILLER PIC X(147).
01 WS-NAME-HOLD-TABLE.
03 WS-NAME-HOLD-REC OCCURS 200 TIMES.
05 FILLER PIC X(01) VALUE SPACE.
05 WS-NH-LNAME PIC X(20).
05 FILLER PIC X(01).
05 WS-NH-FNAME PIC X(14).
05 FILLER PIC X(01) VALUE SPACE.
05 WS-NH-SSN PIC 9(09).
05 FILLER PIC X(01) VALUE SPACE.
05 WS-NH-ID PIC X(09).
01 WS-NAME-DISPLAY-TABLE.
03 WS-NAME-DISPLAY OCCURS 8 TIMES.
05 FILLER PIC X(01) VALUE SPACE.
05 WS-ND-LNAME PIC X(20).
05 FILLER PIC X(01).
05 WS-ND-FNAME PIC X(14).
05 FILLER PIC X(01) VALUE SPACE.
05 WS-ND-SSN PIC 9(09).
05 FILLER PIC X(01) VALUE SPACE.
05 WS-ND-ID PIC X(09).

move spaces to ws-input-name-table, ws-name-hold-table


b100-read-name.
Read sort-file into ws-input-name-table
at end
display "eof:.
go to b100-exit.

If input-lastname = ws-int-lname
move ws-int-lname(i-idx) to ws-nh-lname(h-idx)
move ws-int-fname(i-idx) to ws-nh-fname(h-idx)
move ws-int-id(i-idx) to ws-nh-id(h-idx)
perform b400-selected-names thru b400-exit.


b400-selected-names.

move 1 to h-idx
perform b501a-move-names thru b501a-exit
until ws-name-hold-rec(h-idx) = spaces
or h-idx > 200
perform b502a-display-names thru b502a-exit.

b501a-move-names

perform varying ws-display-sub from 1 by 1
until ws-display-sub > max-display-ct
move ws-name-hold(h-idx) to ws-names-pages(ws-display-sub)
add 1 to h-idx
end-perform.
b501a-exit.
exit.

b502a-display-names.
display screen-name-out
display ws-name-display-table.
b502a-exit.
exit.
 
Aside from the fact that you do not have a data name called
"ws-input-name-table" in the sample code, all of your i/o is going into the beginning of the table, because you are doing "Read sort-file into ws-input-name-table", instead of reading into an incrementally indexed member of the table.

Stephen J Spiro
Member, J4 COBOL Standards Committee
check it out at

stephenjspiro at hotmail.com
 
First, where is your subscript in the first line (the 'IF' statement) in your code here ?

If input-lastname = ws-int-lname


If you coded it like this, I'm surprised that it compiled. Most compilers will give out an error message stating that it is looking for an index or subscript.

Okay, maybe this was a typo when you typed it into this forum. But then, you are doing a 'read' statement. You read thusly:

b100-read-name.
Read sort-file into ws-input-name-table
at end
display "eof:.
go to b100-exit.


This looks like you are reading sort-file 1 record at a time, because you have an 'at end' statement. These records get moved into a 1000 occurrence table.

But the way you have coded it, if you don't reach the EOF, then it falls through to the following 'b400-selected-names'paragraph, which starts up a series of 'performs.'

These tables being processed only go up to 200 or to 8 occurrences. But your previous 'read' statement might be done up to 1000 times. So as soon as record #201 gets read and then passed on to 'b400-selected-names', you go out of subscript range.

What you need to do is have a "mainline" or a "driver." You perform the 'read' paragraph from there, have it load the 1000-occurrence table, iterating from 1 to 1000 (or to EOF). Then have it return to the mainline, where the processing does a sort of pause.

Then from your mainline, it will start up again. You re-initialize what subscripts and indexes you need, and then do your series of 'performs,' starting with 'b400-selected-names' and so forth.

Another thing I noticed in this code:

b400-selected-names.

move 1 to h-idx
perform b501a-move-names thru b501a-exit
until ws-name-hold-rec(h-idx) = spaces
or h-idx > 200
perform b502a-display-names thru b502a-exit.

This paragraph will be performed until you reach spaces or the h-idx reaches more than 200. So you go to the b501a-move-names paragraph:

b501a-move-names

perform varying ws-display-sub from 1 by 1
until ws-display-sub > max-display-ct
move ws-name-hold(h-idx) to ws-names-pages(ws-display-sub)
add 1 to h-idx
end-perform.
b501a-exit.


This paragraph contains an in-line perform. This moves ws-name-hold (h-idx) to ws-names-pages (ws-display-sub). Then both h-idx and ws-display-sub get incremented.

When the display-sub hits the max-display-ct (which has been intialized in Working Storage as 8), the inline perform stops. Nothing happens to it, it is not displayed or processed, it simply returns to the b400-selected-names paragraph.

This paragraph checks the perform condition here, and h-idx hasn't hit 200 yet. So it will go right back to the b501a-move-names paragraph. Which has a perform varying, so the display-sub gets re-initialized to 1. And a new set of values gets placed into this 8-occurrence table, replacing what was there before. And what happens to what was already sitting there, who knows?

These iterations go on until h-idx hits 200 or else we get a blank record. All you are doing is replacing what was in the display table, without doing anything with the data which is already there. So you'll only end up with the last 8 records to be displayed.

Hope this helps, Nina Too
 
PLEASE, do not EVER code PERFORM a paragraph that contains only another, single PERFORM statement. Either put your in-line PERFORM statement where you have

perform b501a-move-names thru b501a-exit

or code it

perform b501a-move-names thru b501a-exit
varying ws-display-sub from 1 by 1
until ws-display-sub > max-display-ct
-
-
b501a-move-names.
move ws-name-hold(h-idx)
to ws-names-pages (ws-display-sub)
add 1 to h-idx.
b501a-exit.

It makes NO SENSE to perform a PERFORM!


Stephen J Spiro
Member, J4 COBOL Standards Committee
check it out at

stephenjspiro at hotmail.com
 
i HAVE PUT IN THE PROGRAM, i THINK MOST OF IT COPIED. THIS ALSO HAS AN INDEXED FILE, I am reading the sorted masterfile (sort-file) into a table (ws-input-name-table with 1000 occurances), I then ask if the user input last name matches the 1st table last name, if they do, I move the fields I need (last name, first name, id and ssn) to the table with 200 occurances.

ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT HHMF-FILE
ASSIGN TO DISK
ORGANIZATION IS INDEXED
ACCESS MODE IS SEQUENTIAL
RECORD KEY IS HHMF-KEY.
SELECT HH0932-FILE
ASSIGN TO DISK
ORGANIZATION IS INDEXED
ACCESS MODE IS DYNAMIC
RECORD KEY IS HH0932-KEY.
SELECT NAMETABLE-FILE
ASSIGN TO '\FDPSYS\TABLES\DATA\NAMETBL.DAT'.
SELECT SORT-WORK
ASSIGN TO DISK.
SELECT SORT-FILE
ASSIGN TO DISK.
*
*
DATA DIVISION.
FILE SECTION.

FD HHMF-FILE
LABEL RECORDS ARE STANDARD
VALUE OF FILE ID
IS '\FDPSYS\TABLES\DATA\HHMF.DAT'.
01 HHMF-REC.
03 HHMF-KEY PIC X(09).
03 FILLER PIC X(775).
FD HH0932-FILE
LABEL RECORDS ARE STANDARD
VALUE OF FILE-ID
IS '\FDPSYS\TABLES\DATA\HH0932.DAT'.
01 HH0932-REC.
03 HH0932-KEY PIC X(09).
03 FILLER PIC X(1224).
FD NAMETABLE-FILE.

01 NAMETABLE-REC.
05 FILLER PIC X(01) VALUE
SPACE.
05 NT-LNAME PIC X(20).
05 FILLER PIC X(01).
05 NT-FNAME PIC X(14).
05 FILLER PIC X(01) VALUE
SPACE.
05 NT-HHLNAME PIC X(20).
05 FILLER PIC X(01) VALUE
SPACE.
05 NT-ID PIC X(09).

SD SORT-WORK.
01 SORT-REC.
03 SR-HHID PIC X(09).
03 SR-SSN PIC 9(09).
03 FILLER PIC X(08).
03 SR-LNAME PIC X(20).
03 SR-FNAME PIC X(14).
03 FILLER PIC X(724).

FD SORT-FILE
LABEL RECORDS ARE STANDARD
VALUE OF FILE-ID
IS '\FDPSYS\TABLES\DATA\SORT.WRK'.
01 SF-REC PIC X(784).


*
*
WORKING-STORAGE SECTION.
*
COPY \SOURCE\HH0932.LIB.
*

01 I-IDX PIC 9(04).
01 H-IDX PIC 9(04).
01 D-IDX PIC 9(04).
01 SS-IN PIC X(01).
01 SI-LNAME PIC X(20).
01 SNO-IN PIC X(01).
01 SNO-IN2 PIC X(01).
01 SSO-IN PIC X(01).

01 HH-DEPENDS.
03 HH-2-8.
05 H-2-8 OCCURS 7 TIMES.
10 H-2-8FNAME PIC X(14).
10 H-2-8LNAME PIC X(20).
10 H-2-8SS PIC 9(09).
10 FILLER PIC X(08).

03 HH-9-16.
05 H-9-16 OCCURS 8 TIMES.
10 H-9-16FNAME PIC X(14).
10 H-9-16LNAME PIC X(20).
10 H-9-16SS PIC 9(09).
10 FILLER PIC X(08).

03 HH-17-24.
05 H-17-24 OCCURS 8 TIMES.
10 H-17-24FNAME PIC X(14).
10 H-17-24LNAME PIC X(20).
10 H-17-24SS PIC 9(09).
10 FILLER PIC X(08).

03 HH-25-32.
05 H-25-32 OCCURS 8 TIMES.
10 H-25-32FNAME PIC X(14).
10 H-25-32LNAME PIC X(20).
10 H-25-32SS PIC 9(09).
10 FILLER PIC X(08).


*
01 WS-TABLE-SUB PIC 9(04).
01 WS-DISPLAY-SUB PIC 9(03).
01 MAX-DISPLAY-CT PIC 9(01) VALUE 8.

01 WS-INPUT-NAME-DATA.
03 WS-INT-TABLE OCCURS 1000 TIMES.
05 WS-INT-ID PIC X(09).
05 WS-INT-SS.
10 WS-INT-SS1 PIC 9(03).
10 WS-INT-SS2 PIC 9(02).
10 WS-INT-SS3 PIC 9(04).
05 FILLER PIC X(08).
05 WS-INT-LNAME PIC X(20).
05 WS-INT-FNAME PIC X(14).
05 FILLER PIC X(58).
05 WS-INT-HHSIZE PIC 9(02).
05 FILLER PIC X(160).
05 WS-INT-OTHERDATA PIC X(357).
05 FILLER PIC X(147).


01 WS-NAME-HOLD-TABLE.
03 WS-NAME-HOLD-REC OCCURS 200 TIMES.
05 FILLER PIC X(01) VALUE
SPACE.
05 WS-NH-LNAME PIC X(20).
05 WS-NH-FNAME PIC X(14).
05 FILLER PIC X(01) VALUE
SPACE.
05 WS-NH-HHLNAME PIC X(20).
05 FILLER PIC X(15) VALUE
SPACE.
05 WS-NH-ID PIC X(09).

01 WS-NAME-DISPLAY-TABLE.
03 WS-NAME-DISPLAY OCCURS 8 TIMES.
05 FILLER PIC X(01) VALUE
SPACE.
05 WS-ND-LNAME PIC X(20).
05 WS-ND-FNAME PIC X(14).
05 FILLER PIC X(01) VALUE
SPACE.
05 WS-ND-HHLNAME PIC X(20).
05 FILLER PIC X(15) VALUE
SPACE.
05 WS-ND-HHID PIC X(09).



*
SCREEN SECTION.


************* MAIN SEARCH MENU***********************

*
01 SEARCH-SCREEN AUTO.
02 BACKGROUND-COLOR 5 FOREGROUND-COLOR 3.
03 BLANK SCREEN.
03 LINE 2 COL 10 HIGHLIGHT VALUE
-"ÉÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ»".
03 LINE 3 COL 10 HIGHLIGHT VALUE "º
-" º".
03 LINE 4 COL 10 HIGHLIGHT VALUE "º ".
03 COL 34 HIGHLIGHT VALUE "SEARCH ONLINE".
03 COL 68 HIGHLIGHT VALUE "º".
03 LINE 5 COL 10 HIGHLIGHT VALUE "º ".
03 COL 22 HIGHLIGHT VALUE
-"BY LAST NAME or social security number.".
03 COL 68 HIGHLIGHT VALUE "º".
03 LINE 6 COL 10 HIGHLIGHT VALUE "º
-" º".
03 LINE 7 COL 10 HIGHLIGHT VALUE "º
-" º".
03 LINE 8 COL 10 HIGHLIGHT VALUE "º
-" º".
03 LINE 9 COL 10 HIGHLIGHT VALUE "º
-" º".
03 LINE 10 COL 10 HIGHLIGHT VALUE "º ".
03 COL 23 HIGHLIGHT VALUE
-"ENTER 'N' FOR LAST NAME SEARCH OR".
03 COL 68 HIGHLIGHT VALUE "º".
03 LINE 11 COL 10 HIGHLIGHT VALUE "º ".
03 COL 23 HIGHLIGHT VALUE
-"ENTER 'S' FOR SOCIAL SECURITY SEARCH OR".
03 COL 68 HIGHLIGHT VALUE "º".
03 LINE 12 COL 10 HIGHLIGHT VALUE "º ".
03 COL 23 HIGHLIGHT VALUE
-"ENTER 'E' TO RETURN TO MAIN MENU".
03 COL 68 HIGHLIGHT VALUE "º".
03 LINE 13 COL 10 HIGHLIGHT VALUE "º
-" º".
03 LINE 14 COL 10 HIGHLIGHT VALUE "º
-" º".
03 LINE 15 COL 10 HIGHLIGHT VALUE "º
-" º".
03 LINE 16 COL 10 HIGHLIGHT VALUE
-"ÈÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍͼ".
03 LINE 15 COL 38 PIC X USING SS-IN AUTO.




*

01 SCREEN-NAME-IN AUTO.
02 BACKGROUND-COLOR 5 FOREGROUND-COLOR 3.
03 BLANK SCREEN.
03 LINE 3 COL 30 HIGHLIGHT VALUE "SEARCH BY".
03 COL 40 HIGHLIGHT VALUE "LAST NAME".
03 LINE 5 COL 7 HIGHLIGHT VALUE "ÉÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ
-"ÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ»".
03 LINE 6 COL 7 HIGHLIGHT VALUE "º".
03 COL 22 HIGHLIGHT VALUE "PLEASE".
03 COL 29 HIGHLIGHT VALUE "ENTER".
03 COL 35 HIGHLIGHT VALUE "THE".
03 COL 39 HIGHLIGHT VALUE "LAST NAME".
03 COL 49 HIGHLIGHT VALUE "TO".
03 COL 52 HIGHLIGHT VALUE "SEARCH.".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 7 COL 7 HIGHLIGHT VALUE "º".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 8 COL 7 HIGHLIGHT VALUE "º".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 9 COL 7 HIGHLIGHT VALUE "º".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 10 COL 7 HIGHLIGHT VALUE "º".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 11 COL 7 HIGHLIGHT VALUE "º".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 12 COL 7 HIGHLIGHT VALUE "º".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 13 COL 7 HIGHLIGHT VALUE "º".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 14 COL 7 HIGHLIGHT VALUE "º".
03 N-LNAME.
05 COL 11 HIGHLIGHT VALUE "ENTER".
05 COL 17 HIGHLIGHT VALUE "LAST".
05 COL 22 HIGHLIGHT VALUE "NAME:".
05 COLUMN 33 PIC X(20) USING SI-LNAME.

03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 15 COL 7 HIGHLIGHT VALUE "º".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 16 COL 7 HIGHLIGHT VALUE "º".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 17 COL 7 HIGHLIGHT VALUE "º".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 18 COL 7 HIGHLIGHT VALUE "º".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 19 COL 7 HIGHLIGHT VALUE "º".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 20 COL 7 HIGHLIGHT VALUE "º".
03 COL 69 HIGHLIGHT VALUE "º".
03 LINE 21 COL 7 HIGHLIGHT VALUE "ÈÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ
-"ÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍͼ".

01 PROCESSING-NAME-SCREEN.
03 BLANK SCREEN.
03 LINE 12 COLUMN 24 HIGHLIGHT FOREGROUND-COLOR 6
'PLEASE WAIT....SEARCHING LIST BY LAST NAME'.






*********************OUTPUT SCREENS*************************
*
01 SCREEN-NAME-OUT AUTO.
02 BACKGROUND-COLOR 5 FOREGROUND-COLOR 3.
03 BLANK SCREEN.
03 LINE 2 COL 20 HIGHLIGHT VALUE "SEARCH".
03 COL 27 HIGHLIGHT VALUE "RESULTS FOR LAST NAME:".
03 COL 50 BACKGROUND-COLOR 2 FOREGROUND-COLOR 4
PIC X(20) FROM SI-LNAME.
03 LINE 3 COL 1 HIGHLIGHT VALUE "ÉÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ
-"ÍÍÍÍÍËÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍËÍÍÍÍÍÍÍÍÍ»".
03 LINE 4 COL 1 HIGHLIGHT VALUE "º".
03 COL 15 HIGHLIGHT VALUE "NAME".
03 COL 35 HIGHLIGHT VALUE "º".
03 COL 45 HIGHLIGHT VALUE "HEAD".
03 COL 50 HIGHLIGHT VALUE "OF".
03 COL 53 HIGHLIGHT VALUE "HOUSEHOLD".
03 COL 70 HIGHLIGHT VALUE "º".
03 COL 74 HIGHLIGHT VALUE "HH-ID".
03 COL 80 HIGHLIGHT VALUE "º".
03 LINE 5 COL 1 HIGHLIGHT VALUE "ÌÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ
-"ÍÍÍÍÍÎÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÎÍÍÍÍÍÍÍÍ͹".
03 LINE 6 COL 1 HIGHLIGHT VALUE "º".
03 COL 35 HIGHLIGHT VALUE "º".
03 COL 70 HIGHLIGHT VALUE "º".
03 COL 80 HIGHLIGHT VALUE "º".
03 LINE 7 COL 1 HIGHLIGHT VALUE "º".
03 COL 35 HIGHLIGHT VALUE "º".
03 COL 70 HIGHLIGHT VALUE "º".
03 COL 80 HIGHLIGHT VALUE "º".
03 LINE 8 COL 1 HIGHLIGHT VALUE "º".
03 COL 35 HIGHLIGHT VALUE "º".
03 COL 70 HIGHLIGHT VALUE "º".
03 COL 80 HIGHLIGHT VALUE "º".
03 LINE 9 COL 1 HIGHLIGHT VALUE "º".
03 COL 35 HIGHLIGHT VALUE "º".
03 COL 70 HIGHLIGHT VALUE "º".
03 COL 80 HIGHLIGHT VALUE "º".
03 LINE 10 COL 1 HIGHLIGHT VALUE "º".
03 COL 35 HIGHLIGHT VALUE "º".
03 COL 70 HIGHLIGHT VALUE "º".
03 COL 80 HIGHLIGHT VALUE "º".
03 LINE 11 COL 1 HIGHLIGHT VALUE "º".
03 COL 35 HIGHLIGHT VALUE "º".
03 COL 70 HIGHLIGHT VALUE "º".
03 COL 80 HIGHLIGHT VALUE "º".
03 LINE 12 COL 1 HIGHLIGHT VALUE "º".
03 COL 35 HIGHLIGHT VALUE "º".
03 COL 70 HIGHLIGHT VALUE "º".
03 COL 80 HIGHLIGHT VALUE "º".
03 LINE 13 COL 1 HIGHLIGHT VALUE "º".
03 COL 35 HIGHLIGHT VALUE "º".
03 COL 70 HIGHLIGHT VALUE "º".
03 COL 80 HIGHLIGHT VALUE "º".
03 LINE 14 COL 1 HIGHLIGHT VALUE "º".
03 COL 35 HIGHLIGHT VALUE "º".
03 COL 70 HIGHLIGHT VALUE "º".
03 COL 80 HIGHLIGHT VALUE "º".
03 LINE 15 COL 1 HIGHLIGHT VALUE "º".
03 COL 35 HIGHLIGHT VALUE "º".
03 COL 70 HIGHLIGHT VALUE "º".
03 COL 80 HIGHLIGHT VALUE "º".
03 LINE 16 COL 1 HIGHLIGHT VALUE "º".
03 COL 35 HIGHLIGHT VALUE "º".
03 COL 70 HIGHLIGHT VALUE "º".
03 COL 80 HIGHLIGHT VALUE "º".
03 LINE 17 COL 1 HIGHLIGHT VALUE "ÈÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍ
-"ÍÍÍÍÍÍÊÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÍÊÍÍÍÍÍÍÍÍͼ".


01 NAMEDATA.
03 LINE 6 COL 2 PIC X(67) FROM WS-NAME-DISPLAY-TABLE.
03 LINE 7 COL 2 PIC X(67) FROM WS-NAME-DISPLAY-TABLE.
03 LINE 8 COL 2 PIC X(67) FROM WS-NAME-DISPLAY-TABLE.
03 LINE 9 COL 2 PIC X(67) FROM WS-NAME-DISPLAY-TABLE.
03 LINE 10 COL 2 PIC X(67) FROM WS-NAME-DISPLAY-TABLE.
03 LINE 11 COL 2 PIC X(67) FROM WS-NAME-DISPLAY-TABLE.
03 LINE 12 COL 2 PIC X(67) FROM WS-NAME-DISPLAY-TABLE.
03 LINE 13 COL 2 PIC X(67) FROM WS-NAME-DISPLAY-TABLE.

01 PROCESSING-RETURN-SCREEN.
03 LINE 18 COL 3 HIGHLIGHT VALUE
"PRESS".
03 COL 9 BACKGROUND-COLOR 2 FOREGROUND-COLOR 4
"ENTER".
03 COL 15 HIGHLIGHT VALUE
"TO GO BACK TO MAIN MENU".
03 LINE 18 COL 58 PIC X USING SNO-IN AUTO.

01 NO-PROCESS-RETURN-SCREEN.
03 LINE 18 COL 3 ' '.
03 COL 9 ' '.
03 COL 16 ' '.
03 COL 58 ' '.

01 PROCESSING-CONTINUE-SCREEN.
03 LINE 18 COL 3 VALUE SPACES.

03 LINE 19 COL 3 HIGHLIGHT FOREGROUND-COLOR 6
'PRESS "RETURN" TO SEE'.
03 LINE 19 COL 25 HIGHLIGHT FOREGROUND-COLOR 6
'THE NEXT 8 RECORDS!'.
03 LINE 19 COL 46 PIC X USING SNO-IN AUTO.

01 PROCESSING-MESSAGE-NAME-SCREEN.
03 BLANK SCREEN.
03 LINE 12 COL 34 HIGHLIGHT FOREGROUND-COLOR 6
'"LAST NAME ENTERED '.
03 LINE 13 COL 34 BACKGROUND-COLOR 2 FOREGROUND-COLOR 4
PIC X(20) FROM SI-LNAME.
03 LINE 14 COL 30 HIGHLIGHT FOREGROUND-COLOR 6
' WAS NOT FOUND-PLEASE TRY ANOTHER."'.
03 LINE 15 COL 3 HIGHLIGHT VALUE
"PRESS".
03 COL 9 BACKGROUND-COLOR 2 FOREGROUND-COLOR 4
"ENTER".
03 COL 15 HIGHLIGHT VALUE
"TO RETURN TO MAIN ONLINE SEARCH MENU".
03 LINE 16 COL 58 PIC X USING SNO-IN AUTO.




*
*
PROCEDURE DIVISION.
*
*
A000-INITIALIZE.
PERFORM A100-ACCEPT-MAIN-SEARCH-INPUT THRU A100-EXIT.
PERFORM A200-ACCEPT-NS-SEARCH-INPUT THRU A200-EXIT.
PERFORM Z000-TERMINATE THRU Z000-EXIT.
STOP RUN.
A000-EXIT.
EXIT.
*
*
A100-ACCEPT-MAIN-SEARCH-INPUT.
MOVE SPACES TO SSO-IN, SNO-IN, SNO-IN2, SI-SSN.
MOVE SPACES TO SS-IN, SI-LNAME.
SET I-IDX TO 1.
SET H-IDX TO 1.
DISPLAY SEARCH-SCREEN.
ACCEPT SEARCH-SCREEN.
DISPLAY "LEAVING A100".
A100-EXIT.
EXIT.



A200-ACCEPT-NS-SEARCH-INPUT.
DISPLAY "ENTERING A200-ACCEPT".
MOVE SPACES TO NAMETABLE-REC, WS-INPUT-NAME-DATA.
IF SS-IN = "N"

DISPLAY SCREEN-NAME-IN
ACCEPT SCREEN-NAME-IN
MOVE SPACES TO WS-NAME-DISPLAY-TABLE,
WS-NAME-HOLD-TABLE
PERFORM A300-SORT THRU A300-EXIT
OPEN INPUT SORT-FILE
HH0932-FILE
I-O NAMETABLE-FILE
DISPLAY PROCESSING-NAME-SCREEN
PERFORM B100-READ-NAME THRU B100-EXIT
PERFORM B400-SELECTED-NAMES-SSN THRU B400-EXIT.


IF SS-IN = "E"
GO TO A200-EXIT.

A200-EXIT.
EXIT.
*
*
A300-SORT.
DISPLAY "ENTERING A300-SORT" STOP ' '.
SORT SORT-WORK
ON ASCENDING KEY SR-LNAME
USING HHMF-FILE
GIVING SORT-FILE.
A300-EXIT.
EXIT.

*

B100-READ-NAME.
COMPUTE I-IDX = I-IDX + 1
ADD 1 TO I-IDX.
READ SORT-FILE INTO WS-INT-TABLE(I-IDX)
AT END
DISPLAY "EOF"
GO TO B100-EXIT.
IF WS-INT-HHSIZE(I-IDX) > 08
MOVE WS-INT-ID(I-IDX) TO HH0932-KEY
READ HH0932-FILE INTO HH0932-DATA
INVALID KEY
MOVE 08 TO WS-INT-HHSIZE(I-IDX).

IF WS-INT-LNAME(I-IDX) = SPACE
GO TO B100-READ-NAME.

IF SI-LNAME = WS-INT-LNAME(I-IDX)
DISPLAY "SILNAME=WSINTLNAME="SI-LNAME,
WS-INT-LNAME(I-IDX)

MOVE WS-INT-LNAME(I-IDX) TO
WS-NH-LNAME(H-IDX),
WS-NH-HHLNAME(H-IDX), NT-LNAME,
NT-HHLNAME
DISPLAY "WS-NH-LNAME="WS-NH-LNAME(H-IDX)
MOVE WS-INT-FNAME(I-IDX) TO
WS-NH-FNAME(H-IDX), NT-FNAME
MOVE WS-INT-ID(I-IDX) TO WS-NH-ID(H-IDX),
NT-ID


PERFORM B300-DEPENDENTS THRU B300-EXIT.
GO TO B100-READ-NAME.
B100-EXIT.
EXIT.




B300-DEPENDENTS.

IF WS-INT-HHSIZE(I-IDX) = 01
GO TO B300-EXIT.
IF WS-INT-HHSIZE(I-IDX) > 01
MOVE WS-INT-OTHERDATA(I-IDX) TO HH-2-8
MOVE ZERO TO D-IDX
PERFORM B301-2-8 THRU B301-EXIT
DISPLAY "B301-2-8 DONE".
IF WS-INT-HHSIZE(I-IDX) > 08
MOVE HHD-0916 TO HH-9-16
MOVE ZERO TO D-IDX
PERFORM B302-9-16 THRU B302-EXIT.

IF WS-INT-HHSIZE(I-IDX) > 16
MOVE HHD-1724 TO HH-17-24
MOVE ZERO TO D-IDX
PERFORM B303-17-24 THRU B303-EXIT.

IF WS-INT-HHSIZE(I-IDX) > 24
MOVE HHD-2532 TO HH-25-32
MOVE ZERO TO D-IDX
PERFORM B304-25-32 THRU B304-EXIT.

B300-EXIT.
EXIT.


B301-2-8.
DISPLAY "ENTERING B301-2-8".
COMPUTE D-IDX = D-IDX + 1.
DISPLAY "D-IDX=" D-IDX.

IF D-IDX = 8
GO TO B301-EXIT.


IF SS-IN = "N"
IF SI-LNAME = H-2-8LNAME(D-IDX)
DISPLAY "SI-LNAME=H28LNAME="SI-LNAME,
H-2-8LNAME(D-IDX)
MOVE H-2-8LNAME(D-IDX) TO
WS-NH-LNAME(H-IDX), NT-LNAME
MOVE H-2-8FNAME(D-IDX) TO
WS-NH-FNAME(H-IDX), NT-FNAME
MOVE WS-INT-LNAME(I-IDX) TO
WS-NH-HHLNAME(H-IDX), NT-HHLNAME
MOVE WS-INT-ID(I-IDX) TO
WS-NH-ID(H-IDX), NT-ID


GO TO B301-2-8.
B301-EXIT.
EXIT.

B302-9-16.

COMPUTE D-IDX = D-IDX + 1.

IF D-IDX = 9
GO TO B302-EXIT.


IF SS-IN = "N"
IF SI-LNAME = H-9-16LNAME(D-IDX)
MOVE H-9-16LNAME(D-IDX) TO
WS-NH-LNAME(H-IDX),
NT-LNAME
MOVE H-9-16FNAME(D-IDX) TO
WS-NH-FNAME(H-IDX),
NT-FNAME
MOVE WS-INT-LNAME(I-IDX) TO
WS-NH-HHLNAME(H-IDX),
NT-HHLNAME
MOVE WS-INT-ID(I-IDX) TO
WS-NH-ID(H-IDX), NT-ID.




GO TO B302-9-16.

B302-EXIT.
EXIT.


B303-17-24.

COMPUTE D-IDX = D-IDX + 1.


IF D-IDX = 9
GO TO B303-EXIT.

IF SS-IN = "N"
IF SI-LNAME = H-17-24LNAME(D-IDX)
MOVE H-17-24LNAME(D-IDX) TO
WS-NH-LNAME(H-IDX),
NT-LNAME
MOVE H-17-24FNAME(D-IDX) TO
WS-NH-FNAME(H-IDX),
NT-FNAME
MOVE WS-INT-LNAME(I-IDX) TO
WS-NH-HHLNAME(H-IDX),
NT-HHLNAME
MOVE WS-INT-ID(I-IDX) TO
WS-NH-ID(H-IDX), NT-ID.




GO TO B303-17-24.

B303-EXIT.
EXIT.


B304-25-32.

COMPUTE D-IDX = D-IDX + 1.

IF D-IDX = 9
GO TO B304-EXIT.

IF SS-IN = "N"
IF SI-LNAME = H-25-32LNAME(D-IDX)
MOVE H-25-32LNAME(D-IDX) TO
WS-NH-LNAME(H-IDX),
NT-LNAME
MOVE H-25-32FNAME(D-IDX) TO
WS-NH-FNAME(H-IDX),
NT-FNAME
MOVE WS-INT-LNAME(I-IDX) TO
WS-NH-HHLNAME(H-IDX),
NT-HHLNAME
MOVE WS-INT-ID(I-IDX) TO
WS-NH-ID(H-IDX), NT-ID.


GO TO B304-25-32.

B304-EXIT.
EXIT.


B400-SELECTED-NAMES-SSN.

IF SS-IN = "N"
MOVE 1 TO H-IDX
PERFORM B501A-MOVE-NAME THRU B501A-EXIT
UNTIL WS-NAME-HOLD-REC(H-IDX) = SPACES
OR H-IDX > 200.


B400-EXIT.
EXIT.



B501A-MOVE-NAME.

INITIALIZE WS-NAME-DISPLAY-TABLE.

IF SI-LNAME NOT = WS-NH-LNAME(H-IDX)
DISPLAY "NO NAMES MATCH"
DISPLAY PROCESSING-MESSAGE-NAME-SCREEN.

PERFORM VARYING WS-DISPLAY-SUB FROM +1 BY +1
UNTIL WS-DISPLAY-SUB > MAX-DISPLAY-CT
MOVE WS-NAME-HOLD-REC(H-IDX)
TO WS-NAME-DISPLAY(WS-DISPLAY-SUB)

ADD +1 TO H-IDX
END-PERFORM.
PERFORM B502A-DISPLAY-NAME THRU B502A-EXIT.
B501A-EXIT.
EXIT.

B502A-DISPLAY-NAME.

IF WS-TABLE-SUB < 9
DISPLAY SCREEN-NAME-OUT STOP ' '
DISPLAY NAMEDATA.


IF WS-TABLE-SUB > 8
DISPLAY SCREEN-NAME-OUT
DISPLAY WS-NAME-DISPLAY-TABLE
DISPLAY NO-PROCESS-RETURN-SCREEN
DISPLAY PROCESSING-CONTINUE-SCREEN.

IF SNO-IN = &quot;E&quot;
GO TO B502A-EXIT.

B502A-EXIT.
EXIT.


Z000-TERMINATE.

CLOSE SORT-FILE
HH0932-FILE
HHMF-FILE
NAMETABLE-FILE


IF SS-IN = 'E'
GO TO Z000-EXIT.

Z000-EXIT.
EXIT PROGRAM.



 
I see a couple of problems right away:

In paragraph A200-ACCEPT-NS-SEARCH-INPUT:

When you get to reading the file, after the sort:

PERFORM B100-READ-NAME THRU B100-EXIT
PERFORM B400-SELECTED-NAMES-SSN THRU B400-EXIT.


And you get to this paragraph:

B100-READ-NAME.
COMPUTE I-IDX = I-IDX + 1
ADD 1 TO I-IDX.
READ SORT-FILE INTO WS-INT-TABLE(I-IDX)
AT END
DISPLAY &quot;EOF&quot;
GO TO B100-EXIT.
IF WS-INT-HHSIZE(I-IDX) > 08
MOVE WS-INT-ID(I-IDX) TO HH0932-KEY
READ HH0932-FILE INTO HH0932-DATA
INVALID KEY
MOVE 08 TO WS-INT-HHSIZE(I-IDX).

IF WS-INT-LNAME(I-IDX) = SPACE
GO TO B100-READ-NAME.


First, you are incrementing your index by 2 when you code both COMPUTE I-IDX = I-IDX + 1 and ADD 1 TO I-IDX. You take the present value of the index, and add 1 to it. Then you add 1 to it again.

Is this what you want, to increment by 2 each time? I don't think so.

Second, you have the following commands: READ SORT-FILE INTO WS-INT-TABLE(I-IDX) AT END DISPLAY &quot;EOF&quot; GO TO B100-EXIT.

And if you are not at the end, you'll go ahead and do whatever follows. After you have already incremented your index by 2.

And you'll do all this only once. Because no where have you told your processing to keep going on through each record until you get to the end of the file.

Somewhere along the line, at a given, strategic point (in your Mainline &quot;driver, preferably), you must have a PERFORM UNTIL &quot;EOF&quot; to tell it to keep processing all the records that are in the table rather than stopping after just 1 record.

Fix this, and then we can go on from there. But I bet this will fix a lot of your problems.

Hope this helps, Nina Too
 
I eliminated the add, I have an &quot;AT END&quot; AND THE RECORDS ARE READY ONE AT A TIME (I put in a display) but when I move the data to the table is where I am getting the subscript error.

 
You wrote:
----------------
&quot;I am reading the sorted masterfile (sort-file) into a table (ws-input-name-table with 1000 occurances), I then ask if the user input last name matches the 1st table last name, if they do, I move the fields I need (last name, first name, id and ssn) to the table with 200 occurances.&quot;
----------------
I think that you need to have some sort of stop-processing switch so that when you are moving fields from the table with 1000 occurences to the table which has only 200 occurences, it will stop right before your subscript or index for the 200 occurence-table goes from 200 to 201, which is where you'll go out of its subscript range.

Otherwise, it keeps trying to move records from the 1000-occurence table into the table with 200 occurences. Even if there are blank records, it tries to keep moving these. You must stop the processing when it goes over 200.

Try this and see if it works, Nina Too
 
Nina,

I am trying something different. I made the ws-input-name-data file NOT a table. I am now reading the master file into ws-input-name-data file. I then ask if the user input last name = ws-int-lname, then I move the specific fields to the table with 200 occurances. I move the specific fields (ex: move ws-int-lname to ws-nh-lname(ws-table-sub) this is when I get the subscript error.
 
Make sure ws-table-sub is initialized to 1. Do you get the subscript error on the first record? Or perhaps the 201st?
Put in a DISPLAY statement to show the value of the index.

Stephen J Spiro
 
So I assume that your sorted master file (SORT-FILE), which is defined as:

01 SF-REC PIC X(784).



is being read into the following:


01 WS-INPUT-NAME-DATA.
05 WS-INT-ID PIC X(09).
05 WS-INT-SS.
10 WS-INT-SS1 PIC 9(03).
10 WS-INT-SS2 PIC 9(02).
10 WS-INT-SS3 PIC 9(04).
05 FILLER PIC X(08).
05 WS-INT-LNAME PIC X(20).
05 WS-INT-FNAME PIC X(14).
05 FILLER PIC X(58).
05 WS-INT-HHSIZE PIC 9(02).
05 FILLER PIC X(160).
05 WS-INT-OTHERDATA PIC X(357).
05 FILLER PIC X(147).

with the following line of code:

READ SORT-FILE INTO WS-INPUT-NAME-DATA
AT END
DISPLAY &quot;EOF&quot;
GO TO B100-EXIT.


And as each record is read, you do the following:

IF SI-LNAME = WS-INT-LNAME
DISPLAY &quot;SILNAME=WSINTLNAME=&quot;SI-LNAME,
WS-INT-LNAME

MOVE WS-INT-LNAME TO
WS-NH-LNAME(H-IDX)
WS-NH-HHLNAME
NT-LNAME
NT-HHLNAME


NOTE: By the way, where is the subscript for WS-NH-HHLNAME? because you still have this field defined as being a part of a table.

Continuing:

DISPLAY &quot;WS-NH-LNAME=&quot;WS-NH-LNAME(H-IDX)
MOVE WS-INT-FNAME TO
WS-NH-FNAME(H-IDX)
NT-FNAME
MOVE WS-INT-ID TO WS-NH-ID(H-IDX)
NT-ID


Which means that each time a record is read, it is moved into the following table:

01 WS-NAME-DISPLAY-TABLE.
03 WS-NAME-DISPLAY OCCURS 8 TIMES.
05 FILLER PIC X(01) VALUE
SPACE.
05 WS-ND-LNAME PIC X(20).
05 WS-ND-FNAME PIC X(14).
05 FILLER PIC X(01) VALUE
SPACE.
05 WS-ND-HHLNAME PIC X(20).
05 FILLER PIC X(15) VALUE
SPACE.
05 WS-ND-HHID PIC X(09).


Okay, now which subscript is going out-of bounds? You need to use a debugging tool to trace the values of each of your subscripts. Are you limiting your moves into WS-NAME-DISPLAY-TABLE so that no processing happens after 8 occurrences?

Also, I don't see where you increment H-IDX. Where does this happen?

Hope this helps, Nina Too



 
I &quot;lied&quot; in the message above. :)

Actually, you aren't moving the names into the ND display table (with 8 occurences), you're moving the name into the following table (with 200 occurences)

01 WS-NAME-HOLD-TABLE.
03 WS-NAME-HOLD-REC OCCURS 200 TIMES.
05 FILLER PIC X(01) VALUE
SPACE.
05 WS-NH-LNAME PIC X(20).
05 WS-NH-FNAME PIC X(14).
05 FILLER PIC X(01) VALUE
SPACE.
05 WS-NH-HHLNAME PIC X(20).
05 FILLER PIC X(15) VALUE
SPACE.
05 WS-NH-ID PIC X(09).


Make sure that you limit your processing to 200 records, and that you stop before you get to the 201st record.

Nina Too
 
I have displays throughout the program. Using displays, only 13 records meet the criteria, so it does not show over 200 records.
 
Okay, next, put displays up for your subscripts. Find out exactly where the error occurs, on which line of code. When you find the exact line which is causing the error message, I think you'll find you can solve the problem. Keep us informed.

Nina Too
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top