MVSFORUMS.com Forum Index MVSFORUMS.com
A Community of and for MVS Professionals
 
 FAQFAQ   SearchSearch   Quick Manuals   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

Reading and Comparing Two Vsam Records

 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Data Management
View previous topic :: View next topic  
Author Message
vinxi
Beginner


Joined: 17 Apr 2005
Posts: 7
Topics: 1

PostPosted: Sun Apr 17, 2005 10:45 pm    Post subject: Reading and Comparing Two Vsam Records Reply with quote

hello guys,

i need to compare two records in a vsam file...
Code:

0001     10012005   JOHN    DOE      MALE
0002     10022005   JAN     DOE      FEMALE


i need to know if these two records are a day apart based on the date. can you give me some hints...

im using a cobol batch....

thanks....
Back to top
View user's profile Send private message MSN Messenger
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12380
Topics: 75
Location: San Jose

PostPosted: Mon Apr 18, 2005 5:23 am    Post subject: Reply with quote

vinxi,


Please search before posting. check this link .

http://mvsforums.com/helpboards/viewtopic.php?t=11&highlight=match

You can find the difference between 2 dates as follows.

Code:

01 WS-DATE-DIFF                PIC S9(08) COMP.
01 WS-DATE1                    PIC 9(08).
01 WS-DATE2                    PIC 9(08). 

COMPUTE WS-DATE-DIFF = FUNCTION INTEGER-OF-DATE(WS-DATE2) - 
                       FUNCTION INTEGER-OF-DATE(WS-DATE1)



Now you can just check if ws-date-diff is equal to 1 or not.



Hope this helps...

Cheers

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
vinxi
Beginner


Joined: 17 Apr 2005
Posts: 7
Topics: 1

PostPosted: Mon Apr 18, 2005 6:08 am    Post subject: thanks sir! Reply with quote

hello sir kolusu,

thank you for your reply... i am speaking of only one VSAM file. i am really a newbie with VSAM.

i need to compare two records inside a single VSAM file.

supposed i have SAMPLE-VSAM-FILE which contains these records:
Code:

0001     10012005   JOHN    DOE      MALE
0002     10022005   JAN     DOE      FEMALE
0003     10032005   JOE     DOE      MALE


i need to compare record 1 and record 2... how can i read record 1 and record 2 if i dont know their record keys? i just need to compare 2 consecutive records inside the VSAM file. can u give me some hints? thank you... Smile
Back to top
View user's profile Send private message MSN Messenger
s_shivaraj
Beginner


Joined: 21 Sep 2004
Posts: 140
Topics: 14
Location: Chennai, India

PostPosted: Mon Apr 18, 2005 6:45 am    Post subject: Reply with quote

Vinxi,

Just read the first Record and move it to a Variable and read the next record and compare that with saved variable.
Quote:
need to compare record 1 and record 2... how can i read record 1 and record 2 if i dont know their record keys?


Reading sequentially will help you even if you dont know the record keys
_________________
Cheers
Sivaraj S

'Technical Skill is the Master of complexity, while Creativity is the Master of Simplicity'
Back to top
View user's profile Send private message AIM Address
s_shivaraj
Beginner


Joined: 21 Sep 2004
Posts: 140
Topics: 14
Location: Chennai, India

PostPosted: Mon Apr 18, 2005 6:56 am    Post subject: Reply with quote

Code:
01 WS-GROUP-NAME.
 03 WS-DATE-DIFF                PIC S9(08) COMP.
 03 WS-DATE1                    PIC 9(08).
....

01 WS-GROUP-NAME-PREV.
 03 WS-DATE-DIFF-PREV                PIC S9(08) COMP.
 03 WS-DATE1-PREV                    PIC 9(08).
...

READ VSAM-FILE INTO WS-GROUP-NAME.
MOVE WS-GROUP-NAME TO WS-GROUP-NAME TO WS-GROUP-NAME-PREV.
READ VSAM-FILE INTO WS-GROUP-NAME.

COMPUTE WS-DATE-DIFF = FUNCTION INTEGER-OF-DATE(WS-DATE1) - 
                       FUNCTION INTEGER-OF-DATE(WS-DATE1-PREV)


This is Just how the solution can be reached plz customize according to the need by using proper loopings.

Hope the above info helps you.
_________________
Cheers
Sivaraj S

'Technical Skill is the Master of complexity, while Creativity is the Master of Simplicity'
Back to top
View user's profile Send private message AIM Address
vinxi
Beginner


Joined: 17 Apr 2005
Posts: 7
Topics: 1

PostPosted: Mon Apr 18, 2005 10:56 pm    Post subject: reading sequentially with dynamic access Reply with quote

hello guys,

thanks for your help. i read in a book that i can read a file sequentially even if i set
Code:
ACCESS IS DYNAMIC


by putting the NEXT RECORD with the AT END/NOT AT END clauses.
Code:
READ file-name NEXT RECORD INTO identifier
   AT END imperative statements
   NOT AT END imperative statements
END-READ


i am recieving an error that
Code:
"AT" was invalid.
A "NOT" phrase did not have a matching verb.
The explicit scope terminator "END-READ" was found without a matching verb.


any help will be appreciated... thanks... Smile
Back to top
View user's profile Send private message MSN Messenger
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12380
Topics: 75
Location: San Jose

PostPosted: Tue Apr 19, 2005 8:03 am    Post subject: Reply with quote

vinxi,

What version of cobol are you using? try this

Code:

FILE-CONTROL.                               
                                           
      SELECT VSAMFILE                       
             ASSIGN TO VSAMFILE             
             ORGANIZATION IS INDEXED       
             ACCESS MODE IS DYNAMIC         
             RECORD KEY IS VSAM-KEY       
             FILE STATUS IS W-VSAM-STATUS.

FILE SECTION.

FD VSAMFILE.                                   
01 VSAM-RECORD              PIC X(100).                         


WORKING-STORAGE SECTION.
                         
01 W-FIRST-REC                     PIC X(100) VALUE SPACES. 
01 W-SECOND-REC                    PIC X(100) VALUE SPACES. 
01 W-VSAM-STATUS                   PIC X(02) VALUE SPACES.   

PROCEDURE DIVISION.                               
                                                 
      OPEN INPUT VSAMFILE.                         
      PERFORM 1000-READ-FILE
      CLOSE  VSAMFILE                             
      GOBACK                                     
      .                                           
1000-READ-FILE.                                   
                                                 
      READ VSAMFILE NEXT RECORD INTO W-SECOND-REC 
        AT END                                   
           DISPLAY 'EOF FILE REACHED'             
       NOT AT END                                 
           MOVE VSAM-RECORD TO W-FIRST-REC 
      END-READ                                   
      .                                           
                                                 


Hope this helps...

Cheers

kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
vinxi
Beginner


Joined: 17 Apr 2005
Posts: 7
Topics: 1

PostPosted: Tue Apr 19, 2005 10:10 pm    Post subject: ver 10 Reply with quote

hi kolusu, i did the same code as yours. im still getting the same compile errors... i was told that we are using version 10. is there an alternative for command that supports COBOL version 10?

thanks again!
Back to top
View user's profile Send private message MSN Messenger
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12380
Topics: 75
Location: San Jose

PostPosted: Wed Apr 20, 2005 3:04 am    Post subject: Reply with quote

Quote:

i was told that we are using version 10. is there an alternative for command that supports COBOL version 10?


vinxi,

Cobol version 10? I haven't heard about till now. If you are talking about COBOL ON MAINFRAME then check this link for history of COBOL compilers. The latest is ENTERPRISE COBOL.

http://www-1.ibm.com/servers/eserver/zseries/zos/le/history/cobmvs.html

kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
vinxi
Beginner


Joined: 17 Apr 2005
Posts: 7
Topics: 1

PostPosted: Wed Apr 20, 2005 5:17 am    Post subject: sorry wrong info... Reply with quote

hello again kolusu...
sorry for the wrong info about the version... things got messed up... Confused
ill keep you posted when i get the right version...
for now, can i use the FILE STATUS 10 as my flag to determine the end of the VSAM file?
if you could suggest better alternatives, it will be greatly appreciated...
thanks again kolusu... hope there are more people like you who are always ready to help newbies like me!

MABUHAY!!! (long live!) Smile
Back to top
View user's profile Send private message MSN Messenger
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12380
Topics: 75
Location: San Jose

PostPosted: Wed Apr 20, 2005 11:45 am    Post subject: Reply with quote

vinxi,


Quote:

for now, can i use the FILE STATUS 10 as my flag to determine the end of the VSAM file?
if you could suggest better alternatives, it will be greatly appreciated...


I can only suggest a solution when you explain the requirements in details. Post detailed information about what you are trying to acheive and it will help you in getting a better soltuion.

Actually comparing 2 records is very easy. Try to keep it simple.

