View previous topic :: View next topic
|
Author |
Message |
hallecodec
New User
Joined: 05 Sep 2006 Posts: 30 Location: Philippines
|
|
|
|
hi everyone,
Please see the code below...
Code: |
01 WS-EMP-REC.
05 WK-EMP-RES PIC 99.
05 WS-SUB1 PIC 999.
05 WS-EMP-NO PIC X(10).
05 WS-EMP-DEP PIC X(2).
05 WS-EMP-RESX PIC X(200).
05 WS-EMP-RESR REDEFINES WS-EMP-RESX OCCURS 100.
10 WS-EMP-RES PIC 9(2).
PROCEDURE DIVISION.
MOVE 1 TO WS-SUB1.
PERFORM 100 TIMES
PERFORM VARYING WS-SUB1 FROM 1 BY 1 UNTIL WS-SUB1 > 100
IF WS-EMP-RES (WS-SUB1) > WS-EMP-RES (WS-SUB1 + 1)
MOVE WS-EMP-RES (WS-SUB1) TO WS-EMP-RES (WS-SUB1 + 1)
MOVE WS-EMP-RES (WS-SUB1) TO WK-EMP-RES
END-IF
END-PERFORM
END-PERFORM. |
This piece of code is a bubble sort. I would like to ask if this code is right to be considered a bubble sort. If it is, what should i do to improve its performance? |
|
Back to top |
|
|
Arun Raj
Moderator
Joined: 17 Oct 2006 Posts: 2481 Location: @my desk
|
|
|
|
Hi
I think that there will be loss of data if you are executing the above code as such, as you are not taking any back up of WS-EMP-RES (WS-SUB1 + 1) before moving to that field.
Quote: |
IF WS-EMP-RES (WS-SUB1) > WS-EMP-RES (WS-SUB1 + 1)
MOVE WS-EMP-RES (WS-SUB1) TO WS-EMP-RES (WS-SUB1 + 1)
MOVE WS-EMP-RES (WS-SUB1) TO WK-EMP-RES
|
And in bubble sort each time the no. of iterations should go on decreasing till the table gets sorted.A simple bubble sort proceeds as first finding the least value and storing it as the first element and finding the next least value and storing as the second element and so on.
Try this code
Code: |
01 WS-EMP-REC.
05 WK-EMP-RES PIC 99.
05 WS-SUB1 PIC 999 VALUE 0.
05 WS-SUB2 PIC 999 VALUE 0.
05 WS-EMP-NO PIC X(10).
05 WS-EMP-DEP PIC X(2).
05 WS-EMP-RESX PIC X(200).
05 WS-EMP-RESR REDEFINES WS-EMP-RESX OCCURS 100.
10 WS-EMP-RES PIC 9(2).
PROCEDURE DIVISION.
PERFORM VARYING WS-SUB1 FROM 1 BY 1 UNTIL WS-SUB1= 100
PERFORM VARYING WS-SUB2 FROM WS-SUB1 BY 1 UNTIL WS-SUB2> 100
IF WS-EMP-RES (WS-SUB2) < WS-EMP-RES (WS-SUB1)
MOVE WS-EMP-RES (WS-SUB1) TO WK-EMP-RES
MOVE WS-EMP-RES (WS-SUB2) TO WS-EMP-RES (WS-SUB1)
MOVE WK-EMP-RES TO WS-EMP-RES (WS-SUB2)
END-IF
END-PERFORM
END-PERFORM. |
Please correct me if wrong
Thanks
Arun. |
|
Back to top |
|
|
hallecodec
New User
Joined: 05 Sep 2006 Posts: 30 Location: Philippines
|
|
|
|
thanks for the code... it's better than mine! hehe... is it because it function like a quick sort (because ws-sub1 acts like a pivot)? |
|
Back to top |
|
|
Arun Raj
Moderator
Joined: 17 Oct 2006 Posts: 2481 Location: @my desk
|
|
|
|
Hi
It should be better than the previous code as data is not getting lost...at least!!!!!
Tell me why do you prefer bubble sort ??
Thanks
Arun |
|
Back to top |
|
|
DavidatK
Active Member
Joined: 22 Nov 2005 Posts: 700 Location: Troy, Michigan USA
|
|
|
|
The bubble sort works by passing sequentially over a list, comparing each value to the one immediately after it. If the first value is greater than the second, their positions are switched. Over a number of passes, at most equal to the number of elements in the list, all of the values drift into their correct positions (large values "bubble" rapidly toward the end, pushing others down around them). Because each pass finds the maximum item and puts it at the end, the portion of the list to be sorted can be reduced at each pass. A boolean variable is used to track whether any changes have been made in the current pass; when a pass completes without changing anything, the algorithm exits.
Dave |
|
Back to top |
|
|
hallecodec
New User
Joined: 05 Sep 2006 Posts: 30 Location: Philippines
|
|
|
|
it's not like that i 'prefer' it... there's an exercise given to me and i needed to check the error of the bubble sort, without the aid of the compiler... i thought the bubble sort was already free from error (i didn't see that the data is being lost in the process); so, i began thinking on how to improve its performance instead...
anyway, thanks for the code suggestion and information... |
|
Back to top |
|
|
DavidatK
Active Member
Joined: 22 Nov 2005 Posts: 700 Location: Troy, Michigan USA
|
|
|
|
Hi hallecodec,
First, I?d like to apologize for the link I posted, when I looked for it today, it was gone. I thought it was an interesting link because it analyzed the code complexity and efficiently of most of the different common sorting algorithms.
I had not used the ?SHELL? sort algorithm before, so I stayed late last night and coded one up in COBOL, the example they gave at the site is in ?C?. They touted how much more efficient the SHELL algorithm is then the bubble sort, that they claimed to be the most inefficient algorithms when sorting more than just a few hundred records.
I have used the bubble sort algorithm in sever programs with very good success, but only sorting less than 200 records. So I was interested in how it would perform on larger record numbers. I created a table with 50,000 records and set the algorithms loose on it.
The code below has three sort algorithms in it. First is the ?BUBBLE? algorithm, then the ?JUMP UP? (A slightly modified version of the algorithm ?Arun? posted), and then the ?SHELL? algorithm. All sort on the identical set of records.
I take timings before and after each sort algorithm, and then check to make sure the sorted table is in sorted order.
Timing results are posted below. This is no joke, I ran the program several times.
Code: |
01 SORT-TABLE.
05 SORT-MIN-VALUE PIC 9(9) VALUE 999999999.
05 SORT-MAX-VALUE PIC 9(9) VALUE 0.
05 SORT-TEMP PIC S9(9) COMP-3.
05 SORT-SIZE PIC S9(9) COMP-3
VALUE 50000.
05 SUB1 PIC S9(9) COMP-3.
05 SUB2 PIC S9(9) COMP-3.
05 SUB2A PIC S9(9) COMP-3.
05 SUB3 PIC S9(9) COMP-3.
05 SUB1-START-VALUE PIC S9(9) COMP-3.
05 SUB2-START-VALUE PIC S9(9) COMP-3.
05 SORT-VALUES-C.
10 SORT-VALUE-C PIC 9(9) COMP-3
OCCURS 1 TO 100000
TIMES
DEPENDING ON SORT-SIZE.
05 SORT-VALUES.
10 SORT-VALUE PIC 9(9) COMP-3
OCCURS 1 TO 100000
TIMES
DEPENDING ON SORT-SIZE.
01 WS-VARIABLES.
05 INCREMENT PIC S9(9) COMP-3.
05 WS-TIME.
10 HH PIC 99.
10 MM PIC 99.
10 SS PIC 99.
10 DD PIC 99.
05 WS-TIME-DISPLAY.
05 WS-TIME-DISPLAY.
10 HH PIC 99.
10 FILLER PIC X VALUE ':'.
10 MM PIC 99.
10 FILLER PIC X VALUE ':'.
10 SS PIC 99.
10 FILLER PIC X VALUE '.'.
10 DD PIC 99.
LINKAGE SECTION.
PROCEDURE DIVISION.
PROGRAM-START.
PERFORM
VARYING SUB1 FROM 1 BY 1
UNTIL SUB1 > SORT-SIZE
COMPUTE SORT-VALUE-C (SUB1)
= FUNCTION RANDOM * 1000000000
IF SORT-VALUE-C (SUB1) < SORT-MIN-VALUE
THEN
MOVE SORT-VALUE-C (SUB1) TO SORT-MIN-VALUE
END-IF
IF SORT-VALUE-C (SUB1) > SORT-MAX-VALUE
THEN
MOVE SORT-VALUE-C (SUB1) TO SORT-MAX-VALUE
END-IF
END-PERFORM.
DISPLAY ' MIN VALUE =' SORT-MIN-VALUE
' MAX VALUE =' SORT-MAX-VALUE
' SORT SIZE =' SORT-SIZE.
MOVE SORT-VALUES-C TO SORT-VALUES.
ACCEPT WS-TIME FROM TIME.
MOVE CORRESPONDING WS-TIME TO WS-TIME-DISPLAY.
DISPLAY ' '
DISPLAY 'START TIME OF BUBBLE SORT ' WS-TIME-DISPLAY.
* TRUE BUBBLE SORT
PERFORM
VARYING SUB1 FROM SORT-SIZE BY -1
UNTIL SUB1 < 2
PERFORM
VARYING SUB2 FROM 1 BY 1
UNTIL SUB2 = SUB1
COMPUTE SUB3 = SUB2 + 1
IF SORT-VALUE (SUB2)
> SORT-VALUE (SUB3)
THEN
MOVE SORT-VALUE (SUB2) TO SORT-TEMP
MOVE SORT-VALUE (SUB3)
TO SORT-VALUE (SUB2)
MOVE SORT-TEMP TO SORT-VALUE (SUB3)
END-IF
END-PERFORM
END-PERFORM.
ACCEPT WS-TIME FROM TIME.
MOVE CORRESPONDING WS-TIME TO WS-TIME-DISPLAY.
DISPLAY 'END TIME OF BUBBLE SORT ' WS-TIME-DISPLAY.
PERFORM
VARYING SUB1 FROM 1 BY 1
UNTIL SUB1 >= SORT-SIZE
COMPUTE SUB2 = SUB1 + 1
IF SORT-VALUE (SUB1) > SORT-VALUE (SUB2)
THEN
DISPLAY 'ERROR IN SORT BETWEEN ' SUB1 ' AND ' SUB2
COMPUTE SUB1 = SORT-SIZE
END-IF
END-PERFORM.
MOVE SORT-VALUES-C TO SORT-VALUES.
ACCEPT WS-TIME FROM TIME.
MOVE CORRESPONDING WS-TIME TO WS-TIME-DISPLAY.
DISPLAY ' '.
DISPLAY 'START TIME OF JUMPUP SORT ' WS-TIME-DISPLAY.
* JUMP UP SORT
PERFORM
VARYING SUB1 FROM 1 BY 1
UNTIL SUB1 >= SORT-SIZE
COMPUTE SUB2-START-VALUE = SUB1 + 1
PERFORM
VARYING SUB2 FROM SUB2-START-VALUE BY 1
UNTIL SUB2 > SORT-SIZE
IF SORT-VALUE (SUB1)
> SORT-VALUE (SUB2)
THEN
MOVE SORT-VALUE (SUB1) TO SORT-TEMP
MOVE SORT-VALUE (SUB2)
TO SORT-VALUE (SUB1)
MOVE SORT-TEMP TO SORT-VALUE (SUB2)
END-IF
END-PERFORM
END-PERFORM.
ACCEPT WS-TIME FROM TIME.
MOVE CORRESPONDING WS-TIME TO WS-TIME-DISPLAY.
DISPLAY 'END TIME OF JUMPUP SORT ' WS-TIME-DISPLAY.
PERFORM
VARYING SUB1 FROM 1 BY 1
UNTIL SUB1 >= SORT-SIZE
COMPUTE SUB2 = SUB1 + 1
IF SORT-VALUE (SUB1) > SORT-VALUE (SUB2)
THEN
DISPLAY 'ERROR IN SORT BETWEEN ' SUB1 ' AND ' SUB2
COMPUTE SUB1 = SORT-SIZE
END-IF
END-PERFORM.
MOVE SORT-VALUES-C TO SORT-VALUES.
ACCEPT WS-TIME FROM TIME.
MOVE CORRESPONDING WS-TIME TO WS-TIME-DISPLAY.
DISPLAY ' '
DISPLAY 'START TIME OF SHELL SORT ' WS-TIME-DISPLAY.
* SHELL SORT
MOVE 10000 TO INCREMENT
PERFORM
UNTIL INCREMENT = 0
COMPUTE SUB1-START-VALUE = INCREMENT + 1
PERFORM
VARYING SUB1 FROM SUB1-START-VALUE BY 1
UNTIL SUB1 > SORT-SIZE
MOVE SUB1 TO SUB2
COMPUTE SUB2A = SUB2 - INCREMENT
MOVE SORT-VALUE (SUB1) TO SORT-TEMP
PERFORM
UNTIL SUB2 <= INCREMENT
OR SORT-VALUE (SUB2A) <= SORT-TEMP
COMPUTE SORT-VALUE (SUB2)
= SORT-VALUE (SUB2A)
COMPUTE SUB2 = SUB2 - INCREMENT
COMPUTE SUB2A = SUB2 - INCREMENT
END-PERFORM
COMPUTE SORT-VALUE (SUB2) = SORT-TEMP
END-PERFORM
IF INCREMENT > 2
THEN
COMPUTE INCREMENT = INCREMENT / 2
ELSE
ELSE
IF INCREMENT = 1
THEN
COMPUTE INCREMENT = 0
ELSE
COMPUTE INCREMENT = 1
END-IF
END-IF
END-PERFORM.
ACCEPT WS-TIME FROM TIME.
MOVE CORRESPONDING WS-TIME TO WS-TIME-DISPLAY.
DISPLAY 'END TIME OF SHELL SORT ' WS-TIME-DISPLAY.
PERFORM
VARYING SUB1 FROM 1 BY 1
UNTIL SUB1 >= SORT-SIZE
COMPUTE SUB2 = SUB1 + 1
IF SORT-VALUE (SUB1) > SORT-VALUE (SUB2)
THEN
DISPLAY 'ERROR IN SORT BETWEEN ' SUB1 ' AND ' SUB2
COMPUTE SUB1 = SORT-SIZE
END-IF
END-PERFORM.
GOBACK.
|
Timing Results of the three sort algorithrms
Code: |
. MIN VALUE =000024504 MAX VALUE =999997169 SORT SIZE =000050000
.
.START TIME OF BUBBLE SORT 16:46:01.37
.END TIME OF BUBBLE SORT 17:11:51.44
.
.START TIME OF JUMPUP SORT 17:11:51.47
.END TIME OF JUMPUP SORT 17:43:49.38
.
.START TIME OF SHELL SORT 17:43:49.41
.END TIME OF SHELL SORT 17:43:50.94
|
I?ll never use the BUBBLE sort again. The SHELL sort is not that much more complex to write and the difference in timing is significant.
Dave |
|
Back to top |
|
|
hallecodec
New User
Joined: 05 Sep 2006 Posts: 30 Location: Philippines
|
|
|
|
Thanks Dave for the information; it really help me a lot... and i'm sorry if my problem made you stay late at night... |
|
Back to top |
|
|
Arun Raj
Moderator
Joined: 17 Oct 2006 Posts: 2481 Location: @my desk
|
|
|
|
Hi Dave
Thank you so much for the information......
Thanks
Arun |
|
Back to top |
|
|
|