Thread Rating:
  • 0 Vote(s) - 0 Average
  • 1
  • 2
  • 3
  • 4
  • 5
games or graphics for 3-D glasses?
#11
(11-15-2024, 07:33 PM)vince Wrote:
(11-15-2024, 05:28 AM)madscijr Wrote: So, why didn't the code work? If you hold up your finger and look at it with your left eye closed, then your right eye closed, the distance between it increases as you move your finger closer to your face. So I'm thinking that the nearer to the viewer we want the image to appear, the further apart the red and cyan frames need to be.

So for the above demo to work, we would need to alter the code so as the "z" coordinate increases (ie closer to the viewer), the further apart the right/left distance between the two is.

It's too late right now to play with the code, but that's my general theory that I might work from.

Thoughts?
I see what you mean -- this is truly mad science.  I may get a pack of those as well my next amazon order, either that or ruin some reading glasses, and get back to you
Sure thing! This definitely has some neat possibilities for QB64PE!
Reply
#12
I like the thinking so far, z adjusting for how close image is and using transparent colors. I don't know how well the glasses can seperate blended blue and red, and if you don't blend would the last color overwrite the first competeing for same pixel?

I do like my avatar method, no need for glasses Smile
b = b + ...
Reply
#13
(11-15-2024, 08:41 PM)bplus Wrote: I like the thinking so far, z adjusting for how close image is and using transparent colors. I don't know how well the glasses can seperate blended blue and red, and if you don't blend would the last color overwrite the first competeing for same pixel?

I do like my avatar method, no need for glasses Smile
What's your avatar method? 

All I know is that the glasses can seperate the blended blue and red fine in the youtube demos, so it should be doable in code? 

Here was my last attempt, using solid shapes, but it just uses flat squares and circles, and so it doesn't look 3d. 
I think it would need to actually draw 3D shapes with different perspective for the right/left images for it to work.
Arrow keys move the 2nd closer shape around, minus key shrinks it, +/= key increases size:

Code: (Select All)
' CONSTANTS
Const FALSE = 0
Const TRUE = Not FALSE

' KEY CODES
Const cUpArrow = 18432
Const cDownArrow = 20480
Const cLeftArrow = 19200
Const cRightArrow = 19712

' COLORS
Dim Shared cRed~&
Dim Shared cCyan~&
Dim Shared cEmpty~&

Dim Shared iScreenWidth%
Dim Shared iScreenHeight%

Dim Shared x, y, z, p, q, t, zoom
Dim Shared sw, sh, mx, my, mb, mw
Dim Shared u
Dim Shared xx0, x0
Dim Shared x1a, y1a, x2a, y2a, x1b, y1b, x2b, y2b, xSkew1, xSkew2, ySkew1, ySkew2

' SET SHARED VALUES
cRed~& = _RGB32(255, 0, 0, 128) ' semi-transparent
cCyan~& = _RGB32(0, 255, 255, 128) ' semi-transparent
cEmpty~& = _RGB32(0, 0, 0, 0) ' _RGBA(red, green, blue, alpha) where alpha& specifies the alpha component transparency value from 0 (fully transparent) to 255 (opaque).

iScreenWidth% = 1024 ' 800
iScreenHeight% = 768 ' 600

'vince_3d_v1
'madscijr_3d_v1
madscijr_3d_v2

System


Sub madscijr_3d_v2
    Screen _NewImage(iScreenWidth%, iScreenHeight%, 32)
    'Screen _NewImage(_DesktopWidth, _DesktopHeight, 32)
    _ScreenMove 0, 0

    Dim square1x, square1y, square1w, square1h, square1dist, square1x2, square1y2, square1w2, square1h2
    Dim circle1x, circle1y, circle1r, circle1dist, circle1x2, circle1y2, circle1r2
    'Dim oval1x, oval1y, oval1w, oval1h, oval1dist, oval1x2, oval1y2, oval1w2, oval1h2

    square1x = 100
    square1y = 100
    square1w = 200
    square1h = 200
    square1dist = 20
    square1y2 = square1y
    square1w2 = square1w + 25
    square1h2 = square1h + 25

    circle1x = 400
    circle1y = 100
    circle1r = 100
    circle1dist = 40
    circle1y2 = circle1y
    circle1r2 = circle1r + 25

    'oval1x = 400
    'oval1y = 100
    'oval1w = 100
    'oval1h = 300
    'oval1dist = 40
    'oval1y2 = oval1y

    Do
        If _KeyDown(cLeftArrow) Then square1dist = square1dist - 1: circle1dist = circle1dist - 1
        If _KeyDown(cRightArrow) Then square1dist = square1dist + 1: circle1dist = circle1dist + 1
        If _KeyDown(cUpArrow) Then square1y2 = square1y2 - 1: circle1y2 = circle1y2 - 1
        If _KeyDown(cDownArrow) Then square1y2 = square1y2 + 1: circle1y2 = circle1y2 + 1
        If _KeyDown(Asc("-")) Then square1w2 = square1w2 - 1: circle1dist = circle1dist - 1: circle1r2 = circle1r2 - 1
        If _KeyDown(Asc("=")) Then square1w2 = square1w2 + 1: circle1dist = circle1dist + 1: circle1r2 = circle1r2 + 1

        square1x2 = square1x + square1dist
        circle1x2 = circle1x + circle1dist

        _Dest 0: Cls , cBlack
        'Locate 1, 1: Print xSkew2

        ' red is to the left
        ' LINE [STEP] [(column1, row1)]-[STEP] (column2, row2), color[, [{B|BF}], style%]
        'Line (x1a, y1a)-(x2a, y2a), _RGB(255, 0, 0)
        Call DrawRectSolid(square1x, square1y, square1w, square1h, cRed~&)
        Call CircleFill(circle1x, circle1y, circle1r, cRed~&)
        'Call EllipseFill(oval1x, oval1y, a, b, C)

        ' cyan is to the right
        ' LINE [STEP] [(column1, row1)]-[STEP] (column2, row2), color[, [{B|BF}], style%]
        'Line (x1b, y1b)-(x2b, y2b), _RGB(0, 255, 255)
        Call DrawRectSolid(square1x2, square1y2, square1w2, square1h2, cCyan~&)
        Call CircleFill(circle1x2, circle1y2, circle1r2, cCyan~&)
        'Call EllipseFill(oval1x2, oval1y, a, b, C)

        _Display
        _Limit 30
    Loop Until _KeyHit = 27

    _AutoDisplay ' RETURN TO AUTODISPLAY
End Sub ' madscijr_3d_v2

' /////////////////////////////////////////////////////////////////////////////
' DRAW A 2-D RECTANGLE (SOLID)

