Skip to content

Commit

Permalink
Some rendering fixes
Browse files Browse the repository at this point in the history
  • Loading branch information
danielholmes committed Feb 24, 2020
1 parent 6b67090 commit a7d681c
Show file tree
Hide file tree
Showing 10 changed files with 238 additions and 207 deletions.
2 changes: 1 addition & 1 deletion app-debug/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ import Wolf3D.Debug.Dummy
import Wolf3D.Debug.Display

main :: IO ()
main = createMain 3 dummyWorld2 $
main = createMain 3 dummyWorld $
\r -> do
setupRenderer r
d <- loadRenderData r
Expand Down
42 changes: 6 additions & 36 deletions src/Wolf3D/Debug/Dummy.hs
Original file line number Diff line number Diff line change
@@ -1,49 +1,19 @@
module Wolf3D.Debug.Dummy (
dummyWorld,
dummyWorld2,
dummyWorldSingleWall
) where

import Wolf3D.Engine
import Wolf3D.Sim
import Data.Vector
import Data.Maybe


fromMetres :: Double -> Double
fromMetres m = m * 10000

fromBlocks :: Double -> Double
fromBlocks i = fromMetres (i * 3)

fromVBlocks :: Vector2 -> Vector2
fromVBlocks (Vector2 x y) = Vector2 (fromBlocks x) (fromBlocks y)

dummyWorld :: World Wolf3DSimEntity
dummyWorld = createWorld GreenCeiling wm items
where
-- metreWalls = [ Wall (Vector2 0 0) (Vector2 0 7) Red
-- , Wall (Vector2 (-4) 4) (Vector2 3 0) Green
-- , Wall (Vector2 (-1) 4) (Vector2 0 6) Blue
-- , Wall (Vector2 (-1) 10) (Vector2 2 0) Red
-- , Wall (Vector2 1 10) (Vector2 0 (-6)) Green
-- , Wall (Vector2 1 4) (Vector2 3 0) Blue
-- , Wall (Vector2 4 4) (Vector2 0 (-7)) Red]
-- walls = map (\(Wall o s m) -> Wall (fromVBlocks o) (fromVBlocks s) m) metreWalls
wm = []
heroPos = (5, 5)
items = [ SEEnvItem (EnvItem Drum (fromVBlocks (Vector2 (-3.5) 3.5)))
, SEEnvItem (EnvItem Light (fromVBlocks (Vector2 0 2)))
, SEEnvItem (EnvItem Flag (fromVBlocks (Vector2 3.5 3.5)))
, SEHero (createHeroFromTilePosition heroPos) ]

dummyWorld2 :: World Wolf3DSimEntity
dummyWorld2 = fromGrid YellowCeiling [["WB1", "WB1", "WG1", "WB1", "WB1"],
["WB1", "DR", "", "DR", "WB1"],
["WB1", "", "", "", "WB1"],
["WB2", "", "H", "", "WB2"],
["WB2", "", "", "", "WB2"],
["WB2", "WB2", "WB2", "WB2", "WB2"]]
dummyWorld = fromGrid GreyCeiling [["WB1", "WB1", "WG1", "WB1", "WB1"],
["WB1", "DR", "", "DR", "WB1"],
["WB1", "", "", "", "WB1"],
["WB2", "", "H", "", "WB2"],
["WB2", "", "", "", "WB2"],
["WB2", "WB2", "WB2", "WB2", "WB2"]]

dummyWorldSingleWall :: World Wolf3DSimEntity
dummyWorldSingleWall = createWorld GreyCeiling [] [SEHero (createHeroFromTilePosition (1, 1))]
Expand Down
5 changes: 2 additions & 3 deletions src/Wolf3D/Display.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,6 @@ import qualified Data.Map as M
import Foreign.C.Types (CInt)
import GHC.Word (Word8)
import Wolf3D.Display.Data
import Debug.Trace


ceilingColors :: M.Map Ceiling (SDL.V4 Word8)
Expand Down Expand Up @@ -92,10 +91,10 @@ renderWallLine r (RenderData {wallTextures=wt}) (pixel, WallRayHit {material=m,
projectedHeight = min actionHeight proposedProjectedHeight
heightRatio = (fromIntegral projectedHeight / fromIntegral proposedProjectedHeight) :: Double
scaledTextureHeight = round (fromIntegral tH * heightRatio)
scaledTY = tY + tH - (scaledTextureHeight `div` 2)
scaledTY = tY + tH `div` 2 - (scaledTextureHeight `div` 2)
actionY = fromIntegral (fromIntegral halfActionHeight - (projectedHeight `div` 2))
textureXDouble = hitWallTextureRatio * (fromIntegral tW - 1)
textureX = traceShow ("dist", distRatio, tH, max 1 (1 / distRatio), scaledTextureHeight) (tX + floor textureXDouble)
textureX = tX + floor textureXDouble
sourceRect = Just (mkSDLRect textureX scaledTY 1 scaledTextureHeight)
destRect = Just (mkSDLRect (pixel + actionAreaX) (actionY + actionAreaY) 1 projectedHeight)

Expand Down
9 changes: 7 additions & 2 deletions src/Wolf3D/Display/Data.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,10 +26,15 @@ data HitDirection = Horizontal | Vertical
data WallRayHit = WallRayHit {material :: WallMaterial
, direction :: HitDirection
, distance :: Int
, tilePosition :: Int
, intercept :: (Int, Int)}
, tilePosition :: Int}
deriving (Eq, Show)

createWallRayHit :: WallMaterial -> HitDirection -> Int -> Int -> WallRayHit
createWallRayHit m dir dist tp
| dist < 0 = error ("Dist < 0: " ++ (show dist))
| tp < 0 || tp >= tileGlobalSize = error ("Tile Post outside bounds [0-" ++ (show tileGlobalSize) ++ "]: " ++ (show tp))
| otherwise = WallRayHit {material=m, direction=dir, distance=dist, tilePosition=tp}

fieldOfView :: Angle
fieldOfView = 75

Expand Down
Loading

0 comments on commit a7d681c

Please sign in to comment.