Thread Rating:
  • 0 Vote(s) - 0 Average
  • 1
  • 2
  • 3
  • 4
  • 5
Optimize....
#1
Let's all try to optimize this piece of code I made.

Rules:

1. No rules. Just make it faster!!!

Yeah, no call absolute. *;*)

Code:
'Okay I was bored ;*)
'SetVideoSeg by Plasma357(Jon Petrosky)
'Happy coding Relsoft
'Yes, unoptimized code. ;*)


DECLARE SUB WuPixel (x!, y!, col%)
DECLARE SUB SetVideoSeg (Segment%)
DEFINT A-Z


DIM coords%(5, 1)
'$DYNAMIC


DIM SHARED Vpage(32009)  'an extra 16 bytes are needed so that the image
Vpage(6) = 2560          'can be aligned evenly on a segment (the 4 bytes for
Vpage(7) = 200           'the x and y sprite size normally throw this off, so
Layer = VARSEG(Vpage(0)) + 1  'we have to shift everything over 12 bytes

PI! = 3.141593
Radius = 40             'Radius of the circle
TiltMag = 2


CLS
SCREEN 13

FOR I = 0 TO 255
  OUT &H3C8, I
  OUT &H3C9, I \ 4
  OUT &H3C9, I \ 4
  OUT &H3C9, I \ 4
NEXT I


SetVideoSeg Layer           'Set the Drawing to the buffer
DO

    LINE (0, 0)-(319, 199), 0, BF
    F& = (F& + 1) AND &H7FFFFFFF
    x% = SIN(F& / 120) * 160
    y% = COS(F& / 150) * 100
    xlis% = x% + 160
    ylis% = y% + 100
    xlis2% = 320 - xlis%
    ylis2% = 200 - ylis%


    I = (I + TiltMag) MOD 360
    aa2! = I * PI! / 180
        FOR angle = 0 TO 359 STEP 5
            a! = angle * PI! / 180
            a2! = a! - aa2!
            a2! = a! + I * 3.14153 / 180
            x! = COS(angle * 3.141593 / 180 + a!) * Radius
            y! = SIN((x!) * 3.141593 / 180 + a2!) * Radius
            x! = COS(y! * 3.141593 / 180 + a!) * Radius
            y! = SIN((x!) * 3.141593 / 180 + a2!) * Radius
            x2! = -y!
            y2! = x!
            WuPixel xlis% + x!, ylis% + y!, 255
            WuPixel xlis% + x2!, ylis% + y2!, 255
            '''2nd
            WuPixel xlis2% + x!, ylis2% + y!, 255
            WuPixel xlis2% + x2!, ylis2% + y2!, 255

        NEXT angle

    SetVideoSeg &HA000                      'Set draw to Screen
    'WAIT &H3DA, 8
    PUT (0, 0), Vpage(6), PSET              'Blit Dbuffer
    SetVideoSeg Layer                       'Restore Draw to buffer
LOOP UNTIL INKEY$ <> ""


END

REM $STATIC
SUB SetVideoSeg (Segment) STATIC

DEF SEG

IF VideoAddrOff& = 0 THEN ' First time the sub is called

' We need to find the location of b$AddrC, which holds the graphics
' offset (b$OffC) and segment (b$SegC). Since b$AddrC is in the default
' segment, we can find it by setting it to a certain value, and then
' searching for that value.

SCREEN 13 ' Set b$SegC to A000 (00A0 in memory)
PSET (160, 100), 0 ' Set b$OffC to 7DA0 (not needed in the IDE)

FOR Offset& = 0 TO 32764 ' Search for b$AddrC, which is
IF PEEK(Offset&) = &HA0 THEN ' in the default segment and
IF PEEK(Offset& + 1) = &H7D THEN ' should have a value of
IF PEEK(Offset& + 2) = &H0 THEN ' A0 7D 00 A0.
IF PEEK(Offset& + 3) = &HA0 THEN
VideoAddrOff& = Offset& + 2 ' If we found it, record the
EXIT FOR ' offset of b$SegC and quit
END IF ' looking. (Oddly, changing
END IF ' the b$OffC doesn't seem to
END IF ' do anything, so this is why
END IF ' this sub only changes b$SegC)
NEXT

END IF

' Change b$SegC to the specified Segment

POKE VideoAddrOff&, Segment AND &HFF
POKE VideoAddrOff& + 1, (Segment AND &HFF00&) \ &H100


END SUB

SUB WuPixel (x!, y!, col)

x1 = FIX(x!)
y1 = FIX(y!)

x2 = x1 + 1
y2 = y1 + 1

xm! = x! - x1
ym! = y! - y1

xm2! = (1 - xm!)
ym2! = (1 - ym!)

c1 = xm2! * ym2! * col
c2 = xm! * ym2! * col
c3 = xm2! * ym! * col
c4 = xm! * ym! * col

PSET (x1, y1), c1
PSET (x2, y1), c2
PSET (x1, y2), c3
PSET (x2, y2), c4

END SUB
y smiley is 24 bit.
[Image: anya2.jpg]

Genso's Junkyard:
http://rel.betterwebber.com/
Reply
#2
(withdrawn)
hrist Jesus came into the world to save sinners, of whom I am first.(I Timothy 1:15)

For God so loved the world, that He gave His only begotten Son,
that whoever believes in Him should not perish, but have eternal life.(John 3:16)
Reply
#3
I replaced every floating point calculation in both the inner angle loop and in WuPixel with fixed point, then I made it use some precalculated look up tables, and yet it isn't much faster on my computer!

My computer: AMD Athlon XP 1600+ with DDR memory, nVidia GeForce4 MX 440 with DDR video memory, running in a command prompt under Windows XP Pro

Is my computer too fast for me to notice much of a difference, or do my optimizations just suck? :(

Code:
'Okay I was bored ;*)
'SetVideoSeg by Plasma357(Jon Petrosky)
'Happy coding Relsoft
'Yes, unoptimized code. ;*)
' Optimized? by Sterling Christensen


DECLARE SUB WuPixel (x&, y&, col%)
DECLARE SUB SetVideoSeg (Segment%)
DEFINT A-Z


CONST PI! = 3.141593
CONST Radius = 40             'Radius of the circle
CONST TiltMag = 2
CONST PiD180! = PI! / 180
CONST RadiusT256 = Radius * 256

'$DYNAMIC

DIM SHARED rSIN(0 TO 359) AS LONG
DIM SHARED rCOS(0 TO 359) AS LONG
FOR i = 0 TO 359
  rSIN(i) = CLNG(SIN(i * PiD180!) * RadiusT256)
  rCOS(i) = CLNG(COS(i * PiD180!) * RadiusT256)
NEXT i


DIM SHARED Vpage(32009)  'an extra 16 bytes are needed so that the image
Vpage(6) = 2560          'can be aligned evenly on a segment (the 4 bytes for
Vpage(7) = 200           'the x and y sprite size normally throw this off, so
Layer = VARSEG(Vpage(0)) + 1  'we have to shift everything over 12 bytes


CLS
SCREEN 13

FOR i = 0 TO 255
  OUT &H3C8, i
  OUT &H3C9, i \ 4
  OUT &H3C9, i \ 4
  OUT &H3C9, i \ 4
NEXT i


SetVideoSeg Layer           'Set the Drawing to the buffer
DO

    LINE (0, 0)-(319, 199), 0, BF
    F& = (F& + 1) AND &H7FFFFFFF
    x% = SIN(F& / 120) * 160
    y% = COS(F& / 150) * 100
    xlis% = x% + 160
    ylis% = y% + 100
    xlis2% = 320 - xlis%
    ylis2% = 200 - ylis%

    xlis& = xlis% * 256&
    ylis& = ylis% * 256&
    xlis2& = xlis2% * 256&
    ylis2& = ylis2% * 256&

    i = (i + TiltMag) MOD 360
    
        FOR angle = 0 TO 359 STEP 5
          
            x& = rCOS((angle + angle) MOD 360)
            a = x& \ 256 + angle + i
            IF a < 0 THEN a = 360 + a
            y& = rSIN(a MOD 360)
            a = y& \ 256 + angle
            IF a < 0 THEN a = 360 + a
            x& = rCOS(a MOD 360)
            y& = rSIN((x& \ 256 + angle + i) MOD 360)

            x2& = -y&
            y2& = x&
          
            WuPixel xlis& + x&, ylis& + y&, 255
            WuPixel xlis& + x2&, ylis& + y2&, 255
            '''2nd
            WuPixel xlis2& + x&, ylis2& + y&, 255
            WuPixel xlis2& + x2&, ylis2& + y2&, 255

        NEXT angle

    SetVideoSeg &HA000                      'Set draw to Screen
    'WAIT &H3DA, 8
    PUT (0, 0), Vpage(6), PSET              'Blit Dbuffer
    SetVideoSeg Layer                       'Restore Draw to buffer
LOOP UNTIL LEN(INKEY$)


END

REM $STATIC
SUB SetVideoSeg (Segment) STATIC

DEF SEG

IF VideoAddrOff& = 0 THEN ' First time the sub is called

' We need to find the location of b$AddrC, which holds the graphics
' offset (b$OffC) and segment (b$SegC). Since b$AddrC is in the default
' segment, we can find it by setting it to a certain value, and then
' searching for that value.

SCREEN 13 ' Set b$SegC to A000 (00A0 in memory)
PSET (160, 100), 0 ' Set b$OffC to 7DA0 (not needed in the IDE)

FOR Offset& = 0 TO 32764 ' Search for b$AddrC, which is
IF PEEK(Offset&) = &HA0 THEN ' in the default segment and
IF PEEK(Offset& + 1) = &H7D THEN ' should have a value of
IF PEEK(Offset& + 2) = &H0 THEN ' A0 7D 00 A0.
IF PEEK(Offset& + 3) = &HA0 THEN
VideoAddrOff& = Offset& + 2 ' If we found it, record the
EXIT FOR ' offset of b$SegC and quit
END IF ' looking. (Oddly, changing
END IF ' the b$OffC doesn't seem to
END IF ' do anything, so this is why
END IF ' this sub only changes b$SegC)
NEXT

END IF

' Change b$SegC to the specified Segment

POKE VideoAddrOff&, Segment AND &HFF
POKE VideoAddrOff& + 1, (Segment AND &HFF00&) \ &H100


END SUB

SUB WuPixel (x&, y&, col)

x1 = x& \ 256
y1 = y& \ 256

x2 = x1 + 1
y2 = y1 + 1

xm& = x& AND &HFF
ym& = y& AND &HFF

xm2& = (256 - xm&)
ym2& = (256 - ym&)

xmTcol& = xm& * col
xm2Tcol& = xm2& * col

c1 = (xm2Tcol& * ym2&) \ &H10000
c2 = (xmTcol& * ym2&) \ &H10000
c3 = (xm2Tcol& * ym&) \ &H10000
c4 = (xmTcol& * ym&) \ &H10000

PSET (x1, y1), c1
PSET (x2, y1), c2
PSET (x1, y2), c3
PSET (x2, y2), c4

END SUB
Reply
#4
tried poking the pixels, but no matter what i did, i'd only get overflows, and when i exe'd it and then ran it, my computer froze... :oops:
Jumping Jahoolipers!
Reply
#5
Quote:tried poking the pixels, but no matter what i did, i'd only get overflows, and when i exe'd it and then ran it, my computer froze... :oops:
Mind if I steal your idea?
Reply
#6
It's using SetVideoSeg, so... PSET would be faster, wouldn't it?
am an asshole. Get used to it.
Reply
#7
POKE is still faster than PSET even when writing to a virtual page.
Reply
#8
But you have to write to the correct address. I bet his attempt freezes 'cause he is writing to &HA000:xxxx
SCUMM (the band) on Myspace!
ComputerEmuzone Games Studio
underBASIC, homegrown musicians
[img]http://www.ojodepez-fanzine.net/almacen/yoghourtslover.png[/i
Reply
#9
Nice.

Okay would someone implement an FPS counter?


BTW, Sterling, I also tried longs but the speed is unnoticeable.

Here's what I had las night...

Longs with PSET= 76 FPS

Singles with PSET (no FFix) =64

Single with PSET(Ffixed) =190 FPS.

;*)

I made a darn cool particle demo which uses Wu Pixels but slow as hell. ;*)
y smiley is 24 bit.
[Image: anya2.jpg]

Genso's Junkyard:
http://rel.betterwebber.com/
Reply
#10
My suggestion: use a table

Code:
'Okay I was bored ;*)
'SetVideoSeg by Plasma357(Jon Petrosky)
'Happy coding Relsoft
'Yes, unoptimized code. ;*)
'Optimization suggested  by Antoni Gual:
'precalculate the Wu coefficients in a table and use integer parameters

DECLARE SUB ffix


DECLARE SUB WuPixel (x%, y%)
DECLARE SUB SetVideoSeg (Segment%)
DEFINT A-Z
ffix

DIM coords%(5, 1)
'$DYNAMIC


DIM SHARED Vpage(32009)  'an extra 16 bytes are needed so that the image
Vpage(6) = 2560          'can be aligned evenly on a segment (the 4 bytes for
Vpage(7) = 200           'the x and y sprite size normally throw this off, so
Layer = VARSEG(Vpage(0)) + 1  'we have to shift everything over 12 bytes

CONST pi = 3.141593
CONST pi180 = pi! / 180
Radius = 40            'Radius of the circle
TiltMag = 2


CLS
SCREEN 13

FOR i = 0 TO 255
  OUT &H3C8, i
  OUT &H3C9, i \ 4
  OUT &H3C9, i \ 4
  OUT &H3C9, i \ 4
NEXT i

DIM SHARED c(16, 16)
FOR i% = 0 TO 16
FOR j% = 0 TO 16
  c(i%, j%) = i% * j% * 255& / 256
NEXT
NEXT


SetVideoSeg Layer           'Set the Drawing to the buffer
t! = TIMER
DO

    LINE (0, 0)-(319, 199), 0, BF
    f& = (f& + 1) AND &H7FFFFFFF
    x% = SIN(f& / 120) * 160
    y% = COS(f& / 150) * 100
    xlis% = x% + 160
    ylis% = y% + 100
  
    xlis2% = (320 - xlis%) * 16
    ylis2% = (200 - ylis%) * 16
    xlis1% = xlis% * 16
    ylis1% = ylis% * 16


    i = (i + TiltMag) MOD 360
    aa2! = i * pi180
        FOR angle = 0 TO 359 STEP 5
            a! = angle * pi180!
            a2! = a! - aa2!
            a2! = a! + i * pi180
            x! = COS(angle * pi180 + a!) * Radius
            y! = SIN((x!) * pi180 + a2!) * Radius
            x! = COS(y! * pi180 + a!) * Radius
            y! = SIN((x!) * pi180 + a2!) * Radius
            x1% = x! * 16
            y1% = y! * 16
            x2% = -y! * 16
            y2% = x! * 16
            WuPixel xlis1% + x1%, ylis1% + y1%
            WuPixel xlis1% + x2%, ylis1% + y2%
            '''2nd
            WuPixel xlis2% + x1%, ylis2% + y1%
            WuPixel xlis2% + x2%, ylis2% + y2%

        NEXT angle

    SetVideoSeg &HA000                      'Set draw to Screen
    'WAIT &H3DA, 8
    PUT (0, 0), Vpage(6), PSET              'Blit Dbuffer
    SetVideoSeg Layer                       'Restore Draw to buffer
LOOP UNTIL INP(&H60) = 1
a$ = INKEY$
COLOR 255
PRINT f& / (TIMER - t!)
a$ = INPUT$(1)
END

REM $STATIC
SUB SetVideoSeg (Segment) STATIC

DEF SEG

IF VideoAddrOff& = 0 THEN ' First time the sub is called

' We need to find the location of b$AddrC, which holds the graphics
' offset (b$OffC) and segment (b$SegC). Since b$AddrC is in the default
' segment, we can find it by setting it to a certain value, and then
' searching for that value.

SCREEN 13 ' Set b$SegC to A000 (00A0 in memory)
PSET (160, 100), 0 ' Set b$OffC to 7DA0 (not needed in the IDE)

FOR Offset& = 0 TO 32764 ' Search for b$AddrC, which is
IF PEEK(Offset&) = &HA0 THEN ' in the default segment and
IF PEEK(Offset& + 1) = &H7D THEN ' should have a value of
IF PEEK(Offset& + 2) = &H0 THEN ' A0 7D 00 A0.
IF PEEK(Offset& + 3) = &HA0 THEN
VideoAddrOff& = Offset& + 2 ' If we found it, record the
EXIT FOR ' offset of b$SegC and quit
END IF ' looking. (Oddly, changing
END IF ' the b$OffC doesn't seem to
END IF ' do anything, so this is why
END IF ' this sub only changes b$SegC)
NEXT

END IF

' Change b$SegC to the specified Segment

POKE VideoAddrOff&, Segment AND &HFF
POKE VideoAddrOff& + 1, (Segment AND &HFF00&) \ &H100


END SUB

SUB WuPixel (x%, y%)
x1 = x% \ 16
y1 = y% \ 16

x2 = x1 + 1
y2 = y1 + 1

xm% = x% AND 15
ym% = y% AND 15

PSET (x1, y1), c(16 - xm%, 16 - ym%)
PSET (x2, y1), c(xm%, 16 - ym%)
PSET (x1, y2), c(16 - xm%, ym%)
PSET (x2, y2), c(xm%, ym%)

END SUB
Don't know how much the speed will increase, in fact a great part of the time is spent erasing the bufer and copying from buffer to screen...
Antoni
Reply


Forum Jump:


Users browsing this thread: 1 Guest(s)