Sub DrawRectSolid (iX As Integer, iY As Integer, iSizeW As Integer, iSizeH As Integer, fgColor As _Unsigned Long)
    Line (iX, iY)-(iX + iSizeW, iY + iSizeH), fgColor, BF ' Draw a solid rectangle
End Sub ' DrawRectSolid

' /////////////////////////////////////////////////////////////////////////////

Sub CircleFill (CX As Integer, CY As Integer, R As Integer, C As _Unsigned Long)
    ' CX = center x coordinate
    ' CY = center y coordinate
    '  R = radius
    '  C = fill color
    Dim Radius As Integer, RadiusError As Integer
    Dim X As Integer, Y As Integer
    Radius = Abs(R)
    RadiusError = -Radius
    X = Radius
    Y = 0
    If Radius = 0 Then PSet (CX, CY), C: Exit Sub
    Line (CX - X, CY)-(CX + X, CY), C, BF
    While X > Y
        RadiusError = RadiusError + Y * 2 + 1
        If RadiusError >= 0 Then
            If X <> Y + 1 Then
                Line (CX - Y, CY - X)-(CX + Y, CY - X), C, BF
                Line (CX - Y, CY + X)-(CX + Y, CY + X), C, BF
            End If
            X = X - 1
            RadiusError = RadiusError - 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 ' CircleFill

' /////////////////////////////////////////////////////////////////////////////

Sub EllipseFill (CX As Integer, CY As Integer, a As Integer, b As Integer, C As _Unsigned Long)
    ' CX = center x coordinate
    ' CY = center y coordinate
    '  a = semimajor axis
    '  b = semiminor axis
    '  C = fill color
    If a = 0 Or b = 0 Then Exit Sub
    Dim h2 As _Integer64
    Dim w2 As _Integer64
    Dim h2w2 As _Integer64
    Dim x As Integer
    Dim y As Integer
    w2 = a * a
    h2 = b * b
    h2w2 = h2 * w2
    Line (CX - a, CY)-(CX + a, CY), C, BF
    Do While y < b
        y = y + 1
        x = Sqr((h2w2 - y * y * w2) \ h2)
        Line (CX - x, CY + y)-(CX + x, CY + y), C, BF
        Line (CX - x, CY - y)-(CX + x, CY - y), C, BF
    Loop
End Sub ' EllipseFill

' /////////////////////////////////////////////////////////////////////////////

Sub EllipseTilt (CX, CY, a, b, ang, C As _Unsigned Long)
    '  CX = center x coordinate
    '  CY = center y coordinate
    '  a = semimajor axis
    '  b = semiminor axis
    ' ang = clockwise orientation of semimajor axis in radians (0 default)
    '  C = fill color
    For k = 0 To 6.283185307179586 + .025 Step .025
        i = a * Cos(k) * Cos(ang) + b * Sin(k) * Sin(ang)
        j = -a * Cos(k) * Sin(ang) + b * Sin(k) * Cos(ang)
        i = i + CX
        j = -j + CY
        If k <> 0 Then
            Line -(i, j), C
        Else
            PSet (i, j), C
        End If
    Next
End Sub ' EllipseTilt

' /////////////////////////////////////////////////////////////////////////////

Sub EllipseTiltFill (destHandle&, CX, CY, a, b, ang, C As _Unsigned Long)
    '  destHandle& = destination handle
    '  CX = center x coordinate
    '  CY = center y coordinate
    '  a = semimajor axis
    '  b = semiminor axis
    ' ang = clockwise orientation of semimajor axis in radians (0 default)
    '  C = fill color
    Dim max As Integer, mx2 As Integer, i As Integer, j As Integer
    Dim prc As _Unsigned Long
    Dim D As Integer, S As Integer
    D = _Dest: S = _Source
    prc = _RGB32(255, 255, 255, 255)
    If a > b Then max = a + 1 Else max = b + 1
    mx2 = max + max
    tef& = _NewImage(mx2, mx2)
    _Dest tef&
    _Source tef&
    For k = 0 To 6.283185307179586 + .025 Step .025
        i = max + a * Cos(k) * Cos(ang) + b * Sin(k) * Sin(ang)
        j = max + a * Cos(k) * Sin(ang) - b * Sin(k) * Cos(ang)
        If k <> 0 Then
            Line (lasti, lastj)-(i, j), prc
        Else
            PSet (i, j), prc
        End If
        lasti = i: lastj = j
    Next
    Dim xleft(mx2) As Integer, xright(mx2) As Integer, x As Integer, y As Integer
    For y = 0 To mx2
        x = 0
        While Point(x, y) <> prc And x < mx2
            x = x + 1
        Wend
        xleft(y) = x
        While Point(x, y) = prc And x < mx2
            x = x + 1
        Wend
        While Point(x, y) <> prc And x < mx2
            x = x + 1
        Wend
        If x = mx2 Then xright(y) = xleft(y) Else xright(y) = x
    Next
    _Dest destHandle&
    For y = 0 To mx2
        If xleft(y) <> mx2 Then Line (xleft(y) + CX - max, y + CY - max)-(xright(y) + CX - max, y + CY - max), C, BF
    Next
    _Dest D: _Dest S
    _FreeImage tef&
End Sub ' EllipseTiltFill

' /////////////////////////////////////////////////////////////////////////////

Function ColorToString$ (MyValue~&)
    Dim Mystring As String
    Select Case MyValue~&
        Case cRed~&:
            Mystring = "Red"
        Case cCyan~&:
            Mystring = "Cyan"
        Case cEmpty~&:
            Mystring = "Empty"
        Case Else:
            Mystring = _Trim$(Str$(MyValue~&))
    End Select
    ColorToString$ = Mystring
End Function ' ColorToString$






















' /////////////////////////////////////////////////////////////////////////////

Sub madscijr_3d_v1
    sw = 800
    sh = 600

    Screen _NewImage(sw, sh, 32)

    If _Resize Then
        sw = _ResizeWidth - 20
        sh = _ResizeHeight - 20
        Screen _NewImage(sw, sh, 32)
    End If

    x1a = 100
    y1a = 100
    x2a = 400
    y2a = 500
    xSkew1 = 10
    ySkew1 = 5
    xSkew2 = 40
    ySkew2 = 10

    Do
        If _KeyDown(19200) Then xSkew2 = xSkew2 + 1
        If _KeyDown(19712) Then xSkew2 = xSkew2 - 1

        x1b = x1a + xSkew1
        y1b = y1a + ySkew1
        x2b = x2a + xSkew2
        y2b = y2a + ySkew2

        Cls
        Locate 1, 1: Print xSkew2

        ' LINE [STEP] [(column1, row1)]-[STEP] (column2, row2), color[, [{B|BF}], style%]

        ' red is to the left
        Line (x1a, y1a)-(x2a, y2a), _RGB(255, 0, 0)

        ' cyan is to the right
        Line (x1b, y1b)-(x2b, y2b), _RGB(0, 255, 255)

        _Display
        _Limit 30
    Loop Until _KeyHit = 27

