Hutch,
Ethan's PDQ came with source assembler source code and he had a
PDQSort in there. You might want to look at that. I'll bet it's
the assembler version of his Qsort.
Russ Srole
------------------
Announcement
Collapse
No announcement yet.
Comb Sort in PowerBASIC
Collapse
X
-
I have just got an assembler version of CombSort going and it seems
to be reliable enough in testing. It is about twice as fast as the
high level version I posted before, the main gain being in the shorter
array handling code that can be done in assembler with the swapped
values in the array.
It was easy enough to make it work ascending or descending so I
added an equate to select either direction. It is into the speed range
of being a useful algorithm but the version of Ethan Winer's Quick
Sort is just on 2 times faster and it is still in mainly high level
code so it looks like that is the next version to do some work on.
Regards and thanks to everyone who helped in this algo.
[email protected]
Code:'########################################################################## SUB CombSort(ByVal Arr as LONG,ByVal Size as LONG) ' ====================== ' 1 for ascending sort ' 0 for descending sort ' ====================== %forward = 1 ' ====================== #REGISTER NONE LOCAL Gap as LONG LOCAL eFlag as LONG LOCAL cons as DOUBLE cons = 1.3 Gap = Size ! mov esi, Arr ; address of 1st element #IF %forward ! dec Size ; comment out for reverse #ENDIF stLbl: ! fild Gap ; load integer memory operand to divide ! fdiv cons ; divide number by 1.3 ! fistp Gap ; store result back in integer memory operand ! dec Gap ! jnz ovr ! mov Gap, 1 ovr: ! mov eFlag, 0 ! mov edi, Size ! sub edi, Gap ! xor ecx, ecx ; low value index iLoop: ! mov edx, ecx ! add edx, Gap ; high value index ! mov eax, [esi+ecx*4] ; lower value ! cmp eax, [esi+edx*4] ; higher value #IF %forward ! jle iLnxt ; sort ascending #ELSE ! jge iLnxt ; sort descending #ENDIF ! mov ebx, [esi+edx*4] ; swap values ! mov [esi+edx*4], eax ! mov [esi+ecx*4], ebx ! inc eFlag iLnxt: ! inc ecx ! cmp ecx, edi ! jle iLoop ! cmp eFlag, 0 ! jg stLbl ! cmp Gap, 1 ! jg stLbl END SUB ' #########################################################################
Leave a comment:
-
-
Bob,
Thanks very much for this optimisation, this is a particularly
good place in the algo to drop an instruction. I still don't
write much FP code and I need to get the swing of how it works
a little better than I have at the moment.
Regards,
[email protected]
------------------
Leave a comment:
-
-
Originally posted by Steve Hutchesson:
! fild Gap ; load integer memory operand to divide
! fld cons ; load the 1.3 FP constant
! fdiv ; divide number by 1.3
! fist Gap ; store result back in integer memory operand
[/CODE]
[/B]
Good... But... Make it: FISTP Gap
You wouldn't want to leave the result on the npx.
Also...
! fild Gap
! fdiv Cons
! fistp Gap ; 3 ops is slightly less than 4
Regards,
Bob Zale
PowerBASIC Inc.
------------------
Leave a comment:
-
-
Keith,
Lucky that the later processors do floating point OK, I tested a
small piece of FP inline code and it seems to work fine.
Code:LOCAL cons as SINGLE Gap = 100 cons = 1.3 ! fild Gap ; load integer memory operand to divide ! fld cons ; load the 1.3 FP constant ! fdiv ; divide number by 1.3 ! fist Gap ; store result back in integer memory operand MsgBox str$(Gap),0,str$(int(100/1.3))
and trying to do integer division would kill the time so I will give this
code a try. It does the division and integer conversion in 4 instructions
so it should be OK.
Regards,
[email protected]
------------------
Leave a comment:
-
-
Hutch, Gary
You both mention the floating-point calculation in Combsort. Presumably you mean the line that calculates the next gap value. In my Fortran version it was,
Code:gap = (gap * 10) / 13 !Much faster than INT(REAL(gap) / 1.3)
I must be missing something. Please put me straight on this.
Regards
Keith
------------------
Leave a comment:
-
-
I'm another former PDQ user!
I stopped using it after I switched to PB/DOS some years ago....
It was a really good program nonetheless. If I remember correctly,
didn't Tom Hanlin also put out a QB replacement library that functioned
similarly to PDQ???
------------------
Paul Squires
www.PlanetSquires.com
<A HREF="mailto:[email protected]
">[email protected]
</A>
[This message has been edited by Paul Squires (edited September 08, 2001).]
Leave a comment:
-
-
Steve,
It's nice to run into another PDQ user! I've still got a few
products on our list that are running in DOS, written with Ethans
PDQ, PDQComm and Graphics packages. About 5 years ago I added
Blinker to my tool kit and could use overlays for some really big
programs. Too bad those days are over, but PBdll & EzGui have
replaced them very nicely.
Russ Srole
------------------
Leave a comment:
-
-
I have just ported Ethan Winer's QSort example from his book and
I am sure the results would make Ethan chuckle some. The file dates
1992 and was written for Quick Basic. This was a 10 minute port,
(its after midnight) and on the reverse order set in the array,
this one is benchmarking faster than any other I have in basic
including the version from PowerBASIC.
The results may have something to do with the data set as different
sorts appear to handle different orderings with different levels of
efficiency. I could not resist the temtation of twiddling a few bits
of it so I replaced the increments and decrements with inline assembler
and it ran about 20% faster so it is an algorithm that has potential
in the speedup area.
Regards,
[email protected]
PS Tom Hanlin, a long time ago when I used to write in Quick Basic in
DOS I used Ethan's PDQ library, as many of my own modules as I needed
and a very good library of yours that I found on a SIMTEL CD. Just on
the off chance, do you have any "screamers" floating around in your archives,
I remembered the libraries as being very good in their time.
Code:' ######################################################################### SUB QSort (Arr() as LONG,ByVal StartEl as LONG,ByVal NumEls as LONG) LOCAL I as LONG, J as LONG, Temp as LONG LOCAL StackPtr as LONG, Last as LONG, First as LONG REDIM QStack(NumEls \ 5 + 10) as LONG 'create a stack First = StartEl 'initialize work variables Last = StartEl + NumEls - 1 DO DO Temp = Arr((Last + First) \ 2) 'seek midpoint I = First J = Last DO 'reverse both < and > below to sort descending WHILE Arr(I) < Temp ! inc I WEND WHILE Arr(J) > Temp ! dec j WEND IF I > J THEN EXIT DO IF I < J THEN SWAP Arr(I), Arr(J) ! inc I ! dec j LOOP WHILE I <= J IF I < Last THEN 'Done QStack(StackPtr) = I 'Push I QStack(StackPtr + 1) = Last 'Push Last ! add StackPtr, 2 END IF Last = J LOOP WHILE First < Last IF StackPtr = 0 THEN EXIT DO ! sub StackPtr, 2 First = QStack(StackPtr) 'Pop First Last = QStack(StackPtr + 1) 'Pop Last LOOP ERASE QStack 'delete the stack array END SUB ' #########################################################################
Leave a comment:
-
-
Guest repliedHello Guys!
Here's what I have to offer. Please let me know what you think
Code:sub QuickSort(lRow as long) dim lCount as long dim lValue as long dim lTop as long dim lBot as long dim lMin as long dim lMid as long dim lMax as long lTop = lbound(ArrayData) lBot = ubound(ArrayData) asm mov eax,lTop asm push eax asm mov eax,lBot asm push eax asm inc lCount while lCount asm pop eax asm mov lBot,eax asm mov lMax,eax asm pop edx asm mov lTop,edx asm mov lMin,edx asm add eax,edx asm shr eax,1 asm mov lMid,eax asm dec lCount lValue = ArrayData(lMid) while (lMin <= lMax) while (ArrayData(lMin) < lValue) and (lMin < lBot) asm inc lMin wend while (ArrayData(lMax) > lValue) and (lMax > lTop) asm dec lMax wend if (lMin <= lMax) then rem prevent same value swapping if (ArrayData(lMin) <> ArrayData(lMax)) then rem swap data swap ArrayData(lMin),ArrayData(lMax) rem track row number if lRow = lMin then lRow = lMax:exit if if lRow = lMax then lRow = lMin:exit if end if asm inc lMin asm dec lMax end if wend if (lMin < lBot) then asm mov eax,lMin asm push eax asm mov eax,lBot asm push eax asm inc lCount end if if (lMax > lTop) then asm mov eax,lTop asm push eax asm mov eax,lMax asm push eax asm inc lCount end if wend end sub
This non-recursive quick-sort will track a given row number and also prevent same values from being sorted/flipped with every sort there after.
------------------
Cheers!
Leave a comment:
-
-
Ethan's book can now be downloaded from his site at http://www.ethanwiner.com/
------------------
Tom Hanlin
PowerBASIC Staff
Leave a comment:
-
-
Steve,
If you're interested in the quick sort routine, there is one presented
in a book by Ethan Winer, "Basic Techniques and Utilities." It not only
documents the routine in Basic, but also one written in assembly.
------------------
Leave a comment:
-
-
I may as well throw in some more sorting code....
This is a non-recursive quicksort that I have used in Visual Basic
To convert to PowerBasic you would just need to change the "optional"
parameters and make them LONGS, and remove the "IsMissing" keywords.
Code:Sub QuickSortStr(arr() As String, Optional ByVal numEls _ As Variant, Optional ByVal descending As Variant) Dim value As String, temp As String Dim sp As Integer Dim leftStk(32) As Long, rightStk(32) As Long Dim leftNdx As Long, rightNdx As Long Dim inverseOrder As Boolean Dim i As Long, j As Long ' account for optional arguments If IsMissing(numEls) Then numEls = UBound(arr) If IsMissing(descending) Then descending = False inverseOrder = (descending <> False) ' init pointers leftNdx = LBound(arr) rightNdx = numEls ' init stack sp = 1 leftStk(sp) = leftNdx rightStk(sp) = rightNdx Do If rightNdx > leftNdx Then value = arr(rightNdx) i = leftNdx - 1 j = rightNdx ' find the pivot item If descending Then Do Do: i = i + 1: Loop Until arr(i) <= value Do j = j - 1 Loop Until j = leftNdx Or arr(j) >= value temp = arr(i) arr(i) = arr(j) arr(j) = temp Loop Until j <= i Else Do Do: i = i + 1: Loop Until arr(i) >= value Do j = j - 1 Loop Until j = leftNdx Or arr(j) <= value temp = arr(i) arr(i) = arr(j) arr(j) = temp Loop Until j <= i End If ' swap found items temp = arr(j) arr(j) = arr(i) arr(i) = arr(rightNdx) arr(rightNdx) = temp ' push on the stack the pair of pointers ' that differ most sp = sp + 1 If (i - leftNdx) > (rightNdx - i) Then leftStk(sp) = leftNdx rightStk(sp) = i - 1 leftNdx = i + 1 Else leftStk(sp) = i + 1 rightStk(sp) = rightNdx rightNdx = i - 1 End If Else ' pop a new pair of pointers off the stacks leftNdx = leftStk(sp) rightNdx = rightStk(sp) sp = sp - 1 If sp = 0 Then Exit Do End If Loop End Sub
------------------
Paul Squires
www.PlanetSquires.com
mailto:[email protected]
[email protected]
</A>
Leave a comment:
-
-
Here Here, I'll go along with all that PB v OOP stuff. Who do they
think they are all of those C++ Java Smalltalk etc programmers out
there.
We should have all carried on working in Assembler, Thats where the
real power lies. Even hand assembled machine code. PB is real slow
when compared.
And to all of those people out there who think PB is the best of
both worlds, having the ability to drop down to assembler if you
want I say this,
People who write programs in OOP enabled languages like C++ think
they can use it to write procedural code in pure C. and we all know
thats total *!&$ don't we.
Regards
Keep up the good ole slagin off
Trevor Lane
------------------
Leave a comment:
-
-
Guest repliedSteve Hutchesson wrote:
Thsi is not a lot of use to programmers who are using PowerBASIC as Bob's sorting code is very fast but in MASM where I do not have an efficient sorting algorithm, this will be very useful.
I've also found the comb sort to be a decent way of sorting VIRTUAL arrays, since PowerBASIC's built-in ARRAY SORT command won't work with those. (Sure, it's not as fast as the recursive-quicksort algorithm, but it's a heck of a lot simpler, quite a lot faster than the bubble sort even with that floating-point calculation in it, and usually my arrays only consist of a few hundred elements, not millions.)
I ran across the comb sort back in the old FidoNET BBS days, on the QuickBASIC forum... and I seem to recall that, after quite a long discussion thread on the subject, we'd determined that there was no easy way to get rid of the floating-point calculation and still have the algorithm work as intended. I may have saved that thread; let me dig through my stack of old 360K floppies and check.
------------------
"Too often those in the high-tech industry view their work as an unquestionable contribution to the greater good, without regard to long-term effects on the way we all live."
--Chad Dickerson, InfoWorld CTO
Leave a comment:
-
-
Guys,
thanks for digging all of these different version up for me, if
you had seen some of the junk I have waded through to get information
on different sorting techniques, you would die laughing.
Mel,
I think the one you have posted is a Selection Sort, I posted an
assembler version in an earlier thread.
Peter,
The heapsort looks interesting, its one of the reference types and
its a pleasure to have them in basic instead of scruffy Pascal and
uncommented ANSI C.
Bruce,
Thanks for the shell sort, its another I need to have a look at. I
recently bought the three volumes by Knuth and they do contain some
good stuff but they also show how far my maths have fallen into
disuse.
The version I keep hearing about is a Quick Sort and I have a Pascal
version almost ported into PowerBASIC but its not well written,
uncommented and will need a lot of work done on it I think.
Regards,
[email protected]
------------------
Leave a comment:
-
-
Guest replied
Neat thread. I join those who would prefer that PB stay away, far away, from OOP. I have read (somewhere) that, often, really heavy duty code (like an operating system kernel) that must be efficient, is still written with C and Assembler. Please correct me if I am misinformed.
I often use a Shell sort to put small arrays in order. It appears to be very similar to the Comb sort. Some PB code is below.
I also have two 20+ year old books that were, and are, highly regarded. They each have code for several sorts, they are:
An Introduction to Database Systems, 3rd Ed.
by C.J. Date
Addison-Wesley ISBN 0-201-14471-9 Pub. 1981
The Art of Computer Programming
Volume 3 / Sorting and Searching
by Donald E. Knuth
Addison-Wesley ISBN 0-201-03803-X Pub. 1973
Here is a code fragment.
Code:TYPE ItemType Wid AS LONG Dist AS LONG END TYPE GLOBAL Item() AS ItemType, tmpItem AS ItemType DIM Item(1:500) span& = MaxItems& WHILE span& > 1 ' Shell Sort span& = span& / 2 DO Sorted& = 1 FOR lo& = 1 TO MaxItems& - span& IF Item(lo&).Wid > Item(lo& + span&).Wid THEN Sorted& = 0 tmpItem = Item(lo&) Item(lo&) = Item(lo& + span&) Item(lo& + span&) = tmpItem END IF NEXT lo& LOOP UNTIL Sorted& = 1 WEND
------------------
Leave a comment:
-
-
I use this sort algorithm, I think it's very fast. Should be easier to port to assembler I believe.
Code:'the idx array is just for indexing the main array. 'it's even simpler without it. REDIM idx(nFiles) FOR i = 1 TO nFiles idx(i) = i NEXT i ofs = nFiles \ 2 DO WHILE ofs > 0 lim = nFiles - ofs DO j = 0 FOR i = 0 TO lim IF Arr(idx(i)) > Arr(idx(i + ofs)) THEN j = i SWAP idx(i), idx(i + ofs) END IF NEXT i lim = j - ofs LOOP WHILE j ofs = ofs \ 2 LOOP
I think it's called Heapsort.
Peter.
------------------
[email protected]
Leave a comment:
-
-
Right On!!!
This makes me want to comment on Oop!s.
I Believe There has become two types of programmers;
* Those that have the tools to create an OOP, and
* Those that use the OOP's already created.
When writting in an OO language,you are limited to "it's"
Design. When writting in PowerBasic you can do "anything".
Thank God! PowerBasic hasn't gone the OO direction.
Maybe PB should be called "The High-Level Assembler".
I do believe it would boost sales, because many people
don't like the word "Basic" I guess they think it's to
elementary. It's just what I believe. B.
------------------
Leave a comment:
-
-
I didn't run the program, but I can see that it's not the most
efficient process I've run across. Each time through the loop,
the program goes through the entire array minus one. Not the
best way to go. PB's array sort, in my opinion is the best and
fastest way but if you want to create your own, try mine that I
developed several years ago on a TI-99/4A.
Assume a$() is holding the array the (I) points to the last
record in the array.
for x = 2 to i
j = x
do until a$(j) => a$(j-1) or j = 1
swap a$(j),a$(j-1)
decr j
loop
next x
This routine goes through the entire array one time. It locks on
a single record and bubbles it up to its proper position in
reference to the records above it.
I would be very interested in seeing how my sort stacks up
against yours. I have really no problem eating crow, if yours is
faster. Won't be the first time.
Cheers
Mel
------------------
Leave a comment:
-
Leave a comment: