Page 2 of 4

Posted: Sat Jan 24, 2004 6:19 pm
by davies
Hi,

Thanks for all the replies. Maybe I should explain my problem further...

At the moment I'm using VB for some physics simulations where all the important variables are (in VB-speak) doubles. The example I gave was very simple but essentially the simulation really does involve simple floating point calculations with the odd Sin() or Cos() thrown in. These calculations are within loops which are repeated countless millions of times.

I have been programming BASIC for 20 years and have used VB for quite a few years and am confident that I have optimised everything as far as can be done. However, the current simulations take 1 or 2 days to complete. I would like to increase the complexity of the simulation but this perhaps 10 times as many loops. Well, I could let the computer just run for 2 or 3 weeks but would prefer to have it run as quickly as possible.

Another constraint I have is that the simulations will need to be understood by undergraduate students, some of whom have only a small knowledge of computer programming. In this case I am limited to a BASIC language which compiles to give fast programmes "out of the box" without the need for tweaking of ASM.

With this in mind, would anyone have an idea on what sort of performance I would expect with PureBasic compared to VB? On some of the forums it seems that C++ programmers look down on VB due to its supposed slow speed. That makes me think that at least some other Windows BASIC langues should be faster than VB. Are there any definitive tests on mathematical function benchmarks for different flavours of BASIC.

On a related topic, would a non-Windows BASIC compiler be faster than a Windows compiler? For example, would the fastest DOS BASIC always beat the fastest Windows BASIC?

In summary, I'm looking for the fastest BASIC language whether or not it runs on Windows.

Many thanks in advance.

Posted: Sat Jan 24, 2004 7:30 pm
by dell_jockey
Reading this thread, I'm sort of getting very interested in comparing PB with 'that other' PB.
Numeric simulation is also one of my interests...

Come to think of it, since it's possible to have PB write out assembly source code files, could't we redefine the optimisation issue as a quest to find an external peep-hole assembly optimising tool.

Would such a tool be available separately or could such a tool be isolated from open source compilers, perhaps GCC ?

Posted: Sat Jan 24, 2004 11:43 pm
by Road Runner
dell_jockey,

the code compiles as follows in "the other PB"

Code: Select all

004015AC   DD05 0C544000    FLD QWORD PTR DS:[40540C]  :yy=1.000001
004015B2   DDD9             FSTP ST(1)                 
004015B4   D9E8             FLD1                       :zz=1
004015B6   DDDA             FSTP ST(2)
004015B8   C7C6 00E1F505    MOV ESI,5F5E100            :FOR xx=100000000 to 1 step-1

004015BE   DCC9             FMUL ST(1),ST              :zz=zz*yy
004015C0   FFCE             DEC ESI                    :next xx
004015C2  ^75 FA            JNZ SHORT TEMP.004015BE
Apart from needing to dump the 2 redundant values from the FPU stack (it compiles YY and ZZ as register variables which live in the FPU stack rather than memory) the code looks good to me.

Disassemble this PB's equivalent and compare for yourself.

Davies,
Another constraint I have is that the simulations will need to be understood by undergraduate students
Why should an undergraduate be able to understand BASIC better than ASM.
Simple ASM routines are easy to understand. If you want speed then you really need to program in ASM if possible, it'll beat any compiler.
PB (this one and "the other one" both have inline ASM so just use BASIC for the setting up of things & I/O and use ASM for the core of the calculations where it will benefit you most.
The calculations you need to do areprobably not as complicated as you think. The FPU includes single instructions for "simple floating point calculations" and sin & cos.

Posted: Sun Jan 25, 2004 11:42 am
by dell_jockey
Hi Road Runner,

this is what PureBasic generates:

Code: Select all

; :
; Global xx.l, yy.f, zz.f 
; 
; yy.f = 1.000001 
  MOV    dword [v_yy],1065353224
; zz.f = 1 
  MOV    dword [v_zz],1065353216
; 
; For xx.l = 1 To 100000000 
  MOV    dword [v_xx],1
_For1:
  MOV    eax,100000000
  CMP    eax,dword [v_xx]
  JL    _Next2
; zz.f = zz.f * yy.f 
  FLD    dword [v_zz]
  FMUL   dword [v_yy]
  FSTP   dword [v_zz]
; Next 
_NextContinue2:
  INC    dword [v_xx]
  JMP   _For1
_Next2:
; ExecutableFormat=Windows
; EOF
I don't know assembly well enough to make a qualified comparison, so I welcome your evaluation...

Posted: Sun Jan 25, 2004 12:15 pm
by Road Runner
dell_jockey,
in this case, the other PB wins.

Loading the variables.. pretty much the same with both.

The FP calculation..PureBASIC loses because it keeps the FP variables in memory, the other PB keeps them in the FPU.
However, at times when the other PB can't keep the variables on the FPU then the code is identical to PureBASIC.

The FOR..NEXT loop PureBASIC loses again because:
a) The other PB notices the loop variable isn't used so it counts down to 0.. saving a CMP
b) PureBASIC appears to test the loop variable at the start of the loop which needs and extra JMP in the resulting code.