End Sub ' madscijr_3d_v1

' /////////////////////////////////////////////////////////////////////////////

Sub vince_3d_v1
    sw = 800
    sh = 600

    Screen _NewImage(sw, sh, 32)

    If _Resize Then
        sw = _ResizeWidth - 20
        sh = _ResizeHeight - 20
        Screen _NewImage(sw, sh, 32)
    End If

    zoom = 100

    x = 1
    y = 0
    z = 0
    proj
    Line (sw / 2, sh / 2)-(sw / 2 + zoom * p, sh / 2 - zoom * q), _RGB(255, 0, 0)
    x = 0
    y = 1
    z = 0
    proj
    Line (sw / 2, sh / 2)-(sw / 2 + zoom * p, sh / 2 - zoom * q), _RGB(0, 0, 255)
    x = 0
    y = 0
    z = 1
    proj
    Line (sw / 2, sh / 2)-(sw / 2 + zoom * p, sh / 2 - zoom * q), _RGB(0, 255, 0)


    y0 = -0.3
    u = 0
    x0 = 0.1
    Do
        u = u + 0.1

        If _KeyDown(19200) Then x0 = x0 + 0.1
        If _KeyDown(19712) Then x0 = x0 - 0.1

        Cls
        Locate 1, 1: Print xx0

        xx0 = 0
        Color _RGB(255, 0, 0)
        square -0.5, y0, -1, -0.5, y0, 1, 0.5, y0, 1, 0.5, y0, -1 'roof
        square -0.5, y0 - 0.5, -1, -0.5, y0 - 0.5, 1, 0.5, y0 - 0.5, 1, 0.5, y0 - 0.5, -1 'floor
        square -0.5, y0, -1, 0.5, y0, -1, 0.5, y0 - 0.5, -1, -0.5, y0 - 0.5, -1 'rear
        square -0.5, y0, 1, 0.5, y0, 1, 0.5, y0 - 0.5, 1, -0.5, y0 - 0.5, 1 'windshield

        xx0 = x0
        Color _RGB(0, 255, 255)
        square -0.5, y0, -1, -0.5, y0, 1, 0.5, y0, 1, 0.5, y0, -1 'roof
        square -0.5, y0 - 0.5, -1, -0.5, y0 - 0.5, 1, 0.5, y0 - 0.5, 1, 0.5, y0 - 0.5, -1 'floor
        square -0.5, y0, -1, 0.5, y0, -1, 0.5, y0 - 0.5, -1, -0.5, y0 - 0.5, -1 'rear
        square -0.5, y0, 1, 0.5, y0, 1, 0.5, y0 - 0.5, 1, -0.5, y0 - 0.5, 1 'windshield

        _Display
        _Limit 30
    Loop Until _KeyHit = 27
End Sub ' 'vince_3d_v1

' /////////////////////////////////////////////////////////////////////////////

Sub square (x1, y1, z1, x2, y2, z2, x3, y3, z3, x4, y4, z4)
    x = x1
    y = y1
    z = z1
    proj
    PReset (sw / 2 + zoom * p, sh / 2 - zoom * q)

    x = x2
    y = y2
    z = z2
    proj
    Line -(sw / 2 + zoom * p, sh / 2 - zoom * q)

    x = x3
    y = y3
    z = z3
    proj
    Line -(sw / 2 + zoom * p, sh / 2 - zoom * q)

    x = x4
    y = y4
    z = z4
    proj
    Line -(sw / 2 + zoom * p, sh / 2 - zoom * q)

    x = x1
    y = y1
    z = z1
    proj
    Line -(sw / 2 + zoom * p, sh / 2 - zoom * q)
End Sub

' /////////////////////////////////////////////////////////////////////////////

Sub proj
    rot u, 1, 1, 0

    x = x + xx0

    d = 100
    p = x * d / (100 + y)
    q = y * d / (100 + y)
End Sub

' /////////////////////////////////////////////////////////////////////////////

Sub rot (u, rx, ry, rz)
    dd = Sqr(rx * rx + ry * ry + rz * rz)
    rx = rx / dd
    ry = ry / dd
    rz = rz / dd

    x1 = x
    y1 = y
    z1 = z

    x2 = ry * z - rz * y
    y2 = rz * x - rx * z
    z2 = rx * y - ry * x

    x3 = rx * (rx * x + ry * y + rz * z)
    y3 = ry * (rx * x + ry * y + rz * z)
    z3 = rz * (rx * x + ry * y + rz * z)

    x = x1 * Cos(u) + x2 * Sin(u) + x3 * (1 - Cos(u))
    y = y1 * Cos(u) + y2 * Sin(u) + y3 * (1 - Cos(u))
    z = z1 * Cos(u) + z2 * Sin(u) + z3 * (1 - Cos(u))

End Sub

' /////////////////////////////////////////////////////////////////////////////

Sub rotx (u, x0, y0, z0)
    xx = x - x0
    yy = (y - y0) * Cos(u) - (z - z0) * Sin(u)
    zz = (y - y0) * Sin(u) + (z - z0) * Cos(u)

    x = xx + x0
    y = yy + y0
    z = zz + z0
End Sub

' /////////////////////////////////////////////////////////////////////////////

Sub roty (u, x0, y0, z0)
    xx = (x - x0) * Cos(u) + (z - z0) * Sin(u)
    yy = y - y0
    zz = -(x - x0) * Sin(u) + (z - z0) * Cos(u)

    x = xx + x0
    y = yy + y0
    z = zz + z0
End Sub

' /////////////////////////////////////////////////////////////////////////////

Sub rotz (u, x0, y0, z0)
    xx = (x - x0) * Cos(u) - (y - y0) * Sin(u)
    yy = (x - x0) * Sin(u) + (y - y0) * Cos(u)
    zz = z - z0

    x = xx + x0
    y = yy + y0
    z = zz + z0
End Sub
Reply
#14
Quote:What's your avatar method?

Code: (Select All)
_Title "3D per Parallelism test Cube 1" ' started Parallelism b+ 2024-02-20
'  "parallelism suggests a connection of meaning through an echo of form"
' 2024-02-21 Pyramid 2 screw around with pyramid numbers fix projection formula
' 2024-02-21 now test cubes with DrawCube sub
' 2024-02-21 return to Pyramid 2 and fix that according to how this Project sub works.

Dim Shared As Long SW, SH: SW = 600: SH = 600
Screen _NewImage(SW, SH, 32)
_ScreenMove 340, 60

