Qbasicnews.com

Full Version: 3D raycasting program help
You're currently viewing a stripped down version of our content. View the full version with proper formatting.
Pages: 1 2
Hello. I have modified a raycasting engine i found in a tutorial to have the mouse look around. However, i am having problems with the program. here is the url to the program, as well as an explanation as to what is going on.

http://www.network54.com/Hide/Forum/mess...1066755647

feel free to reply to that message if you want.[/img]
does it usually take this long for someone to reply, or does nobody know 3D programming?

Anyways, incase you would rather see the code than a link to it, the code's right here.
The raycaster works fine, for the most part. one problem with it is that when you look down a hallway or something, you notice that the floor suddenly comes up in a slope and eventually meets the celling. why? also, if you look down too far or up too far, it bombs out. also, when you get close to a wall, the top part of the wall that shouldn't show on the screen (the part thats cut off) is shown at the bottom of the screen. any advice, tips, or help is welcome. it uses the mouse to look around, and w,s,a,d to move (thats the setup i use when playing quake. more comfortable for me). sometimes when you start, it will only show a blue screen. just stop and re-run it.


Code:
DEFINT A-Z

DECLARE SUB UpdateKeys (k%())

CONST TRUE = -1
CONST FALSE = 0

DIM keys(127)

DIM block(16, 16)

DIM X AS INTEGER, Y AS INTEGER
DIM i AS INTEGER

CONST PI = 3.141592

'- I made these LONG to prevent overflows
DIM wallup AS LONG
DIM WallDown AS LONG

DIM Texture(64, 64) AS INTEGER

DIM Scale AS LONG
DIM TexCount AS LONG
DIM Offset AS INTEGER


DIM mIn(7) AS INTEGER
DIM mOut(7) AS INTEGER

DIM SinTable(1280) AS SINGLE
DIM CosTable(1280) AS SINGLE
DIM TanTable(1280) AS SINGLE
DIM InvTanTable(1280) AS SINGLE
DIM AtnTable(-160 TO 159) AS SINGLE

Midline% = 100 '===== our midline variable

FOR i = 0 TO 1280
IF i = 0 OR i = 320 OR i = 640 OR i = 960 THEN X = 1
SinTable(i) = SIN((i + X) * PI / 640)
CosTable(i) = COS((i + X) * PI / 640)
TanTable(i) = TAN((i + X) * PI / 640)
InvTanTable(i) = 1 / TAN((i + X) * PI / 640)
NEXT i

FOR i = -160 TO 159
AtnTable(i) = ATN(i / 160) * 640 / PI
NEXT i

DIM xStep AS INTEGER
DIM yStep AS INTEGER

DIM ang AS SINGLE
DIM Slope AS SINGLE
DIM InvSlope AS SINGLE


DIM Slope64 AS SINGLE
DIM InvSlope64 AS SINGLE

DIM WallHitX AS INTEGER
DIM WallHitY AS INTEGER

DIM DirX AS INTEGER
DIM DirY AS INTEGER

DIM DistanceX AS SINGLE
DIM DistanceY AS SINGLE
DIM Distance AS SINGLE

DIM XonY AS SINGLE
DIM YonY AS SINGLE
DIM XonX AS SINGLE
DIM YonX AS SINGLE

TYPE tViewer
Angle AS SINGLE
X AS SINGLE
Y AS SINGLE
ox AS SINGLE '- Stores old X coordinate of viewer
oy AS SINGLE '- Stores old Y coordinate of viewer
END TYPE

DIM Viewer AS tViewer

CONST UP = -1
CONST DOWN = 1
CONST LEFT = -1
CONST RIGHT = 1


FOR Y = 1 TO 10
FOR X = 1 TO 10
READ Grid(X, Y)
IF Grid(X, Y) = 9 THEN
Viewer.X = X * 64 - 32
Viewer.Y = Y * 64 - 32
Grid(X, Y) = 0
END IF
NEXT X
NEXT Y

SCREEN 13
CLS

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

FOR Y = 0 TO 15
FOR X = 1 TO 16
READ block(16 - X, Y)
NEXT
NEXT

FOR Y = 0 TO 63 STEP 16
FOR X = 0 TO 63 STEP 16
FOR y2 = 0 TO 15
FOR x2 = 0 TO 15
Texture(X + x2, Y + y2) = block(x2, y2)
'Texture(x, y) = (x XOR y) * 4
NEXT
NEXT
NEXT X
NEXT Y


'main loop
DO

UpdateKeys keys() 'updates the keys array

COLOR 15

'strafing
IF keys(32) THEN 'ky$ = CHR$(0) + "M" THEN
'Viewer.Angle = Viewer.Angle + 32
Viewer.X = Viewer.X - SIN(Viewer.Angle * PI / 640) * 8
IF Grid(Viewer.X \ 64, Viewer.Y \ 64) THEN Viewer.X = Viewer.ox

Viewer.Y = Viewer.Y - COS(Viewer.Angle * PI / 640) * 8
IF Grid(Viewer.X \ 64, Viewer.Y \ 64) THEN Viewer.Y = Viewer.oy
END IF

IF keys(30) THEN 'ky$ = CHR$(0) + "K" THEN
'Viewer.Angle = Viewer.Angle - 32
Viewer.X = Viewer.X + SIN(Viewer.Angle * PI / 640) * 8
IF Grid(Viewer.X \ 64, Viewer.Y \ 64) THEN Viewer.X = Viewer.ox

Viewer.Y = Viewer.Y + COS(Viewer.Angle * PI / 640) * 8
IF Grid(Viewer.X \ 64, Viewer.Y \ 64) THEN Viewer.Y = Viewer.oy
END IF

Viewer.ox = Viewer.X
Viewer.oy = Viewer.Y

'\\\\\keys forward and backward////
IF keys(17) THEN 'ky$ = CHR$(0) + "H" THEN
Viewer.X = Viewer.X + COS(Viewer.Angle * PI / 640) * 8
IF Grid(Viewer.X \ 64, Viewer.Y \ 64) THEN Viewer.X = Viewer.ox

Viewer.Y = Viewer.Y - SIN(Viewer.Angle * PI / 640) * 8
IF Grid(Viewer.X \ 64, Viewer.Y \ 64) THEN Viewer.Y = Viewer.oy
END IF
IF keys(31) THEN 'ky$ = CHR$(0) + "P" THEN
Viewer.X = Viewer.X - COS(Viewer.Angle * PI / 640) * 8
IF Grid(Viewer.X \ 64, Viewer.Y \ 64) THEN Viewer.X = Viewer.ox

Viewer.Y = Viewer.Y + SIN(Viewer.Angle * PI / 640) * 8
IF Grid(Viewer.X \ 64, Viewer.Y \ 64) THEN Viewer.Y = Viewer.oy
END IF

mIn(0) = 11
CALL INT86OLD(&H33, mIn(), mOut())
Viewer.Angle = Viewer.Angle + mOut(2)


'\\\\\mouse forward and backward/////

Midline% = Midline% - mOut(3)

'Viewer.X = Viewer.X - COS(Viewer.Angle * PI / 640) * mOut(3)
'IF Grid(Viewer.X \ 64, Viewer.Y \ 64) THEN Viewer.X = Viewer.ox

'Viewer.Y = Viewer.Y + SIN(Viewer.Angle * PI / 640) * mOut(3)
'IF Grid(Viewer.X \ 64, Viewer.Y \ 64) THEN Viewer.Y = Viewer.oy

IF Viewer.Angle < 0 THEN Viewer.Angle = Viewer.Angle + 1280
IF Viewer.Angle > 1280 THEN Viewer.Angle = Viewer.Angle - 1280

FOR i = -160 TO 159

ang = Viewer.Angle + AtnTable(i)

IF ang < 0 THEN ang = ang + 1280
IF ang >= 1280 THEN ang = ang - 1280

IF ang = 0 OR ang = 320 OR ang = 640 OR ang = 960 THEN ang = ang + 1

Slope = TanTable(ang)
Slope = ABS(Slope)

