tracer/src/MainGame/WorldMap.hs

581 lines
20 KiB
Haskell
Raw Normal View History

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
2018-07-19 04:56:31 +02:00
{-# LANGUAGE BangPatterns #-}
2018-06-28 21:07:58 +02:00
module MainGame.WorldMap where
2018-05-30 17:32:00 +02:00
import Affection as A
2018-06-28 21:07:58 +02:00
import Algebra.Graph as AG
2018-02-18 03:11:41 +01:00
import qualified SDL
2018-03-12 00:21:16 +01:00
import NanoVG hiding (V2(..))
2018-02-18 03:11:41 +01:00
2018-05-30 17:32:00 +02:00
import Control.Monad (when, void)
import Control.Monad.IO.Class (liftIO)
import Control.Concurrent.MVar
2018-06-08 00:29:46 +02:00
import Control.Concurrent (forkIO)
2018-02-25 10:30:13 +01:00
import Data.Map.Strict as Map
2018-03-01 23:33:08 +01:00
import qualified Data.Set as S
import qualified Data.Text as T
2018-03-03 11:06:38 +01:00
import Data.Matrix as M
2018-02-18 05:31:34 +01:00
import Data.Ecstasy as E
2018-03-04 22:24:30 +01:00
import Data.Maybe
2018-06-28 21:07:58 +02:00
import Data.List as L (sortOn, partition, find)
2018-04-14 18:43:05 +02:00
import System.Random (randomRIO)
2018-05-26 08:34:49 +02:00
import Linear hiding (E)
2018-02-18 03:11:41 +01:00
import Foreign.C.Types (CFloat(..))
2018-03-02 02:10:35 +01:00
-- internal imports
2018-03-03 17:03:17 +01:00
import Interior
2018-03-02 02:10:35 +01:00
import Util
2018-03-12 00:21:16 +01:00
import Types
import Floorplan
2018-06-28 21:07:58 +02:00
import MindMap
2018-04-14 11:18:37 +02:00
import NPC
2018-03-02 02:10:35 +01:00
loadMap :: Affection UserData ()
loadMap = do
ud <- getAffection
2018-06-24 00:42:39 +02:00
let (Subsystems _ m k) = subsystems ud
2018-06-28 21:07:58 +02:00
uu1 <- partSubscribe m movePlayer
uu2 <- partSubscribe k changeMaps
2018-07-03 16:19:27 +02:00
future <- liftIO newEmptyMVar
2018-07-19 04:51:07 +02:00
progress <- liftIO $ newMVar (0, "Ohai!")
_ <- liftIO $ forkIO $ loadMapFork ud future progress
2018-06-08 00:29:46 +02:00
putAffection ud
{ stateData = None
2018-06-28 21:07:58 +02:00
, uuid = [uu1, uu2]
, stateMVar = future
, stateProgress = progress
2018-06-08 00:29:46 +02:00
}
2018-06-28 21:07:58 +02:00
changeMaps :: KeyboardMessage -> Affection UserData ()
changeMaps (MsgKeyboardEvent _ _ SDL.Pressed False sym)
| SDL.keysymKeycode sym == SDL.KeycodeF1 = do
ud <- getAffection
putAffection ud
{ state = Main WorldMap
}
| SDL.keysymKeycode sym == SDL.KeycodeF2 = do
ud <- getAffection
putAffection ud
{ state = Main MindMap
}
| otherwise = return ()
changeMaps _ = return ()
loadMapFork
:: UserData
-> MVar (SystemState Entity IO, StateData)
2018-07-19 04:51:07 +02:00
-> MVar (Float, T.Text)
-> IO ()
loadMapFork ud future progress = do
2018-07-21 06:43:26 +02:00
let loadSteps = 19
fc = FloorConfig
2018-05-30 16:20:58 +02:00
(10, 10)
2018-06-24 00:43:27 +02:00
[(5, 5), (5, 45)]
2018-05-18 20:05:21 +02:00
(50, 50)
2018-07-19 04:51:07 +02:00
_ <- liftIO $ swapMVar progress (1 / loadSteps, "Building floor")
(mat, gr) <- buildHallFloorIO fc progress (1 / loadSteps)
2018-07-19 04:51:07 +02:00
_ <- liftIO $ swapMVar progress (11 / loadSteps, "Converting to images")
let imgmat = convertTileToImg mat
exits = Prelude.foldl
2018-07-21 06:43:26 +02:00
(\acc coord@(r, c) -> if imgmat M.! coord == Just (ImgEmpty [])
then ReachPoint RoomExit (V2 r c) NE : acc
else acc
)
[]
((,) <$> [1 .. nrows mat] <*> [1 .. ncols mat])
2018-07-19 04:51:07 +02:00
_ <- liftIO $ swapMVar progress (12 / loadSteps, "Placing furniture")
2018-06-08 00:29:46 +02:00
(inter, rps) <- placeInteriorIO mat imgmat exits gr
2018-07-19 04:51:07 +02:00
_ <- liftIO $ swapMVar progress (13 / loadSteps, "Placing NPCs")
2018-06-08 00:29:46 +02:00
logIO A.Debug ("number of reachpoints: " ++ show (length rps))
let nnex = Prelude.filter (\p -> pointType p /= RoomExit) rps
2018-07-21 06:43:26 +02:00
npcposs <- placeNPCs inter mat rps 10 -- (length $ filter (\a -> pointType a == Table) nnex)
2018-07-19 04:56:31 +02:00
_ <- liftIO $ swapMVar progress (14 / loadSteps, "Preparing MindMap graph")
2018-06-08 00:29:46 +02:00
A.logIO A.Debug $ "number of placed NPCs: " ++ show (length npcposs)
2018-07-19 04:56:31 +02:00
!(mmintmat, mmgraph) <- buildFloorMap . springField <$>
2018-07-19 04:51:07 +02:00
buildMindMap (length npcposs) 2
2018-07-19 04:56:31 +02:00
_ <- liftIO $ swapMVar progress (15 / loadSteps, "Unfolding and Converting MindMap to images")
let !mmimgmat = convertTileToImg $ manhattan mmgraph mmintmat
2018-07-19 04:51:07 +02:00
_ <- liftIO $ swapMVar progress (16 / loadSteps, "Creating WorldState")
2018-06-08 00:29:46 +02:00
(nws, _) <- yieldSystemT (worldState ud) $ do
2018-07-03 16:19:27 +02:00
let pmmpos = (+ 0.5) . (fromIntegral :: Int -> Double) . floor <$> mmPos
2018-06-28 21:07:58 +02:00
(fromJust $ find (\a -> mmId a == 0) (vertexList mmgraph))
2018-07-03 16:19:27 +02:00
delta = (0, 0) :
2018-06-28 21:07:58 +02:00
Prelude.filter (/= (0,0)) ((,) <$> [-1 .. 1] <*> [-1 .. 1]) :: [(Int, Int)]
2018-07-03 16:19:27 +02:00
mmmpos = Prelude.foldl (\acc (dr, dc) ->
2018-06-28 21:07:58 +02:00
let (V2 pmr pmc) = floor <$> pmmpos
seekpos = (pmr + fromIntegral dr, pmc + fromIntegral dc)
2018-07-03 16:19:27 +02:00
in if isNothing (mmimgmat M.! seekpos) && mmintmat M.! seekpos == 0
&& isNothing acc
2018-06-28 21:07:58 +02:00
then Just (pmmpos + (fromIntegral <$> V2 dr dc))
else acc
) Nothing delta
2018-05-30 17:32:00 +02:00
void $ createEntity $ newEntity
2018-05-30 16:20:58 +02:00
{ pos = Just (V2 10.5 10.5)
2018-07-03 16:19:27 +02:00
, mmpos = mmmpos
2018-05-27 16:03:31 +02:00
, vel = Just (V2 0 0)
2018-06-28 21:07:58 +02:00
, mmvel = Just (V2 0 0)
2018-05-27 16:03:31 +02:00
, player = Just ()
, rot = Just SE
2018-07-21 06:43:26 +02:00
, anim = Just $ AnimState (AnimId "intruder" "standing" SE) 0 0
2018-02-18 05:31:34 +01:00
}
2018-07-21 06:43:26 +02:00
void $ liftIO $ swapMVar progress (17 / loadSteps, "Registering copiers into WorldState")
let copiers = Prelude.filter (\a -> pointType a == Copier) rps
mapM_ (\(ReachPoint _ icoord _) -> do
let reachCoord = fmap ((+ 0.5) . fromIntegral) icoord
void $ createEntity $ newEntity
{ pos = Just $ reachCoord - V2 1 0
, obstacle = Just $ Boundaries (10/36, 8/36) (28/36, 30/36)
, anim = Just $ AnimState (AnimId "copier" "closed" N) 0 0
, objAccess = Just $ V2 1 0
}
) (A.log A.Debug ("number of copiers: " ++ show (length copiers)) copiers)
void $ liftIO $ swapMVar progress (18 / loadSteps, "Registering NPCs into WorldState")
2018-07-03 16:19:27 +02:00
mapM_ (\npcpos@(V2 nr nc) -> do
2018-05-15 19:27:40 +02:00
fact <- liftIO $ randomRIO (0.5, 1.5)
2018-07-03 16:19:27 +02:00
fut <- liftIO newEmptyMVar
_ <- liftIO $ forkIO $ getPath (fmap floor npcpos) fut nnex inter
2018-05-30 17:32:00 +02:00
void $ createEntity $ newEntity
2018-05-27 16:03:31 +02:00
{ pos = Just (V2 (nr + 0.5) (nc + 0.5))
, vel = Just (V2 0 0)
, velFact = Just fact
, rot = Just SE
2018-07-03 16:19:27 +02:00
, npcMoveState = Just (NPCStanding 0 fut)
2018-07-21 06:43:26 +02:00
, anim = Just $ AnimState (AnimId "jdoem" "standing" SE) 0 0
2018-04-14 11:18:37 +02:00
}
) npcposs
2018-07-21 06:43:26 +02:00
void $ liftIO $ swapMVar progress (19 / loadSteps, "Handing over")
2018-06-25 23:59:12 +02:00
putMVar future (nws, MainData
2018-03-06 21:58:55 +01:00
{ mapMat = mat
2018-03-31 23:22:10 +02:00
, imgMat = M.fromList (nrows inter) (ncols inter) $
Prelude.map
2018-07-21 06:43:26 +02:00
(\a -> if a == Just (ImgEmpty []) then Nothing else a)
2018-03-31 23:22:10 +02:00
(M.toList inter)
2018-04-14 18:43:05 +02:00
, reachPoints = rps
2018-06-28 21:07:58 +02:00
, mmImgMat = mmimgmat
2018-06-08 00:29:46 +02:00
})
2018-02-18 05:31:34 +01:00
mouseToPlayer :: V2 Int32 -> Affection UserData ()
mouseToPlayer mv2 = do
2018-02-18 03:11:41 +01:00
ud <- getAffection
2018-03-06 21:58:55 +01:00
(V2 rx ry) <- liftIO $ relativizeMouseCoords mv2
2018-02-24 23:15:16 +01:00
let dr = (ry / sin (atan (1/2)) / 2) + rx
dc = rx - (ry / sin (atan (1/2)) / 2)
2018-05-30 17:32:00 +02:00
(nws, _) <- liftIO $ yieldSystemT (worldState ud) $
2018-05-17 13:06:13 +02:00
emap allEnts $ do
2018-02-18 05:31:34 +01:00
with player
2018-05-17 13:06:13 +02:00
pure $ unchanged
2018-05-13 22:01:05 +02:00
{ vel = Set $ 4 * V2 dr dc
2018-02-18 05:31:34 +01:00
}
2018-02-18 03:11:41 +01:00
putAffection ud
2018-02-25 02:03:25 +01:00
{ worldState = nws
2018-02-18 05:31:34 +01:00
}
movePlayer :: MouseMessage -> Affection UserData ()
movePlayer (MsgMouseMotion _ _ _ [SDL.ButtonLeft] m _) = mouseToPlayer m
movePlayer (MsgMouseButton _ _ SDL.Pressed _ SDL.ButtonLeft _ m) =
mouseToPlayer m
2018-03-06 21:58:55 +01:00
movePlayer (MsgMouseButton _ _ SDL.Released _ SDL.ButtonLeft _ _) = do
2018-02-18 05:31:34 +01:00
ud <- getAffection
2018-05-30 17:32:00 +02:00
(nws, _) <- liftIO $ yieldSystemT (worldState ud) $
2018-05-17 13:06:13 +02:00
emap allEnts $ do
2018-02-18 05:31:34 +01:00
with player
2018-05-17 13:06:13 +02:00
pure $ unchanged
2018-02-18 05:31:34 +01:00
{ vel = Set $ V2 0 0
}
putAffection ud
2018-02-25 02:03:25 +01:00
{ worldState = nws
2018-02-18 03:11:41 +01:00
}
movePlayer _ = return ()
drawMap :: Affection UserData ()
drawMap = do
ud <- getAffection
2018-06-08 00:29:46 +02:00
let ctx = nano ud
case stateData ud of
None -> liftIO $ do
progress <- readMVar (stateProgress ud)
drawLoadScreen ud progress
2018-06-08 00:29:46 +02:00
_ -> do
dt <- getDelta
(_, (playerPos, posanims)) <- liftIO $ yieldSystemT (worldState ud) $ do
pc <- fmap head $ efor allEnts $ do
with player
with pos
query pos
posanims <- efor allEnts $ do
with anim
with pos
stat <- query anim
pos' <- query pos
2018-07-21 06:43:26 +02:00
mbnds <- queryMaybe obstacle
return (pos', stat, mbnds)
2018-06-08 00:29:46 +02:00
return (pc, posanims)
let V2 pr pc = playerPos
mat = imgMat (stateData ud)
cols = fromIntegral (ncols mat)
rows = fromIntegral (nrows mat)
tileWidth = 64 :: Double
tileHeight = 32 :: Double
x = realToFrac $ 640 + ((1 - pc) + (1 - pr)) * (tileWidth / 2)
y = realToFrac $ 360 + ((1 - pr) - (1 - pc)) * (tileHeight / 2)
partposanims = M.fromList
(nrows $ mapMat $ stateData ud)
(ncols $ mapMat $ stateData ud)
((reverse . fst)
(Prelude.foldl
(\(done, proc) coord ->
let (ndone, nproc) = processList proc coord
in (ndone : done, nproc)
)
([], posanims)
((,)
<$> [1 .. (nrows $ mapMat $ stateData ud)]
<*> [1 .. (ncols $ mapMat $ stateData ud)]
)
)
2018-06-03 04:28:39 +02:00
)
2018-06-08 00:29:46 +02:00
processList
2018-07-21 06:43:26 +02:00
:: [(V2 Double, AnimState, Maybe (Boundaries Double))]
2018-06-08 00:29:46 +02:00
-> (Int, Int)
2018-07-21 06:43:26 +02:00
-> ( [(V2 Double, AnimState, Maybe (Boundaries Double))]
, [(V2 Double, AnimState, Maybe (Boundaries Double))]
)
2018-07-03 16:19:27 +02:00
processList list (r, c) =
2018-07-21 06:43:26 +02:00
let delimiter (V2 nr nc, _, _) =
2018-06-08 00:29:46 +02:00
floor nr == r && floor nc == c
in L.partition delimiter list
liftIO $ do -- draw floor
beginPath ctx
moveTo ctx (x + realToFrac tileWidth / 2) y
lineTo ctx
(x + cols * (realToFrac tileWidth / 2))
(y - (realToFrac tileHeight / 2) * (cols - 1))
lineTo ctx
(x + (realToFrac tileWidth / 2) * (cols + rows - 1))
(y + (rows - cols) * (realToFrac tileHeight / 2))
lineTo ctx
(x + (realToFrac tileWidth / 2) * rows)
(y + (realToFrac tileHeight / 2) * (rows - 1))
closePath ctx
fillColor ctx (rgb 255 255 255)
fill ctx
mapM_ (\(i, ls) -> mapM_
(\(j, t) -> drawTile ud ctx (partposanims M.! (i, j)) pr pc i j t)
(reverse $ zip [1..] ls))
(zip [1..] (toLists mat))
fontSize ctx 20
fontFace ctx (assetFonts ud Map.! FontBedstead)
textAlign ctx (S.fromList [AlignCenter,AlignTop])
fillColor ctx (rgb 255 128 0)
textBox ctx 0 0 200 ("FPS: " `T.append` T.pack (Prelude.take 5 $ show (1/dt)))
2018-05-30 16:20:58 +02:00
drawTile
:: UserData
-> Context
2018-07-21 06:43:26 +02:00
-> [(V2 Double, AnimState, Maybe (Boundaries Double))]
2018-05-30 16:20:58 +02:00
-> Double
-> Double
-> Int
-> Int
-> Maybe ImgId
-> IO ()
drawTile ud ctx posanims pr pc row col img =
when ((realToFrac x > -tileWidth && realToFrac y > -tileHeight) &&
2018-05-30 17:32:00 +02:00
((realToFrac x :: Double) < 1280 &&
(realToFrac (y - (74 - (realToFrac tileHeight :: CFloat))) :: Double) < 720)) $
2018-05-30 16:20:58 +02:00
do
let (bef, beh) = L.partition delimiter sorted
2018-05-30 16:20:58 +02:00
save ctx
2018-06-16 11:40:51 +02:00
mapM_ drawAnim beh
maybe (return ()) (draw ud x (y - 42) 64 74 fact)
2018-07-21 06:43:26 +02:00
((assetImages ud Map.!) <$> case img of
Just (ImgEmpty _) -> Nothing
_ -> img
)
2018-06-16 11:40:51 +02:00
mapM_ drawAnim bef
2018-05-30 16:20:58 +02:00
restore ctx
2018-07-21 06:43:26 +02:00
when (floor pr == row && floor pc == col) $ do
A.logIO A.Debug ("sorted: " ++ show sorted)
A.logIO A.Debug ("beh: " ++ show beh)
A.logIO A.Debug ("bef: " ++ show bef)
2018-05-30 16:20:58 +02:00
where
2018-07-21 06:43:26 +02:00
delimiter (V2 nr nc, _, mbnds) =
2018-06-16 11:40:51 +02:00
all delimit mb
where
delimit b
| nnr > fst (matmin b) && nnr < fst (matmax b) =
nnc < snd (matmin b)
| nnc > snd (matmin b) && nnc < snd (matmax b) =
nnr > fst (matmax b)
| otherwise =
True
2018-07-21 06:43:26 +02:00
nnr = case mbnds of
Just (Boundaries (minr, minc) (maxr, maxc)) -> maxr
Nothing -> nr - fromIntegral ((floor nr) :: Int) :: Double
nnc = case mbnds of
Just (Boundaries (minr, minc) (maxr, maxc)) -> minc
Nothing -> nc - fromIntegral ((floor nc) :: Int) :: Double
2018-06-16 11:40:51 +02:00
-- any (\m -> nr < fromIntegral (floor nr :: Int) + m) maxrs &&
-- any (\m -> nc > fromIntegral (floor nc :: Int) + m) mincs
2018-05-30 16:20:58 +02:00
tileWidth = 64 :: Double
tileHeight = 32 :: Double
2018-07-21 06:43:26 +02:00
sorted = sortOn (\(V2 sr sc, _, mbnds) -> case mbnds of
Just (Boundaries (minr, minc) (maxr, maxc)) -> minr * 10 + (1 - minc)
_ -> (sr - (fromIntegral ((floor sr) :: Int))) * 10 +
(1 - (sc - (fromIntegral ((floor sc) :: Int))))
) posanims
-- sorted = posanims
2018-05-31 05:25:08 +02:00
minrs = Prelude.map (fst . matmin) mb
2018-05-30 16:20:58 +02:00
maxrs = Prelude.map (fst . matmax) mb
mincs = Prelude.map (snd . matmin) mb
maxcs = Prelude.map (snd . matmax) mb
x = realToFrac $ 640 + ((fromIntegral col - pc) +
(fromIntegral row - pr)) * (tileWidth / 2) :: CFloat
y = realToFrac $ 360 - (tileHeight / 2) + ((fromIntegral row - pr) -
(fromIntegral col - pc)) * (tileHeight / 2) :: CFloat
dist = distance (V2 (fromIntegral row) (fromIntegral col))
(V2 (realToFrac pr - 1) (realToFrac pc)) / 4
fact =
if (pr <= fromIntegral row + minimum maxrs &&
pc >= fromIntegral col + maximum mincs) &&
isWall (fromJust img)
then min 1 dist
else 1
mb = maybe [] collisionObstacle img
2018-07-21 06:43:26 +02:00
drawAnim (V2 nr nc, as, _) = do
let ax = realToFrac $ 640 + ((nc - pc) + (nr - pr)) * 32 - 32
ay = realToFrac $ 360 + ((nr - pr) - (nc - pc)) * 16 - 58
draw ud ax ay 64 74 1 as
2018-05-30 16:20:58 +02:00
2018-02-18 05:31:34 +01:00
updateMap :: Double -> Affection UserData ()
2018-02-24 22:24:48 +01:00
updateMap dt = do
2018-02-18 05:31:34 +01:00
ud <- getAffection
isFut <- liftIO $ isEmptyMVar (stateMVar ud)
2018-06-08 00:29:46 +02:00
if not isFut && stateData ud == None
then do
liftIO $ logIO A.Debug "Loaded game data"
Just (nws, mendat) <- liftIO $ tryTakeMVar (stateMVar ud)
2018-06-08 00:29:46 +02:00
putAffection ud
{ worldState = nws
, stateData = mendat
}
else do
(nws, _) <- liftIO $ yieldSystemT (worldState ud) $ do
emap allEnts $ do
with anim
2018-06-28 21:07:58 +02:00
with pos
2018-06-08 00:29:46 +02:00
stat <- query anim
let an = assetAnimations ud Map.! asId stat
ntime = asElapsedTime stat + dt
nstate = if ntime > fromIntegral (asCurrentFrame stat) *
(animDuration an / fromIntegral (length $ animSprites an))
then
let nframe = asCurrentFrame stat + 1
in case animPlay an of
APLoop ->
let (nnframe, nntime) =
if nframe >= length (animSprites an)
then (0, 0)
else (nframe, ntime)
in stat
{ asCurrentFrame = nnframe
, asElapsedTime = nntime
}
APOnce ->
let nnframe = if nframe >= length (animSprites an)
then nframe - 1
else nframe
in stat
{ asCurrentFrame = nnframe
, asElapsedTime = ntime
}
else
2018-05-30 22:15:49 +02:00
stat
2018-06-08 00:29:46 +02:00
{ asElapsedTime = ntime
2018-05-30 22:15:49 +02:00
}
2018-06-08 00:29:46 +02:00
return $ unchanged
{ anim = Set nstate
}
emap allEnts $ do
without player
with vel
with velFact
with pos
with rot
with anim
pos' <- query pos
vel' <- query vel
rot' <- query rot
fact' <- query velFact
stat <- query anim
let npos = pos' + fmap (* (dt * fact')) vel'
aId = asId stat
nstat = case aiName aId of
"walking"
| sqrt (vel' `dot` vel') > 0 ->
stat
{ asId = aId
2018-07-06 17:17:57 +02:00
{ aiDirection = fromMaybe rot' (direction vel')
2018-06-08 00:29:46 +02:00
}
2018-05-30 22:15:49 +02:00
}
2018-06-08 00:29:46 +02:00
| otherwise ->
stat
{ asId = aId
2018-07-06 17:17:57 +02:00
{ aiDirection = fromMaybe rot' (direction vel')
2018-06-08 00:29:46 +02:00
, aiName = "standing"
}
, asCurrentFrame = 0
2018-05-30 22:15:49 +02:00
}
2018-06-08 00:29:46 +02:00
"standing"
| sqrt (vel' `dot` vel') > 0 ->
stat
{ asId = aId
2018-07-06 17:17:57 +02:00
{ aiDirection = fromMaybe rot' (direction vel')
2018-06-08 00:29:46 +02:00
, aiName = "walking"
}
, asCurrentFrame = 0
2018-05-30 22:15:49 +02:00
}
2018-06-08 00:29:46 +02:00
| otherwise ->
stat
{ asId = aId
2018-07-06 17:17:57 +02:00
{ aiDirection = fromMaybe rot' (direction vel')
2018-06-08 00:29:46 +02:00
}
2018-05-30 22:15:49 +02:00
}
2018-06-08 00:29:46 +02:00
x -> error ("unknown animation name" ++ x)
ent = unchanged
{ pos = Set npos
2018-07-06 17:17:57 +02:00
, rot = Set $ fromMaybe rot' (direction vel')
2018-06-08 00:29:46 +02:00
, anim = Set nstat
}
return ent
emap allEnts $ do
with player
with vel
with pos
with rot
with anim
pos'@(V2 pr pc) <- query pos
vel' <- query vel
rot' <- query rot
stat <- query anim
let npos = pos' + fmap (* dt) vel'
dpos@(V2 dpr dpc) = npos - pos'
aId = asId stat
nstat = case aiName aId of
"walking"
| sqrt (colldpos `dot` colldpos) > 0 ->
stat
{ asId = aId
2018-07-06 17:17:57 +02:00
{ aiDirection = fromMaybe rot' (direction vel')
2018-06-08 00:29:46 +02:00
}
2018-05-30 22:15:49 +02:00
}
2018-06-08 00:29:46 +02:00
| otherwise ->
stat
{ asId = aId
2018-07-06 17:17:57 +02:00
{ aiDirection = fromMaybe rot' (direction vel')
2018-06-08 00:29:46 +02:00
, aiName = "standing"
}
, asCurrentFrame = 0
2018-05-30 22:15:49 +02:00
}
2018-06-08 00:29:46 +02:00
"standing"
| sqrt (colldpos `dot` colldpos) > 0 ->
stat
{ asId = aId
2018-07-06 17:17:57 +02:00
{ aiDirection = fromMaybe rot' (direction vel')
2018-06-08 00:29:46 +02:00
, aiName = "walking"
}
, asCurrentFrame = 0
2018-05-30 22:15:49 +02:00
}
2018-06-08 00:29:46 +02:00
| otherwise ->
stat
{ asId = aId
2018-07-06 17:17:57 +02:00
{ aiDirection = fromMaybe rot' (direction vel')
2018-06-08 00:29:46 +02:00
}
}
x -> error ("unknown animation name" ++ x)
lll = (,)
<$> (
if dpr < 0
then [(floor dpr :: Int) .. 0]
else [0 .. (ceiling dpr :: Int)])
<*> (
if dpc < 0
then [(floor dpc :: Int) .. 0]
else [0 .. (ceiling dpc :: Int)])
colldpos = dpos * Prelude.foldl
(\acc a -> let ret = checkBoundsCollision2 pos' npos dt acc a
in A.log A.Verbose (show ret) ret)
(V2 1 1)
(
concatMap
(\(dr, dc) ->
let bs = maybe [] collisionObstacle (fromMaybe Nothing $ M.safeGet
2018-06-08 00:29:46 +02:00
(fromIntegral $ floor pr + dr)
(fromIntegral $ floor pc + dc)
(imgMat (stateData ud)))
in Prelude.map (\(Boundaries (minr, minc) (maxr, maxc))->
Boundaries
(minr + fromIntegral dr, minc + fromIntegral dc)
(maxr + fromIntegral dr, maxc + fromIntegral dc)
) bs
)
lll -- (A.log A.Verbose (show lll ++ " " ++ show len) lll)
2018-06-02 22:04:05 +02:00
)
2018-06-08 00:29:46 +02:00
ent = unchanged
{ pos = Set $ pos' + colldpos
2018-07-06 17:17:57 +02:00
, rot = Set (fromMaybe rot' $ direction vel')
2018-06-08 00:29:46 +02:00
, anim = Set nstat
}
2018-07-21 06:43:26 +02:00
-- liftIO $ A.logIO A.Debug ("player position: " ++ show (pos' + colldpos))
2018-06-08 00:29:46 +02:00
return ent
updateNPCs
(imgMat $ stateData ud)
(Prelude.filter
(\p -> pointType p /= RoomExit)
(reachPoints $ stateData ud)
)
dt
putAffection ud
{ worldState = nws
}
2018-02-18 05:31:34 +01:00
2018-05-01 23:00:20 +02:00
checkBoundsCollision2
:: V2 Double
-> V2 Double
-> Double
-> V2 Double
-> Boundaries Double
-> V2 Double
checkBoundsCollision2
2018-05-30 17:32:00 +02:00
pre@(V2 pr pc) nex dt acc (Boundaries (minr, minc) (maxr, maxc))
2018-05-14 18:12:37 +02:00
| colltr < dt && colltc < dt = V2 0 0
| colltr < dt && incol = V2 0 1 * acc
| colltc < dt && inrow = V2 1 0 * acc
| otherwise = acc
2018-05-01 23:00:20 +02:00
where
2018-05-30 17:32:00 +02:00
V2 vr vc = fmap (/ dt) (nex - pre)
2018-05-01 23:00:20 +02:00
colltr
2018-05-14 18:12:37 +02:00
| vr > 0 && prr <= maxr =
2018-05-30 17:32:00 +02:00
((fromIntegral (floor pr :: Int) + minr - 0.15) - pr) / vr
2018-05-14 18:12:37 +02:00
| vr < 0 && prr >= minr =
2018-05-30 17:32:00 +02:00
((fromIntegral (floor pr :: Int) + maxr + 0.15) - pr) / vr
2018-05-14 17:54:55 +02:00
| otherwise = dt
2018-05-01 23:00:20 +02:00
colltc
2018-05-14 18:12:37 +02:00
| vc > 0 && prc <= maxc =
2018-05-30 17:32:00 +02:00
((fromIntegral (floor pc :: Int) + minc - 0.15) - pc) / vc
2018-05-14 18:12:37 +02:00
| vc < 0 && prc >= minc =
2018-05-30 17:32:00 +02:00
((fromIntegral (floor pc :: Int) + maxc + 0.15) - pc) / vc
2018-05-14 17:54:55 +02:00
| otherwise = dt
2018-05-13 14:05:15 +02:00
inrow = pr > minr && pr < maxr
incol = pc > minc && pc < maxc
2018-05-30 17:32:00 +02:00
prr = pr - fromIntegral (floor pr :: Int)
prc = pc - fromIntegral (floor pc :: Int)