Type XYZ
    As Single x, y, z
End Type
Type XY
    As Single x, y
End Type
Dim Shared PC: PC = .35 ' or something  PC = Parallel Constant
Window (-5, -5)-(5, 5) ' setup for 3D

drawCube 0, 0, -2, 2, _RGB32(0, 160, 0)

drawCube 0, -2, 0, 2, _RGB32(0, 0, 255)
drawCube -2, 0, 0, 2, _RGB32(255, 0, 0)
'drawCube 0, 0, 0, 2, _RGB32(255, 255, 255) ' dont need
drawCube 2, 0, 0, 2, _RGB32(255, 0, 0)
drawCube 0, 2, 0, 2, _RGB32(0, 0, 255)

drawCube 0, 0, 2, 2, _RGB32(0, 160, 0) ' front most

Sub drawCube (cx, cy, cz, side, colr~&) 'draw a cube on screen from an xyz() 3D array
    Dim As Integer i, r, g, b
    Dim sd2, lx, rx, ty, by, fz, bz
    Dim c2 As _Unsigned Long
    r = _Red32(colr~&): g = _Green32(colr~&): b = _Blue32(colr~&)
    ReDim corners(0 To 7) As XYZ
    sd2 = side / 2
    rx = cx + sd2: lx = cx - sd2
    ty = cy + sd2: by = cy - sd2
    fz = cz + sd2: bz = cz - sd2
    'bck face
    corners(0).x = lx: corners(0).y = ty: corners(0).z = bz
    corners(1).x = rx: corners(1).y = ty: corners(1).z = bz
    corners(2).x = rx: corners(2).y = by: corners(2).z = bz
    corners(3).x = lx: corners(3).y = by: corners(3).z = bz
    'frt face
    corners(4).x = lx: corners(4).y = ty: corners(4).z = fz
    corners(5).x = rx: corners(5).y = ty: corners(5).z = fz
    corners(6).x = rx: corners(6).y = by: corners(6).z = fz
    corners(7).x = lx: corners(7).y = by: corners(7).z = fz

    ReDim xy(0 To 7) As XY
    For i = 0 To 7
        Project corners(i), xy(i) ' take a corner x,y,z and convert to screen coordinates x,y
        ' Print i; corners(i).x; corners(i).y; corners(i).z; " >>>  "; xy(i).x; xy(i).y
    Next
    'Sleep
    'Cls
    'back face
    'Line (xy(0).x, xy(0).y)-(xy(1).x, xy(1).y), &HFFFF0000
    'Line (xy(1).x, xy(1).y)-(xy(2).x, xy(2).y), colr~&
    'Line (xy(2).x, xy(2).y)-(xy(3).x, xy(3).y), colr~&
    'Line (xy(3).x, xy(3).y)-(xy(0).x, xy(0).y), colr~&

    'front face
    'Line (xy(4).x, xy(4).y)-(xy(5).x, xy(5).y), colr~&
    'Line (xy(5).x, xy(5).y)-(xy(6).x, xy(6).y), colr~&
    'Line (xy(6).x, xy(6).y)-(xy(7).x, xy(7).y), colr~&
    'Line (xy(7).x, xy(7).y)-(xy(4).x, xy(4).y), colr~&


    ' left side of face
    'If xy(0).x > 0 Then
    '    c2 = _RGB32(.6 * r, .6 * g, .6 * b)
    '    FillTriangle PMap(xy(0).x, 0), PMap(xy(0).y, 1), PMap(xy(3).x, 0), PMap(xy(3).y, 1), PMap(xy(7).x, 0), PMap(xy(7).y, 1), c2
    '    FillTriangle PMap(xy(4).x, 0), PMap(xy(4).y, 1), PMap(xy(7).x, 0), PMap(xy(7).y, 1), PMap(xy(0).x, 0), PMap(xy(0).y, 1), c2
    'End If

    ' top face
    'If xy(0).y < 0 Then
    c2 = _RGB32(.85 * r, .85 * g, .85 * b)
    FillTriangle PMap(xy(0).x, 0), PMap(xy(0).y, 1), PMap(xy(1).x, 0), PMap(xy(1).y, 1), PMap(xy(4).x, 0), PMap(xy(4).y, 1), c2
    FillTriangle PMap(xy(4).x, 0), PMap(xy(4).y, 1), PMap(xy(5).x, 0), PMap(xy(5).y, 1), PMap(xy(1).x, 0), PMap(xy(1).y, 1), c2
    'End If

    ' right face
    'If xy(1).x < 0 Then
    c2 = _RGB32(.6 * r, .6 * g, .6 * b)
    FillTriangle PMap(xy(1).x, 0), PMap(xy(1).y, 1), PMap(xy(2).x, 0), PMap(xy(2).y, 1), PMap(xy(5).x, 0), PMap(xy(5).y, 1), c2
    FillTriangle PMap(xy(5).x, 0), PMap(xy(5).y, 1), PMap(xy(6).x, 0), PMap(xy(6).y, 1), PMap(xy(2).x, 0), PMap(xy(2).y, 1), c2
    'End If

    ' bottom face
    'If xy(0).y > 0 Then
    '    c2 = _RGB32(45 * r, .45 * g, .45 * b)
    '    FillTriangle PMap(xy(3).x, 0), PMap(xy(3).y, 1), PMap(xy(2).x, 0), PMap(xy(2).y, 1), PMap(xy(7).x, 0), PMap(xy(7).y, 1), c2
    '    FillTriangle PMap(xy(7).x, 0), PMap(xy(7).y, 1), PMap(xy(6).x, 0), PMap(xy(6).y, 1), PMap(xy(2).x, 0), PMap(xy(2).y, 1), c2
    'End If

    ' front face
    FillTriangle PMap(xy(4).x, 0), PMap(xy(4).y, 1), PMap(xy(5).x, 0), PMap(xy(5).y, 1), PMap(xy(6).x, 0), PMap(xy(6).y, 1), colr~&
    FillTriangle PMap(xy(6).x, 0), PMap(xy(6).y, 1), PMap(xy(7).x, 0), PMap(xy(7).y, 1), PMap(xy(4).x, 0), PMap(xy(4).y, 1), colr~&

End Sub

' steves latest version to check out, seems to be working OK
Sub FillTriangle (x1, y1, x2, y2, x3, y3, K As _Unsigned Long)
    $Checking:Off
    Static a&, m As _MEM
    If a& = 0 Then a& = _NewImage(1, 1, 32): m = _MemImage(a&)
    _MemPut m, m.OFFSET, K
    _MapTriangle _Seamless(0, 0)-(0, 0)-(0, 0), a& To(x1, y1)-(x2, y2)-(x3, y3)
    $Checking:On
End Sub

' here I am working with a Window so Screen obeys right hand rule so as z increases
' the image x, y plane is closer to the eye/camera so is bigger
' but should be distance squared
' thankyou vince '2024-02  the bigger the Z the closer it is to the eye the greater the image
Sub Project (pIN As XYZ, pOut As XY) 'M2SPP = Model (3D) 2 Screen Per Parallelism
    pOut.x = pIN.x - PC * pIN.z
    pOut.y = pIN.y - PC * pIN.z
End Sub

Here is more interesting example:
Code: (Select All)
_Title "3D per Parallelism test Game of Life - hold enter to reset" ' started Parallelism b+ 2024-02-20
'  "parallelism suggests a connection of meaning through an echo of form"
' 2024-02-21 Pyramid 2 screw around with pyramid numbers fix projection formula
' 2024-02-21 now test cubes with DrawCube sub
' 2024-02-21 return to Pyramid 2 and fix that according to how this Project sub works.
' 2024-02-22 test Game of Life code from thisversion of DrawCube
'            Ah! apply some tips I learned with 3D Rendering of Game of Life

Dim Shared As Long SW, SH: SW = 720: SH = 720
Screen _NewImage(SW, SH, 32)
_ScreenMove 280, 0
Randomize Timer

Type XYZ
    As Single x, y, z
End Type
Type XY
    As Single x, y
End Type
Dim Shared PC: PC = .35 ' or something  PC = Parallel Constant
Window (-15, 35)-(35, -15) ' setup for 3D

' setup for Game of Life
Dim As Integer xmin, xmax, ymin, ymax, zmin, zmax
xmin = 1: xmax = 30: ymin = 1: ymax = 30: zmin = 1: zmax = 30
Dim As Integer x, y, z, r, g, b, mm, xx, yy, zz, rr, gg, bb, gen
Color &HFFDDDDFF, &HFF000000

ResetStart:
gen = 0
ReDim As Integer U(xmin To xmax, ymin To ymax, zmin To zmax), U2(xmin To xmax, ymin To ymax, zmin To zmax)
'For z = zmin + 10 To zmax - 10
'    For x = xmin + 10 To xmax - 10
'        For y = ymin + 10 To ymax - 10
'            If Rnd > .9 Then U(x, y, z) = 1
'Next y, x, z

'try a blinker
U(14, 15, 15) = 1: U(15, 15, 15) = 1: U(16, 15, 15) = 1
rr = Rnd * 50 + 50: gg = Rnd * 50 + 50: bb = Rnd * 50 + 50

Do
    Cls
    _PrintString (10, 10), "Generation:" + Str$(gen) + "  press any for next, escape to quit... "
    r = rr: g = gg: b = bb
    For z = zmin + 1 To zmax - 1
        r = r * 1.04: g = g * 1.04: b = b * 1.04
        For x = xmin + 1 To xmax - 1
            For y = ymin + 1 To ymax - 1
                If U(x, y, z) = 1 Then
                    drawCube x, y, z, .9, _RGB32(r, g, b)
                End If
        Next y, x
        _Display
        _Limit 30
    Next z
    _Display
    Sleep
    If _KeyDown(13) Then Cls: _Delay .5: GoTo ResetStart
    For z = zmin + 1 To zmax - 1
        For x = xmin + 1 To xmax - 1
            For y = ymin + 1 To ymax - 1
                mm = 0
                For xx = x - 1 To x + 1
                    For yy = y - 1 To y + 1
                        For zz = z - 1 To z + 1
                            If x = xx And y = yy And z = zz Then
                            Else
                                If U(xx, yy, zz) = 1 Then mm = mm + 1
                            End If
                Next zz, yy, xx
                If (mm > 1) And (mm < 4) Then ' neighbors for birth
                    U2(x, y, z) = 1
                ElseIf U(x, y, z) = 1 And mm = 3 Then ' neighbors to survive
                    U2(x, y, z) = 1
                Else
                    U2(x, y, z) = 0
                End If
        Next y, x
    Next z

    For z = zmin + 1 To zmax - 1
        For x = xmin + 1 To xmax - 1
            For y = ymin + 1 To ymax - 1
                U(x, y, z) = U2(x, y, z)
    Next y, x, z
    gen = gen + 1
Loop Until _KeyDown(27)

Sub drawCube (cx, cy, cz, side, colr~&) 'draw a cube on screen from an xyz() 3D array
    Dim As Integer i, r, g, b
    Dim sd2, lx, rx, ty, by, fz, bz
    Dim c2 As _Unsigned Long
    r = _Red32(colr~&): g = _Green32(colr~&): b = _Blue32(colr~&)
    ReDim corners(0 To 7) As XYZ
    sd2 = side / 2
    rx = cx + sd2: lx = cx - sd2
    ty = cy + sd2: by = cy - sd2
    fz = cz + sd2: bz = cz - sd2
    'bck face
    corners(0).x = lx: corners(0).y = ty: corners(0).z = bz
    corners(1).x = rx: corners(1).y = ty: corners(1).z = bz
    corners(2).x = rx: corners(2).y = by: corners(2).z = bz
    corners(3).x = lx: corners(3).y = by: corners(3).z = bz
    'frt face
    corners(4).x = lx: corners(4).y = ty: corners(4).z = fz
    corners(5).x = rx: corners(5).y = ty: corners(5).z = fz
    corners(6).x = rx: corners(6).y = by: corners(6).z = fz
    corners(7).x = lx: corners(7).y = by: corners(7).z = fz

    ReDim xy(0 To 7) As XY
    For i = 0 To 7
        Project corners(i), xy(i) ' take a corner x,y,z and convert to screen coordinates x,y
    Next

    'debug
    'back face
    'Line (xy(0).x, xy(0).y)-(xy(1).x, xy(1).y), &HFFFF0000
    'Line (xy(1).x, xy(1).y)-(xy(2).x, xy(2).y), colr~&
    'Line (xy(2).x, xy(2).y)-(xy(3).x, xy(3).y), colr~&
    'Line (xy(3).x, xy(3).y)-(xy(0).x, xy(0).y), colr~&

    'front face
    'Line (xy(4).x, xy(4).y)-(xy(5).x, xy(5).y), colr~&
    'Line (xy(5).x, xy(5).y)-(xy(6).x, xy(6).y), colr~&
    'Line (xy(6).x, xy(6).y)-(xy(7).x, xy(7).y), colr~&
    'Line (xy(7).x, xy(7).y)-(xy(4).x, xy(4).y), colr~&

    ' top face
    c2 = _RGB32(.85 * r, .85 * g, .85 * b)
    FillTriangle PMap(xy(0).x, 0), PMap(xy(0).y, 1), PMap(xy(1).x, 0), PMap(xy(1).y, 1), PMap(xy(4).x, 0), PMap(xy(4).y, 1), c2
    FillTriangle PMap(xy(4).x, 0), PMap(xy(4).y, 1), PMap(xy(5).x, 0), PMap(xy(5).y, 1), PMap(xy(1).x, 0), PMap(xy(1).y, 1), c2

    ' right face
    c2 = _RGB32(.6 * r, .6 * g, .6 * b)
    FillTriangle PMap(xy(1).x, 0), PMap(xy(1).y, 1), PMap(xy(2).x, 0), PMap(xy(2).y, 1), PMap(xy(5).x, 0), PMap(xy(5).y, 1), c2
    FillTriangle PMap(xy(5).x, 0), PMap(xy(5).y, 1), PMap(xy(6).x, 0), PMap(xy(6).y, 1), PMap(xy(2).x, 0), PMap(xy(2).y, 1), c2

    ' front face
    FillTriangle PMap(xy(4).x, 0), PMap(xy(4).y, 1), PMap(xy(5).x, 0), PMap(xy(5).y, 1), PMap(xy(6).x, 0), PMap(xy(6).y, 1), colr~&
    FillTriangle PMap(xy(6).x, 0), PMap(xy(6).y, 1), PMap(xy(7).x, 0), PMap(xy(7).y, 1), PMap(xy(4).x, 0), PMap(xy(4).y, 1), colr~&