There are times when PureBASIC beats the other one..but in this case, it doesn't. although, without getting a stopwatch out you might not notice the difference.

Another important point.
I think PureBASIC lacks extended precision FP variables. This may be significant in physics simulations.

Posted: Sun Jan 25, 2004 3:04 pm
by Psychophanta
RoadRunner wrote:
I think PureBASIC lacks extended precision FP variables. This may be significant in physics simulations.
"the other PB" lacks too, coz extended precision floats are intended to be 80 bit, not 64.
RoadRunner wrote:
The FOR..NEXT loop PureBASIC loses again because:
a) The other PB notices the loop variable isn't used so it counts down to 0.. saving a CMP
b) PureBASIC appears to test the loop variable at the start of the loop which needs and extra JMP in the resulting code.
You are comparing different sources.

Posted: Sun Jan 25, 2004 5:35 pm
by dell_jockey
You are comparing different sources.
Road Runner compared assembler code that was generated by both PB's using the following six lines of basic code:

Code: Select all

Global xx.l, yy.f, zz.f 

yy.f = 1.000001 
zz.f = 1 

For xx.l = 1 To 100000000 
zz.f = zz.f * yy.f 
Next 
Since both compilers apparently generate code of different quality, he was comparing different assembler sources, of course.

Also, I second Road Runner about PureBasic lacking floats that are of a higher precision than the current ones. That's why I asked about 64-bit doubles in another thread.

Real math precision and code generation quality apparently leave room for improvement. I can see that real math precision might not be all too important to game programmers but binary code quality definitely is.

Posted: Sun Jan 25, 2004 5:44 pm
by dell_jockey
For what it's worth, this is what that other PB has to offer in terms of numeric data storage and precision:
Numeric Data storage requirements and ranges

Data Type Size Decimal Range Binary Range

Integer 16 bits (2 bytes), signed -32,768 to 32,767 -2^15 to 2^15-1
Long-integer 32 bits (4 bytes), signed -2,147,483,648 to 2,147,483,647 -2^31 to 2^31-1
Quad-integer 64 bits (8 bytes), signed -9.22x10^18 to +9.22x10^18 -2^63 to 2^63-1
Byte 8 bits (1 byte), unsigned 0 to 255 0 to 2^8 -1
Word 16 bits (2 bytes), unsigned 0 to 65,535 0 to 2^16 -1
Double-word 32 bits (4 bytes), unsigned 0 to 4,294,967,295 0 to 2^32 -1

Single-precision 32 bits (4 bytes) 8.43x10^-37 to 3.40x10^38
Double-precision 64 bits (8 bytes) 4.19x10^-307 to 1.79x10^308
Extended-precision 80 bits (10 bytes) 3.4x10^-4932 to 1.2x10^4932
Currency 64 bits (8 bytes) -9.22x10^14 to +9.22x10^14
Extended-currency 64 bits (8 bytes) -9.22x10^16 to +9.22x10^16

Variant 128 bits (16 bytes) {data-dependent} {data-dependent}

Posted: Sun Jan 25, 2004 6:21 pm
by Psychophanta
dell_jockey wrote:
Road Runner compared assembler code that was generated by both PB's using the following six lines of basic code:

Code:
Global xx.l, yy.f, zz.f

yy.f = 1.000001
zz.f = 1

For xx.l = 1 To 100000000
zz.f = zz.f * yy.f
Next
That affirmation is FALSE, at least RoadRunner lied when said:
the code compiles as follows in "the other PB"
Code:
004015AC DD05 0C544000 FLD QWORD PTR DS:[40540C] :yy=1.000001
004015B2 DDD9 FSTP ST(1)
004015B4 D9E8 FLD1 :zz=1
004015B6 DDDA FSTP ST(2)
004015B8 C7C6 00E1F505 MOV ESI,5F5E100 :FOR xx=100000000 to 1 step-1

