Skip to content

Commit

Permalink
BJ Face and some hero state and render stuff
Browse files Browse the repository at this point in the history
  • Loading branch information
danielholmes committed Mar 1, 2020
1 parent fb89300 commit de934f6
Show file tree
Hide file tree
Showing 26 changed files with 198 additions and 103 deletions.
Binary file removed assets/bj.png
Binary file not shown.
Binary file removed assets/hud-base.png
Binary file not shown.
Binary file added assets/hud/base.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file added assets/hud/bj.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
File renamed without changes
File renamed without changes
File renamed without changes
File renamed without changes
File renamed without changes
File renamed without changes
File renamed without changes
File renamed without changes
File renamed without changes
File renamed without changes
File renamed without changes
8 changes: 2 additions & 6 deletions src/Wolf3D/Animation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,9 +58,5 @@ createAnimation = Animation
animationTexture :: Animation -> SDL.Texture
animationTexture (Animation s) = spriteSheetTexture s

getAnimationFrame :: Animation -> Double -> AnimationFrame
getAnimationFrame (Animation s@(SpriteSheet _ _ ls)) progress
| progress >= 0 && progress <= 1 = getSpriteSheetLocation s locationIndex
| otherwise = error ("Invalid progress " ++ show progress)
where
locationIndex = round (progress * fromIntegral (length ls - 1))
getAnimationFrame :: Animation -> Int -> AnimationFrame
getAnimationFrame (Animation s) i = getSpriteSheetLocation s i
2 changes: 1 addition & 1 deletion src/Wolf3D/Debug/Display.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ render r drd@(DebugRenderData rd _) sr = do
where
w = simRunWorld sr
runRender = do
D.renderHud r rd
D.renderHud r rd (worldHero w)
D.renderWorld r rd w

createDebugText :: SimRun -> Integer -> String
Expand Down
23 changes: 12 additions & 11 deletions src/Wolf3D/Display.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,6 @@ import Wolf3D.Runner
import Wolf3D.SDLUtils
import Wolf3D.Geom
import Wolf3D.WorldData
import Wolf3D.Hero
import Wolf3D.Display.Utils
import Wolf3D.Display.Hud
import Wolf3D.Display.Ray
Expand All @@ -24,7 +23,6 @@ import Data.StateVar (($=))
import Data.Foldable
import Data.Maybe
import Data.Bits
import Control.Monad (mfilter)
import qualified Data.Map as M
import Foreign.C.Types (CInt)
import GHC.Word (Word8)
Expand All @@ -45,8 +43,9 @@ setupRenderer r = SDL.rendererDrawBlendMode r $= SDL.BlendAlphaBlend

render :: SDL.Renderer -> RenderData -> SimRun -> IO ()
render r d s = do
renderHud r d
renderWorld r d (simRunWorld s)
let w@(World{worldHero=h}) = simRunWorld s
renderHud r d h
renderWorld r d w
SDL.present r

