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

checking for duplicates and rewrite

Status
Not open for further replies.

Guest_imported

New member
Jan 1, 1970
0
0
0
I am trying to search all hm-ssn-2 for duplicate ssn#'s but I am having problems. It will only search the hm-ssn-2 within each record.


01 NEWMAST-DATA-2.
03 HMFN-ID-2 PIC X(09).
03 HMFN-SS-ID-2 PIC 9(09).
03 FILLER PIC 9(08).
03 HMFN-LNAME-2 PIC X(20).
03 HMFN-FNAME-2 PIC X(14).
03 FILLER PIC X(498).
03 HMFN-MEMBERS-2.
05 HM-MEMBERS-2 OCCURS 23 TIMES.
07 HM-FNAME-2 PIC X(14).
07 HM-LNAME-2 PIC X(20).
07 HM-SSN-2 PIC 9(09).
07 HM-DOB-2 PIC 9(08).
03 FILLER PIC X(317).


 
How about a snapshot of the code around the area where you are getting a subscript out of range?
Tom Morrison
 
There is also a checkbox below the area where you type your reply (in the area labelled "Step 2 Options") which will enable e-mail notification. If there is still a problem, perhaps there is a problem with your registration (such as no email address, perhaps) that you can fix.

I have also noticed that you sometimes have to log out and log in again to get changes to take effect (eg when there has been activity since the last visit). I guess they fetch the info when you log in and keep it around for the session so it takes a logout to cause them to refetch your info.
Tom Morrison
 
I think the problem is that the number of occurances is zero. You see, not all records will have 23 member ssn#, some households may not even have one. What do you suggest?
 
Deidre,

Yes, this is clear. In fact, on Feb 27 I asked, How do you determine what is a valid SSN?

Clearly you should apply some programming logic in the sort input procedure.
Code:
    perform varying SORT-OCCURS from 1 by 1 
              until SORT-OCCURS > 23
        move HMFN-ID to SORT-MAST-KEY
        move HM-SSN (SORT-OCCURS) to SORT-SSN
        release SORT-RECORD
    end-perform
should be modified to:
Code:
    perform varying SORT-OCCURS from 1 by 1 
              until SORT-OCCURS > 23
        if <<HM-SSN (SORT-OCCURS) is a valid SSN>>
            move HMFN-ID to SORT-MAST-KEY
            move HM-SSN (SORT-OCCURS) to SORT-SSN
            release SORT-RECORD
        end-if
    end-perform
but you have to determine what it is in the input record that indicates how many SSN in the array are valid.

Perhaps you can post your sort input and sort output procedures?
Tom Morrison
 
A100-SORT.
DISPLAY 'ENTERING A100-SORT'.
SORT SORT-WORK
ON ASCENDING KEY SR-SSN
INPUT PROCEDURE B100-SORT-IN-PROC
OUTPUT PROCEDURE C100-SORT-OUT-PROC.
STOP RUN.
A100-EXIT.
EXIT.


B100-SORT-IN-PROC.
DISPLAY 'ENTERING B100-SORT-IN'.
PERFORM B101-OPEN-FILES.
PERFORM B102-READ.
WRITE SF-REC FROM SORT-REC.
B100-EXIT.
EXIT.

B101-OPEN-FILES.
DISPLAY 'B101-OPEN-FILES'.
OPEN INPUT NEW-HHMF-FILE
OUTPUT SORT-FILE.
B101-EXIT.
EXIT.

B102-READ.
DISPLAY 'B102-READ-FILES'.
READ NEW-HHMF-FILE NEXT INTO NEWMAST-DATA
AT END
CLOSE NEW-HHMF-FILE
DISPLAY 'EOF'
GO B102-EXIT
END-READ.

DISPLAY 'HMFN-HHSIZE=' HMFN-HHSIZE
IF HMFN-HHSIZE = 01
GO TO B102-READ.