End Sub

' steves latest version to check out, seems to be working OK
Sub FillTriangle (x1, y1, x2, y2, x3, y3, K As _Unsigned Long)
    $Checking:Off
    Static a&, m As _MEM
    If a& = 0 Then a& = _NewImage(1, 1, 32): m = _MemImage(a&)
    _MemPut m, m.OFFSET, K
    _MapTriangle _Seamless(0, 0)-(0, 0)-(0, 0), a& To(x1, y1)-(x2, y2)-(x3, y3)
    $Checking:On
End Sub

' here I am working with a Window so Screen obeys right hand rule so as z increases
' the image x, y plane is closer to the eye/camera so is bigger
' but should be distance squared
' thankyou vince '2024-02  the bigger the Z the closer it is to the eye the greater the image
Sub Project (pIN As XYZ, pOut As XY) 'M2SPP = Model (3D) 2 Screen Per Parallelism
    pOut.x = pIN.x - PC * pIN.z
    pOut.y = pIN.y - PC * pIN.z
End Sub

   
b = b + ...
Reply
#15
(11-15-2024, 10:53 PM)bplus Wrote:
Quote:What's your avatar method?

Code: (Select All)
_Title "3D per Parallelism test Cube 1" ' started Parallelism b+ 2024-02-20
'  "parallelism suggests a connection of meaning through an echo of form"
...
Here is more interesting example:
Code: (Select All)
_Title "3D per Parallelism test Game of Life - hold enter to reset" ' started Parallelism b+ 2024-02-20
'  "parallelism suggests a connection of meaning through an echo of form"
This is the kind of thing that would look great in anaglyphic 3D! 
Just draw it in red, and then draw the same thing in cyan but with a slightly shifted perspective, to the right. 
The closer to the viewer you get, the farther over it needs to be shifted. 
I'm speaking from theory, of course, I haven't actually done it myself! LOL

UPDATE:
I tried modifying your program to shift the perspective and draw in red and cyan, it maybe kinda sorta works? 
You'll need to view it with the 3D glasses - get 'em cheap at the Amazon link I posted or make your own (google it). 
Thoughts? 

Code: (Select All)
_Title "3D per Parallelism test Game of Life - hold enter to reset" ' started Parallelism b+ 2024-02-20
'  "parallelism suggests a connection of meaning through an echo of form"
' 2024-02-21 Pyramid 2 screw around with pyramid numbers fix projection formula
' 2024-02-21 now test cubes with DrawCube sub
' 2024-02-21 return to Pyramid 2 and fix that according to how this Project sub works.
' 2024-02-22 test Game of Life code from thisversion of DrawCube
'            Ah! apply some tips I learned with 3D Rendering of Game of Life
' 2024-12-15 Madscijr tried modifying it to draw everything in anaglyphic 3D
'            per thread at https://qb64phoenix.com/forum/showthread.php?tid=3206

Const FALSE = 0
Const TRUE = Not FALSE
Const cMinZ = 1
Const cMaxZ = 30

' THESE ARE THE VALUES WE NEED TO FIND THE OPTIMAL VALUE FOR
' (MAY DEPEND ON HOW FAR AWAY FROM THE SCREEN YOU ARE SITTING?)
Const cMaxShift = 4 ' max pixels to shift right when closest to viewer
Const cAlpha = 54

Dim Shared As Long SW, SH: SW = 720: SH = 720

Screen _NewImage(SW, SH, 32)
_ScreenMove 280, 0

Randomize Timer

Type XYZ
    As Single x, y, z
End Type
Type XY
    As Single x, y
End Type
Dim Shared PC: PC = .35 ' or something  PC = Parallel Constant
Window (-15, 35)-(35, -15) ' setup for 3D

' setup for Game of Life
Dim As Integer xmin, xmax, ymin, ymax, zmin, zmax
xmin = 1: xmax = 30: ymin = 1: ymax = 30: zmin = cMinZ: zmax = cMaxZ
Dim As Integer x, y, z, r, g, b, mm, xx, yy, zz, rr, gg, bb, gen
Color &HFFDDDDFF, &HFF000000

ResetStart:
gen = 0
ReDim As Integer U(xmin To xmax, ymin To ymax, zmin To zmax), U2(xmin To xmax, ymin To ymax, zmin To zmax)
'For z = zmin + 10 To zmax - 10
'    For x = xmin + 10 To xmax - 10
'        For y = ymin + 10 To ymax - 10
'            If Rnd > .9 Then U(x, y, z) = 1
'Next y, x, z

'try a blinker
U(14, 15, 15) = 1: U(15, 15, 15) = 1: U(16, 15, 15) = 1
rr = Rnd * 50 + 50: gg = Rnd * 50 + 50: bb = Rnd * 50 + 50