InvSlope = InvTanTable(ang)
InvSlope = ABS(InvSlope)

SELECT CASE ang
CASE 0 TO 320 '- Quadrant I
DirX = RIGHT
DirY = UP
CASE 321 TO 640 '- Quadrant II
DirX = LEFT
DirY = UP
CASE 641 TO 960 '- Quadrant III
DirX = LEFT
DirY = DOWN
CASE 961 TO 1280 '- Quadrant IV
DirX = RIGHT
DirY = DOWN
END SELECT


IF DirX = LEFT THEN
XonY = (Viewer.X \ 64) * 64 - .001
ELSE
XonY = (Viewer.X \ 64) * 64 + 64
END IF

YonY = ABS(Viewer.X - XonY) * Slope

YonY = Viewer.Y + YonY * DirY

IF DirY = UP THEN
YonX = (Viewer.Y \ 64) * 64 - .001
ELSE
YonX = (Viewer.Y \ 64) * 64 + 64
END IF

XonX = ABS(Viewer.Y - YonX) * InvSlope
XonX = Viewer.X + XonX * DirX

Slope64 = Slope * 64 * DirY
InvSlope64 = InvSlope * 64 * DirX

WallHitX = 0 '- Set our wall check values to zero
WallHitY = 0 '- Set our wall check values to zero
xStep = 64 * DirX '- Calculate the step values out here, no need to keep
yStep = 64 * DirY '- on re-calculating them in the loop below
DO

IF XonY < 0 OR XonY > 640 OR YonY < 0 OR YonY > 640 THEN WallHitY = 1
IF YonX < 0 OR YonX > 640 OR XonX < 0 OR XonX > 640 THEN WallHitX = 1

IF WallHitY = 0 THEN WallHitY = Grid((XonY - .5) \ 64, (YonY - .5) \ 64)
IF WallHitX = 0 THEN WallHitX = Grid((XonX - .5) \ 64, (YonX - .5) \ 64)

IF WallHitY = 0 THEN
XonY = XonY + xStep
YonY = YonY + Slope64
END IF

IF WallHitX = 0 THEN
YonX = YonX + yStep
XonX = XonX + InvSlope64
END IF

LOOP WHILE WallHitY = 0 OR WallHitX = 0


DistanceY = ABS((XonY - Viewer.X) * CosTable(Viewer.Angle) - (YonY - Viewer.Y) * SinTable(Viewer.Angle))
DistanceX = ABS((XonX - Viewer.X) * CosTable(Viewer.Angle) - (YonX - Viewer.Y) * SinTable(Viewer.Angle))

IF DistanceY < DistanceX THEN
Distance = DistanceY
Offset = YonY AND 63
ELSE
Distance = DistanceX
Offset = XonX AND 63
END IF

IF Distance = 0 THEN Distance = 1

Distance = 4096 / Distance
Distance = INT(Distance)

LINE (i + 160, -1)-(i + 160, 99 - Distance + (wallup - 75)), 55

Scale = 6400000 \ (Distance + Distance + 3)

TexCount = 0

wallup = Midline% - Distance 'Wallup =100-Distance

IF wallup < -90 THEN
wallup = -90
TexCount = ABS(100 - Distance) * Scale
END IF

WallDown = Midline% + Distance 'WallDown = 100 + Distance

IF WallDown > 200 THEN WallDown = 200

DEF SEG = &HA000
n& = wallup * 320 + i + 160
FOR Y = wallup TO WallDown

TexCount = TexCount + Scale

POKE (n&), Texture(Offset, TexCount \ 100000)
n& = n& + 320

NEXT Y
DEF SEG

LINE (i + 160, 101 + Distance + (WallDown - 125))-(i + 160, 200), 1

'crosshair
LINE (155, 95)-STEP(0, 4), 4
LINE (155, 101)-STEP(0, 4), 4
LINE (150, 100)-STEP(4, 0), 4
LINE (156, 100)-STEP(4, 0), 4

IF i = 0 THEN
LOCATE 1, 1
PRINT WallDown
END IF

NEXT i

LOOP UNTIL keys(1)

DATA 1,1,1,1,1,1,1,1,1,1
DATA 1,0,0,0,0,0,0,1,1,1
DATA 1,0,1,0,0,1,0,1,1,1
DATA 1,1,1,0,0,1,0,0,0,1
DATA 1,0,0,0,0,1,0,0,0,1
DATA 1,0,0,9,0,1,0,1,1,1
DATA 1,0,0,0,0,1,0,1,1,1
DATA 1,0,0,0,0,0,0,0,0,1
DATA 1,0,0,0,0,0,0,0,0,1
DATA 1,1,1,1,1,1,1,1,1,1

DATA 8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8
DATA 8,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7
DATA 8,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7
DATA 8,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7
DATA 8,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7
DATA 8,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7
DATA 8,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7
DATA 8,7,7,7,7,7,7,7,7,7,7,7,7,7,7,7
DATA 8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8
DATA 7,7,7,7,7,7,7,8,7,7,7,7,7,7,7,7
DATA 7,7,7,7,7,7,7,8,7,7,7,7,7,7,7,7
DATA 7,7,7,7,7,7,7,8,7,7,7,7,7,7,7,7
DATA 7,7,7,7,7,7,7,8,7,7,7,7,7,7,7,7
DATA 7,7,7,7,7,7,7,8,7,7,7,7,7,7,7,7
DATA 7,7,7,7,7,7,7,8,7,7,7,7,7,7,7,7
DATA 7,7,7,7,7,7,7,8,7,7,7,7,7,7,7,7

DEFSNG A-Z
SUB UpdateKeys (k%())
STATIC lastPress
press = INP(96)

IF press < 128 THEN 'when a key is pressed, the keyboard scan code is
k%(press) = TRUE 'returned. when released, the scan code + 128 is
lastPress = press 'returned
ELSE
k%(press - 128) = FALSE
IF press = 170 THEN k%(lastPress) = FALSE 'if 170 is returned, then
END IF 'last key that was pressed
'should be released
DEF SEG = 0
POKE 1052, PEEK(1050) 'clears keyboard buffer (gets rid of beeping)

END SUB
Answer:
http://rel.betterwebber.com/monodisc.zip

That's 3d programming.

No comments in code no help. ;*)

