QB64 Phoenix Edition
Angle Collisions - Printable Version

+- QB64 Phoenix Edition (https://qb64phoenix.com/forum)
+-- Forum: QB64 Rising (https://qb64phoenix.com/forum/forumdisplay.php?fid=1)
+--- Forum: Code and Stuff (https://qb64phoenix.com/forum/forumdisplay.php?fid=3)
+---- Forum: Help Me! (https://qb64phoenix.com/forum/forumdisplay.php?fid=10)
+---- Thread: Angle Collisions (/showthread.php?tid=972)

Pages: 1 2 3 4 5 6 7 8 9 10


RE: Angle Collisions - bplus - 10-22-2022

(10-22-2022, 10:29 PM)james2464 Wrote: Yeah I think the math is there now, but programming is a different story.  So far I've failed to get this to work.  The bounces sometimes go in the wrong direction, the ball goes through the line sometimes.  The problem seems to be that the calculations are sometimes using wrong info, backwards +/- values etc so I'll need to sort all that out.   One thing I'll be thrilled to get right is breaking up a frame.   Sometimes the ball is moving at say 10 pixels per frame and it could go past the line by 7 pixels for example.  I'd like to somehow correctly break that into two parts so that the ball bounces back those 7 pixels in the new direction.   If that makes sense.

Makes absolute sense and backing a ball up is easy if you maintain a variable for the ball heading, say ba (in radians to avoid conversions for sin and cos)

Then
Code: (Select All)
while (intersect is reported as true) ' back up ball
   bx = bx + ballSpeed * cos(ba - pi)  ' reversed ball heading = ba +- pi
   by = by + ballSpeed * sin(ba - pi)  ' ditto
wend

On old games of Ping Pong, Break Out, Air Hockey, maybe even Pool, I did not back up balls making that old code less than perfect.
I use to add dx and dy to ball location and if that was beyond a boundary I'd just move the ball back inside the boundary x, or y not both (wrong) and then just change dx = -dx for left and right side and dy = -dy for upper or lower boundary. It works but crude.

Also never make ballSpeed > ball radius for best result max ball speed = .5 * ball radius, that way ball doesn't jump past any obstacle like a wall that is supposed to stop it.

Here is how I use to code bouncing a ball around inside a rectangular frame:
Code: (Select All)
Option _Explicit
_Title "Standard Reflection in a Rectangle Container, spacebar to restart" ' b+ 2022-10-21
' A quick demo of the wrong way I was doing bouncing balls and circles on rectangular borders
' Air Hockey, Ping Pong, Break Out games

Screen _NewImage(800, 600, 32)
_ScreenMove 250, 50
Randomize Timer
Dim Top, Left, Bottom, Right ' borders for rectangle
Top = 10: Bottom = _Height - 10: Left = 10: Right = _Width - 10
Dim x, y, r, a, speed, dx, dy ' for ball x, y position moving with heading a and speed so dx, dy with radius r
Dim i
restart:
x = _Width / 2: y = _Height / 2: speed = 5
r = 15 ' make ball radius (br) at least 2* speed
a = Rnd * _Pi(2) ' setup up ball in middle of screen/container random heading = ba (ball angle)
dx = speed * Cos(a): dy = speed * Sin(a)
Color &HFFFFFFF, &HFF008844
Do
    Cls
    Line (Left, Top)-(Right, Bottom), &HFF000000, BF
    For i = 0 To r Step .25
        Circle (x, y), i, &HFFFFFFFF
    Next
    x = x + dx ' test x, y is new ball position if dont run into wall
    If x < Left + r Then x = Left + r: dx = -dx
    If x > Right - r Then x = Right - r: dx = -dx
    y = y + dy
    If y < Top + r Then y = Top + r: dy = -dy
    If y > Bottom - r Then y = Bottom - r: dy = -dy
    _Display
    _Limit 60
Loop Until _KeyDown(27) Or _KeyDown(32)
If _KeyDown(32) Then GoTo restart



RE: Angle Collisions - justsomeguy - 10-22-2022

Not sure if it will help, but I wrote a Pool Game a while back using a 2d physics engine I ported to QB from Randy Gaul's Impulse Engine.

I'm sure you want to do it yourself, but It might give you some ideas on how attack certain problems. I'm no expert on the math, but If you have questions, I'd be happy to help.


RE: Angle Collisions - Pete - 10-23-2022

I need to have a look at it after I get this parsing project finished. The jpeg looks amazing.

Pete


RE: Angle Collisions - OldMoses - 10-23-2022

A while back I found a ray tracing function for 3D vectors that I used to check for spacecraft/planet collisions. By chopping out the Z axis stuff, I got it a little smaller and working for a 2D screen. Detects when a circle/ball in question; of a certain radius, touches or intersects a line in question. Needed are the start and end points of a line, a circle center position and radius.

Maybe useful, maybe not.

EDIT: Ah, turns out it's not. It's for infinite rays crossing the ball, rather than a ball intersecting lines. Changing ball4.y to 350 reveals the issue

Code: (Select All)
'Intersection test

'Up & down arrows change the radius of balls 1 - 3
'left and right arrows move ball 4 across its line

TYPE V2
    x AS SINGLE
    y AS SINGLE
END TYPE
DIM radius AS INTEGER
radius = 25

DIM AS V2 ball1, ball2, ball3, ball4, line1s, line1e, line2s, line2e, line3s, line3e, line4s, line4e
ball1.x = 50: ball1.y = 200
line1s.x = 100: line1s.y = 25
line1e.x = 100: line1e.y = 300
ball2.x = 150: ball2.y = 200
line2s.x = 175: line2s.y = 25
line2e.x = 175: line2e.y = 300
ball3.x = 300: ball3.y = 200
line3s.x = 310: line3s.y = 25
line3e.x = 310: line3e.y = 300
ball4.x = 50: ball4.y = 450
line4s.x = 200: line4s.y = 350
line4e.x = 400: line4e.y = 550


SCREEN _NEWIMAGE(800, 600, 32)
DO
    CLS
    IF _KEYDOWN(20480) THEN radius = radius - 1
    IF _KEYDOWN(18432) THEN radius = radius + 1
    IF _KEYDOWN(19200) THEN ball4.x = ball4.x - 1
    IF _KEYDOWN(19712) THEN ball4.x = ball4.x + 1

    IF Intersect(line1s, line1e, ball1, radius) < 0 THEN c& = &HFF00FF00 ELSE c& = &HFFFF0000
    CIRCLE (ball1.x, ball1.y), radius, c&
    LINE (line1s.x, line1s.y)-(line1e.x, line1e.y), c&

    IF Intersect(line2s, line2e, ball2, radius) < 0 THEN c& = &HFF00FF00 ELSE c& = &HFFFF0000
    CIRCLE (ball2.x, ball2.y), radius, c&
    LINE (line2s.x, line2s.y)-(line2e.x, line2e.y), c&

    IF Intersect(line3s, line3e, ball3, radius) < 0 THEN c& = &HFF00FF00 ELSE c& = &HFFFF0000
    CIRCLE (ball3.x, ball3.y), radius, c&
    LINE (line3s.x, line3s.y)-(line3e.x, line3e.y), c&

    IF Intersect(line4s, line4e, ball4, 30) < 0 THEN c& = &HFF00FF00 ELSE c& = &HFFFF0000
    CIRCLE (ball4.x, ball4.y), 30, c&
    LINE (line4s.x, line4s.y)-(line4e.x, line4e.y), c&

    _DISPLAY
    _LIMIT 30
LOOP UNTIL _KEYDOWN(27)
END

FUNCTION Intersect (lsrt AS V2, lend AS V2, bpos AS V2, rd AS INTEGER)
    dx! = lend.x - lsrt.x: dy! = lend.y - lsrt.y
    A## = dx! * dx! + dy! * dy!
    B## = 2 * dx! * (lsrt.x - bpos.x) + 2 * dy! * (lsrt.y - bpos.y)
    C## = (bpos.x * bpos.x) + (bpos.y * bpos.y) + (lsrt.x * lsrt.x) + (lsrt.y * lsrt.y) + -2 * (bpos.x * lsrt.x + bpos.y * lsrt.y) - (rd * rd)
    Intersect = (B## * B##) - 4 * A## * C##
    'if Intersect < 0 then no intersection; if = 0 then tangent; if > 0 then intersection
END FUNCTION



RE: Angle Collisions - james2464 - 10-24-2022

Making some progress.   I worked out the line endpoint collisions, and I'm in the process of sorting out the side collisions.  Some things don't quite add up.  The endpoints work really well - when rotating the line with the mouse wheel,  you can kind of make the ball go where you want.

Code: (Select All)
'vector reflection and line detection demo
'james2464

Dim Shared scx, scy As Integer
scx = 800: scy = 600
Screen _NewImage(scx, scy, 32)

Const PI = 3.141592654#

Dim Shared x, y, h, xv, yv, ndpx, ndpy, rx, ry
Dim Shared cpa, cpb, a, b, a2, b2, xx, yy

Dim Shared c(10) As Long
c(0) = _RGB(30, 30, 30)
c(1) = _RGB(255, 255, 255)
c(2) = _RGB(255, 255, 0)
c(3) = _RGB(255, 0, 0)
c(4) = _RGB(0, 255, 0)
c(5) = _RGB(0, 255, 255)
c(6) = _RGB(255, 0, 255)

'location of wall center point
xx = 400
yy = 300
na = 45 'wall starting angle (mouse wheel controlled)
wlen = 150 'wall length - each half
ballrad = 40 'ball radius

xv = 1.5 'ball x velocity
yv = -3.5 'ball y velocity
sbx = 200 'starting x position
sby = 200 'starting y position

flag = 0
message = 0
Do

    _Limit 50
    Cls

    '=====================================================
    mouseclick1 = 0
    _MouseHide
    Do While _MouseInput
        na = na + _MouseWheel * 2
    Loop
    mx% = _MouseX
    my% = _MouseY
    If mx% < 0 Then mx% = 0
    If mx% > scx Then mx% = scx
    If my% < 0 Then my% = 0
    If my% > scy Then my% = scy
    lc% = _MouseButton(1)
    rc% = _MouseButton(2)
    If lc% = -1 Then mouseclick1 = 1
    If rc% = -1 Then mouseclick2 = 1

    'sbx = mx%: sby = my% 'ball controlled by mouse
    sbx = sbx + xv
    sby = sby + yv
    If sbx > (scx - ballrad) Then
        xv = xv * -1
        t = sbx - (scx - ballrad)
        sbx = sbx - t
    End If
    If sby > (scy - ballrad) Then
        yv = yv * -1
        t = sby - (scy - ballrad)
        sby = sby - t
    End If
    If sbx < ballrad Then
        xv = xv * -1
        t = ballrad - sbx
        sbx = sbx + t
    End If
    If sby < ballrad Then
        yv = yv * -1
        t = ballrad - sby
        sby = sby + t
    End If


    '=====================================================
    'origin lines
    'Line (0, yy)-(800, yy), c(0)
    'Line (xx, 0)-(xx, 600), c(0)

    '=====================================================
    Circle (sbx, sby), (ballrad - 1), c(2) 'screen location of ball
    x = sbx - xx: y = 0 - sby + yy 'location relative to wall
    'Locate 1, 1
    'Print na, x, y
    h = (_Hypot(-x, y))

    '=====================================================
    nx = Cos(na * (PI / 180)) 'normalize wall angle
    ny = Sin(na * (PI / 180)) 'normalize wall angle

    dx = -x * ny * -1: dy = y * nx: ndp = dx + dy
    'dot product V.N - used to find distance of N
    'The distance of N is from the point of collision to the middle of line A
    'line A is a line from point I to point R (parallel to the angled wall)

    ndpx = Sin(na * (PI / 180)) * ndp
    ndpy = Cos(na * (PI / 180)) * ndp


    sidecollisionpoint



    '=====================================================
    'angled wall
    a = (Sin(na * .017453292)) * wlen
    b = (Cos(na * .017453292)) * wlen
    a2 = a * -1: b2 = b * -1


    c(9) = c(1)

    'find length of line A
    segx = Abs(x - rx)
    segy = Abs((yy - y) - (yy + ry))
    sega = _Hypot(segx, segy)

    'find distance from point I to wall endpoints
    i2w1x = Abs(x - b)
    i2w1y = Abs(a + y)
    i2w2x = Abs(x + b)
    i2w2y = Abs(y - a)

    i2wh1 = _Hypot(i2w1x, i2w1y)
    i2wh2 = _Hypot(i2w2x, i2w2y)

    If i2wh1 < i2wh2 Then 'determine which end the ball is closer to
        i2ws = 1: i2w = i2wh1
    Else
        i2ws = 2: i2w = i2wh2
    End If

    If sega < (wlen * 2) Then
        If Abs(ndp) <= ballrad Then '                                          *****  collision with side of the line  *****
            c(9) = c(3) 'if beside the wall, just check length of line N
            collisionpointa = (Sin(na * .017453292)) * (sega / 2)
            collisionpointb = (Cos(na * .017453292)) * (sega / 2)
            If i2ws = 1 Then
                cpa = yy + collisionpointa: cpb = xx + collisionpointb
            End If
            If i2ws = 2 Then
                cpa = yy - collisionpointa: cpb = xx - collisionpointb
            End If
            Locate 3, 1
            Print "                      i2ws"; i2ws
            Circle (cpb, cpa), 5, c(4) 'circle the collision point
            sidecollisionvector
        End If
    Else
        If i2w <= ballrad Then '                                              *****  collision with endpoint of the line  *****
            c(9) = c(3)

            If i2ws = 1 Then
                cpa = yy - a2: cpb = xx + b
                endpointcollision1
            End If

            If i2ws = 2 Then
                cpa = yy - a: cpb = xx + b2
                endpointcollision2
            End If

            Circle (cpb, cpa), 5, c(4) 'circle the collision point
        End If
    End If

    '==========================================================================================


    Line (xx, yy)-(xx + b, yy + a), c(9) 'angled wall (collision with ball changes colour)
    Line (xx, yy)-(xx - b, yy - a), c(9) 'angled wall (collision with ball changes colour)


    If mouseclick1 = 1 Then 'show geometry lines
        If sega <= (wlen * 2) Then
            Line (cpb, cpa)-(cpb - xv * 80, cpa - yv * 80), c(2) 'collision to point I
            'Line (cpb + x, cpa - y)-(cpb + rx, cpa + ry), c(4) 'line A
            Line (cpb, cpa)-(cpb + rx, cpa + ry), c(3) 'collision to point R

            Line (cpb, cpa)-(cpb + ndpx, cpa - ndpy), c(5) 'line N
        End If
        If sega > (wlen * 2) Then
            If i2ws = 1 Then
                Line (xx + x, yy - y)-(xx + b, yy + a), c(6) 'endpoint collision line
            End If
            If i2ws = 2 Then
                Line (xx + x, yy - y)-(xx - b, yy - a), c(6) 'endpoint collision line
            End If
        End If
        message = 1
    End If


    If message = 0 Then
        Locate 1, 1
        Print "Left click to show lines"
        Print "Scroll mouse wheel to rotate"
    End If

    _Display
    If mouseclick2 = 1 Then flag = 1

Loop Until flag = 1


Sub sidecollisionpoint
    'calculate point R
    th1 = _Atan2(-y, x) 'radian value of ball (point I)
    'th1 = _Atan2(-yv, xv)
    th2 = _Atan2(-ndpy, ndpx) 'radian value of line N
    thd = th1 - th2 'find difference
    th3 = th2 - thd 'subtract difference from line N
    rx = Cos(th3) * h: ry = Sin(th3) * h 'point R position - th3 * length of point I to collision point
End Sub


Sub sidecollisionvector
    tx = xv: ty = yv: th = _Hypot(tx, ty)
    tx2 = tx / th: ty2 = ty / th
    spd = _Hypot(tx, ty) 'speed of existing motion vector
    th1 = _Atan2(tx, -ty) 'radian value of motion vector
    th2 = _Atan2(-ndpy, ndpx) 'radian value of line N
    thd = th1 - th2 'find difference
    th3 = th2 - thd 'subtract difference from line N
    newxv = Cos(th3): newyv = Sin(th3)
    xv = newxv * spd: yv = newyv * spd * -1
End Sub

Sub endpointcollision1
    tx = x - b: ty = y - a2: th = _Hypot(tx, ty)
    tx2 = tx / th: ty2 = ty / th
    txv = Abs(xv): tyv = Abs(yv): spd = _Hypot(txv, tyv)
    xv = tx2 * spd: yv = ty2 * spd * -1
End Sub


Sub endpointcollision2
    tx = x - b2: ty = y - a: th = _Hypot(tx, ty)
    tx2 = tx / th: ty2 = ty / th
    txv = Abs(xv): tyv = Abs(yv): spd = _Hypot(txv, tyv)
    xv = tx2 * spd: yv = ty2 * spd * -1
End Sub



RE: Angle Collisions - james2464 - 10-24-2022

After finding some mistakes in the reflection subroutine, this finally works as intended.   Other than so far I haven't done any frame splitting.   But the line seems to be doing the proper job of reflecting the ball at any angle - unless rotating the line at the same time it's colliding, then it errors out a bit.  I suppose I could disable the mouse during the collisions.


Code: (Select All)
'vector reflection and line detection demo
'james2464

Dim Shared scx, scy As Integer
scx = 800: scy = 600
Screen _NewImage(scx, scy, 32)

Const PI = 3.141592654#

Dim Shared x, y, h, xv, yv, ndpx, ndpy, rx, ry
Dim Shared cpa, cpb, a, b, a2, b2, xx, yy

Dim Shared c(10) As Long
c(0) = _RGB(30, 30, 30)
c(1) = _RGB(255, 255, 255)
c(2) = _RGB(255, 255, 0)
c(3) = _RGB(255, 0, 0)
c(4) = _RGB(0, 255, 0)
c(5) = _RGB(0, 255, 255)
c(6) = _RGB(255, 0, 255)

'location of wall center point
xx = 400
yy = 300
na = 44 'wall starting angle (mouse wheel controlled)
wlen = 150 'wall length - each half
ballrad = 40 'ball radius

xv = 1. 'ball x velocity
yv = 2. 'ball y velocity
sbx = 200 'starting x position
sby = 200 'starting y position

flag = 0

Do

    _Limit 100
    Cls
    Line (1, 1)-(scx - 1, scy - 1), c(1), B 'screen border

    '=====================================================
    mouseclick1 = 0
    _MouseHide
    Do While _MouseInput
        na = na + _MouseWheel * 2
    Loop
    mx% = _MouseX
    my% = _MouseY
    If mx% < 0 Then mx% = 0
    If mx% > scx Then mx% = scx
    If my% < 0 Then my% = 0
    If my% > scy Then my% = scy
    lc% = _MouseButton(1)
    rc% = _MouseButton(2)
    If lc% = -1 Then mouseclick1 = 1
    If rc% = -1 Then mouseclick2 = 1

    'sbx = mx%: sby = my% 'ball controlled by mouse
    sbx = sbx + xv
    sby = sby + yv
    If sbx > (scx - ballrad) Then
        xv = xv * -1
        t = sbx - (scx - ballrad)
        sbx = sbx - t
    End If
    If sby > (scy - ballrad) Then
        yv = yv * -1
        t = sby - (scy - ballrad)
        sby = sby - t
    End If
    If sbx < ballrad Then
        xv = xv * -1
        t = ballrad - sbx
        sbx = sbx + t
    End If
    If sby < ballrad Then
        yv = yv * -1
        t = ballrad - sby
        sby = sby + t
    End If


    '=====================================================
    'origin lines
    'Line (0, yy)-(800, yy), c(0)
    'Line (xx, 0)-(xx, 600), c(0)

    '=====================================================
    Circle (sbx, sby), (ballrad - 1), c(2) 'screen location of ball
    x = sbx - xx: y = 0 - sby + yy 'location relative to wall
    'Locate 1, 1
    'Print na, x, y
    h = (_Hypot(-x, y))

    '=====================================================
    nx = Cos(na * (PI / 180)) 'normalize wall angle
    ny = Sin(na * (PI / 180)) 'normalize wall angle

    dx = -x * ny * -1: dy = y * nx: ndp = dx + dy
    'dot product V.N - used to find distance of N
    'The distance of N is from the point of collision to the middle of line A
    'line A is a line from point I to point R (parallel to the angled wall)

    ndpx = Sin(na * (PI / 180)) * ndp
    ndpy = Cos(na * (PI / 180)) * ndp


    sidecollisionpoint



    '=====================================================
    'angled wall
    a = (Sin(na * .017453292)) * wlen
    b = (Cos(na * .017453292)) * wlen
    a2 = a * -1: b2 = b * -1


    c(9) = c(1)

    'find length of line A
    segx = Abs(x - rx)
    segy = Abs((yy - y) - (yy + ry))
    sega = _Hypot(segx, segy)

    'find distance from point I to wall endpoints
    i2w1x = Abs(x - b)
    i2w1y = Abs(a + y)
    i2w2x = Abs(x + b)
    i2w2y = Abs(y - a)

    i2wh1 = _Hypot(i2w1x, i2w1y)
    i2wh2 = _Hypot(i2w2x, i2w2y)

    If i2wh1 < i2wh2 Then 'determine which end the ball is closer to
        i2ws = 1: i2w = i2wh1
    Else
        i2ws = 2: i2w = i2wh2
    End If

    If sega < (wlen * 2) Then
        If Abs(ndp) <= ballrad Then '                                          *****  collision with side of the line  *****
            c(9) = c(3) 'if beside the wall, just check length of line N
            collisionpointa = (Sin(na * .017453292)) * (sega / 2)
            collisionpointb = (Cos(na * .017453292)) * (sega / 2)
            If i2ws = 1 Then
                cpa = yy + collisionpointa: cpb = xx + collisionpointb
            End If
            If i2ws = 2 Then
                cpa = yy - collisionpointa: cpb = xx - collisionpointb
            End If
            Circle (cpb, cpa), 5, c(4) 'circle the collision point
            _Display
            _Delay .05
            sidecollisionvector
        End If
    Else
        If i2w <= ballrad Then '                                              *****  collision with endpoint of the line  *****
            c(9) = c(3)

            If i2ws = 1 Then
                cpa = yy - a2: cpb = xx + b
                endpointcollision1
            End If

            If i2ws = 2 Then
                cpa = yy - a: cpb = xx + b2
                endpointcollision2
            End If

            Circle (cpb, cpa), 5, c(4) 'circle the collision point
            _Display
            _Delay .05
        End If
    End If

    '==========================================================================================


    Line (xx, yy)-(xx + b, yy + a), c(9) 'angled wall (collision with ball changes colour)
    Line (xx, yy)-(xx - b, yy - a), c(9) 'angled wall (collision with ball changes colour)



    _Display
    If mouseclick2 = 1 Then flag = 1

Loop Until flag = 1


Sub sidecollisionpoint
    'calculate point R
    th1 = _Atan2(-y, x) 'radian value of ball (point I)
    'th1 = _Atan2(-yv, xv)
    th2 = _Atan2(-ndpy, ndpx) 'radian value of line N
    thd = th1 - th2 'find difference
    th3 = th2 - thd 'subtract difference from line N
    rx = Cos(th3) * h: ry = Sin(th3) * h 'point R position - th3 * length of point I to collision point
End Sub


Sub sidecollisionvector
    tx = xv: ty = yv: th = _Hypot(tx, ty)
    tx2 = tx / th: ty2 = ty / th
    spd = _Hypot(tx, ty) 'speed of existing motion vector
    th1 = _Atan2(tx, -ty) 'radian value of motion vector
    th2 = _Atan2(-ndpy, ndpx) 'radian value of line N
    thd = th1 - th2 'find difference
    th3 = th2 - thd 'subtract difference from line N
    newxv = Sin(th3): newyv = Cos(th3)
    xv = newxv * spd: yv = newyv * spd * -1
End Sub

Sub endpointcollision1
    tx = x - b: ty = y - a2: th = _Hypot(tx, ty)
    tx2 = tx / th: ty2 = ty / th
    txv = Abs(xv): tyv = Abs(yv): spd = _Hypot(txv, tyv)
    xv = tx2 * spd: yv = ty2 * spd * -1
End Sub


Sub endpointcollision2
    tx = x - b2: ty = y - a: th = _Hypot(tx, ty)
    tx2 = tx / th: ty2 = ty / th
    txv = Abs(xv): tyv = Abs(yv): spd = _Hypot(txv, tyv)
    xv = tx2 * spd: yv = ty2 * spd * -1
End Sub



RE: Angle Collisions - bplus - 10-25-2022

This looks much better, the ball reflections look correct. Very nice coverage of end points.


RE: Angle Collisions - james2464 - 10-25-2022

(10-25-2022, 12:37 AM)bplus Wrote: This looks much better, the ball reflections look correct. Very nice coverage of end points.

Thanks!  Now hopefully I can use this to make that angled outer boundary wall.


RE: Angle Collisions - OldMoses - 10-25-2022

This procedure should work good for stationary walls. I noticed if you "swing the bat" at the ball it will often stick together and gradually work its way, wiggling, to one end or the other before releasing. Kind of like it gets confused about which side of the line it hit.


RE: Angle Collisions - james2464 - 10-25-2022

(10-25-2022, 10:47 PM)OldMoses Wrote: This procedure should work good for stationary walls. I noticed if you "swing the bat" at the ball it will often stick together and gradually work its way, wiggling, to one end or the other before releasing. Kind of like it gets confused about which side of the line it hit.

Yeah if the line moves during a collision....it doesn't really work too well.    I'm starting to work on a multi (static) line version.