2018-02-17 01:36:06 +00:00
|
|
|
module Test where
|
|
|
|
|
2018-02-18 02:11:41 +00:00
|
|
|
import Affection as A hiding (get)
|
2018-02-17 01:36:06 +00:00
|
|
|
|
2018-02-18 02:11:41 +00:00
|
|
|
import SDL (get, ($=))
|
|
|
|
import qualified SDL
|
|
|
|
import qualified Graphics.Rendering.OpenGL as GL hiding (get)
|
2018-03-11 23:21:16 +00:00
|
|
|
import NanoVG hiding (V2(..))
|
2018-02-18 02:11:41 +00:00
|
|
|
|
2018-03-02 01:10:35 +00:00
|
|
|
import Control.Monad (when, unless, void)
|
2018-02-17 01:36:06 +00:00
|
|
|
import Control.Monad.IO.Class (liftIO)
|
2018-05-16 14:23:23 +00:00
|
|
|
import Control.Concurrent.MVar
|
2018-05-18 18:05:21 +00:00
|
|
|
import Control.Concurrent (forkOS)
|
2018-02-17 01:36:06 +00:00
|
|
|
|
2018-02-25 09:30:13 +00:00
|
|
|
import Data.Map.Strict as Map
|
2018-03-01 22:33:08 +00:00
|
|
|
import qualified Data.Set as S
|
|
|
|
import qualified Data.Text as T
|
2018-03-03 10:06:38 +00:00
|
|
|
import Data.Matrix as M
|
2018-02-18 04:31:34 +00:00
|
|
|
import Data.Ecstasy as E
|
2018-03-04 21:24:30 +00:00
|
|
|
import Data.Maybe
|
2018-02-17 01:36:06 +00:00
|
|
|
|
2018-04-14 16:43:05 +00:00
|
|
|
import System.Random (randomRIO)
|
|
|
|
|
2018-02-18 02:11:41 +00:00
|
|
|
import Linear
|
|
|
|
|
2018-02-17 01:36:06 +00:00
|
|
|
import Foreign.C.Types (CFloat(..))
|
|
|
|
|
2018-02-18 02:11:41 +00:00
|
|
|
import Debug.Trace
|
2018-02-17 01:36:06 +00:00
|
|
|
|
2018-03-02 01:10:35 +00:00
|
|
|
-- internal imports
|
|
|
|
|
2018-03-03 16:03:17 +00:00
|
|
|
import Interior
|
2018-03-02 01:10:35 +00:00
|
|
|
import Util
|
2018-03-11 23:21:16 +00:00
|
|
|
import Types
|
|
|
|
import Floorplan
|
2018-04-14 09:18:37 +00:00
|
|
|
import NPC
|
2018-03-02 01:10:35 +00:00
|
|
|
|
2018-02-17 01:36:06 +00:00
|
|
|
loadMap :: Affection UserData ()
|
|
|
|
loadMap = do
|
|
|
|
ud <- getAffection
|
2018-03-03 16:42:24 +00:00
|
|
|
let fc = FloorConfig
|
|
|
|
(20, 20)
|
2018-03-11 23:21:16 +00:00
|
|
|
[(5,5), (35, 35)]
|
2018-05-18 18:05:21 +00:00
|
|
|
(50, 50)
|
2018-02-18 02:11:41 +00:00
|
|
|
(Subsystems _ m) = subsystems ud
|
2018-03-06 20:58:55 +00:00
|
|
|
(mat, gr) <- liftIO $ buildHallFloorIO fc
|
2018-04-02 14:29:35 +00:00
|
|
|
let imgmat = convertTileToImg mat
|
|
|
|
exits = Prelude.foldl
|
|
|
|
(\acc coord@(r, c) -> if imgmat M.! coord == Just ImgEmpty
|
|
|
|
then ReachPoint RoomExit (V2 r c) : acc
|
|
|
|
else acc
|
|
|
|
)
|
|
|
|
[]
|
|
|
|
((,) <$> [1 .. nrows mat] <*> [1 .. ncols mat])
|
|
|
|
-- liftIO $ A.logIO A.Debug (show exits)
|
2018-04-14 11:34:28 +00:00
|
|
|
(inter, rps) <- liftIO $ placeInteriorIO mat imgmat exits gr
|
2018-05-01 21:52:40 +00:00
|
|
|
liftIO $ logIO A.Debug ("number of reachpoints: " ++ show (length rps))
|
2018-05-16 14:23:23 +00:00
|
|
|
let nnex = Prelude.filter (\p -> pointType p /= RoomExit) rps
|
|
|
|
liftIO $ A.logIO A.Debug $ "number of placed NPCs: " ++ show (length nnex)
|
2018-05-18 18:05:21 +00:00
|
|
|
npcposs <- placeNPCs inter mat rps gr 50 -- (length nnex)
|
2018-05-17 11:06:13 +00:00
|
|
|
(nws, _) <- liftIO $ yieldSystemT (worldState ud) $ do
|
|
|
|
void $ createEntity $ newEntity
|
2018-02-25 01:03:46 +00:00
|
|
|
{ pos = Just (V2 20.5 20.5)
|
2018-02-18 04:31:34 +00:00
|
|
|
, vel = Just (V2 0 0)
|
2018-04-14 09:18:37 +00:00
|
|
|
, player = Just ()
|
2018-05-20 22:40:40 +00:00
|
|
|
, rot = Just SE
|
2018-02-18 04:31:34 +00:00
|
|
|
}
|
2018-05-16 14:23:23 +00:00
|
|
|
void $ mapM_ (\npcpos@(V2 nr nc) -> do
|
2018-04-14 17:00:21 +00:00
|
|
|
-- ttl <- liftIO $ randomRIO (5, 30)
|
2018-05-15 17:27:40 +00:00
|
|
|
fact <- liftIO $ randomRIO (0.5, 1.5)
|
2018-05-16 14:23:23 +00:00
|
|
|
future <- liftIO $ newEmptyMVar
|
2018-05-18 18:05:21 +00:00
|
|
|
_ <- liftIO $ forkOS $ getPath (fmap floor npcpos) future nnex inter
|
2018-05-17 11:06:13 +00:00
|
|
|
createEntity $ newEntity
|
2018-04-14 16:43:05 +00:00
|
|
|
{ pos = Just (V2 (nr + 0.5) (nc + 0.5))
|
|
|
|
, vel = Just (V2 0 0)
|
2018-05-20 22:40:40 +00:00
|
|
|
, velFact = Just fact
|
|
|
|
, rot = Just SE
|
2018-05-16 14:23:23 +00:00
|
|
|
, npcState = Just (NPCStanding 0 future)
|
2018-04-14 09:18:37 +00:00
|
|
|
}
|
|
|
|
) npcposs
|
2018-02-18 02:11:41 +00:00
|
|
|
uu <- partSubscribe m movePlayer
|
2018-02-17 01:36:06 +00:00
|
|
|
putAffection ud
|
2018-02-25 01:03:25 +00:00
|
|
|
{ worldState = nws
|
2018-02-18 04:31:34 +00:00
|
|
|
, stateData = MenuData
|
2018-03-06 20:58:55 +00:00
|
|
|
{ mapMat = mat
|
2018-03-31 21:22:10 +00:00
|
|
|
, imgMat = M.fromList (nrows inter) (ncols inter) $
|
|
|
|
Prelude.map
|
|
|
|
(\a -> if a == Just ImgEmpty then Nothing else a)
|
|
|
|
(M.toList inter)
|
2018-02-23 12:07:24 +00:00
|
|
|
, initCoords = (0, 500)
|
2018-04-14 16:43:05 +00:00
|
|
|
, reachPoints = rps
|
2018-02-17 01:36:06 +00:00
|
|
|
}
|
2018-02-18 02:11:41 +00:00
|
|
|
, uuid = [uu]
|
2018-02-17 01:36:06 +00:00
|
|
|
}
|
|
|
|
|
2018-02-18 04:31:34 +00:00
|
|
|
mouseToPlayer :: V2 Int32 -> Affection UserData ()
|
|
|
|
mouseToPlayer mv2 = do
|
2018-02-18 02:11:41 +00:00
|
|
|
ud <- getAffection
|
2018-03-06 20:58:55 +00:00
|
|
|
(V2 rx ry) <- liftIO $ relativizeMouseCoords mv2
|
2018-02-24 22:15:16 +00:00
|
|
|
let dr = (ry / sin (atan (1/2)) / 2) + rx
|
|
|
|
dc = rx - (ry / sin (atan (1/2)) / 2)
|
2018-05-17 11:06:13 +00:00
|
|
|
(nws, _) <- liftIO $ yieldSystemT (worldState ud) $ do
|
|
|
|
emap allEnts $ do
|
2018-02-18 04:31:34 +00:00
|
|
|
with player
|
2018-05-17 11:06:13 +00:00
|
|
|
pure $ unchanged
|
2018-05-13 20:01:05 +00:00
|
|
|
{ vel = Set $ 4 * V2 dr dc
|
2018-02-18 04:31:34 +00:00
|
|
|
}
|
2018-02-18 02:11:41 +00:00
|
|
|
putAffection ud
|
2018-02-25 01:03:25 +00:00
|
|
|
{ worldState = nws
|
2018-02-18 04:31:34 +00:00
|
|
|
}
|
|
|
|
|
|
|
|
movePlayer :: MouseMessage -> Affection UserData ()
|
|
|
|
movePlayer (MsgMouseMotion _ _ _ [SDL.ButtonLeft] m _) = mouseToPlayer m
|
|
|
|
movePlayer (MsgMouseButton _ _ SDL.Pressed _ SDL.ButtonLeft _ m) =
|
|
|
|
mouseToPlayer m
|
2018-03-06 20:58:55 +00:00
|
|
|
movePlayer (MsgMouseButton _ _ SDL.Released _ SDL.ButtonLeft _ _) = do
|
2018-02-18 04:31:34 +00:00
|
|
|
ud <- getAffection
|
2018-05-17 11:06:13 +00:00
|
|
|
(nws, _) <- liftIO $ yieldSystemT (worldState ud) $ do
|
|
|
|
emap allEnts $ do
|
2018-02-18 04:31:34 +00:00
|
|
|
with player
|
2018-05-17 11:06:13 +00:00
|
|
|
pure $ unchanged
|
2018-02-18 04:31:34 +00:00
|
|
|
{ vel = Set $ V2 0 0
|
|
|
|
}
|
|
|
|
putAffection ud
|
2018-02-25 01:03:25 +00:00
|
|
|
{ worldState = nws
|
2018-02-18 02:11:41 +00:00
|
|
|
}
|
|
|
|
movePlayer _ = return ()
|
|
|
|
|
2018-02-17 01:36:06 +00:00
|
|
|
drawMap :: Affection UserData ()
|
|
|
|
drawMap = do
|
|
|
|
ud <- getAffection
|
2018-03-01 22:33:08 +00:00
|
|
|
dt <- getDelta
|
2018-05-20 22:40:40 +00:00
|
|
|
(_, (playerPos, playerRot, npcposrots)) <- liftIO $ yieldSystemT (worldState ud) $ do
|
|
|
|
(pc, dir) <- fmap head $ efor allEnts $ do
|
2018-04-14 09:18:37 +00:00
|
|
|
with player
|
2018-04-14 16:43:05 +00:00
|
|
|
with pos
|
2018-05-20 22:40:40 +00:00
|
|
|
with rot
|
2018-05-17 11:06:13 +00:00
|
|
|
pos' <- query pos
|
2018-05-20 22:40:40 +00:00
|
|
|
rot' <- query rot
|
|
|
|
pure (pos', rot')
|
2018-04-22 09:59:14 +00:00
|
|
|
-- (_, npcposs) <- yieldSystemT (worldState ud) $ do
|
2018-05-20 22:40:40 +00:00
|
|
|
npcsrots <- efor allEnts $ do
|
2018-04-14 16:43:05 +00:00
|
|
|
with npcState
|
|
|
|
with pos
|
2018-05-17 11:06:13 +00:00
|
|
|
pos' <- query pos
|
2018-05-20 22:40:40 +00:00
|
|
|
rot' <- query rot
|
|
|
|
pure (pos', rot')
|
|
|
|
return (pc, dir, npcsrots)
|
|
|
|
let V2 pr pc = playerPos
|
2018-03-06 20:58:55 +00:00
|
|
|
mat = imgMat (stateData ud)
|
2018-03-03 10:06:38 +00:00
|
|
|
ctx = nano ud
|
2018-03-06 20:58:55 +00:00
|
|
|
cols = fromIntegral (ncols mat)
|
|
|
|
rows = fromIntegral (nrows mat)
|
2018-03-03 10:06:38 +00:00
|
|
|
tileWidth = 64 :: Double
|
|
|
|
tileHeight = 32 :: Double
|
|
|
|
x = realToFrac $ 640 + ((1 - pc) + (1 - pr)) * (tileWidth / 2)
|
|
|
|
y = realToFrac $ 360 + ((1 - pr) - (1 - pc)) * (tileHeight / 2)
|
2018-04-14 09:18:53 +00:00
|
|
|
liftIO $ do -- draw floor
|
2018-03-03 10:06:38 +00:00
|
|
|
beginPath ctx
|
2018-03-30 19:30:27 +00:00
|
|
|
moveTo ctx (x + realToFrac tileWidth / 2) y
|
2018-03-03 10:06:38 +00:00
|
|
|
lineTo ctx
|
|
|
|
(x + cols * (realToFrac tileWidth / 2))
|
2018-03-30 19:30:27 +00:00
|
|
|
(y - (realToFrac tileHeight / 2) * (cols - 1))
|
2018-03-03 10:06:38 +00:00
|
|
|
lineTo ctx
|
2018-03-30 19:30:27 +00:00
|
|
|
(x + (realToFrac tileWidth / 2) * (cols + rows - 1))
|
2018-03-03 10:06:38 +00:00
|
|
|
(y + (rows - cols) * (realToFrac tileHeight / 2))
|
|
|
|
lineTo ctx
|
2018-03-30 19:30:27 +00:00
|
|
|
(x + (realToFrac tileWidth / 2) * rows)
|
|
|
|
(y + (realToFrac tileHeight / 2) * (rows - 1))
|
2018-03-03 10:06:38 +00:00
|
|
|
closePath ctx
|
|
|
|
fillColor ctx (rgb 255 255 255)
|
|
|
|
fill ctx
|
2018-05-15 17:27:54 +00:00
|
|
|
mapM_ (\(i, ls) -> mapM_
|
|
|
|
(\(j, t) -> do
|
2018-05-20 22:40:40 +00:00
|
|
|
drawTile (assetImages ud) ctx pr pc i j t (dirToImgId playerRot)
|
|
|
|
drawNPCs (assetImages ud) ctx ud npcposrots pr pc i j t
|
2018-05-15 17:27:54 +00:00
|
|
|
)
|
|
|
|
(reverse $ zip [1..] ls))
|
|
|
|
(zip [1..] (toLists mat))
|
|
|
|
-- liftIO $ do -- draw FPS
|
2018-03-01 22:33:08 +00:00
|
|
|
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-02-17 01:36:06 +00:00
|
|
|
|
2018-02-18 04:31:34 +00:00
|
|
|
updateMap :: Double -> Affection UserData ()
|
2018-02-24 21:24:48 +00:00
|
|
|
updateMap dt = do
|
2018-05-20 22:40:40 +00:00
|
|
|
let direction vel'@(V2 vr _) rot' = if sqrt (vel' `dot` vel') > 0
|
|
|
|
then toEnum (
|
|
|
|
let xuu = floor
|
|
|
|
((((acos ((vel' `dot` V2 0 1) / sqrt (vel' `dot` vel'))) /
|
|
|
|
pi) + 0.25) * 4 )
|
|
|
|
xu = if vr < 0 then 7 - xuu else xuu
|
|
|
|
in A.log A.Debug ("xu: " ++ show xu) xu)
|
|
|
|
else rot'
|
2018-02-18 04:31:34 +00:00
|
|
|
ud <- getAffection
|
2018-05-17 11:06:13 +00:00
|
|
|
(nws, _) <- liftIO $ yieldSystemT (worldState ud) $ do
|
|
|
|
emap allEnts $ do
|
2018-05-01 21:00:20 +00:00
|
|
|
without player
|
|
|
|
with vel
|
2018-05-15 17:27:40 +00:00
|
|
|
with velFact
|
2018-05-01 21:00:20 +00:00
|
|
|
with pos
|
2018-05-20 22:40:40 +00:00
|
|
|
with rot
|
2018-05-17 11:06:13 +00:00
|
|
|
pos'@(V2 pr pc) <- query pos
|
|
|
|
vel' <- query vel
|
2018-05-20 22:40:40 +00:00
|
|
|
rot' <- query rot
|
2018-05-17 11:06:13 +00:00
|
|
|
fact' <- query velFact
|
2018-05-15 17:27:40 +00:00
|
|
|
let npos@(V2 nr nc) = pos' + fmap (* (dt * fact')) vel'
|
2018-05-01 21:00:20 +00:00
|
|
|
dpos = npos - pos'
|
2018-05-17 11:06:13 +00:00
|
|
|
ent = unchanged
|
2018-05-01 21:00:20 +00:00
|
|
|
{ pos = Set $ npos
|
2018-05-20 22:40:40 +00:00
|
|
|
, rot = Set $ direction vel' rot'
|
2018-05-01 21:00:20 +00:00
|
|
|
}
|
|
|
|
return ent
|
2018-05-17 11:06:13 +00:00
|
|
|
emap allEnts $ do
|
2018-05-01 21:00:20 +00:00
|
|
|
with player
|
2018-02-25 01:03:25 +00:00
|
|
|
with vel
|
|
|
|
with pos
|
2018-05-20 22:40:40 +00:00
|
|
|
with rot
|
2018-05-17 11:06:13 +00:00
|
|
|
pos'@(V2 pr pc) <- query pos
|
2018-05-20 22:40:40 +00:00
|
|
|
vel'@(V2 vr vc) <- query vel
|
|
|
|
rot' <- query rot
|
2018-05-13 20:01:05 +00:00
|
|
|
let npos@(V2 nr nc) = pos' + fmap (* dt) vel'
|
2018-05-01 21:52:40 +00:00
|
|
|
dpos@(V2 dpr dpc) = npos - pos'
|
2018-05-05 17:23:24 +00:00
|
|
|
len = sqrt (dpos `dot` dpos)
|
2018-05-13 12:05:15 +00:00
|
|
|
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)])
|
|
|
|
-- lll = Prelude.map (\i ->
|
|
|
|
-- let lrow =
|
|
|
|
-- [ (nr - (fromIntegral $ floor nr))
|
|
|
|
-- , (nr - (fromIntegral $ floor nr)) + (dpr / len)
|
|
|
|
-- ..
|
|
|
|
-- ]
|
|
|
|
-- lcol =
|
|
|
|
-- [ (nc - (fromIntegral $ floor nc))
|
|
|
|
-- , (nc - (fromIntegral $ floor nc)) + (dpc / len)
|
|
|
|
-- ..
|
|
|
|
-- ]
|
|
|
|
-- in (fromIntegral (floor (lrow !! i)), fromIntegral (floor (lcol !! i)))
|
|
|
|
-- )
|
|
|
|
-- [ 0 .. floor len]
|
2018-05-17 11:06:13 +00:00
|
|
|
ent = unchanged
|
2018-03-06 15:37:21 +00:00
|
|
|
{ pos = Set $ pos' + dpos * Prelude.foldl
|
2018-05-01 21:00:20 +00:00
|
|
|
(\acc a -> let ret = checkBoundsCollision2 pos' npos dt acc a
|
2018-05-14 16:12:37 +00:00
|
|
|
in A.log A.Verbose (show ret) ret)
|
2018-03-06 15:37:21 +00:00
|
|
|
(V2 1 1)
|
2018-03-10 09:07:37 +00:00
|
|
|
(
|
|
|
|
concatMap
|
|
|
|
(\(dr, dc) ->
|
2018-03-10 13:02:14 +00:00
|
|
|
let bs = fromMaybe [] (imgObstacle <$> (M.safeGet
|
2018-05-14 15:54:55 +00:00
|
|
|
(fromIntegral $ floor pr + dr)
|
|
|
|
(fromIntegral $ floor pc + dc)
|
2018-03-10 13:02:14 +00:00
|
|
|
(imgMat (stateData ud))))
|
2018-03-10 09:07:37 +00:00
|
|
|
in Prelude.map (\(Boundaries (minr, minc) (maxr, maxc))->
|
|
|
|
Boundaries
|
2018-05-13 12:05:15 +00:00
|
|
|
(minr + fromIntegral dr, minc + fromIntegral dc)
|
|
|
|
(maxr + fromIntegral dr, maxc + fromIntegral dc)
|
2018-03-10 09:07:37 +00:00
|
|
|
) bs
|
|
|
|
)
|
2018-05-14 16:12:37 +00:00
|
|
|
(A.log A.Verbose (show lll ++ " " ++ show len) lll)
|
2018-03-10 09:07:37 +00:00
|
|
|
)
|
2018-05-20 22:40:40 +00:00
|
|
|
, rot = Set (A.log A.Debug ("dir: " ++ show (direction vel' rot'))
|
|
|
|
(direction vel' rot'))
|
2018-03-05 20:11:38 +00:00
|
|
|
}
|
2018-02-25 09:30:13 +00:00
|
|
|
return ent
|
2018-04-14 16:43:05 +00:00
|
|
|
updateNPCs
|
|
|
|
(imgMat $ stateData ud)
|
|
|
|
(Prelude.filter
|
|
|
|
(\p -> pointType p /= RoomExit)
|
|
|
|
(reachPoints $ stateData ud)
|
|
|
|
)
|
|
|
|
dt
|
2018-02-18 04:31:34 +00:00
|
|
|
putAffection ud
|
2018-02-25 01:03:25 +00:00
|
|
|
{ worldState = nws
|
2018-02-18 04:31:34 +00:00
|
|
|
}
|
|
|
|
|
2018-03-03 16:03:17 +00:00
|
|
|
drawTile
|
|
|
|
:: Map ImgId Image
|
|
|
|
-> Context
|
|
|
|
-> Double
|
|
|
|
-> Double
|
|
|
|
-> Int
|
|
|
|
-> Int
|
|
|
|
-> Maybe ImgId
|
2018-05-20 22:40:40 +00:00
|
|
|
-> ImgId
|
2018-03-03 16:03:17 +00:00
|
|
|
-> IO ()
|
2018-05-20 22:40:40 +00:00
|
|
|
drawTile ai ctx pr pc row col img playerImg =
|
2018-04-22 09:59:14 +00:00
|
|
|
when ((realToFrac x > -tileWidth && realToFrac y > -tileHeight) &&
|
|
|
|
(realToFrac x < 1280 && realToFrac (y - (74 - realToFrac tileHeight)) < 720)) $
|
|
|
|
do
|
|
|
|
save ctx
|
|
|
|
if (isNothing img)
|
|
|
|
then drawPlayer
|
2018-03-04 21:24:30 +00:00
|
|
|
else do
|
2018-04-22 09:59:14 +00:00
|
|
|
if (Prelude.null mb)
|
|
|
|
then do
|
|
|
|
drawImage
|
|
|
|
drawPlayer
|
|
|
|
else do
|
|
|
|
if (all (\m -> pr > (fromIntegral (floor pr :: Int)) + m) minrs &&
|
|
|
|
all (\m -> pc < (fromIntegral (floor pc :: Int)) + m) mincs) ||
|
|
|
|
(all (\m -> pr > (fromIntegral (floor pr :: Int)) + m) minrs &&
|
|
|
|
all (\m -> pc < (fromIntegral (floor pc :: Int)) + m) maxcs)
|
|
|
|
then do
|
|
|
|
drawImage
|
|
|
|
drawPlayer
|
|
|
|
else do
|
|
|
|
drawPlayer
|
|
|
|
drawImage
|
|
|
|
restore ctx
|
2018-03-04 21:24:30 +00:00
|
|
|
where
|
|
|
|
tileWidth = 64 :: Double
|
|
|
|
tileHeight = 32 :: Double
|
2018-03-05 20:11:38 +00:00
|
|
|
minrs = Prelude.map (fst . matmin) mb
|
|
|
|
maxrs = Prelude.map (fst . matmax) mb
|
|
|
|
mincs = Prelude.map (snd . matmin) mb
|
2018-03-06 22:04:52 +00:00
|
|
|
maxcs = Prelude.map (snd . matmax) mb
|
2018-03-04 21:24:30 +00:00
|
|
|
x = realToFrac $ 640 + ((fromIntegral col - pc) +
|
2018-04-22 09:59:14 +00:00
|
|
|
(fromIntegral row - pr)) * (tileWidth / 2) :: CFloat
|
2018-03-04 21:24:30 +00:00
|
|
|
y = realToFrac $ 360 - (tileHeight / 2) + ((fromIntegral row - pr) -
|
2018-04-22 09:59:14 +00:00
|
|
|
(fromIntegral col - pc)) * (tileHeight / 2) :: CFloat
|
2018-03-04 21:24:30 +00:00
|
|
|
dist = distance (V2 (fromIntegral row) (fromIntegral col))
|
|
|
|
(V2 (realToFrac pr - 1) (realToFrac pc)) / 4
|
|
|
|
fact =
|
2018-03-06 22:04:52 +00:00
|
|
|
if (pr <= fromIntegral row + minimum maxrs &&
|
|
|
|
pc >= fromIntegral col + maximum mincs) &&
|
2018-03-05 20:11:38 +00:00
|
|
|
isWall (fromJust img)
|
2018-03-04 21:24:30 +00:00
|
|
|
then min 1 dist
|
|
|
|
else 1
|
|
|
|
mb = imgObstacle img
|
|
|
|
drawImage = do
|
|
|
|
beginPath ctx
|
|
|
|
paint <- imagePattern
|
2018-03-08 19:19:53 +00:00
|
|
|
ctx x (y - (74 - realToFrac tileHeight))
|
2018-03-04 21:24:30 +00:00
|
|
|
(realToFrac tileWidth) 74
|
|
|
|
0
|
|
|
|
(ai Map.! fromJust img)
|
|
|
|
fact
|
2018-03-08 19:19:53 +00:00
|
|
|
rect ctx x (y - (74 - realToFrac tileHeight)) (realToFrac tileWidth) 74
|
2018-03-04 21:24:30 +00:00
|
|
|
fillPaint ctx paint
|
|
|
|
fill ctx
|
|
|
|
drawPlayer = do
|
|
|
|
when (floor pr == row && floor pc == col) $ do
|
|
|
|
beginPath ctx
|
2018-05-20 22:40:40 +00:00
|
|
|
paint <- imagePattern
|
|
|
|
ctx 608 302 64 74 0 (ai Map.! playerImg) 1
|
|
|
|
rect ctx 608 302 64 74
|
|
|
|
fillPaint ctx paint
|
|
|
|
-- circle ctx 640 360 5
|
|
|
|
-- closePath ctx
|
|
|
|
-- fillColor ctx (rgba 0 255 255 255)
|
2018-03-04 21:24:30 +00:00
|
|
|
fill ctx
|
2018-03-05 20:11:38 +00:00
|
|
|
|
|
|
|
checkBoundsCollision
|
|
|
|
:: V2 Double
|
|
|
|
-> V2 Double
|
2018-03-06 15:37:21 +00:00
|
|
|
-> V2 Double
|
2018-03-05 20:11:38 +00:00
|
|
|
-> Boundaries Double
|
|
|
|
-> V2 Double
|
|
|
|
checkBoundsCollision
|
2018-03-06 20:58:55 +00:00
|
|
|
(V2 pr pc) (V2 fr fc) (V2 mr mc) (Boundaries (minr, minc) (maxr, maxc))
|
2018-03-10 13:02:14 +00:00
|
|
|
| ntestc && ntestr && not testr && not testc = V2 (1 * mr) (1 * mc)
|
|
|
|
| ntestc && ntestr && not testc = V2 (1 * mr) (0 * mc)
|
|
|
|
| ntestr && ntestc && not testr = V2 (0 * mr) (1 * mc)
|
|
|
|
| not ntestr && not ntestc = V2 (1 * mr) (1 * mc)
|
|
|
|
| not ntestr && ntestc = V2 (1 * mr) (1 * mc)
|
|
|
|
| not ntestc && ntestr = V2 (1 * mr) (1 * mc)
|
|
|
|
| otherwise = V2 (0 * mr) (0 * mc)
|
2018-03-06 20:29:17 +00:00
|
|
|
where
|
|
|
|
ntestr
|
2018-04-30 18:34:45 +00:00
|
|
|
= ndistr <= hheight + 0.15
|
2018-03-10 09:07:37 +00:00
|
|
|
-- | ncdistsq <= 0.005 = True
|
2018-03-06 20:29:17 +00:00
|
|
|
ntestc
|
2018-04-30 18:34:45 +00:00
|
|
|
= ndistc <= hwidth + 0.15
|
2018-03-10 09:07:37 +00:00
|
|
|
-- | ncdistsq <= 0.005 = True
|
2018-03-06 20:29:17 +00:00
|
|
|
testr
|
2018-04-30 18:34:45 +00:00
|
|
|
= distr <= hheight + 0.15
|
2018-03-10 09:07:37 +00:00
|
|
|
-- | cdistsq <= 0.005 = True
|
2018-03-06 20:29:17 +00:00
|
|
|
testc
|
2018-04-30 18:34:45 +00:00
|
|
|
= distc <= hwidth + 0.15
|
2018-03-10 09:07:37 +00:00
|
|
|
-- | cdistsq <= 0.005 = True
|
2018-03-07 15:01:37 +00:00
|
|
|
ndistr = abs (fr - (fromIntegral (floor fr :: Int) + (minr + hheight)))
|
|
|
|
ndistc = abs (fc - (fromIntegral (floor fc :: Int) + (minc + hwidth)))
|
|
|
|
distr = abs (pr - (fromIntegral (floor fr :: Int) + (minr + hheight)))
|
|
|
|
distc = abs (pc - (fromIntegral (floor fc :: Int) + (minc + hwidth)))
|
2018-03-06 20:29:17 +00:00
|
|
|
hheight = (maxr - minr) / 2
|
|
|
|
hwidth = (maxc - minc) / 2
|
2018-03-06 20:58:55 +00:00
|
|
|
ncdistsq = (ndistr - hheight) ^ (2 :: Int) + (ndistc - hwidth) ^ (2 :: Int)
|
|
|
|
cdistsq = (distr - hheight) ^ (2 :: Int) + (distc - hwidth) ^ (2 :: Int)
|
2018-05-01 21:00:20 +00:00
|
|
|
|
|
|
|
checkBoundsCollision2
|
|
|
|
:: V2 Double
|
|
|
|
-> V2 Double
|
|
|
|
-> Double
|
|
|
|
-> V2 Double
|
|
|
|
-> Boundaries Double
|
|
|
|
-> V2 Double
|
|
|
|
checkBoundsCollision2
|
|
|
|
pre@(V2 pr pc) next@(V2 nr nc) dt acc (Boundaries (minr, minc) (maxr, maxc))
|
2018-05-14 16:12:37 +00: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 21:00:20 +00:00
|
|
|
where
|
|
|
|
vel@(V2 vr vc) = fmap (/ dt) (next - pre)
|
|
|
|
colltr
|
2018-05-14 16:12:37 +00:00
|
|
|
| vr > 0 && prr <= maxr =
|
|
|
|
(((fromIntegral (floor pr :: Int)) + minr - 0.15) - pr) / vr
|
|
|
|
| vr < 0 && prr >= minr =
|
|
|
|
(((fromIntegral (floor pr :: Int)) + maxr + 0.15) - pr) / vr
|
2018-05-14 15:54:55 +00:00
|
|
|
| otherwise = dt
|
2018-05-01 21:00:20 +00:00
|
|
|
colltc
|
2018-05-14 16:12:37 +00:00
|
|
|
| vc > 0 && prc <= maxc =
|
|
|
|
(((fromIntegral (floor pc :: Int)) + minc - 0.15) - pc) / vc
|
|
|
|
| vc < 0 && prc >= minc =
|
|
|
|
(((fromIntegral (floor pc :: Int)) + maxc + 0.15) - pc) / vc
|
2018-05-14 15:54:55 +00:00
|
|
|
| otherwise = dt
|
2018-05-13 12:05:15 +00:00
|
|
|
inrow = pr > minr && pr < maxr
|
|
|
|
incol = pc > minc && pc < maxc
|
2018-05-14 16:00:18 +00:00
|
|
|
prr = pr - (fromIntegral $ floor pr)
|
|
|
|
prc = pc - (fromIntegral $ floor pc)
|