PERFORM VARYING SR-OCCURS FROM 1 BY 1
UNTIL SR-OCCURS > 23
DISPLAY '1-HM-SSN='HM-SSN(SR-OCCURS)
IF HM-SSN(SR-OCCURS) NOT = SPACES
MOVE HMFN-ID TO SR-ID
MOVE HM-SSN(SR-OCCURS) TO SR-SSN
DISPLAY 'SR-SSN=' SR-SSN
* WRITE SF-REC FROM SORT-REC
DISPLAY 'SORT-FILE='SF-REC
RELEASE SORT-REC
END-PERFORM

GO TO B102-READ.

B102-EXIT.
EXIT.




C100-SORT-OUT-PROC.
DISPLAY 'C100-READING FILES'
PERFORM C101-OPEN-FILES.
PERFORM C102-READ-FILES.
C100-EXIT.
EXIT.

C101-OPEN-FILES.
DISPLAY 'C101-OPEN'.
OPEN I-O NEW-HHMF-FILE
OUTPUT ERROR-FILE.
MOVE 999999999 TO LAST-SSN.
C101-EXIT.
EXIT.

C102-READ-FILES.
DISPLAY 'C102-READ'.
DISPLAY 'SORT-REC='SORT-REC STOP ' '.
RETURN SORT-WORK
AT END
CLOSE NEW-HHMF-FILE
ERROR-FILE
DISPLAY 'C102-EOF'
GO TO C102-EXIT
END-RETURN

DISPLAY 'SR-SSN=LAST-SSN='SR-SSN, LAST-SSN STOP ' '.
DISPLAY 'COMPARING'.
IF SR-SSN = LAST-SSN
DISPLAY 'SR-ID=' SR-ID
MOVE SR-ID TO NEW-HHMF-KEY
READ NEW-HHMF-FILE INTO NEWMAST-DATA
INVALID KEY
DISPLAY 'KEY DOES NOT MATCH'
NOT INVALID KEY
DISPLAY 'GOING TO C103-HELP'
PERFORM C103-SSN
REWRITE NEW-HHMF-REC FROM NEWMAST-DATA
END-READ
ELSE
MOVE SR-SSN TO LAST-SSN
END-IF
GO TO C102-READ-FILES.

C102-EXIT.
EXIT.


C103-SSN.
DISPLAY 'IN C103-HELP'.
DISPLAY 'HM-SSN=' HM-SSN(SR-OCCURS)
MOVE HM-SSN(SR-OCCURS) TO ER-ORG-SSN.
COMPUTE B-IDX = B-IDX + 1
MOVE B-IDX TO BAD-SSN
MOVE BAD-SSN TO HM-SSN(SR-OCCURS), ER-NEW-SSN
MOVE HMFN-ID TO ER-ID
MOVE HM-FNAME(SR-OCCURS) TO ER-FNAME
MOVE HM-LNAME(SR-OCCURS) TO ER-LNAME
WRITE ERROR-REC FROM ERROR-RECORDS.
C103-EXIT.
EXIT.



C103-SSN IS WHERE i GET THE SAME ERROR.
 
Hi Deidre,

My .02 worth.

Your perform in p# B201-READ is missing an END-IF.

One other thing: if the ssn's are contiguous in the array until spaces are found to signal the end of the ssn's, you could code the perform as follows to limit the iterations to the # of ssn's present in the array, making it more efficient. In most cases you’ll probably have less than 5 ssn’s in an array.
Code:
  PERFORM VARYING SR-OCCURS FROM 1 BY 1
    UNTIL HM-SSN(SR-OCCURS)    = SPACES
          OR
          SR-OCCURS            > 23
          DISPLAY '1-HM-SSN='HM-SSN(SR-OCCURS)
          MOVE HMFN-ID        TO SR-ID
          MOVE HM-SSN(SR-OCCURS) 
                              TO SR-SSN
          DISPLAY 'SR-SSN= '     SR-SSN
*         WRITE SF-REC      FROM SORT-REC
          DISPLAY 'SORT-FILE= '  SF-REC
          RELEASE SORT-REC
  END-PERFORM
Regards, Jack.