004015BE DCC9 FMUL ST(1),ST :zz=zz*yy
004015C0 FFCE DEC ESI :next xx
004015C2 ^75 FA JNZ SHORT TEMP.004015BE

Posted: Sun Jan 25, 2004 7:02 pm
by dell_jockey
Psychophanta,
That affirmation is FALSE, at least RoadRunner lied when said:
Please substantiate! A mere statement like that has no merit.

Posted: Sun Jan 25, 2004 7:09 pm
by syntax error
Would somebody care to test this HeapSort code and see what speed they get?

I have tested the same routine in two languages and get these results:

NOTE: Used 10000 items to sort

IBasic = 5266 m/secs
BlitzPlus = 42 m/secs

PUREBASIC VERSION

Code: Select all

; PureBasic heapsort demo

Declare.l hsort(numitems)
Declare.l heapify(hleft,hright)
Declare.l swap(ij,ik)

OpenConsole()
maxsize.l=0
Print("Number of items to sort: ")
maxsize=Val(Input())
Dim testarray$(maxsize)
Print("generating a random array with "+ Str(maxsize) + " elements ...")

; fill an array with random characters -- array generator by David 
For i = 1 To MaxSize-1  
 char1= Int(Random(26)+65)  
 a$ = Chr$(char1)   
 b$ = ""  
 While Len(b$) < Int(Random(4)) + 4
  char2 = Int(Random(26)+95)  
  b$ = b$+Chr$(char2)  
  Wend  
 rndStr$ = a$ + b$  
 testarray$(i) = rndStr$  
Next

starttime=GetTickCount_()
hsort(maxsize-1)
totaltime=GetTickCount_()-starttime

For i = 1 To maxsize-1 
 Print(testarray$(i)+",")
Next

Print("")
Print("_______________________________________________")
Print("Sorted "+ Str(maxsize)+" items in "+Str(totaltime)+" milliseconds")
Input()
CloseConsole()

End 

;'----------------------------------------------- 

Procedure.l hsort(numitems) 
 ; first phase -- build heap 
 ix=Int(numitems/2) 
 While (ix >= 1) 
  heapify(ix,numitems)
  ix=ix-1 
 Wend
 ; second phase -- put largest at end of array, 
 ; use heapify to grab the next remaining largest 
 ix = numitems  
 While (ix > 1)
  swap(1,ix)
  heapify(1,ix-1)
  ix=ix-1
 Wend
EndProcedure

;'----------------------------------------------- 

; instill heap condition 
Procedure.l heapify(hleft,hright) 
 ip = hleft 
 ic = 2*ip 
 While (ic <= hright) 
  If (ic < hright) And (testarray$(ic+1) > testarray$(ic))
    ic = ic + 1 
   EndIf
  If (testarray$(ip) < testarray$(ic))
    swap(ic,ip)
  EndIf
  ip = ic 
  ic=2*ip 
 Wend
EndProcedure

; ------------------------------------------------ 

Procedure.l swap(ij,ik) 
 t$=testarray$(ij): testarray$(ij)=testarray$(ik): testarray$(ik)=t$
EndProcedure

Posted: Sun Jan 25, 2004 7:09 pm
by syntax error
BLITZPLUS VERSION

Code: Select all

; Blitz heapsort demo

maxsize%=0

maxsize%=Input("Number of items to sort: ")
Dim testarray$(maxsize)
Print "generating a random array with "+maxsize+" elements ..."

; fill an array with random characters -- array generator by David 
For i = 1 To MaxSize-1  
	char1= Int(Rnd(26)+65)  
	a$ = Chr$(char1)   
	b$ = ""  
	While Len(b$) < Int(Rnd(4)) + 4
		char2 = Int(Rnd(26)+95)  
		b$ = b$+Chr$(char2)  
 	Wend  
	rndStr$ = a$ + b$  
	testarray$(i) = rndStr$  
Next
 
starttime=MilliSecs()
hsort maxsize-1
totaltime=MilliSecs()-starttime

For i = 1 To maxsize-1 
	Write testarray$(i)+","
Next
Print ""
Print  "_______________________________________________"
Print "Sorted "+maxsize+" items in "+totaltime+" milliseconds"
 
Input
End 
 