psuedo code would be

Code:

open vsam file
prime read the vsam file into first-rec
perform main process until vsam file eof
goback.

main process

read the vsam file into second-rec
compare first-rec to second-rec
if matched
   perform some logic
else
   perform invalid logic
end-if

initialize first-rec and second-rec
read the vsam file into first-rec
.


Hope this helps...

Cheers

kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
vinxi
Beginner


Joined: 17 Apr 2005
Posts: 7
Topics: 1

PostPosted: Thu Apr 21, 2005 1:40 am    Post subject: Reply with quote

thanks kolusu...
here is the scenario that i am working on...
i have a vsam file
Code:
VSAM-SAMPLE

that has 4 record keys...
Code:
RK1, RK2, RK3, RK4

RK4 is a date.

i need to find records in the VSAM-SAMPLE file with the values RK1=AAA RK2=222 RK3=BBB.
my goal is to get the latest and the earliest record based on RK4(date).

hope i make sense to you...

thanks again for the help...
Back to top
View user's profile Send private message MSN Messenger
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12380
Topics: 75
Location: San Jose

PostPosted: Thu Apr 21, 2005 5:43 am    Post subject: Reply with quote

Vinxi,

You don't even need a program to get the latest/oldest date.A simple sort step will get you the desired results. I am assumming that your vsam file lrecl is 80 bytes and is of FB record format. I am also assuming that your RK1 is at pos 1 and Rk2 at pos 10 and Rk3 at pos 20 and the date is at pos 30

Code:

//STEP0100  EXEC PGM=SORT
//SYSOUT    DD SYSOUT=*   
//SORTIN    DD DSN=YOUR VSAM FILE,
//             DISP=SHR
//SORTOUT   DD SYSOUT=*
//SYSIN     DD *
   INCLUDE COND=(01,3,CH,EQ,C'AAA',AND,
                 10,3,CH,EQ,C'222',AND,
                 20,3,CH,EQ,C'BBB')
   SORT FILEDS=(01,3,CH,A,
                10,3,CH,A,
                20,3,CH,A,
                30,10,CH,D)
   OUTFIL NODETAIL,REMOVECC,     
   HEADER1=(1,80),        $ LATEST DATE RECORD       
   TRAILER1=(1,80)        $ OLDEST DATE RECORD       
/*


Hope this helps...

Cheers

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
vinxi
Beginner


Joined: 17 Apr 2005
Posts: 7
Topics: 1

PostPosted: Thu Apr 21, 2005 6:12 am    Post subject: Reply with quote

hi kolusu... i am really grateful for your help... but i need the cobol program because i will be filling in values of my record keys from another process...

another question... supposed i declared this in my code:
Code:

       ENVIRONMENT DIVISION.                                             
       CONFIGURATION SECTION.                                           
       SOURCE-COMPUTER. IBM-3033.                                       
       OBJECT-COMPUTER. IBM-3033.                                       
       INPUT-OUTPUT SECTION.                                             
       FILE-CONTROL.                                                     
           SELECT VSAM-PROTYPE-FILE                                     
              ASSIGN VSAMPROT                                           
              ORGANIZATION IS INDEXED                                   
              ACCESS MODE  IS DYNAMIC                                   
              RECORD KEY   IS DATA-KEY                                   
              FILE STATUS  IS STATUS-CODE                               
                              VSAM-STATUS.                               
      ******************************************************************
      *                                                                *
      *                       DATA DIVISION                            *
      *                                                                *
      ******************************************************************
       DATA DIVISION.                                                   
       FILE SECTION.                                                     
       FD  VSAM-PROTYPE-FILE                                             
           RECORD CONTAINS 65 CHARACTERS.                               
       01  FD-FILE-RECORD.                                               
      ** INDICATE RECORD LAYOUT BELOW                                   
           10  DATA-KEY.                                                 
             15  EMP-NUM                                PIC 9(10).       
             15  LAST-NAME                              PIC X(25).       
             15  TEAM                                   PIC X(10).       
           10  DATA-GRP.                                                 
             15  FIRST-NAME                             PIC X(20).       

i only have values for EMP-NUM and TEAM... how can i get all the records that has the same EMP-NUM and TEAM in the VSAM file...

thanks!
Back to top
View user's profile Send private message MSN Messenger
Display posts from previous:   
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Data Management All times are GMT - 5 Hours
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


MVSFORUMS
Powered by phpBB © 2001, 2005 phpBB Group