P.S. I don't know how powerful your text editor is, but you might consider prefixing your DISPLAY text with something like DEBUG~ (that's what I use). When I'm finished with the DISPLAYs I just find all the DEBUG~ strings and delete them. With the editor I use on the mainframe I can delete all the DISPLAYs I put in the pgm with 3 edit commands, no matter how many displays there were.
 
i AM STILL GETTING THE SAME ERROR IN THE SAME SECTION. iT DOES NOT LIKE THE HM-SSN(SR-OCCURS).

C103-SSN.
DISPLAY 'IN C103-HELP'.
DISPLAY 'HM-SSN=' HM-SSN(SR-OCCURS)
MOVE HM-SSN(SR-OCCURS) TO ER-ORG-SSN.
COMPUTE B-IDX = B-IDX + 1
MOVE B-IDX TO BAD-SSN
MOVE BAD-SSN TO HM-SSN(SR-OCCURS), ER-NEW-SSN
MOVE HMFN-ID TO ER-ID
MOVE HM-FNAME(SR-OCCURS) TO ER-FNAME
MOVE HM-LNAME(SR-OCCURS) TO ER-LNAME
WRITE ERROR-REC FROM ERROR-RECORDS.
C103-EXIT.
EXIT.




 
Hi Deidre,

The problem that you are having is the result of incorrect PERFORM ranges. You are falling into C103-SSN!

Let's take it from the top.
Code:
SORT SORT-WORK       
  ON ASCENDING KEY SR-SSN
  INPUT PROCEDURE B100-SORT-IN-PROC
  OUTPUT PROCEDURE C100-SORT-OUT-PROC.

Now, B100-SORT-IN-PROC is a paragraph. In it you end executing:
PERFORM B102-READ.
Within B102-READ you eventually hit an end-of-file, causing you to execute:
AT END
CLOSE NEW-HHMF-FILE
DISPLAY 'EOF'
GO B102-EXIT
But B102-EXIT is not within the scope of the PERFORMed procedures, so it falls through into C100-SORT-OUT-PROC:
B102-EXIT.
EXIT.
C100-SORT-OUT-PROC.
DISPLAY 'C100-READING FILES'
PERFORM C101-OPEN-FILES.
PERFORM C102-READ-FILES.

This is not the way you want your program to execute. You can continue to examine your code and you will discover how you manage to fall into C103-SSN from C102-EXIT.

Go back to my example. Notice that I use SECTIONs to promote readability in the SORT and PERFORM statements. (I personally don't like the
PERFORM a THRU b
construct, but this is a coding style issue that is not too important here.)

Put some section headers in your procedure division, or otherwise clean up your PERFORMs so that you are not branch out of the scope of the invoking PERFORM. Suggested SECTIONs:
A100-SORT
B100-SORT-IN-PROC
B101-OPEN-FILES
B102-READ
C100-SORT-OUT-PROC
C101-OPEN-FILES
C102-READ-FILES
C103-SSN
Tom Morrison
 
I TRIED THE PERFORM VARYING STATEMENT AND IT GIVES ME AN ERROR OF SUBSCRIPT OUT OF RANGE ON THE HM-SSN-2 (SR-OCCURS) = SPACES POINT.

PERFORM VARYING SR-OCCURS FROM 1 BY 1
UNTIL HM-SSN-2(SR-OCCURS) = SPACES
OR
SR-OCCURS > 23
MOVE HMFN-ID-2 TO SR-ID
MOVE HM-SSN-2(SR-OCCURS) TO SR-SSN
RELEASE SORT-REC
END-PERFORM
 
Hi Deidre,
I notice that you have now correctly referenced HM-SSN-2 rather than HM-SSN as in previous posts. From your original listing, I can see no definition of SR-OCCURS. Have you added this, as I can see nothing wrong with the PERFORM VARYING other than this possibility?
Regards,
Marc
 
i HAVE BOTH HM-SSN AND HM-SSN-2, HM-SSN-2 IS A SHORTER VERSION OF HM-SSN, I JUST DECIDED TO MOVE THE DATA INTO THE NWMAST-DATA-2 WORKING STORAGE FILE INSTEAD OF THE NEWMAST-DATA.

