Thread Rating:
  • 0 Vote(s) - 0 Average
  • 1
  • 2
  • 3
  • 4
  • 5
Help with hardware and software graphics
#11
(04-28-2022, 01:07 PM)bplus Wrote: Wow! you've allot going on, 1 regular looking screen and 6 screenettes! I hope you aren't redrawing the whole 7 when you update only one screenette(=tiny screen).

I suspect you have a large monitor you are doing this on.
My monitor is 24'' ... ¿redrawing the whole 7? eh... oh... glupbs... maybe this is one of the problems...  Angel

(04-28-2022, 02:51 PM)OldMoses Wrote: That looks amazing! I can't wait to see it working.
Thanks !!!

(04-28-2022, 02:58 PM)Gets Wrote:
Quote:The HARDWARE  screen is cleared every time you use DISPLAY, so you’ll need to repaste it each time you update. This can be an issue if you were sometimes only updating mini screens to save time. The SOFTWARE  page shouldn’t be cleared unless you do  it yourself, so guessing why that wouldn’t display is more difficult. Could be a DISPLAYORDER issue,maybe you used it multiple times and didn’t always include the SOFTWARE layer?  In general, you should set the DISPLAYORDER once and forget about it
The biggest question is this: I don't know how to use hardware and software screens. I would need a manual about it, because integrated help and wiki are not enough for me Sad

(04-28-2022, 09:01 PM)johnno56 Wrote: Fascinating. Using both 'Constitution' and 'Galaxy' class starships in the same game... lol

Thank you for the image. Much appreciated.

J

ps: My cpc464 died a natural death some decades ago... I now use an emulator. I actually still have the user manual... You just have to love hardcopy for reference... lol
¿'Galaxy' starship? ¿Are you saying that or maybe 'Sovereign') Big Grin Wink

It is not relevant, I only tried to show some starships in order to check how are they displayed on the screen Wink

Thanks!
IKZ
10 PRINT "Hola! Smile"
20 GOTO 10
Reply
#12
Of course for really sophisticated Star Trek graphics you need SCREEN 12 combined with SCREEN 9.

https://qb64phoenix.com/forum/showthread...white+cake

Pete
If eggs are brain food, Biden has his scrambled.

Reply
#13
Sovereign? You may be right. My eyesight is not what it used to be...
May your journey be free of incident. Live long and prosper.
Reply
#14
I'm going to bump this in the hopes someone can shed some light on the issue.

After your initial post, I decided to get some experience in working with hardware images, and I've been able to reproduce the problem that I understand you're having.

Using my billiards WIP, I converted the table and balls to hardware images and all that displays fine, but my targeting lines and strike power indicator won't display, and their remnants only show up when I escape out of the program and the hardware images are blanked. I'm left to assume that they're there, only layered underneath the hardware images, even though they are drawn after the hard images are placed. Use of _DISPLAYORDER doesn't make a difference in any combination I've tried, so I'm assuming it isn't the issue.

Code: (Select All)
$COLOR:32
$CONSOLE
'ball colors 1 yellow 2 blue 3 red 4 purple 5 orange 6 green 7 maroon 8 black
'9 yellow/s 10 blue/s 11 red/s 12 purple/s 13 orange/s 14 green/s 15 maroon/s
'_DISPLAYORDER _HARDWARE1 , _SOFTWARE '                         shows software draws no hardware
'_DISPLAYORDER _HARDWARE1 '                                     shows nothing
'_DISPLAYORDER _SOFTWARE '                                       shows software draws no hardware
'_DISPLAYORDER _SOFTWARE , _HARDWARE1 '
'_DISPLAYORDER _HARDWARE , _SOFTWARE
'_DISPLAYORDER _SOFTWARE , _HARDWARE

TYPE V2
    x AS SINGLE
    y AS SINGLE
END TYPE

TYPE ball
    sunk AS _BYTE '                                             has ball been sunk true/false
    c AS _UNSIGNED LONG '                                       ball color
    p AS V2 '                                                   position vector
    d AS V2 '                                                   direction vector
    n AS V2 '                                                   normalized direction vector
    s AS SINGLE '                                               speed
    r AS _BYTE '                                                rack position
END TYPE