Don't have QB right now so I can't run it.
that's pretty cool though. i dont know anything about 3D, but i say put a restiction on the angles you can look. some thing boolen with degrees.
I can't really comment the code, seeing how its not mine. Over half of it is from a tutorial that i downloaded and started screwwing around with, and some of the time, I don't even know whats going on, which is why im having trouble fixing it. Im taking trig right now, so my knowledge of the trig functions is very limited, but i know enough to barly hang on to whats going on. I'll check the tutorial to see if there is a version of this raycaster with more comments, but there are no garenties....
I only modify code that disgusts me.
i too trig but i dont get qb use of sin and cos in 3D. will some one just please explane it sothat it easy to understand!! :x
Code:
'-----------------------------------------------------------------------------
'                                                            November, 2002
' ÜÜÜ    ÃœÃœ  Ãœ   Ü  ÃœÃœÃœ  ÃœÃœ   ÜÜÜ ÜÜÜÜÜ Ü Ü   Ü  ÃœÃœÃœ         by Joe King
' Û  Ã›  Ã›  Ã› Û   Û Û    Ã›  Ã› Û      Ã›   Û ÛÛ  Ã› Û
' 󧧆  Ã›ÃŸÃŸÃ›  ÃŸÃ›ÃŸ  Ã›    Ã›ÃŸÃŸÃ›  ÃŸÃŸÃœ   Û   Û Û Û Û Û ßßÜ
' Û   Û Û  Ã›   Û   ßÜÜÜ Û  Ã› ÜÜÜß   Û   Û Û  Ã›Ã› ßÜÜÜß
'      
'    ÃœÃœÃœÃœÃœ Ü  Ãœ ÜÜÜÜÜ  ÃœÃœÃœ  ÃœÃœÃœ  Ãœ  ÃœÃœ  Ãœ    ÃœÃœÃœ    ÃœÃœÃœÃœÃœ
'      Ã›   Û  Ã›   Û   Û   Û Û  Ã› Û Û  Ã› Û   Û            Ã›   FOR QBASIC
'      Ã›   Û  Ã›   Û   Û   Û 󧧆 Û ÛßßÛ Û    ÃŸÃŸÃœ    ÃŸÃŸÃŸÃŸÃŸÃœ
'      Ã›   ßÜÜß   Û   ßÜÜÜß Û  Ã› Û Û  Ã› ÛÜÜ ÜÜÜß    ÃœÃœÃœÃœÃœÃŸ   PART 12:
'                                                            Optimized
'                                                            Raycaster with
'                                                            Texture Mapping
'------------------------------------------------------------------------------

  DIM x AS INTEGER, y AS INTEGER
  DIM i AS INTEGER

  CONST PI = 3.141592
                  
  DIM WallUp AS INTEGER               '- Top of wall slice
  DIM WallDown AS INTEGER             '- Bottom of wall slice

  DIM Texture(64, 64) AS INTEGER      '- The texture array that will hold the
                                      '- texture
  DIM Scale AS LONG                   '- The scale
  DIM TexCount AS LONG                '- The texture counter
  DIM Offset AS INTEGER               '- This is the offset of the wall that
                                      '- the ray hit

  DIM mIn(7) AS INTEGER
  DIM mOut(7) AS INTEGER

  DIM SinTable(1280) AS SINGLE
  DIM CosTable(1280) AS SINGLE
  DIM TanTable(1280) AS SINGLE
  DIM InvTanTable(1280) AS SINGLE
  DIM AtnTable(-160 TO 159) AS SINGLE

  FOR i = 0 TO 1280
    IF i = 0 OR i = 320 OR i = 640 OR i = 960 THEN x = 1
    SinTable(i) = SIN((i + x) * PI / 640)
    CosTable(i) = COS((i + x) * PI / 640)
    TanTable(i) = TAN((i + x) * PI / 640)
    InvTanTable(i) = 1 / TAN((i + x) * PI / 640)
  NEXT i

  FOR i = -160 TO 159
    AtnTable(i) = ATN(i / 160) * 640 / PI
  NEXT i

  DIM xStep AS INTEGER
  DIM yStep AS INTEGER

  DIM ang AS SINGLE
  DIM Slope AS SINGLE
  DIM InvSlope AS SINGLE
                      

  DIM Slope64 AS SINGLE
  DIM InvSlope64 AS SINGLE

  DIM WallHitX AS INTEGER
  DIM WallHitY AS INTEGER

  DIM DirX AS INTEGER
  DIM DirY AS INTEGER

  DIM DistanceX AS SINGLE
  DIM DistanceY AS SINGLE
  DIM Distance AS SINGLE

  DIM XonY AS SINGLE
  DIM YonY AS SINGLE
  DIM XonX AS SINGLE
  DIM YonX AS SINGLE

  TYPE tViewer
    Angle AS SINGLE
    x AS SINGLE
    y AS SINGLE
  END TYPE

  DIM Viewer AS tViewer

  CONST UP = -1
  CONST DOWN = 1
  CONST LEFT = -1
  CONST RIGHT = 1


  FOR y = 1 TO 10
    FOR x = 1 TO 10
      READ Grid(x, y)
      IF Grid(x, y) = 9 THEN
        Viewer.x = x * 64 - 32
        Viewer.y = y * 64 - 32
        Grid(x, y) = 0
      END IF
    NEXT x
  NEXT y

  SCREEN 13
  CLS

  '- Create the gray-scale palettte
  FOR i = 0 TO 255
    OUT &H3C8, i

    OUT &H3C9, i / 4
    OUT &H3C9, i / 4
    OUT &H3C9, i / 4
  NEXT i

  '- Create the texture
  FOR y = 0 TO 63
    FOR x = 0 TO 63
      Texture(x, y) = (x XOR y) * 4
    NEXT x
  NEXT y

  DO

    key$ = INKEY$

    IF key$ = CHR$(27) THEN END
    IF key$ = CHR$(0) + "M" THEN Viewer.Angle = Viewer.Angle + 32
    IF key$ = CHR$(0) + "K" THEN Viewer.Angle = Viewer.Angle - 32
    IF key$ = CHR$(0) + "H" THEN
      Viewer.x = Viewer.x + COS(Viewer.Angle * PI / 640) * 8
      Viewer.y = Viewer.y - SIN(Viewer.Angle * PI / 640) * 8
    END IF
    IF key$ = CHR$(0) + "P" THEN
      Viewer.x = Viewer.x - COS(Viewer.Angle * PI / 640) * 8
      Viewer.y = Viewer.y + SIN(Viewer.Angle * PI / 640) * 8
    END IF

    mIn(0) = 11
    CALL INT86OLD(&H33, mIn(), mOut())
    Viewer.Angle = Viewer.Angle + mOut(2)

    Viewer.x = Viewer.x - COS(Viewer.Angle * PI / 640) * mOut(3)
    Viewer.y = Viewer.y + SIN(Viewer.Angle * PI / 640) * mOut(3)


    IF Viewer.Angle < 0 THEN Viewer.Angle = Viewer.Angle + 1280
    IF Viewer.Angle > 1280 THEN Viewer.Angle = Viewer.Angle - 1280

  FOR i = -160 TO 159
                  
    ang = Viewer.Angle + AtnTable(i)

    IF ang < 0 THEN ang = ang + 1280
    IF ang >= 1280 THEN ang = ang - 1280

    IF ang = 0 OR ang = 320 OR ang = 640 OR ang = 960 THEN ang = ang + 1

    Slope = TanTable(ang)
    Slope = ABS(Slope)
  
    InvSlope = InvTanTable(ang)
    InvSlope = ABS(InvSlope)
  
    SELECT CASE ang
      CASE 0 TO 320         '- Quadrant I
        DirX = RIGHT
        DirY = UP
      CASE 321 TO 640       '- Quadrant II
        DirX = LEFT
        DirY = UP
      CASE 641 TO 960       '- Quadrant III
        DirX = LEFT
        DirY = DOWN
      CASE 961 TO 1280      '- Quadrant IV
        DirX = RIGHT
        DirY = DOWN
    END SELECT

  
    IF DirX = LEFT THEN
      XonY = (Viewer.x \ 64) * 64 - .001
    ELSE
      XonY = (Viewer.x \ 64) * 64 + 64
    END IF

    YonY = ABS(Viewer.x - XonY) * Slope
  
    YonY = Viewer.y + YonY * DirY
  
    IF DirY = UP THEN
      YonX = (Viewer.y \ 64) * 64 - .001
    ELSE
      YonX = (Viewer.y \ 64) * 64 + 64
    END IF

    XonX = ABS(Viewer.y - YonX) * InvSlope
    XonX = Viewer.x + XonX * DirX
  
    Slope64 = Slope * 64 * DirY
    InvSlope64 = InvSlope * 64 * DirX

    WallHitX = 0  '- Set our wall check values to zero
    WallHitY = 0  '- Set our wall check values to zero
    xStep = 64 * DirX '- Calculate the step values out here, no need to keep
    yStep = 64 * DirY '- on re-calculating them in the loop below
    DO

      IF XonY < 0 OR XonY > 640 OR YonY < 0 OR YonY > 640 THEN WallHitY = 1
      IF YonX < 0 OR YonX > 640 OR XonX < 0 OR XonX > 640 THEN WallHitX = 1

      IF WallHitY = 0 THEN WallHitY = Grid((XonY - .5) \ 64, (YonY - .5) \ 64)
      IF WallHitX = 0 THEN WallHitX = Grid((XonX - .5) \ 64, (YonX - .5) \ 64)
  
      IF WallHitY = 0 THEN
        XonY = XonY + xStep
        YonY = YonY + Slope64
      END IF

      IF WallHitX = 0 THEN
        YonX = YonX + yStep
        XonX = XonX + InvSlope64
      END IF
  
    LOOP WHILE WallHitY = 0 OR WallHitX = 0

  
    DistanceY = ABS((XonY - Viewer.x) * CosTable(Viewer.Angle) - (YonY - Viewer.y) * SinTable(Viewer.Angle))
    DistanceX = ABS((XonX - Viewer.x) * CosTable(Viewer.Angle) - (YonX - Viewer.y) * SinTable(Viewer.Angle))

    IF DistanceY < DistanceX THEN
      Distance = DistanceY
      Offset = YonY AND 63
    ELSE
      Distance = DistanceX
      Offset = XonX AND 63
    END IF

    IF Distance = 0 THEN Distance = 1
                                    
    Distance = 4096 / Distance
    Distance = INT(Distance)          '- Important: once your done with the
                                      '- distance, chop of the decimals.
                                      '- This helps make the texturing look
                                      '- nicer. You can removed that line and
                                      '- see what I mean.

    '- Draw the line
    LINE (i + 160, -1)-(i + 160, 99 - Distance), 55
  
    '- I used an extra couple of more zeros for better quality
    Scale = 6400000 \ (Distance + Distance + 3) '- I put 3 instead of 2
                                                '- since 3 is odd, it helps
                                                '- make the texturing look
                                                '- nicer
                                        '- The size of the wallstrip is
                                        '- distance * 2, or distance+distance
    TexCount = 0                        '- Set the texture counter to zero
  
    WallUp = 100 - Distance             '- Calculate the top of the wall slice
  
    '- If the wall slice is too big, make the top of the wall slice start at
    '- zero and set the TexCount to start at the right spot
    IF WallUp < 0 THEN
      WallUp = 0
      TexCount = ABS(100 - Distance) * Scale
    END IF

    WallDown = 100 + Distance           '- Calculate the bottom of the wall
                                        '- slice
    IF WallDown > 200 THEN WallDown = 200   '- If the wall slice is too big,
                                            '- chop it down
  
    DEF SEG = &HA000
    n& = WallUp * 320 + i + 160
    FOR y = WallUp TO WallDown          '- Go from WallUp to WallDown, since
                                        '- we clipped the wall slice, the
                                        '- program won't go super slow when
                                        '- up close and personal with a wall
    
      TexCount = TexCount + Scale       '- Add the texture counter by the
                                        '- scale
    
      POKE (n&), Texture(Offset, TexCount \ 100000)'- Plot the pixel
      n& = n& + 320
    
    NEXT y
    DEF SEG
  
    LINE (i + 160, 101 + Distance)-(i + 160, 200), 1

  NEXT i

  LOOP

  DATA 1,1,1,1,1,1,1,1,1,1
  DATA 1,0,0,0,0,0,0,1,1,1
  DATA 1,0,1,0,0,1,0,1,1,1
  DATA 1,1,1,0,0,1,0,0,0,1
  DATA 1,0,0,0,0,1,0,0,0,1
  DATA 1,0,0,9,0,1,0,1,1,1
  DATA 1,0,0,0,0,1,0,1,1,1
  DATA 1,0,0,0,0,0,0,0,0,1
  DATA 1,0,0,0,0,0,0,0,0,1
  DATA 1,1,1,1,1,1,1,1,1,1


'- As you can see, with these little optimizations, the ray caster runs much
'- faster and nicer.
'---------------------------------------------------------------------------

unfortunatly, it is not the exact same as the one i have, but i hope it helps.
Check out joe kings tutorials on raycasting. There the ones I used.
goto

http://users.sisna.com/joeking2/deltacode/downloads.htm
click on "Raycasting Tutorials I" or "Raycasting Tutorials II" or "Raycasting Tutorials III" in the Dos section.

meaby they will help explain cos & sin for 3d programming.
I think the problem is that this is not 3D after all so your vision can't be completely free. To know what I am saying just check commercial raycasters. In Duke Nukem 3D or Rise Of The Triad, for example, you can free look but only within some limits, and even that way, if the angle is too wide you get deformation. That's because of the projection used, the vertical lines are always vertical so you lose perspective when you stretch stuff so much.
Pages: 1 2