tHE SR-OCCURS IS WHAT YOU HAD ME PUT IN, I JUST CALLED IT SR-OCCURS INSTEAD OF SORT-OCCURS.
 
I think it might be worthwhile if you posted the amended source again, if that's not a problem.

Marc
 
Hi Deidre,

Sorry, my mistake. Just reverse the 2 UNTIL phrases, i.e.:
Code:
  PERFORM VARYING SR-OCCURS FROM 1 BY 1
    UNTIL SR-OCCURS            > 23
          OR
          HM-SSN(SR-OCCURS)    = SPACES
          MOVE HMFN-ID        TO SR-ID
          MOVE HM-SSN(SR-OCCURS) 
                              TO SR-SSN
          RELEASE SORT-REC
  END-PERFORM
Regards, Jack.

 
Hi Mark, et al,

I think, what was wrong w/my original perform was that, when the the occurs count went to 24, it was used to test for SPACES in HM-SSN(SR-OCCURS) and was out of the occurs range, a no-no. Switching the 2 phrases should eliminate the problem.

Regards, Jack.
 
tHANKS, THAT WORKED, BUT IT DID NOT CATCH THE FIRST DUPLICATE SSN#. DID I MISS SOMETHING?
 
aCUTALLY IT DID NOT CATCH ALL THE DUPLICATES. examples:

I have 3 duplicate ssn# with all 4's
I have 20 duplicate ssn#'s with 123456789
 
Jack,
You are correct. It is critical to order the phrases so that the subscript value test is to the left of any use of the subscript value in the same conditional expression. The standard specifies left-to-right evaluation, and further specifies that evaluation terminates as soon as the value of the conditional expression can be determined. Thus, when the subscript test evaluates TRUE, TRUE ORed with any value is TRUE, so evaluation must terminate.
Tom Morrison
 
Hi Deidre,

I agree with Marc. It is time to post the source to your program again, since we are otherwise speculating about possible causes.

Tom Morrison
 
Here is the code.

FD NEW-HHMF-FILE
LABEL RECORDS IS STANDARD
VALUE OF FILE-ID IS '\FDPSYS\TABLES\DATA\NEWHMFI.DAT'.
01 NEW-HHMF-REC.
03 NEW-HHMF-KEY PIC X(09).
03 FILLER PIC X(2039).
FD ERROR-FILE
LABEL RECORDS IS STANDARD
VALUE OF FILE-ID IS '\FDPSYS\TABLES\DATA\ERROR.DAT'.
01 ERROR-REC PIC X(68).
SD SORT-WORK.
01 SORT-REC.
03 SR-SSN PIC 9(09).
03 SR-ID PIC X(09).
03 SR-OCCURS PIC 9(02).