;'----------------------------------------------- 
Function hsort(numitems) 
	; first phase -- build heap 
	ix=Int(numitems/2) 
	While (ix >= 1) 
		heapify ix,numitems
		ix=ix-1 
	Wend
 	; second phase -- put largest at end of array, 
	; use heapify to grab the next remaining largest 
	ix = numitems  
	While (ix > 1)
		swap 1,ix
		heapify 1,ix-1
		ix=ix-1
	Wend
End Function
 
;'----------------------------------------------- 
; instill heap condition 
Function heapify(hleft,hright) 
	ip = hleft 
	ic = 2*ip 
	While (ic <= hright) 
		If (ic < hright) And (testarray$(ic+1) > testarray$(ic)) Then ic = ic + 1 
		If (testarray$(ip) < testarray$(ic)) Then swap ic,ip
		ip = ic 
		ic=2*ip 
	Wend
End Function
 
; ------------------------------------------------ 
Function swap(ij,ik) 
	t$=testarray$(ij): testarray$(ij)=testarray$(ik): testarray$(ik)=t$
End Function

Posted: Sun Jan 25, 2004 7:11 pm
by syntax error
IBASIC VERSION

Code: Select all

'iBasic heapsort demo 
DEF i:INT 
DECLARE hsort(A[]:STRING,inr:INT) 
DECLARE heapify(A[]:STRING,hleft:INT,hright:INT) 
DECLARE swap(A[]:STRING,ij:INT,ik:INT) 
Declare "kernel32", GetTickCount(),int  
 
def maxsize:int  
OPENCONSOLE 
INPUT "Number of items to sort: ",maxsize 
def testarray[maxsize]:string  
print "generating a random array with ",maxsize," elements"  
' fill an array with random integers -- array generator by David 
for i = 1 to MaxSize-1  
 a = int(rnd(26)+65)  
 a$ = chr$(a)   
 b$ = ""  
 while len(B$) < int(rnd(4)) + 4  
  b = int(rnd(26)+97)  
  b$ = b$+chr$(b)  
 endwhile  
rndStr$ = a$ + b$  
testarray[i] = rndStr$  
next i  
 
aa = gettickcount() 
hsort(testarray,maxsize-1) 
bb = gettickcount() 
FOR i = 1 TO maxsize-1 
PRINT testarray[i],",", 
NEXT i 
PRINT  
print "Sorted ",maxsize,"items in ",(bb-aa)," milliseconds" 
 
DO 
UNTIL INKEY$ <> "" 
CLOSECONSOLE 
END 
 
'----------------------------------------------- 
SUB hsort(A[],inr) 
DEF ix:INT 
 
'first phase -- build heap 
ix=INT(inr/2) 
WHILE (ix >= 1) 
 heapify(A,ix,inr) 
 ix=ix-1 
ENDWHILE 
 
'second phase -- put largest at end of array, 
'use heapify to grab the next remaining largest 
ix = inr  
WHILE (ix > 1) 
 swap(A,1,ix) 
 heapify(A,1,ix-1) 
 ix=ix-1 
ENDWHILE 
RETURN 
 
'----------------------------------------------- 
'instill heap condition 
SUB heapify(A[],hleft,hright) 
DEF ic,ip:INT 
ip = hleft 
ic = 2*ip 
WHILE (ic <= hright) 
 IF (ic < hright) & (A[ic+1] > A[ic]) THEN ic = ic + 1 
 IF (A[ip] < A[ic]) THEN swap(A,ic,ip) 
 ip = ic 
 ic=2*ip 
ENDWHILE 
RETURN 
 
'------------------------------------------------ 
SUB swap(A[],ij,ik) 
DEF t:STRING 
t=A[ij]: A[ij]=A[ik]: A[ik]=t 
RETURN 

Posted: Sun Jan 25, 2004 7:14 pm
by Rings
sometimes it is better to sell vegetables to a customer instead of comparing apples and pears .

but all these discussions produce homework for fred :)

Posted: Sun Jan 25, 2004 7:27 pm
by Psychophanta
sometimes it is better to sell vegetables to a customer instead of comparing apples and pears
:lol:
but all these discussions produce homework for fred
and headache for sure :arrow:

Dell_Jockey; sorry, i thought you would see it inmediatly. I explain:
Is it for you "For xx.l = 1 To 100000000" same than "FOR xx=100000000 to 1 step-1" :!: :?: