IBM Mainframe Forum Index
 
Log In
 
IBM Mainframe Forum Index Mainframe: Search IBM Mainframe Forum: FAQ Register
 

Most Common Interview Question


IBM Mainframe Forums -> Mainframe Interview Questions
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
ovreddy

Active User


Joined: 06 Dec 2004
Posts: 211
Location: Keane Inc., Minneapolis USA.

PostPosted: Mon Dec 06, 2004 3:49 pm
Reply with quote

Hi all,

This question is asked in one interview. Any one can please solve this.

There is a COBOL flat file which contains 'n' records. each record contains 10 numbers. the format is...
Eg:

1233 3432 4543 5545 ....(10 times)
"
"
"
( N Records)

U need to write a complete program to find out second greatest number of the file. Think in depth then start writing..

Thanks in advance...
Back to top
View user's profile Send private message
jz1b0c

Active User


Joined: 25 Jan 2004
Posts: 160
Location: Toronto, Canada

PostPosted: Thu Dec 09, 2004 12:47 am
Reply with quote

Great Day Reddy!

I am not sure if you want everything to be done in cobol, but here is one way.


1234 3454 2121 1980 ... 10(times)
:
:n records


sort each record and put them in descender like this
(either rewrite or create a new file for the result)

3454 2121 1980 1234 .....
:
:
n records

so now
first number of every record contains the maximum number in that row

now you need to sort this file based on first number, (in descending order).

by doing so..

maximum value comes as the first number of the first record.
now you compare the first number of second record with remaining nine numbers of the first record, which ever is greatest becomes the second maximum number.
Back to top
View user's profile Send private message
jz1b0c

Active User


Joined: 25 Jan 2004
Posts: 160
Location: Toronto, Canada

PostPosted: Thu Dec 09, 2004 4:45 am
Reply with quote

reddy,

Here is the complete program


IDENTIFICATION DIVISION.
PROGRAM-ID. SECMAXN.
********AUTHOR. JZ1B0C - MASADE.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT INP-FILE ASSIGN TO INPFILE.
SELECT OUT-FILE ASSIGN TO OUTFILE.
*
DATA DIVISION.
FILE SECTION.
FD INP-FILE
RECORDING MODE IS F
BLOCK CONTAINS 0 RECORDS
DATA RECORD IS FD-LOANTRAN-REC.

01 INP-FILE01.
05 INP-REC.
10 INP-NUM PIC 9(4)
OCCURS 10 TIMES.
FD OUT-FILE
RECORDING MODE IS F
BLOCK CONTAINS 0 RECORDS
DATA RECORD IS FD-LOANTRAN-REC.

01 OUT-FILE01.
05 OUT-REC.
10 OUT-NUM PIC 9(4)
OCCURS 10 TIMES.
WORKING-STORAGE SECTION.
*
01 CONSTANTS-AREA.
05 C-ONE PIC 9(01) VALUE 1.
05 C-TWO PIC 9(01) VALUE 2.
05 C-TEN PIC 9(02) VALUE 10.
01 WS01-TEMP PIC 9(04).
01 WS01-I PIC 9(08).
01 WS01-J PIC 9(08).
01 WS01-WORK-AREA.
05 WS05-COUNT PIC 9(08) VALUE ZERO.
*
01 WS01-EOF PIC X(01) VALUE 'X'.
88 EOF VALUE 'Y'.
88 NOT-EOF VALUE 'X'.
01 WS01-SWAPS PIC X(01) VALUE 'X'.
88 NO-MORE-SWAPS VALUE 'Y'.
88 MORE-SWAPS VALUE 'X'.
*
01 WS01-INPFILE.
05 WS05-FILE OCCURS 1200 TIMES.
15 WS15-NUM-REC PIC 9(04)
OCCURS 10 TIMES.
01 WS01-TMPREC PIC X(40).
*
01 WS01-TEMP-REC.
05 WS05-TEMP-REC.
10 WS10-INP-NUM PIC 9(4)
OCCURS 10 TIMES.
*
PROCEDURE DIVISION.
*
PERFORM 000-INITIALIZE.
PERFORM 100-MAINLINE.
PERFORM 900-FINALIZE.

GOBACK.
*
000-INITIALIZE SECTION.
OPEN INPUT INP-FILE.
OPEN OUTPUT OUT-FILE.
READ INP-FILE
AT END MOVE 'Y' TO WS01-EOF.
000-EXIT.
EXIT.

100-MAINLINE SECTION.
PERFORM 101-FIRST-LEVEL-SORT UNTIL EOF.
MOVE 'X' TO WS01-SWAPS.
PERFORM 110-SORT-SORTED UNTIL NO-MORE-SWAPS.
PERFORM 300-WRITE-OUTFILE.
100-EXIT.
EXIT.

101-FIRST-LEVEL-SORT SECTION.
MOVE 'X' TO WS01-SWAPS.
PERFORM 105-SORT-READ-ROW UNTIL NO-MORE-SWAPS.
ADD 1 TO WS05-COUNT
MOVE INP-REC TO WS05-FILE(WS05-COUNT)
PERFORM 200-READ-INP-REC.
101-EXIT.
EXIT.

105-SORT-READ-ROW SECTION.
MOVE C-ONE TO WS01-I.
MOVE 'Y' TO WS01-SWAPS.
PERFORM UNTIL WS01-I >= C-TEN
COMPUTE WS01-J = WS01-I + C-ONE
IF INP-NUM(WS01-I) < INP-NUM (WS01-J)
MOVE INP-NUM(WS01-I) TO WS01-TEMP
MOVE INP-NUM(WS01-J) TO INP-NUM(WS01-I)
MOVE WS01-TEMP TO INP-NUM(WS01-J)
MOVE 'X' TO WS01-SWAPS
END-IF
COMPUTE WS01-I = WS01-I + C-ONE
END-PERFORM.
105-EXIT.
EXIT.

110-SORT-SORTED SECTION.
MOVE C-ONE TO WS01-I.
MOVE 'Y' TO WS01-SWAPS.
PERFORM UNTIL WS01-I >= WS05-COUNT
COMPUTE WS01-J = WS01-I + C-ONE
IF WS15-NUM-REC(WS01-I,C-ONE)< WS15-NUM-REC(WS01-J,C-ONE)
MOVE WS05-FILE(WS01-I) TO WS01-TMPREC
MOVE WS05-FILE(WS01-J) TO WS05-FILE(WS01-I)
MOVE WS01-TMPREC TO WS05-FILE(WS01-J)
MOVE 'X' TO WS01-SWAPS
END-IF
COMPUTE WS01-I = WS01-I + C-ONE
END-PERFORM.
110-EXIT.
EXIT.

200-READ-INP-REC SECTION.
READ INP-FILE
AT END MOVE 'Y' TO WS01-EOF.
200-EXIT.
EXIT.
300-WRITE-OUTFILE SECTION.
MOVE C-ONE TO WS01-I.
PERFORM UNTIL WS01-I > WS05-COUNT
MOVE WS05-FILE (WS01-I) TO OUT-FILE01
WRITE OUT-FILE01
ADD 1 TO WS01-I
END-PERFORM.
300-EXIT.
EXIT.

900-FINALIZE SECTION.
IF WS15-NUM-REC(C-ONE,C-TWO) > WS15-NUM-REC(C-TWO,C-ONE)
DISPLAY 'SECOND MAX :' WS15-NUM-REC(C-ONE,C-TWO)
ELSE
DISPLAY 'SECOND MAX :' WS15-NUM-REC(C-TWO,C-ONE)
END-IF.
DISPLAY 'MAX NUM :' WS15-NUM-REC(C-ONE,C-ONE).
CLOSE INP-FILE.
CLOSE OUT-FILE.
900-EXIT.
EXIT.
Back to top
View user's profile Send private message
bryan-yang

New User


Joined: 16 Apr 2006
Posts: 16
Location: BeiJing, China

PostPosted: Tue Apr 25, 2006 7:51 pm
Reply with quote

If the first maximum number and the second maximum number are in the same record, result will be bad.
Back to top
View user's profile Send private message
mmwife

Super Moderator


Joined: 30 May 2003
Posts: 1592

PostPosted: Thu Apr 27, 2006 4:39 am
Reply with quote

Here's my entry (in pseudo code):
Code:
 WS

01  ip-rec.
    05  ip-nbr-tbl.
        10  ip-nbr pic  x(004) occurs 10 times.
01  wrk-flds.
    05  1st-nbr    pic  x(004) value all X'00'.
    05  2nd-nbr    pic  x(004) value all X'00'.
    05  nbr-ss     pic s9(002) comp.

PD

open file
read 1st rec
if ip-eof
   display error-msg
end-if
perform 100-proc-ip-recs until ip-eof
close file
display 2nd-highest-nbr
stop run
.
100-proc-ip-recs.
    perform 110-proc-nbrs-in-rec varying
            nbr-ss from +1 by +1
      until nbr-ss > +10
    perform 710-read-next-rec
    .
110-proc-nbrs-in-rec.
    evaluate true
    when ip-nbr(nbr-ss) = 1st-nbr
    when ip-nbr(nbr-ss) = 2nd-nbr
         continue
    when ip-nbr(nbr-ss)       > 1st-nbr
         move 1st-nbr        to 2nd-nbr
         move ip-nbr(nbr-ss) to 1st-nbr
    when ip-nbr(nbr-ss) > 2nd-nbr
         move ip-nbr(nbr-ss) to 2nd-nbr
    end-evaluate
    .
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> Mainframe Interview Questions

 


Similar Topics
Topic Forum Replies
No new posts Question for file manager IBM Tools 7
No new posts question for Pedro TSO/ISPF 2
No new posts question on Outrec and sort #Digvijay DFSORT/ICETOOL 20
No new posts panel creation question TSO/ISPF 12
This topic is locked: you cannot edit posts or make replies. COBOL-Common routine that contains al... COBOL Programming 4
Search our Forums:

Back to Top