WORKING-STORAGE SECTION.
*
01 NEW-HHMF-CNT PIC 9(06) VALUE ZERO.
01 NEW-MEM-CNT PIC 9(06) VALUE ZERO.
01 NEW-CNT PIC 9(06) VALUE ZERO.
01 SORT-CNT PIC 9(06) VALUE ZERO.
01 BAD-SSN-CNT PIC 9(09) VALUE ZERO.
01 ERROR-CNT PIC 9(09) VALUE ZERO.
01 SR-OCCURS-CNT PIC 9(09) VALUE ZERO.
01 LAST-SSN PIC 9(09).
01 NEW-SSN PIC 9(09).
01 B-IDX PIC 9(09).
01 BAD-SSN PIC 9(09).
01 ERROR-RECORDS.
03 ER-ID PIC X(09).
03 FILLER PIC X(02).
03 ER-ORG-SSN PIC 9(09).
03 FILLER PIC X(04).
03 ER-LNAME PIC X(20).
03 ER-FNAME PIC X(14).
03 FILLER PIC X(01).
03 ER-NEW-SSN PIC 9(09).
01 NEWMAST-DATA.
03 HMFN-ID PIC X(09).
03 HMFN-SS-ID PIC 9(09).
03 FILLER PIC 9(08).
03 HMFN-LNAME PIC X(20).
03 HMFN-FNAME PIC X(14).
03 FILLER PIC X(61).
03 HMFN-HHSIZE PIC 9(02).
03 FILLER PIC X(435).
03 HMFN-MEMBERS.
05 HM-MEMBERS OCCURS 23 TIMES.
07 HM-FNAME PIC X(14).
07 HM-LNAME PIC X(20).
07 HM-SSN PIC 9(09).
07 HM-DOB PIC 9(08).
03 FILLER PIC X(317).
*
PROCEDURE DIVISION.
*
A000-BEGIN.
SORT SORT-WORK
ON ASCENDING KEY SR-SSN
INPUT PROCEDURE B000-SORT-IN-PROC
OUTPUT PROCEDURE C000-SORT-OUT-PROC.
DISPLAY 'NEW-HHMF-CNT RECORDS READ:' NEW-HHMF-CNT.
DISPLAY 'SR-OCCURS-CNT RECORDS READ:' SR-OCCURS-CNT.
DISPLAY 'SORT-CNT RECORDS READ:' SORT-CNT.
DISPLAY 'ERROR RECORDS READ:' ERROR-CNT.
STOP RUN.
A000-EXIT.
EXIT.

B000-SORT-IN-PROC SECTION.
B100-OPEN-FILES.
OPEN INPUT NEW-HHMF-FILE.
B200-READ-FILES.
READ NEW-HHMF-FILE NEXT INTO NEWMAST-DATA
AT END
CLOSE NEW-HHMF-FILE
GO TO B000-EXIT-SECTION
END-READ
COMPUTE NEW-HHMF-CNT = NEW-HHMF-CNT + 1.

PERFORM VARYING SR-OCCURS FROM 1 BY 1
UNTIL SR-OCCURS > 23
OR
HM-FNAME(SR-OCCURS) = SPACES
MOVE HM-SSN(SR-OCCURS) TO SR-SSN
MOVE HMFN-ID TO SR-ID, SORT-ID
COMPUTE SR-OCCURS-CNT = SR-OCCURS-CNT + 1
RELEASE SORT-REC
END-PERFORM
GO B200-READ-FILES.

B000-EXIT-SECTION.
EXIT.

C000-SORT-OUT-PROC SECTION.
C100-OPEN-FILES.
OPEN I-O NEW-HHMF-FILE
OUTPUT ERROR-FILE.
MOVE 999999999 TO LAST-SSN.
MOVE ZERO TO B-IDX.

C200-READ-FILES.
RETURN SORT-WORK
AT END
CLOSE NEW-HHMF-FILE
ERROR-FILE
GO C000-EXIT-SECTION
END-RETURN
COMPUTE SORT-CNT = SORT-CNT + 1.
IF SR-SSN = LAST-SSN
MOVE SR-ID TO NEW-HHMF-KEY
READ NEW-HHMF-FILE INTO NEWMAST-DATA
INVALID KEY
DISPLAY 'NOT VALID'
NOT INVALID KEY
MOVE HM-SSN(SR-OCCURS) TO BAD-SSN,
ER-ORG-SSN
COMPUTE B-IDX = B-IDX + 1
MOVE B-IDX TO BAD-SSN
MOVE BAD-SSN TO HM-SSN(SR-OCCURS),
ER-NEW-SSN
MOVE HMFN-ID TO ER-ID
MOVE HM-FNAME(SR-OCCURS) TO ER-FNAME
MOVE HM-LNAME(SR-OCCURS) TO ER-LNAME
WRITE ERROR-REC FROM ERROR-RECORDS
COMPUTE ERROR-CNT = ERROR-CNT + 1
REWRITE NEW-HHMF-REC FROM NEWMAST-DATA
END-READ
ELSE
MOVE SR-SSN TO LAST-SSN
END-IF
GO TO C200-READ-FILES.

C000-EXIT-SECTION.
EXIT.

 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top