Do
    Cls
    _PrintString (10, 10), "Generation:" + Str$(gen) + "  press any for next, escape to quit... "
    'r = rr: g = gg: b = bb
    For z = zmin + 1 To zmax - 1
        'r = r * 1.04: g = g * 1.04: b = b * 1.04
       
        For x = xmin + 1 To xmax - 1
            For y = ymin + 1 To ymax - 1
                If U(x, y, z) = 1 Then
                    'drawCube x, y, z, .9, _RGB32(r, g, b)
                   
                    ' first draw it in red (left eye)
                    drawCube x, y, z, .9, _RGB32(255, 0, 0), FALSE
                   
                    ' then draw it in cyan (right eye)
                    drawCube x, y, z, .9, _RGB32(0, 255, 255), TRUE
                   
                End If
        Next y, x
        _Display
        _Limit 30
    Next z
   
    _Display
    Sleep
   
    If _KeyDown(13) Then Cls: _Delay .5: GoTo ResetStart
    For z = zmin + 1 To zmax - 1
        For x = xmin + 1 To xmax - 1
            For y = ymin + 1 To ymax - 1
                mm = 0
                For xx = x - 1 To x + 1
                    For yy = y - 1 To y + 1
                        For zz = z - 1 To z + 1
                            If x = xx And y = yy And z = zz Then
                            Else
                                If U(xx, yy, zz) = 1 Then mm = mm + 1
                            End If
                Next zz, yy, xx
                If (mm > 1) And (mm < 4) Then ' neighbors for birth
                    U2(x, y, z) = 1
                ElseIf U(x, y, z) = 1 And mm = 3 Then ' neighbors to survive
                    U2(x, y, z) = 1
                Else
                    U2(x, y, z) = 0
                End If
        Next y, x
    Next z

    For z = zmin + 1 To zmax - 1
        For x = xmin + 1 To xmax - 1
            For y = ymin + 1 To ymax - 1
                U(x, y, z) = U2(x, y, z)
    Next y, x, z
    gen = gen + 1
Loop Until _KeyDown(27)

Sub drawCube (cx, cy, cz, side, colr~&, bShift) 'draw a cube on screen from an xyz() 3D array
    Dim As Integer i, r, g, b
    Dim sd2, lx, rx, ty, by, fz, bz
    Dim c2 As _Unsigned Long
    Dim PercentShift As Single
    Dim PixelsRight

    ' if bShift=TRUE then shift right for the right eye image
    If bShift = TRUE Then
        ' cz can be from zmin to zmin (1-30)
        ' use this value to determine how far right to shift cube
        ' (farther away = shift less far right, closer = shift farther right)
        '
        ' So: what percent of (cMaxZ - cMinZ) is cz?
        PercentShift = cz / (cMaxZ - cMinZ)
        PixelsRight = Int(cMaxShift * PercentShift)
    Else
        PixelsRight = 0
    End If

    r = _Red32(colr~&): g = _Green32(colr~&): b = _Blue32(colr~&)

    ReDim corners(0 To 7) As XYZ
    sd2 = side / 2
    rx = (cx + sd2) + PixelsRight: lx = (cx - sd2) + PixelsRight
    ty = cy + sd2: by = cy - sd2
    fz = cz + sd2: bz = cz - sd2

    'bck face
    corners(0).x = lx: corners(0).y = ty: corners(0).z = bz
    corners(1).x = rx: corners(1).y = ty: corners(1).z = bz
    corners(2).x = rx: corners(2).y = by: corners(2).z = bz
    corners(3).x = lx: corners(3).y = by: corners(3).z = bz
    'frt face
    corners(4).x = lx: corners(4).y = ty: corners(4).z = fz
    corners(5).x = rx: corners(5).y = ty: corners(5).z = fz
    corners(6).x = rx: corners(6).y = by: corners(6).z = fz
    corners(7).x = lx: corners(7).y = by: corners(7).z = fz

    ReDim xy(0 To 7) As XY
    For i = 0 To 7
        Project corners(i), xy(i) ' take a corner x,y,z and convert to screen coordinates x,y
    Next

    'debug
    'back face
    'Line (xy(0).x, xy(0).y)-(xy(1).x, xy(1).y), &HFFFF0000
    'Line (xy(1).x, xy(1).y)-(xy(2).x, xy(2).y), colr~&
    'Line (xy(2).x, xy(2).y)-(xy(3).x, xy(3).y), colr~&
    'Line (xy(3).x, xy(3).y)-(xy(0).x, xy(0).y), colr~&

    'front face
    'Line (xy(4).x, xy(4).y)-(xy(5).x, xy(5).y), colr~&
    'Line (xy(5).x, xy(5).y)-(xy(6).x, xy(6).y), colr~&
    'Line (xy(6).x, xy(6).y)-(xy(7).x, xy(7).y), colr~&
    'Line (xy(7).x, xy(7).y)-(xy(4).x, xy(4).y), colr~&

    ' top face
    'c2 = _RGB32(.5 * r, .5 * g, .5 * b, 128)
    c2 = _RGB32(.7 * r, .7 * g, .7 * b, cAlpha)
    FillTriangle PMap(xy(0).x, 0), PMap(xy(0).y, 1), PMap(xy(1).x, 0), PMap(xy(1).y, 1), PMap(xy(4).x, 0), PMap(xy(4).y, 1), c2
    FillTriangle PMap(xy(4).x, 0), PMap(xy(4).y, 1), PMap(xy(5).x, 0), PMap(xy(5).y, 1), PMap(xy(1).x, 0), PMap(xy(1).y, 1), c2

    ' right face
    'c2 = _RGB32(.25 * r, .25 * g, .25 * b, 128)
    c2 = _RGB32(.5 * r, .5 * g, .5 * b, cAlpha)
    FillTriangle PMap(xy(1).x, 0), PMap(xy(1).y, 1), PMap(xy(2).x, 0), PMap(xy(2).y, 1), PMap(xy(5).x, 0), PMap(xy(5).y, 1), c2
    FillTriangle PMap(xy(5).x, 0), PMap(xy(5).y, 1), PMap(xy(6).x, 0), PMap(xy(6).y, 1), PMap(xy(2).x, 0), PMap(xy(2).y, 1), c2

    ' front face
    'c2 = _RGB32(.75 * r, .75 * g, .75 * b, 128)
    c2 = _RGB32(.9 * r, .9 * g, .9 * b, cAlpha)
    FillTriangle PMap(xy(4).x, 0), PMap(xy(4).y, 1), PMap(xy(5).x, 0), PMap(xy(5).y, 1), PMap(xy(6).x, 0), PMap(xy(6).y, 1), c2
    FillTriangle PMap(xy(6).x, 0), PMap(xy(6).y, 1), PMap(xy(7).x, 0), PMap(xy(7).y, 1), PMap(xy(4).x, 0), PMap(xy(4).y, 1), c2
End Sub ' drawCube

' steves latest version to check out, seems to be working OK
Sub FillTriangle (x1, y1, x2, y2, x3, y3, K As _Unsigned Long)
    $Checking:Off
    Static a&, m As _MEM
    If a& = 0 Then a& = _NewImage(1, 1, 32): m = _MemImage(a&)
    _MemPut m, m.OFFSET, K
    _MapTriangle _Seamless(0, 0)-(0, 0)-(0, 0), a& To(x1, y1)-(x2, y2)-(x3, y3)
    $Checking:On