TYPE pylon '                                                    pocket throat radii 2 per pocket
    'poc as _byte '                                              'pocket #
    p AS V2 '                                                   pylon position
    vert AS V2 '                                                bumper vertex
END TYPE


DIM SHARED xtable AS INTEGER '                                  x & y limits of screen/table
DIM SHARED ytable AS INTEGER
DIM SHARED xt5 AS INTEGER '                                     table border depth (5% of xtable)
DIM SHARED bsiz AS INTEGER '                                    radius of ball
DIM SHARED bsiz2 AS INTEGER '                                   ball diameter or sphere of contact
DIM SHARED psiz AS INTEGER '                                    pocket radius
DIM SHARED bl(15) AS ball '                                     ball data
DIM SHARED pl(12) AS pylon '                                    pocket throat bumpers
DIM SHARED bnum(15) AS LONG '                                   ball image handles
DIM SHARED tbl AS LONG '                                        table image handle
DIM SHARED origin AS V2 '                                       zero vector
DIM maxstrk AS INTEGER
origin.x = 0: origin.y = 0
maxstrk = 50

'Set the table size
IF _DESKTOPWIDTH > _DESKTOPHEIGHT * 1.6 THEN
    xtable = _DESKTOPWIDTH - 100: ytable = xtable / 2
ELSE
    ytable = _DESKTOPHEIGHT - 80: xtable = ytable * 2
END IF


bsiz = INT(((xtable / 118.1102) * 2.375) / 2) '                 size balls to table
_ECHO STR$(bsiz)
bsiz2 = bsiz * 2
xt5 = xtable * .05

RANDOMIZE TIMER
RESTORE hue
FOR x = 0 TO 15
    READ bl(x).c
NEXT x

SCREEN _NEWIMAGE(xtable, ytable, 32)
DO: LOOP UNTIL _SCREENEXISTS
MakeTable
MakeBalls
RackEmUp
_DEST 0
bl(0).p.y = INT(ytable * .5) '                                  position the cue
bl(0).p.x = INT(xtable * .75)

_SCREENMOVE 5, 5

DO
    CLS

    _PUTIMAGE , tbl '                                           overlay table

    FOR x% = 0 TO 15 '                                          overlay balls
        IF bl(x%).sunk THEN
            IF x% = 0 THEN
                'scratch
                bl(0).p.y = INT(ytable * .5) '                  position the cue
                bl(0).p.x = INT(xtable * .75)
            ELSE
                _CONTINUE
            END IF
        END IF
        VecAdd bl(x%).p, bl(x%).d, 1
        VecMult bl(x%).d, .99
        IF PyT(origin, bl(x%).d) < .05 THEN bl(x%).d = origin
        ColCheck x%
        _PUTIMAGE (INT(bl(x%).p.x) - _SHR(CINT(_WIDTH(bnum(x%))), 1), INT(bl(x%).p.y) - _SHR(CINT(_HEIGHT(bnum(x%))), 1)), bnum(x%)
    NEXT x%

    ms = MBS%
    IF ms AND 1 THEN
        IF (origin.x = bl(0).d.x) AND (origin.y = bl(0).d.y) THEN
            bl(0).d.x = bl(0).p.x - _MOUSEX '                   get the cue strike vector
            bl(0).d.y = bl(0).p.y - _MOUSEY
            VecNorm bl(0).d '                                   shrink it
            VecMult bl(0).d, su '                               grow it
            DO UNTIL NOT _MOUSEBUTTON(1) '                      prevents cue thrusting,
                WHILE _MOUSEINPUT: WEND '                       i.e. constant acceleration across table
            LOOP '                                              while holding down mouse button
            su = 0 '                                            reset strike units
        END IF
    END IF
    IF ms AND 2 THEN '                                          if mouse right button reset the rack
        BallStop '                                              all displacements to = origin
        bl(0).p.y = INT(ytable * .5)
        bl(0).p.x = INT(xtable * .75)
        RackEmUp
    END IF
    IF ms AND 4 THEN '                                          if mouse center button, set full strike
        IF su = maxstrk THEN su = 0
        IF su = 0 THEN su = maxstrk
    END IF
    IF ms AND 512 THEN '                                        roll mousewheel back, accelerate away from mouse cursor
        su = Limit%(maxstrk, su + 1) '                               like pulling back a pinball spring
    END IF
    IF ms AND 1024 THEN '                                       roll mousewheel frw'd, accelerate towards mouse cursor
        su = su + 1 * (su > -maxstrk) '                              helpful in aiming from table edge
    END IF

    IF (bl(0).d.x = 0) AND (bl(0).d.y = 0) THEN
        LINE (_MOUSEX, _MOUSEY)-(CINT(bl(0).p.x), CINT(bl(0).p.y))
        'slope of target line
        pathx = CINT(bl(0).p.x) - _MOUSEX: pathy = CINT(bl(0).p.y) - _MOUSEY
        LINE (bl(0).p.x, bl(0).p.y)-(pathx * 1000, pathy * 1000), Blue

        _PRINTSTRING (bl(0).p.x - 8, bl(0).p.y - 8), STR$(su)
    END IF
    _DISPLAY
    _LIMIT 100
LOOP UNTIL _KEYDOWN(27)

END

'                                                               DATA SECTION
hue:
DATA 4294967295,4294967040,4278190335,4294901760,4286578816,4294944000,4278222848,4286578688
DATA 4278190080,4294967040,4278190335,4294901760,4286578816,4294944000,4278222848,4286578688

start:
DATA 1,2,15,14,8,3,4,6,11,13,12,7,9,10,5,0

SUB B2BCollision (ball1 AS ball, ball2 AS ball)

    DIM AS V2 un, ut, ncomp1, ncomp2, tcomp1, tcomp2
    un = ball2.p: VecAdd un, ball1.p, -1: VecNorm un '          establish unit normal
    ut.x = -un.y: ut.y = un.x '                                 establish unit tangent
    bnci1 = VecDot(un, ball1.d) '                               ball 1 normal component of input velocity
    bnci2 = VecDot(un, ball2.d) '                               ball 2 normal component of input velocity
    btci1 = VecDot(ut, ball1.d) '                               ball 1 tangent component of input velocity
    btci2 = VecDot(ut, ball2.d) '                               ball 2 tangent component of input velocity

    bncx1 = bnci2 '                                             compute normal component of ball 1 exit velocity
    bncx2 = bnci1 '                                             compute normal component of ball 2 exit velocity

    ncomp1 = un: VecMult ncomp1, bncx1 '                        unit normal exit vector x normal component of exit vector ball1
    tcomp1 = ut: VecMult tcomp1, btci1 '                        unit tangent exit vector x tangent component of exit vector
    ncomp2 = un: VecMult ncomp2, bncx2 '                        same for ball2, unit normal...
    tcomp2 = ut: VecMult tcomp2, btci2 '                        same for ball2, unit tangent...

    ball1.d = ncomp1: VecAdd ball1.d, tcomp1, 1 '               add normal and tangent exit vectors
    ball2.d = ncomp2: VecAdd ball2.d, tcomp2, 1 '               add normal and tangent exit vectors

    VecMult ball1.d, .95 '                                      let's take 5% of energy in entropic factors
    VecMult ball2.d, .95

END SUB 'B2BCollision


SUB BallStop

    FOR x = 0 TO 15
        bl(x).d = origin
    NEXT x

END SUB 'BallStop


SUB ColCheck (var AS INTEGER)

    'check for ball in displacement radius
    disp = SQR(bl(var).d.x * bl(var).d.x + bl(var).d.y * bl(var).d.y) 'vector magnitude for this iteration
    FOR x = 0 TO 15 '
        IF x = var THEN _CONTINUE
        dist = PyT(bl(var).p, bl(x).p) '                calculate distance between var and x
        IF dist < bsiz2 THEN '                          are they closer than two radii, i.e. stuck together
            DIM AS V2 un
            un = bl(var).p: VecAdd un, bl(x).p, -1 '    get a normal vector between them
            VecNorm un '                                shrink it to a unit vector
            VecMult un, (bsiz2 - dist) '                grow it by the amount they intersect
            VecAdd bl(var).p, un, 1 '                   add it to the position
            'but what if a ball penetrates past the other balls center?
        END IF
        IF dist - bsiz2 < disp THEN '                   if ball x is within reach of magnitude
            disabc## = Ray_Trace##(bl(var).p, bl(var).d, bl(x).p, bsiz2)
            IF disabc## > 0 THEN '                          ray intersects ball x position
                '''still need an impact point, or balls deflect while their still out a ways
                'DIM AS ball vball, xball
                'DIM AS V2 neari
                'vball = bl(var) '                               use temporary balls for B2BCollision call
                'xball = bl(x)
                '''// near intersect quadratic returns percentage of displacement to contact point
                't## = (-B## - ((B## * B##) - 4 * A## * C##) ^ .5) / (2 * A##)
                '''// contact point- because bsiz2 is twice radius we have ball var coordinate as impact point, not
                '''// the actual surface point of impact- we may deflect the var from this point
                'neari.x = bl(var).p.x + t## * bl(var).d.x: neari.y = bl(var).p.y + t## * bl(var).d.y
                '''// now that we have a contact point, we can proceed to deflect the displacements of var and x
                '''// omitting this makes it crash readily, but we have to do something with remaining motion {1-t##} if
                '''// we retain it. We also must use that portion to move ball x
                'vball.p = neari

                B2BCollision bl(var), bl(x) 'USE THIS ALONE IN THE IF BLOCK FOR GOOD, BUT NOT MATHEMATICAL ACTION
                'B2BCollision vball, xball
                'f## = 1 - t##
                'vball.p.x = vball.p.x + f## + vball.d.x: vball.p.y = vball.p.y + f## + vball.d.y
                'bl(var) = vball
                'bl(x) = xball

            END IF '                                        end: disabc <= 0  aka ball missed
        END IF '                                            end: dist < disp test
    NEXT x

    'wall bounces - now we need to work in pocket corners which we will tentatively treat like immobile balls flanking the holes
    'LEFT/RIGHT
    IF bl(var).p.x < bsiz + xt5 OR bl(var).p.x > xtable - bsiz - xt5 THEN
        bl(var).d.x = -bl(var).d.x
        IF bl(var).p.x < bsiz + xt5 THEN '                            if beyond left edge
            bl(var).p.x = bl(var).p.x + (2 * (bsiz + xt5 - bl(var).p.x))
        END IF
        IF bl(var).p.x > xtable - bsiz - xt5 THEN '                   if beyond right edge
            bl(var).p.x = bl(var).p.x - (2 * (bl(var).p.x - (xtable - bsiz - xt5)))
        END IF
    END IF
    'TOP/BOTTOM
    IF bl(var).p.y < bsiz + xt5 OR bl(var).p.y > ytable - bsiz - xt5 THEN
        bl(var).d.y = -bl(var).d.y
        IF bl(var).p.y < bsiz + xt5 THEN '                            if beyond top edge
            bl(var).p.y = bl(var).p.y + (2 * (bsiz + xt5 - bl(var).p.y))
        END IF
        IF bl(var).p.y > ytable - bsiz - xt5 THEN '                   if beyond bottom edge
            bl(var).p.y = bl(var).p.y - (2 * (bl(var).p.y - (ytable - bsiz - xt5)))
        END IF
    END IF

END SUB 'ColCheck


SUB FCirc (CX AS INTEGER, CY AS INTEGER, RR AS INTEGER, C AS _UNSIGNED LONG, C2 AS _UNSIGNED LONG)
    DIM R AS INTEGER, RError AS INTEGER '                       SMcNeill's circle fill
    DIM X AS INTEGER, Y AS INTEGER

    R = ABS(RR)
    RError = -R
    X = R
    Y = 0
    IF R = 0 THEN PSET (CX, CY), C: EXIT SUB
    LINE (CX - X, CY)-(CX + X, CY), C, BF
    WHILE X > Y
        RError = RError + Y * 2 + 1
        IF RError >= 0 THEN
            IF X <> Y + 1 THEN
                LINE (CX - Y, CY - X)-(CX + Y, CY - X), C2, BF 'these two need white here for 9-15 balls
                LINE (CX - Y, CY + X)-(CX + Y, CY + X), C2, BF
            END IF
            X = X - 1
            RError = RError - X * 2
        END IF
        Y = Y + 1
        LINE (CX - X, CY - Y)-(CX + X, CY - Y), C, BF
        LINE (CX - X, CY + Y)-(CX + X, CY + Y), C, BF
    WEND
END SUB 'FCirc


FUNCTION Limit% (lim AS INTEGER, var AS INTEGER)

    Limit% = lim - ((var - lim) * (var < lim + 1))

END FUNCTION 'Limit%


SUB MakeBalls

    'create billiard ball hardware images
    FOR x% = 0 TO 15
        tmp& = _NEWIMAGE(bsiz * 2 + 4, bsiz * 2 + 4, 32)
        _DEST tmp&
        wd% = _SHR(_WIDTH(tmp&), 1)
        ht% = _SHR(_HEIGHT(tmp&), 1)
        IF x% = 0 THEN '                                        Cue ball
            FCirc wd%, ht%, bsiz, bl(x%).c, bl(x%).c
            CIRCLE (wd%, ht%), bsiz + 1, Black
        ELSE '                                                  Solid/stripe numbered balls
            IF x <= 8 THEN
                FCirc wd%, ht%, bsiz, bl(x%).c, bl(x%).c '      solid
            ELSE
                FCirc wd%, ht%, bsiz, bl(x%).c, White '         stripe
            END IF
            FCirc wd%, ht%, bsiz - 5, White, White '            number circle
            CIRCLE (wd%, ht%), bsiz + 1, Black '                dark outling
            n$ = _TRIM$(STR$(x%))
            t& = _NEWIMAGE(16, 16, 32)
            _DEST t&
            COLOR Black
            _PRINTMODE _KEEPBACKGROUND
            IF LEN(n$) > 1 THEN a = 0 ELSE a = 4
            _PRINTSTRING (a, 0), n$, t& '                       stamp number on ball
            _DEST tmp&
            _PUTIMAGE (8, 8)-(_WIDTH(tmp&) - 8, _HEIGHT(tmp&) - 8), t&, tmp&
            _FREEIMAGE t&
        END IF
        bnum(x%) = _COPYIMAGE(tmp&, 33)
        _FREEIMAGE tmp&
    NEXT x%

END SUB 'MakeBalls


SUB MakeTable

    'tbl = _NEWIMAGE(xtable, ytable, 32)
    '_DEST tbl
    'COLOR , &HFF007632
    'CLS
    'FOR x = 0 TO 2
    '    LINE (x, x)-(xtable - x, ytable - x), Black, B
    'NEXT x
    'FCirc xtable * .75, ytable * .5, 5, Gray, Gray
    'FCirc xtable * .75, ytable * .5, 2, White, White
    'LINE (xt5, xt5)-(xtable - xt5, ytable - xt5), &HFFFF0000, B , &HF0F0

    'DIM tablesoft&
    'tablesoft& = _NEWIMAGE(xtable, ytable, 32)
    '_DEST tablesoft&
    'COLOR , &HFF007632
    'CLS
    'FOR x = 0 TO 2
    '    LINE (x, x)-(xtable - x, ytable - x), Black, B
    'NEXT x
    'FCirc xtable * .75, ytable * .5, 5, Gray, Gray
    'FCirc xtable * .75, ytable * .5, 2, White, White
    'LINE (xt5, xt5)-(xtable - xt5, ytable - xt5), &HFFFF0000, B , &HF0F0
    '_DEST 0
    'tbl = _COPYIMAGE(tablesoft&, 33)
    '_ECHO STR$(tbl)
    '_FREEIMAGE tablesoft&
    tmp& = _COPYIMAGE(0)
    _DEST tmp&
    COLOR , &HFF007632
    CLS
    FOR x = 0 TO 2
        LINE (x, x)-(xtable - x, ytable - x), Black, B
    NEXT x
    FCirc xtable * .75, ytable * .5, 5, Gray, Gray
    FCirc xtable * .75, ytable * .5, 2, White, White
    LINE (xt5, xt5)-(xtable - xt5, ytable - xt5), &HFFFF0000, B , &HF0F0
    tbl = _COPYIMAGE(tmp&, 33)
    _FREEIMAGE tmp&

END SUB 'MakeTable


FUNCTION map! (value!, minRange!, maxRange!, newMinRange!, newMaxRange!)

    map! = ((value! - minRange!) / (maxRange! - minRange!)) * (newMaxRange! - newMinRange!) + newMinRange!

END FUNCTION 'map!


FUNCTION MBS% 'Mouse Button Status  Author: Steve McNeill
    STATIC StartTimer AS _FLOAT
    STATIC ButtonDown AS INTEGER
    STATIC ClickCount AS INTEGER
    CONST ClickLimit## = 0.2 'Less than 1/4th of a second to down, up a key to count as a CLICK.
    '                          Down longer counts as a HOLD event.
    SHARED Mouse_StartX, Mouse_StartY, Mouse_EndX, Mouse_EndY
    WHILE _MOUSEINPUT 'Remark out this block, if mouse main input/clear is going to be handled manually in main program.
        SELECT CASE SGN(_MOUSEWHEEL)
            CASE 1: tempMBS = tempMBS OR 512
            CASE -1: tempMBS = tempMBS OR 1024
        END SELECT
    WEND

    IF _MOUSEBUTTON(1) THEN tempMBS = tempMBS OR 1
    IF _MOUSEBUTTON(2) THEN tempMBS = tempMBS OR 2
    IF _MOUSEBUTTON(3) THEN tempMBS = tempMBS OR 4

    IF StartTimer = 0 THEN
        IF _MOUSEBUTTON(1) THEN 'If a button is pressed, start the timer to see what it does (click or hold)
            ButtonDown = 1: StartTimer = TIMER(0.01)
            Mouse_StartX = _MOUSEX: Mouse_StartY = _MOUSEY
        ELSEIF _MOUSEBUTTON(2) THEN
            ButtonDown = 2: StartTimer = TIMER(0.01)
            Mouse_StartX = _MOUSEX: Mouse_StartY = _MOUSEY
        ELSEIF _MOUSEBUTTON(3) THEN
            ButtonDown = 3: StartTimer = TIMER(0.01)
            Mouse_StartX = _MOUSEX: Mouse_StartY = _MOUSEY
        END IF
    ELSE
        BD = ButtonDown MOD 3
        IF BD = 0 THEN BD = 3
        IF TIMER(0.01) - StartTimer <= ClickLimit THEN 'Button was down, then up, within time limit.  It's a click
            IF _MOUSEBUTTON(BD) = 0 THEN tempMBS = 4 * 2 ^ ButtonDown: ButtonDown = 0: StartTimer = 0
        ELSE
            IF _MOUSEBUTTON(BD) = 0 THEN 'hold event has now ended
                tempMBS = 0: ButtonDown = 0: StartTimer = 0
                Mouse_EndX = _MOUSEX: Mouse_EndY = _MOUSEY
            ELSE 'We've now started the hold event
                tempMBS = tempMBS OR 32 * 2 ^ ButtonDown
            END IF
        END IF
    END IF
    MBS% = tempMBS
END FUNCTION 'MBS%


SUB PylonPosition

    'UNDER CONSTRUCTION
    'side pocket width = bsiz * 2.28
    'corner pocket width = bsiz2 * 2 throat width

    'FOR x = 1 TO 12
    'NEXT x

END SUB 'PylonPosition


FUNCTION PyT (var1 AS V2, var2 AS V2)

    PyT = _HYPOT(ABS(var1.x - var2.x), ABS(var1.y - var2.y)) '  distances and magnitudes

END FUNCTION 'PyT


SUB RackEmUp

    yoff = bsiz2 + 4
    xoff = SQR((yoff / 2) * (yoff / 2) + yoff * yoff) - 4

    RESTORE start
    FOR rank = 1 TO 5
        FOR b = 1 TO rank
            READ k
            bl(k).p.x = (.25 * xtable) - (xoff * (rank - 1))
            bl(k).p.y = (.5 * ytable) - ((rank - 1) * (.5 * yoff)) + ((b - 1) * yoff)
    NEXT b, rank

END SUB 'RackEmUp


FUNCTION Ray_Trace## (var1 AS V2, var2 AS V2, var3 AS V2, var4 AS _INTEGER64)

    'var1= ball initial position, var2= ball displacement, var3= target ball position, var4= strike radius

    'typical syntax: result = Ray_Trace##(bl(var).p, bl(var).d, bl(x).p, bsiz2)

    dx## = var2.x: dy## = var2.y '                              displacement of ball
    A## = (dx## * dx##) + (dy## * dy##) '                       displacement magnitude squared
    B## = 2 * dx## * (var1.x - var3.x) + 2 * dy## * (var1.y - var3.y)
    C## = (var3.x * var3.x) + (var3.y * var3.y) + (var1.x * var1.x) + (var1.y * var1.y) + -2 * (var3.x * var1.x + var3.y * var1.y) - (var4 * var4)
    Ray_Trace## = (B## * B##) - 4 * A## * C## ' if disabc## < 0 then no intersection =0 tangent >0 intersects two points

END FUNCTION 'Ray_Trace##


SUB VecAdd (var AS V2, var2 AS V2, var3 AS INTEGER)

    var.x = var.x + (var2.x * var3) '                           add (or subtract) two vectors defined by unitpoint
    var.y = var.y + (var2.y * var3) '                           var= base vector, var2= vector to add

END SUB 'VecAdd


FUNCTION VecDot (var AS V2, var2 AS V2)

    VecDot = var.x * var2.x + var.y * var2.y '                  get dot product of var & var2

END FUNCTION 'VecDot


SUB VecMult (vec AS V2, multiplier AS SINGLE)

    vec.x = vec.x * multiplier '                                multiply vector by scalar value
    vec.y = vec.y * multiplier

END SUB 'VecMult

SUB VecNorm (var AS V2)

    m = SQR(var.x * var.x + var.y * var.y) '                    convert var to unit vector
    var.x = var.x / m
    var.y = var.y / m

END SUB 'VecNorm
DO: LOOP: DO: LOOP
sha_na_na_na_na_na_na_na_na_na:
Reply
#15
@OldMoses could you need a well placed _Display, not sure how it works with hardware images, but when something is not showing up or is after... I always suspect a needed _Display for showing immediately.
b = b + ...
Reply
#16
Set _DisplayOrder to _Hardware,_Software and then make CLS transparent( CLS , _rgb32(0,0,0,0) ), otherwise CLS covers the background
Reply
#17
(05-01-2022, 02:38 PM)bplus Wrote: @OldMoses could you need a well placed _Display, not sure how it works with hardware images, but when something is not showing up or is after... I always suspect a needed _Display for showing immediately.

I've tried moving display around {though not sure where it might go, if not at the end of the display loop}. I've tried multiple _DISPLAYs which generally yields various weird screen flickers. I've tried defining a software image handle copy of the screen, drawing to that, then using _PUTIMAGE after the hardware images are drawn. I've tried every combination of _DISPLAYORDER that seems reasonable or even crazy to try, they usually blank out one or the other.

I tried _DISPLAYORDER _HARDWARE before drawing hardware images then switching to _SOFTWARE just before drawing the targeting elements. That resulted in hardware images occasionally flickering on a black targeting screen, then changing to full hardware displays while the cueball was moving, which makes sense given the code arrangement, which only activates targeting elements once the cueball has stopped moving.

So far, any software defined image, LINE or _PRINTSTRING command seems determined to go UNDER the hardware images.

Just as Ikerkaz indicated, there is something I'm not getting about the nature of hardware images.
DO: LOOP: DO: LOOP
sha_na_na_na_na_na_na_na_na_na:
Reply
#18
(05-01-2022, 03:41 PM)Gets Wrote: Set _DisplayOrder to _Hardware,_Software and then make CLS transparent( CLS , _rgb32(0,0,0,0) ), otherwise CLS covers the background

Ah, thanks. One that I didn't think of, I will try that.


EDIT: Thank you Gets, that turned the trick nicely. Problem solved.
DO: LOOP: DO: LOOP
sha_na_na_na_na_na_na_na_na_na:
Reply
#19
I will try your examples with _DisplayOrder soon, I have been on holidays and now I have to work Tongue

In the meantime I used the VIEW command in order to make small graphics windows, and my game has speeded up a little Smile

Thankz!
IKZ
10 PRINT "Hola! Smile"
20 GOTO 10
Reply




Users browsing this thread: 1 Guest(s)