renderWorld :: SDL.Renderer -> RenderData -> World -> IO ()
Expand Down Expand Up @@ -82,7 +81,9 @@ renderWallLine r (RenderData {wallTextures=wt}) (pixel, WallRayHit {material=m,
shadingIndex = if d == Horizontal then 1 else 0
(SDL.Rectangle (SDL.P (SDL.V2 tX tY)) (SDL.V2 tW tH)) = getSpriteSheetLocation wallSheet shadingIndex
texture = spriteSheetTexture wallSheet
hitWallTextureRatio = (fromIntegral tilePos / fromIntegral tileGlobalSize) :: Double
-- tileGlobalSize - because textures on walls displaying flipped.
-- Not sure where the difference is with original
hitWallTextureRatio = (fromIntegral (tileGlobalSize - tilePos) / fromIntegral tileGlobalSize) :: Double

distRatio = (fromIntegral viewDist / fromIntegral dist) :: Double
globalDist = (round (distRatio * fromIntegral tileGlobalSize)) :: CInt
Expand Down Expand Up @@ -118,16 +119,16 @@ renderWallLine r (RenderData {wallTextures=wt}) (pixel, WallRayHit {material=m,
-- destRect = mkSDLRect x projectedTop (round projectedWidth) projectedHeight

renderWeapon :: SDL.Renderer -> RenderData -> WorldTicks -> Weapon -> IO ()
renderWeapon r RenderData {weaponTextures=wt} t w =
renderWeapon r RenderData {weaponTextures=wt} _ _ =
copyWithActionOffset r (intRectPos actionArea) texture sourceRect destRect
where
totalAnimationTime = 400
sinceUsed = fmap (t -) (lastTimeWeaponUsed w)
animationTime = mfilter (< totalAnimationTime) sinceUsed
progress = maybe 0 ((/ fromIntegral totalAnimationTime) . fromIntegral) animationTime
-- totalAnimationTime = 400
-- sinceUsed = fmap (t -) (lastTimeWeaponUsed w)
-- animationTime = mfilter (< totalAnimationTime) sinceUsed
-- progress = maybe 0 ((/ fromIntegral totalAnimationTime) . fromIntegral) animationTime
animation = fromJust (M.lookup "Pistol" wt)
texture = animationTexture animation
sourceRect@(SDL.Rectangle _ (SDL.V2 tW tH)) = getAnimationFrame animation progress
sourceRect@(SDL.Rectangle _ (SDL.V2 tW tH)) = getAnimationFrame animation 0
destX = actionAreaX + ((actionWidth - tW) `div` 2)
destY = actionAreaY + (actionHeight - tH)
destRect = mkSDLRect destX destY tW tH
19 changes: 12 additions & 7 deletions src/Wolf3D/Display/Hud.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,15 @@
module Wolf3D.Display.Hud (renderHud) where

import Wolf3D.Display.Data
import Wolf3D.WorldData
import Wolf3D.SDLUtils
import Wolf3D.Animation
import Foreign.C.Types (CInt)
import qualified SDL
import Control.Monad (void)

bjFaceX :: CInt
bjFaceX = 134
bjFaceX = 136

bjFaceY :: CInt
bjFaceY = fromIntegral (screenHeight - 35)
Expand All @@ -19,11 +20,11 @@ hudWeaponX = 254
hudWeaponY :: CInt
hudWeaponY = fromIntegral (screenHeight - 33)

renderHud :: SDL.Renderer -> RenderData -> IO ()
renderHud r d = do
renderHud :: SDL.Renderer -> RenderData -> Hero -> IO ()
renderHud r d h = do
let textY = 176
renderHudBase r d
renderHudFace r d
renderHudFace r d h
renderHudNum r d (34, textY) 1 -- Floor
renderHudNum r d (120, textY) 3 -- Lives
renderHudNum r d (96, textY) 0 -- Score
Expand Down Expand Up @@ -52,14 +53,18 @@ renderHudNum r d (x, y) num = do
from@(SDL.Rectangle _ (SDL.V2 width height)) = getSpriteSheetLocation numsSheet lastNum
destRect = mkSDLRect (x - width) y width height

renderHudFace :: SDL.Renderer -> RenderData -> IO ()
renderHudFace r (RenderData {bjFace=a}) = do
-- TODO: Draw dead face if no health left
-- TODO: Alter which face based on health
-- StatusDrawPic (17,4,FACE1APIC+3*((100-gamestate.health)/16)+gamestate.faceframe);
renderHudFace :: SDL.Renderer -> RenderData -> Hero -> IO ()
renderHudFace r (RenderData {bjFace=a}) (Hero{heroFace=HeroFace _ faceFrame}) = do
SDL.copy r texture (Just sourceRect) (Just destRect)
where
texture = animationTexture a
sourceRect@(SDL.Rectangle _ (SDL.V2 tW tH)) = getAnimationFrame a 0
sourceRect@(SDL.Rectangle _ (SDL.V2 tW tH)) = getAnimationFrame a faceFrame
destRect = mkSDLRect bjFaceX bjFaceY tW tH


renderHudWeapon :: SDL.Renderer -> RenderData -> IO ()
renderHudWeapon r (RenderData {hudWeapons=w}) = do
SDL.copy r texture (Just sourceRect) (Just destRect)
Expand Down
45 changes: 24 additions & 21 deletions src/Wolf3D/Display/Ray.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,26 +39,29 @@ focalCosTable = listArray (0, fineAngles - 1) (map (* fromIntegral focalLength)
tanTable :: Array FineAngle Double
tanTable = array (0, fineAngles - 1) [(i, tan (fineToNormalAngle i * degToRad)) | i <- allFineAngles]

data RayData = DiagonalRayData {focal :: (Int, Int)
, fineViewAngleOffset :: FineAngle
, horInterceptYTile :: Int
, verInterceptXTile :: Int
, xTileStep :: Int
, yTileStep :: Int
, xStep :: Int
, yStep :: Int
, horNextIntercept :: (Int, Int)
, verNextIntercept :: (Int, Int)} |
HorizontalRayData {focal :: (Int, Int)
, fineViewAngleOffset :: FineAngle
, interceptY :: Int
, interceptXTile :: Int
, tileStep :: Int} |
VerticalRayData {focal :: (Int, Int)
, fineViewAngleOffset :: FineAngle
, interceptX :: Int
, interceptYTile :: Int
, tileStep :: Int}
data RayData = DiagonalRayData
{ focal :: (Int, Int)
, fineViewAngleOffset :: FineAngle
, horInterceptYTile :: Int
, verInterceptXTile :: Int
, xTileStep :: Int
, yTileStep :: Int
, xStep :: Int
, yStep :: Int
, horNextIntercept :: (Int, Int)
, verNextIntercept :: (Int, Int)} |
HorizontalRayData
{ focal :: (Int, Int)
, fineViewAngleOffset :: FineAngle
, interceptY :: Int
, interceptXTile :: Int
, tileStep :: Int} |
VerticalRayData
{ focal :: (Int, Int)
, fineViewAngleOffset :: FineAngle
, interceptX :: Int
, interceptYTile :: Int
, tileStep :: Int}
deriving (Show)

fineViewAngleOffsets :: [FineAngle]
Expand Down Expand Up @@ -230,7 +233,7 @@ verRayCheck wm d@DiagonalRayData {focal=f
, yStep=dy
, verNextIntercept=currentIntercept@(x, y)} = case hitting of
Nothing -> nextRayCheck wm currentIntercept nextD
Just m -> WallRayHit {material=m
Just m -> WallRayHit { material=m
, direction=Vertical
, distance=hitDistance vAO f currentIntercept
, tilePosition=y `mod` tileGlobalSize}
Expand Down
94 changes: 69 additions & 25 deletions src/Wolf3D/Hero.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@ module Wolf3D.Hero (
staticHeroActionsState,
createHeroFromTilePosition,
modifyHeroActionState,
updateHeroActionsState,

heroSize,
createHero,
Expand All @@ -18,6 +17,7 @@ import Wolf3D.Geom
import Data.Vector
import Data.Maybe
import Data.List
import Data.Bits


simUpdateWeapon :: World -> Weapon -> Weapon
Expand Down Expand Up @@ -50,34 +50,69 @@ notBeingUsed (Pistol t _) = Pistol t False
Hero
-----------------------------------------------------------------------------------------------------------------------}
staticHeroActionsState :: HeroActionsState
staticHeroActionsState = HeroActionsState False False False False False
staticHeroActionsState = HeroActionsState False False False False False False

modifyHeroActionState :: HeroActionsState -> HeroAction -> Bool -> HeroActionsState
modifyHeroActionState (HeroActionsState _ d l r s) MoveForward a = HeroActionsState a d l r s
modifyHeroActionState (HeroActionsState u _ l r s) MoveBackward a = HeroActionsState u a l r s
modifyHeroActionState (HeroActionsState u d _ r s) TurnLeft a = HeroActionsState u d a r s
modifyHeroActionState (HeroActionsState u d l _ s) TurnRight a = HeroActionsState u d l a s
modifyHeroActionState (HeroActionsState u d l r _) UseWeapon a = HeroActionsState u d l r a
modifyHeroActionState s MoveForward a = s{heroActionsStateMoveForward=a}
modifyHeroActionState s MoveBackward a = s{heroActionsStateMoveBackward=a}
modifyHeroActionState s TurnLeft a = s{heroActionsStateTurnLeft=a}
modifyHeroActionState s TurnRight a = s{heroActionsStateTurnRight=a}
modifyHeroActionState s UseWeapon a = s{heroActionsStateUseWeapon=a}
modifyHeroActionState s Strafe a = s{heroActionsStateStrafe=a}

simUpdateHero :: World -> Hero -> Hero
simUpdateHero w h@(Hero {actionsState=has}) = h3
simUpdateHero _ (Hero {heroState=HeroAttack}) = error "Not implemented"
simUpdateHero w h@(Hero {heroState=HeroDefault}) = pipeline h
where
rotationDelta = heroRotationDelta has
h1 = rotateHero h rotationDelta
pipeline = (updateWeapon w)
. (moveHeroByActionsState w)
. rotateHeroByActionsState
. (updateFace w)

-- CheckWeaponChange ();
--
-- if ( buttonstate[bt_use] )
-- Cmd_Use ();
--
-- if ( buttonstate[bt_attack] && !buttonheld[bt_attack])
-- Cmd_Fire ();
--
-- ControlMovement (ob);
-- if (gamestate.victoryflag) // watching the BJ actor
-- return;
--
--
-- plux = player->x >> UNSIGNEDSHIFT; // scale to fit in unsigned
-- pluy = player->y >> UNSIGNEDSHIFT;
-- player->tilex = player->x >> TILESHIFT; // scale to tile values
-- player->tiley = player->y >> TILESHIFT;

updateFace :: World -> Hero -> Hero
updateFace w h@(Hero{heroFace=HeroFace count frames})
| newCount > randomNum = h{heroFace=HeroFace 0 newFrame}
| otherwise = h{heroFace=HeroFace newCount frames}
where
newCount = count + 1
randomNum = worldTickRandomNum w
nextRandomNum = worldTickNextRandomNum w
proposedFrame = nextRandomNum `shiftR` 6
newFrame = if proposedFrame == 3 then 1 else proposedFrame
-- TODO: If shooting gatling gun, don't change face (assume it is switched to some
-- strained face elsewehere


moveHeroByActionsState :: World -> Hero -> Hero
moveHeroByActionsState w h@(Hero{actionsState=has}) = moveHero w velocity h
where
movementDelta = heroMoveDelta has
movementScale = if movementDelta < 0 then moveScale else backMoveScale
-- TODO: set a thrustspeed for AI to use later
-- thrustspeed += speed;
velocity = movementScale * movementDelta
-- TODO
-- ClipMove(player,xmove,ymove);
-- player->tilex = player->x >> TILESHIFT; // scale to tile values
-- player->tiley = player->y >> TILESHIFT;
-- offset = farmapylookup[player->tiley]+player->tilex;
-- player->areanumber = *(mapsegs[0] + offset) -AREATILE;
h2 = moveHero w h1 velocity
h3 = updateWeapon w h2

rotateHeroByActionsState :: Hero -> Hero
rotateHeroByActionsState h@(Hero{actionsState=has}) = rotateHero h rotationDelta
where rotationDelta = heroRotationDelta has

angleScale :: Int
angleScale = 20
Expand Down Expand Up @@ -105,14 +140,21 @@ updateWeaponUsed has w
where current = isUsingWeapon w

createHero :: Vector2 -> Hero
createHero pos = Hero pos 0 0 staticHeroActionsState (Pistol Nothing False)
createHero pos = Hero
{ heroFace=HeroFace 0 0
, heroState=HeroDefault
, position=pos
, snappedRotation=0
, rotationRemainder=0
, actionsState=staticHeroActionsState
, weapon=(Pistol Nothing False) }

createHeroFromTilePosition :: TileCoord -> Hero
createHeroFromTilePosition p = createHero (tileCoordToCentreGlobalPos p)

moveHero :: World -> Hero -> Int -> Hero
moveHero _ h 0 = h
moveHero w h@(Hero {position=p, snappedRotation=sr}) velocity = h {position=fromJust firstOkay}
moveHero :: World -> Int -> Hero -> Hero
moveHero _ 0 h = h
moveHero w velocity h@(Hero {position=p, snappedRotation=sr}) = h {position=fromJust firstOkay}
where
speed = abs velocity
moveAngle = if velocity < 0 then sr else bindAngle (sr + (angles `div` 2))
Expand All @@ -124,9 +166,11 @@ moveHero w h@(Hero {position=p, snappedRotation=sr}) velocity = h {position=from
potentialOffsets = [Vector2 xOffset yOffset, Vector2 xOffset 0, Vector2 0 yOffset, Vector2 0 0]
potentialPositions = map (p +) potentialOffsets
firstOkay = find (\pos -> not (isHittingWall w pos heroSize)) potentialPositions

updateHeroActionsState :: HeroActionsState -> Hero -> Hero
updateHeroActionsState a (Hero p sr rr _ w) = Hero p sr rr a w
-- TODO
-- player->tilex = player->x >> TILESHIFT; // scale to tile values
-- player->tiley = player->y >> TILESHIFT;
-- offset = farmapylookup[player->tiley]+player->tilex;
-- player->areanumber = *(mapsegs[0] + offset) -AREATILE;

heroMoveDelta :: HeroActionsState -> Int
heroMoveDelta s = forwardMovement + backwardMovement
Expand Down
4 changes: 3 additions & 1 deletion src/Wolf3D/Input.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,8 @@ processKeyAction active p keySym = case keysymKeycode keySym of
KeycodeDown -> modifyHeroActionState p MoveBackward active
KeycodeLeft -> modifyHeroActionState p TurnLeft active
KeycodeRight -> modifyHeroActionState p TurnRight active
KeycodeLAlt -> modifyHeroActionState p UseWeapon active
KeycodeLCtrl -> modifyHeroActionState p UseWeapon active
KeycodeLAlt -> modifyHeroActionState p Strafe active
-- KeycodeLSpace -> modifyHeroActionState p Strafe active
_ -> p

18 changes: 9 additions & 9 deletions src/Wolf3D/Loader.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,16 +24,16 @@ loadRenderData r = do
return (RenderData w i weapons hBase face nums hWeapons)

loadHudBaseData :: SDL.Renderer -> IO (SDL.Texture, SDL.Rectangle CInt)
loadHudBaseData r = loadTexture r "hud-base.png"
loadHudBaseData r = loadTexture r "hud/base.png"

loadBjFace :: SDL.Renderer -> IO (Animation)
loadBjFace r = loadAnimation r "bj.png" (30, 30)
loadBjFace r = loadAnimation r "hud/bj.png" (24, 32)

loadNumbers :: SDL.Renderer -> IO (SpriteSheet)
loadNumbers r = loadSpriteSheet r "hud-numbers.png" (8, 16)
loadNumbers r = loadSpriteSheet r "hud/numbers.png" (8, 16)

loadHudWeapons :: SDL.Renderer -> IO (SpriteSheet)
loadHudWeapons r = loadSpriteSheet r "hud-weapons.png" (48, 24)
loadHudWeapons r = loadSpriteSheet r "hud/weapons.png" (48, 24)

loadWallDatas :: SDL.Renderer -> IO (WallData)
loadWallDatas r = do
Expand All @@ -49,14 +49,14 @@ loadWallDatas r = do

loadEnvItemsData :: SDL.Renderer -> IO (Map EnvItemType (SDL.Texture, SDL.Rectangle CInt))
loadEnvItemsData r = do
drum <- loadTexture r "drum.png"
flag <- loadTexture r "flag.png"
light <- loadTexture r "light.png"
drum <- loadTexture r "items/drum.png"
flag <- loadTexture r "items/flag.png"
light <- loadTexture r "items/light.png"
return (fromList [ (Drum, drum), (Flag, flag), (Light, light)])

loadWeaponData :: SDL.Renderer -> IO (Map String Animation)
loadWeaponData r = do
pistol <- loadAnimation r "pistol.png" (128, 60)
pistol <- loadAnimation r "weapons/pistol.png" (128, 60)
return (fromList [("Pistol", pistol)])

loadTexture :: SDL.Renderer -> FilePath -> IO (SDL.Texture, SDL.Rectangle CInt)
Expand All @@ -69,7 +69,7 @@ loadTexture r p = do

loadWallSheet :: SDL.Renderer -> FilePath -> IO SpriteSheet
loadWallSheet r p = do
(t, SDL.Rectangle _ tSize@(SDL.V2 tW _)) <- loadTexture r p
(t, SDL.Rectangle _ tSize@(SDL.V2 tW _)) <- loadTexture r ("walls/" ++ p)
let sSize = (tW, tW)
return (fromJust (createSpriteSheet t tSize sSize))

Expand Down
Loading

0 comments on commit de934f6

Please sign in to comment.