End Sub ' FillTriangle

' here I am working with a Window so Screen obeys right hand rule so as z increases
' the image x, y plane is closer to the eye/camera so is bigger
' but should be distance squared
' thankyou vince '2024-02  the bigger the Z the closer it is to the eye the greater the image
Sub Project (pIN As XYZ, pOut As XY) 'M2SPP = Model (3D) 2 Screen Per Parallelism
    pOut.x = pIN.x - PC * pIN.z
    pOut.y = pIN.y - PC * pIN.z
End Sub ' Project

' =============================================================================
' SOME USEFUL STUFF FOR REFERENCE:

' Type Name               Type suffix symbol   Minimum value                  Maximum value                Size in Bytes
' ---------------------   ------------------   ----------------------------   --------------------------   -------------
' _BIT                    `                    -1                             0                            1/8
' _BIT * n                `n                   -128                           127                          n/8
' _UNSIGNED _BIT          ~`                   0                              1                            1/8
' _BYTE                   %%                   -128                           127                          1
' _UNSIGNED _BYTE         ~%%                  0                              255                          1
' INTEGER                 %                    -32,768                        32,767                       2
' _UNSIGNED INTEGER       ~%                   0                              65,535                       2
' LONG                    &                    -2,147,483,648                 2,147,483,647                4
' _UNSIGNED LONG          ~&                   0                              4,294,967,295                4
' _INTEGER64              &&                   -9,223,372,036,854,775,808     9,223,372,036,854,775,807    8
' _UNSIGNED _INTEGER64    ~&&                  0                              18,446,744,073,709,551,615   8
' SINGLE                  ! or none            -2.802597E-45                  +3.402823E+38                4
' DOUBLE                  #                    -4.490656458412465E-324        +1.797693134862310E+308      8
' _FLOAT                  ##                   -1.18E-4932                    +1.18E+4932                  32(10 used)
' _OFFSET                 %&                   -9,223,372,036,854,775,808     9,223,372,036,854,775,807    Use LEN
' _UNSIGNED _OFFSET       ~%&                  0                              18,446,744,073,709,551,615   Use LEN
' _MEM                    none                 combined memory variable type  N/A                          Use LEN

' div: int1% = num1% \ den1%
' mod: rem1% = num1% MOD den1%
Reply
#16
Sorry that I can't see your results, because I don't have any glasses to test this stuff with.  (I've always preferred parallel stereo pairs m'self)

Remember that you need to take distance into account, so simply shifting the entire image by a so many pixels would not be enough.  For proper perspective, the red & blue offsets need to be a function of the "distance" from the viewer: "nearer" pixels in the scene get shifted more, "distant" pixels get shifted less.

For a program like @bplus's 3D cubes, you could divide the image into layers of cubes along the Z axis and shift each layer according to distance.  This would give a "ViewMaster effect" where you have several flat objects hovering in front of each other, but it would be something.

The best solution would be to have a 3D engine to generate the left-eye image (with full perspective) from one point of view, then generate the right-eye image from a point of view slightly to the right.
Reply
#17
@madscijr my thoughts are it's blurry as hell without glasses and I don't have the glasses to offer opinion on your results. Logically it seems redundant to apply 2 very different 3D techniques. My offer was very cheap 3D effect that might be comapred to minecraft' drawing everything as cubes ie 3d pixels. Yes for better 3D effect get the expensive 3D engine for sure.

Something tells me you are too hooked on idea of wearing those wierd glasses from the 50's Smile
b = b + ...
Reply
#18
(11-16-2024, 10:22 AM)JRace Wrote: Sorry that I can't see your results, because I don't have any glasses to test this stuff with.  (I've always preferred parallel stereo pairs m'self)

Remember that you need to take distance into account, so simply shifting the entire image by a so many pixels would not be enough.  For proper perspective, the red & blue offsets need to be a function of the "distance" from the viewer: "nearer" pixels in the scene get shifted more, "distant" pixels get shifted less.

For a program like @bplus's 3D cubes, you could divide the image into layers of cubes along the Z axis and shift each layer according to distance.  This would give a "ViewMaster effect" where you have several flat objects hovering in front of each other, but it would be something.

Exactly right - that's what we've been saying, and what that last code I posted is doing.

(11-16-2024, 10:22 AM)JRace Wrote: The best solution would be to have a 3D engine to generate the left-eye image (with full perspective) from one point of view, then generate the right-eye image from a point of view slightly to the right.

Yes, yes, that's the part I would need help with.

Thanks for your reply! Now get some red/blue glasses, they're cheap! LoL... Actually, if you send me a snail mail address in a private message, I'll be happy to mail you a pair so you can actually see if this is working!
Reply
#19
(11-16-2024, 03:06 PM)in bplus Wrote: @madscijr my thoughts are it's blurry as hell without glasses and I don't have the glasses to offer opinion on your results. Logically it seems redundant to apply 2 very different 3D techniques. My offer was very cheap 3D effect that might be comapred to minecraft' drawing everything as cubes ie 3d pixels. Yes for better 3D effect get the expensive 3D engine for sure.

Something tells me you are too hooked on idea of wearing those wierd glasses from the 50's Smile
Think about it - when we watch a regular movie or TV show in 2-D, the picture is not "3-D", but unless the program is a completely 2-D cartoon, the images ARE "three dimensional" in the same way your technique is - that is, there is perspective which shows depth, the people and buildings get smaller as they go farther away, etc. What makes a "3-D" movie (where you wear the glasses) or a hologram different from this, is that the same perspective and people and objects have depth, and seem to be coming out of the screen at you, because now your eyes are each seeing the picture from a different perspective, because our brains interpret this to allow us to perceive depth. So your 3-D method and the anaglyphic piece are not redundant to one another. The anaglyph simply takes the isometric image and makes it "pop"!  Big Grin

I think my last code starts to achieve the "viewmaster" effect JRace is talking about, but I haven't had a chance to test whether I got the "z" coordinate right - I could have it backwards. The closer to us the row of cubes is, the further it is supposed to be shifted right, but right now the code assumes a higher Z value means closer, and it could be that a LOWER z value is closer (which would make my code bass-ackwards!) When I am back at my PC, and have a minute, I will verify. 

PS If you are interested in 3D glasses, send me a mailing address in a private message and I'll send you a pair, cuz I got 10 of them!
Reply
#20
Well one of us is confusing 3D which does not need glasses with Stereoscopic vision which needs 2 slightly different perspectives, 2 eyes and a brain to rearrange/combine signals. POP is good word for effect.
b = b + ...
Reply




Users browsing this thread: 1 Guest(s)