2018-07-03 00:20:17 +00:00
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
|
|
|
{-# LANGUAGE TypeFamilies #-}
|
2018-07-19 02:56:31 +00:00
|
|
|
{-# LANGUAGE BangPatterns #-}
|
2018-06-28 19:07:58 +00:00
|
|
|
module MainGame.WorldMap where
|
2018-02-17 01:36:06 +00:00
|
|
|
|
2018-05-30 15:32:00 +00:00
|
|
|
import Affection as A
|
2018-02-17 01:36:06 +00:00
|
|
|
|
2018-09-12 22:51:22 +00:00
|
|
|
import Algebra.Graph as AG hiding (Context(..))
|
2018-06-28 19:07:58 +00:00
|
|
|
|
2018-02-18 02:11:41 +00:00
|
|
|
import qualified SDL
|
2018-03-11 23:21:16 +00:00
|
|
|
import NanoVG hiding (V2(..))
|
2018-02-18 02:11:41 +00:00
|
|
|
|
2018-05-30 15:32:00 +00:00
|
|
|
import Control.Monad (when, void)
|
2018-02-17 01:36:06 +00:00
|
|
|
import Control.Monad.IO.Class (liftIO)
|
2018-08-10 06:58:26 +00:00
|
|
|
import Control.Monad.State.Strict (evalStateT)
|
2018-05-16 14:23:23 +00:00
|
|
|
import Control.Concurrent.MVar
|
2018-06-07 22:29:46 +00:00
|
|
|
import Control.Concurrent (forkIO)
|
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-06-28 19:07:58 +00:00
|
|
|
import Data.List as L (sortOn, partition, find)
|
2018-02-17 01:36:06 +00:00
|
|
|
|
2018-04-14 16:43:05 +00:00
|
|
|
import System.Random (randomRIO)
|
|
|
|
|
2018-05-26 06:34:49 +00:00
|
|
|
import Linear hiding (E)
|
2018-02-18 02:11:41 +00:00
|
|
|
|
2018-02-17 01:36:06 +00:00
|
|
|
import Foreign.C.Types (CFloat(..))
|
|
|
|
|
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-06-28 19:07:58 +00:00
|
|
|
import MindMap
|
2018-04-14 09:18:37 +00:00
|
|
|
import NPC
|
2018-08-18 03:01:52 +00:00
|
|
|
-- import Object
|
2018-07-30 12:34:46 +00:00
|
|
|
import Animation
|
2019-02-15 19:01:14 +00:00
|
|
|
import Collision
|
2018-03-02 01:10:35 +00:00
|
|
|
|
2018-02-17 01:36:06 +00:00
|
|
|
loadMap :: Affection UserData ()
|
|
|
|
loadMap = do
|
|
|
|
ud <- getAffection
|
2018-08-10 06:58:26 +00:00
|
|
|
ad <- get
|
2018-10-12 22:07:19 +00:00
|
|
|
let (Subsystems _ m k j t) = subsystems ud
|
2019-02-11 23:11:53 +00:00
|
|
|
uu0 <- partSubscribe k emitKbdActionMessage
|
|
|
|
uu1 <- partSubscribe j emitJoyActionMessage
|
|
|
|
uu2 <- partSubscribe t movePlayer2
|
|
|
|
uu3 <- partSubscribe t playerInteract2
|
|
|
|
uu4 <- partSubscribe t changeMaps2
|
2018-07-03 14:19:27 +00:00
|
|
|
future <- liftIO newEmptyMVar
|
2018-07-19 02:51:07 +00:00
|
|
|
progress <- liftIO $ newMVar (0, "Ohai!")
|
2018-08-10 06:58:26 +00:00
|
|
|
_ <- liftIO $ forkIO $ loadMapFork ud ad future progress
|
2018-06-07 22:29:46 +00:00
|
|
|
putAffection ud
|
|
|
|
{ stateData = None
|
2019-02-11 23:11:53 +00:00
|
|
|
, uuid = [ uu0, uu1, uu2, uu3, uu4 ]
|
2018-06-08 23:17:03 +00:00
|
|
|
, stateMVar = future
|
|
|
|
, stateProgress = progress
|
2018-10-12 22:07:19 +00:00
|
|
|
, state = Main WorldMap
|
2018-06-07 22:29:46 +00:00
|
|
|
}
|
|
|
|
|
2018-06-28 19:07:58 +00:00
|
|
|
changeMaps :: KeyboardMessage -> Affection UserData ()
|
|
|
|
changeMaps (MsgKeyboardEvent _ _ SDL.Pressed False sym)
|
|
|
|
| SDL.keysymKeycode sym == SDL.KeycodeF1 = do
|
2019-02-11 23:11:53 +00:00
|
|
|
ud <- getAffection
|
|
|
|
case state ud of
|
|
|
|
Main MindMap ->
|
|
|
|
putAffection ud
|
|
|
|
{ state = Main WorldMap
|
|
|
|
}
|
|
|
|
Main WorldMap ->
|
|
|
|
putAffection ud
|
|
|
|
{ state = Main MindMap
|
|
|
|
}
|
|
|
|
_ -> return ()
|
2018-06-28 19:07:58 +00:00
|
|
|
| otherwise = return ()
|
|
|
|
changeMaps _ = return ()
|
|
|
|
|
2018-10-13 18:12:10 +00:00
|
|
|
changeMaps2 :: ActionMessage -> Affection UserData ()
|
2019-02-11 23:11:53 +00:00
|
|
|
changeMaps2 (ActionMessage ActSwitchMap _) = do
|
2018-10-13 18:12:10 +00:00
|
|
|
ud <- getAffection
|
|
|
|
case state ud of
|
|
|
|
Main MindMap ->
|
|
|
|
putAffection ud
|
|
|
|
{ state = Main WorldMap
|
|
|
|
}
|
|
|
|
Main WorldMap ->
|
|
|
|
putAffection ud
|
|
|
|
{ state = Main MindMap
|
|
|
|
}
|
|
|
|
_ -> return ()
|
|
|
|
changeMaps2 _ = return ()
|
|
|
|
|
2018-06-08 23:17:03 +00:00
|
|
|
loadMapFork
|
|
|
|
:: UserData
|
2018-08-10 06:58:26 +00:00
|
|
|
-> AffectionData UserData
|
|
|
|
-> MVar (SystemState Entity (AffectionState (AffectionData UserData) IO), StateData)
|
2018-07-19 02:51:07 +00:00
|
|
|
-> MVar (Float, T.Text)
|
2018-06-08 23:17:03 +00:00
|
|
|
-> IO ()
|
2018-08-10 06:58:26 +00:00
|
|
|
loadMapFork ud ad future progress = do
|
2019-02-14 21:31:00 +00:00
|
|
|
let loadSteps = 23
|
2018-09-07 17:12:04 +00:00
|
|
|
increment = 1 / loadSteps
|
2018-06-08 23:17:03 +00:00
|
|
|
fc = FloorConfig
|
2018-09-08 12:05:07 +00:00
|
|
|
(V2 10 10)
|
|
|
|
[(V2 5 5), (V2 5 20)]
|
2018-11-13 03:16:02 +00:00
|
|
|
(50, 50)
|
2018-09-07 17:12:04 +00:00
|
|
|
modifyMVar_ progress (return . (\(p, _) ->
|
|
|
|
( p + increment
|
|
|
|
, "Building floor"
|
|
|
|
)))
|
2019-02-07 04:23:44 +00:00
|
|
|
(mat, gr) <- buildHallFloorIO fc progress increment -- 11 increments inside
|
2018-09-07 17:12:04 +00:00
|
|
|
modifyMVar_ progress (return . (\(p, _) ->
|
|
|
|
( p + increment
|
|
|
|
, "Converting to images"
|
|
|
|
)))
|
2018-09-16 21:29:02 +00:00
|
|
|
let !imgmat = convertTileToImg mat
|
|
|
|
!exits = Prelude.foldl
|
2018-07-21 18:37:01 +00:00
|
|
|
(\acc coord@(r, c) -> if imgmat M.! coord == Just ImgEmpty
|
2019-02-09 00:23:38 +00:00
|
|
|
then ReachPoint RoomExit (V2 r c) NE 0 : acc
|
2018-04-02 14:29:35 +00:00
|
|
|
else acc
|
|
|
|
)
|
|
|
|
[]
|
|
|
|
((,) <$> [1 .. nrows mat] <*> [1 .. ncols mat])
|
2018-09-07 17:12:04 +00:00
|
|
|
modifyMVar_ progress (return . (\(p, _) ->
|
|
|
|
( p + increment
|
|
|
|
, "Placing furniture"
|
|
|
|
)))
|
2019-01-18 18:02:45 +00:00
|
|
|
(!inter, !rawrps) <- placeInteriorIO mat imgmat exits gr
|
2019-02-09 00:23:38 +00:00
|
|
|
let !rps = ReachPoint Elevator (fcElevator fc) SE 0 : rawrps
|
2018-09-07 17:12:04 +00:00
|
|
|
modifyMVar_ progress (return . (\(p, _) ->
|
|
|
|
( p + increment
|
2018-09-07 17:49:16 +00:00
|
|
|
, "Creating WorldState"
|
2018-09-07 17:12:04 +00:00
|
|
|
)))
|
2018-09-07 17:49:16 +00:00
|
|
|
(nws, mmimgmat) <- evalStateT (runState (yieldSystemT (worldState ud) $ do
|
2018-09-07 17:12:04 +00:00
|
|
|
liftIO $ modifyMVar_ progress (return . (\(p, _) ->
|
|
|
|
( p + increment
|
|
|
|
, "Registering copiers into WorldState"
|
|
|
|
)))
|
2018-09-16 21:29:02 +00:00
|
|
|
let !copiers = Prelude.filter (\a -> pointType a == Copier) rps
|
2019-02-09 00:23:38 +00:00
|
|
|
mapM_ (\(ReachPoint _ icoord _ _) -> do
|
2018-07-21 04:43:26 +00:00
|
|
|
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)
|
2019-02-14 21:31:00 +00:00
|
|
|
, anim = Just $ AnimState (AnimId AnimCopier "open" N) 0 0
|
2018-09-02 08:44:33 +00:00
|
|
|
, objAccess = Just (V2 1 0, NW)
|
2018-07-22 20:30:17 +00:00
|
|
|
, objType = Just ObjCopier
|
2018-08-10 06:58:26 +00:00
|
|
|
, objState = Just "idle"
|
2018-07-21 04:43:26 +00:00
|
|
|
}
|
|
|
|
) (A.log A.Debug ("number of copiers: " ++ show (length copiers)) copiers)
|
2018-09-07 17:12:04 +00:00
|
|
|
liftIO $ modifyMVar_ progress (return . (\(p, _) ->
|
|
|
|
( p + increment
|
|
|
|
, "Registering computers into WorldState"
|
|
|
|
)))
|
2019-02-14 21:31:00 +00:00
|
|
|
let !computers = Prelude.filter ((Computer ==) . pointType) rps
|
2019-02-09 00:23:38 +00:00
|
|
|
mapM_ (\(ReachPoint _ icoord dir _) -> do
|
2018-07-30 12:34:46 +00:00
|
|
|
let reachCoord = fmap ((+ 0.5) . fromIntegral) icoord
|
2019-02-09 14:19:16 +00:00
|
|
|
access = case dir of
|
|
|
|
N -> V2 1 (-1)
|
|
|
|
NE -> V2 0 (-1)
|
2019-02-09 21:39:42 +00:00
|
|
|
NW -> V2 1 0
|
|
|
|
x -> error ("computer placement " ++ show x ++ " not defined")
|
2018-09-08 12:05:07 +00:00
|
|
|
void $ createEntity $ newEntity
|
2019-02-09 14:19:16 +00:00
|
|
|
{ pos = Just $ reachCoord - fmap fromIntegral access
|
2019-02-14 21:31:00 +00:00
|
|
|
, anim = Just $ AnimState (AnimId AnimComputer "off" dir) 0 0
|
2019-02-09 14:19:16 +00:00
|
|
|
, objAccess = Just (access, dir)
|
2018-07-30 12:34:46 +00:00
|
|
|
, objType = Just ObjComputer
|
2018-08-11 09:51:20 +00:00
|
|
|
, objState = Just "off"
|
2018-07-30 12:34:46 +00:00
|
|
|
}
|
|
|
|
) (A.log A.Debug ("number of computers: " ++ show (length computers)) computers)
|
2018-09-07 17:12:04 +00:00
|
|
|
liftIO $ modifyMVar_ progress (return . (\(p, _) ->
|
|
|
|
( p + increment
|
|
|
|
, "Registering toilets into WorldState"
|
|
|
|
)))
|
2018-09-16 21:29:02 +00:00
|
|
|
let !toilets = Prelude.filter (\a -> pointType a == Toilet) rps
|
2019-02-09 00:23:38 +00:00
|
|
|
mapM_ (\(ReachPoint _ icoord dir _) -> do
|
2018-07-31 20:59:25 +00:00
|
|
|
let reachCoord = fmap ((+ 0.5) . fromIntegral) icoord
|
|
|
|
void $ createEntity $ newEntity
|
|
|
|
{ pos = Just $ reachCoord - V2 0 (-1)
|
|
|
|
, obstacle = Just $ Boundaries (0, 0) (1, 1)
|
2019-02-14 21:31:00 +00:00
|
|
|
, anim = Just $ AnimState (AnimId AnimToilet "free" N) 0 0
|
2018-09-02 08:44:33 +00:00
|
|
|
, objAccess = Just (V2 0 (-1), dir)
|
2018-07-31 20:59:25 +00:00
|
|
|
, objType = Just ObjToilet
|
|
|
|
}
|
|
|
|
) (A.log A.Debug ("number of toilets: " ++ show (length toilets)) toilets)
|
2018-09-07 17:49:16 +00:00
|
|
|
liftIO $ modifyMVar_ progress (return . (\(p, _) ->
|
|
|
|
( p + increment
|
|
|
|
, "Preparing MindMap graph"
|
|
|
|
)))
|
|
|
|
(mmintmat, mmgraph) <- liftIO $ buildFloorMap . springField <$>
|
2018-09-12 22:51:22 +00:00
|
|
|
buildMindMap (length computers) 2
|
2018-09-07 17:49:16 +00:00
|
|
|
liftIO $ modifyMVar_ progress (return . (\(p, _) ->
|
|
|
|
( p + increment
|
|
|
|
, "Unfolding and Converting MindMap to images"
|
|
|
|
)))
|
|
|
|
let !mmimgmat = convertTileToImg $ manhattan mmgraph mmintmat
|
2018-09-16 21:29:02 +00:00
|
|
|
!pmmpos = (+ 0.5) . (fromIntegral :: Int -> Double) . floor <$> mmPos
|
2018-09-07 17:49:16 +00:00
|
|
|
(fromJust $ find (\a -> mmId a == 0) (vertexList mmgraph))
|
2018-09-16 21:29:02 +00:00
|
|
|
!delta = (0, 0) :
|
2018-09-07 17:49:16 +00:00
|
|
|
Prelude.filter (/= (0,0)) ((,) <$> [-1 .. 1] <*> [-1 .. 1]) :: [(Int, Int)]
|
2018-09-16 21:29:02 +00:00
|
|
|
!mmmpos = Prelude.foldl (\acc (dr, dc) ->
|
2018-09-07 17:49:16 +00:00
|
|
|
let (V2 pmr pmc) = floor <$> pmmpos
|
|
|
|
seekpos = (pmr + fromIntegral dr, pmc + fromIntegral dc)
|
|
|
|
in if isNothing (mmimgmat M.! seekpos) && mmintmat M.! seekpos == 0
|
|
|
|
&& isNothing acc
|
|
|
|
then Just (pmmpos + (fromIntegral <$> V2 dr dc))
|
|
|
|
else acc
|
|
|
|
) Nothing delta
|
|
|
|
void $ createEntity $ newEntity
|
|
|
|
{ pos = Just (V2 10.5 10.5)
|
|
|
|
, mmpos = mmmpos
|
|
|
|
, vel = Just (V2 0 0)
|
2018-10-12 22:07:19 +00:00
|
|
|
, xyvel = Just (V2 0 0)
|
2018-09-07 17:49:16 +00:00
|
|
|
, mmvel = Just (V2 0 0)
|
|
|
|
, player = Just ()
|
|
|
|
, rot = Just SE
|
2019-02-14 21:31:00 +00:00
|
|
|
, anim = Just $ AnimState (AnimId AnimIntruder "standing" SE) 0 0
|
2018-09-07 17:49:16 +00:00
|
|
|
}
|
2018-09-12 22:51:22 +00:00
|
|
|
liftIO $ A.logIO A.Debug $ "number of placed NPCs: " ++ show (length computers)
|
2018-09-07 17:12:04 +00:00
|
|
|
liftIO $ modifyMVar_ progress (return . (\(p, _) ->
|
|
|
|
( p + increment
|
|
|
|
, "Registering NPCs into WorldState"
|
|
|
|
)))
|
2019-02-08 05:36:52 +00:00
|
|
|
mapM_ (\cpr -> do
|
2018-05-15 17:27:40 +00:00
|
|
|
fact <- liftIO $ randomRIO (0.5, 1.5)
|
2018-09-12 22:51:22 +00:00
|
|
|
-- fut <- liftIO newEmptyMVar
|
2018-09-07 21:39:53 +00:00
|
|
|
stats <- liftIO $ NPCStats
|
|
|
|
<$> (randomRIO (0, 1))
|
|
|
|
<*> (randomRIO (0, 1))
|
|
|
|
<*> (randomRIO (0, 1))
|
|
|
|
<*> (randomRIO (0, 1))
|
|
|
|
<*> (randomRIO (0, 1))
|
|
|
|
<*> (randomRIO (0, 1))
|
2019-02-08 05:36:52 +00:00
|
|
|
let room = head
|
|
|
|
(Prelude.filter
|
|
|
|
((inBounds $ pointCoord cpr) . bounds)
|
|
|
|
(Types.connects (head gr) ++ tail gr)
|
|
|
|
)
|
2018-05-30 15:32:00 +00:00
|
|
|
void $ createEntity $ newEntity
|
2019-02-14 21:31:00 +00:00
|
|
|
{ pos = Just (fmap ((+ 0.5) . fromIntegral) (pointCoord cpr))
|
|
|
|
, vel = Just (V2 0 0)
|
|
|
|
, velFact = Just fact
|
|
|
|
, rot = Just SE
|
|
|
|
, npcMoveState = Just (NPCWalking [pointCoord cpr])
|
|
|
|
, npcWorkplace = Just cpr
|
|
|
|
, npcActionState = Just ASWork
|
|
|
|
, npcStats = Just stats
|
|
|
|
, clearanceLvl = Just (clearance room)
|
|
|
|
, anim = Just $ AnimState (AnimId AnimJDoeM "standing" SE) 0 0
|
2018-04-14 09:18:37 +00:00
|
|
|
}
|
2018-09-12 22:51:22 +00:00
|
|
|
) computers
|
2018-09-07 17:12:04 +00:00
|
|
|
liftIO $ modifyMVar_ progress (return . (\(p, _) ->
|
2019-02-14 21:31:00 +00:00
|
|
|
( p + increment
|
|
|
|
, "Registering doors into WorldState"
|
|
|
|
)))
|
2019-02-15 05:50:39 +00:00
|
|
|
let doors = Prelude.filter ((\t -> t == RoomExit || t == Elevator) . pointType) rps
|
2019-02-14 21:31:00 +00:00
|
|
|
mapM_ (\door -> do
|
|
|
|
let rooms = Prelude.foldl
|
|
|
|
(\acc coord ->
|
|
|
|
let rs = Prelude.filter ((inBounds coord) . bounds) graph
|
|
|
|
in
|
|
|
|
if not (Prelude.null rs)
|
|
|
|
then (coord, head rs) : acc
|
|
|
|
else acc
|
|
|
|
)
|
|
|
|
[]
|
|
|
|
coords
|
|
|
|
[coord] = Prelude.filter
|
|
|
|
(\(V2 r c) -> (Door ==) $ (mat M.! (r, c)))
|
|
|
|
coords
|
|
|
|
graph = Types.connects (head gr) ++ tail gr
|
|
|
|
coords = Prelude.map (pointCoord door +) deltas
|
|
|
|
dcoords = Prelude.map (coord +) deltas
|
|
|
|
deltas =
|
|
|
|
[ V2 0 1
|
|
|
|
, V2 1 0
|
|
|
|
, V2 (-1) 0
|
|
|
|
, V2 0 (-1)
|
|
|
|
]
|
|
|
|
wall = Prelude.filter
|
|
|
|
(\delta ->
|
|
|
|
let V2 r c = coord + delta
|
|
|
|
in
|
|
|
|
fromMaybe False (isWall <$> imgmat M.! (r, c)))
|
|
|
|
deltas
|
|
|
|
orientation
|
|
|
|
| head wall == V2 0 1 || head wall == V2 0 (-1) = NE
|
|
|
|
| head wall == V2 1 0 || head wall == V2 (-1) 0 = NW
|
|
|
|
| otherwise = error ("strange wall: " ++ show wall)
|
|
|
|
void $ createEntity $ newEntity
|
2019-02-15 19:02:34 +00:00
|
|
|
{ pos = Just (fmap ((+ 0.5) . fromIntegral) coord)
|
|
|
|
, clearanceLvl = Just (maximum $ 0 : Prelude.map clearance (Prelude.map snd rooms))
|
|
|
|
, anim = Just $ AnimState (AnimId AnimDoor0 "shut" orientation) 0 0
|
2019-02-16 01:21:07 +00:00
|
|
|
, obstacle = Just $ case orientation of
|
|
|
|
NE -> Boundaries (4/9, 0) (5/9, 1)
|
|
|
|
NW -> Boundaries (0, 4/9) (1, 5/9)
|
|
|
|
_ -> error "strange orientation for door"
|
2019-02-15 19:02:34 +00:00
|
|
|
, ignoreObstacle = Just ()
|
2019-02-14 21:31:00 +00:00
|
|
|
}
|
|
|
|
) doors
|
|
|
|
liftIO $ modifyMVar_ progress (return . (\(p, _) ->
|
2018-09-07 17:12:04 +00:00
|
|
|
( p + increment
|
|
|
|
, "Handing over"
|
|
|
|
)))
|
2018-09-07 17:49:16 +00:00
|
|
|
return mmimgmat
|
2018-08-10 06:58:26 +00:00
|
|
|
)) ad
|
2018-09-16 21:29:02 +00:00
|
|
|
let !retMat = M.fromList (nrows inter) (ncols inter) $
|
2018-03-31 21:22:10 +00:00
|
|
|
Prelude.map
|
2018-07-21 18:37:01 +00:00
|
|
|
(\a -> if a == Just ImgEmpty || a == Just ImgEmptyNoWalk
|
|
|
|
then Nothing
|
|
|
|
else a)
|
2018-03-31 21:22:10 +00:00
|
|
|
(M.toList inter)
|
2018-09-15 17:22:04 +00:00
|
|
|
putMVar future (nws, MainData
|
|
|
|
{ mapMat = mat
|
|
|
|
, imgMat = retMat
|
2018-04-14 16:43:05 +00:00
|
|
|
, reachPoints = rps
|
2018-06-28 19:07:58 +00:00
|
|
|
, mmImgMat = mmimgmat
|
2019-02-09 00:23:38 +00:00
|
|
|
, roomGraph = gr
|
2018-06-07 22:29:46 +00:00
|
|
|
})
|
2018-02-17 01:36:06 +00:00
|
|
|
|
2019-02-11 23:11:53 +00:00
|
|
|
-- mouseToPlayer :: V2 Int32 -> Affection UserData ()
|
|
|
|
-- mouseToPlayer mv2 = do
|
|
|
|
-- ud <- getAffection
|
|
|
|
-- (V2 rx ry) <- liftIO $ relativizeMouseCoords mv2
|
|
|
|
-- (nws, _) <- yieldSystemT (worldState ud) $
|
|
|
|
-- emap allEnts $ do
|
|
|
|
-- with player
|
|
|
|
-- return $ unchanged
|
|
|
|
-- { xyvel = Set $ V2 rx ry
|
|
|
|
-- }
|
|
|
|
-- putAffection ud
|
|
|
|
-- { worldState = nws
|
|
|
|
-- }
|
|
|
|
--
|
|
|
|
-- movePlayer :: MouseMessage -> Affection UserData ()
|
|
|
|
-- movePlayer (MsgMouseMotion _ _ _ [SDL.ButtonLeft] m _) = mouseToPlayer m
|
|
|
|
-- movePlayer (MsgMouseButton _ _ SDL.Pressed _ SDL.ButtonLeft _ m) =
|
|
|
|
-- mouseToPlayer m
|
|
|
|
-- movePlayer (MsgMouseButton _ _ SDL.Released _ SDL.ButtonLeft _ _) = do
|
|
|
|
-- ud <- getAffection
|
|
|
|
-- (nws, _) <- yieldSystemT (worldState ud) $
|
|
|
|
-- emap allEnts $ do
|
|
|
|
-- with player
|
|
|
|
-- return $ unchanged
|
|
|
|
-- { xyvel = Set $ V2 0 0
|
|
|
|
-- }
|
|
|
|
-- putAffection ud
|
|
|
|
-- { worldState = nws
|
|
|
|
-- }
|
|
|
|
-- movePlayer _ = return ()
|
2018-02-18 04:31:34 +00:00
|
|
|
|
2019-02-11 23:11:53 +00:00
|
|
|
movePlayerKbd :: KeyboardMessage -> Affection UserData ()
|
|
|
|
movePlayerKbd (MsgKeyboardEvent _ _ press False sym)
|
|
|
|
| SDL.keysymKeycode sym == SDL.KeycodeW = do
|
|
|
|
ud <- getAffection
|
|
|
|
(nws, _) <- yieldSystemT (worldState ud) $
|
|
|
|
emap allEnts $ do
|
|
|
|
with player
|
|
|
|
(V2 vx _) <- query xyvel
|
|
|
|
let ry = if (press == SDL.Pressed)
|
|
|
|
then 1
|
|
|
|
else 0
|
|
|
|
return $ unchanged
|
|
|
|
{ xyvel = Set $ V2 vx ry
|
|
|
|
}
|
|
|
|
putAffection ud
|
|
|
|
{ worldState = nws
|
|
|
|
}
|
|
|
|
| SDL.keysymKeycode sym == SDL.KeycodeS = do
|
|
|
|
ud <- getAffection
|
|
|
|
(nws, _) <- yieldSystemT (worldState ud) $
|
|
|
|
emap allEnts $ do
|
|
|
|
with player
|
|
|
|
(V2 vx _) <- query xyvel
|
|
|
|
let ry = if (press == SDL.Pressed)
|
|
|
|
then -1
|
|
|
|
else 0
|
|
|
|
return $ unchanged
|
|
|
|
{ xyvel = Set $ V2 vx ry
|
|
|
|
}
|
|
|
|
putAffection ud
|
|
|
|
{ worldState = nws
|
|
|
|
}
|
|
|
|
| SDL.keysymKeycode sym == SDL.KeycodeA = do
|
|
|
|
ud <- getAffection
|
|
|
|
(nws, _) <- yieldSystemT (worldState ud) $
|
|
|
|
emap allEnts $ do
|
|
|
|
with player
|
|
|
|
(V2 _ vy) <- query xyvel
|
|
|
|
let rx = if (press == SDL.Pressed)
|
|
|
|
then -1
|
|
|
|
else 0
|
|
|
|
return $ unchanged
|
|
|
|
{ xyvel = Set $ V2 rx vy
|
|
|
|
}
|
|
|
|
putAffection ud
|
|
|
|
{ worldState = nws
|
|
|
|
}
|
|
|
|
| SDL.keysymKeycode sym == SDL.KeycodeD = do
|
|
|
|
ud <- getAffection
|
|
|
|
(nws, _) <- yieldSystemT (worldState ud) $
|
|
|
|
emap allEnts $ do
|
|
|
|
with player
|
|
|
|
(V2 _ vy) <- query xyvel
|
|
|
|
let rx = if (press == SDL.Pressed)
|
|
|
|
then 1
|
|
|
|
else 0
|
|
|
|
return $ unchanged
|
|
|
|
{ xyvel = Set $ V2 rx vy
|
|
|
|
}
|
|
|
|
putAffection ud
|
|
|
|
{ worldState = nws
|
|
|
|
}
|
|
|
|
| otherwise = return ()
|
|
|
|
movePlayerKbd _ = return ()
|
2018-02-18 02:11:41 +00:00
|
|
|
|
2018-10-12 22:07:19 +00:00
|
|
|
movePlayer2 :: ActionMessage -> Affection UserData ()
|
2019-02-11 23:11:53 +00:00
|
|
|
movePlayer2 (ActionMessage mov _) = do
|
2018-10-12 22:07:19 +00:00
|
|
|
ud <- getAffection
|
|
|
|
(nws, _) <- yieldSystemT (worldState ud) $
|
|
|
|
emap allEnts $ do
|
|
|
|
with player
|
2019-02-11 23:11:53 +00:00
|
|
|
V2 vx vy <- query xyvel
|
2018-10-12 22:07:19 +00:00
|
|
|
return $ unchanged
|
2019-02-11 23:11:53 +00:00
|
|
|
{ xyvel = Set $ case mov of
|
|
|
|
ActUp f -> V2 vx (-f)
|
|
|
|
ActDown f -> V2 vx f
|
|
|
|
ActLeft f -> V2 (-f) vy
|
|
|
|
ActRight f -> V2 f vy
|
|
|
|
_ -> V2 vx vy
|
2018-10-12 22:07:19 +00:00
|
|
|
}
|
|
|
|
putAffection ud
|
|
|
|
{ worldState = nws
|
|
|
|
}
|
|
|
|
movePlayer2 _ = return ()
|
|
|
|
|
2018-07-22 20:30:17 +00:00
|
|
|
playerInteract :: MouseMessage -> Affection UserData ()
|
|
|
|
playerInteract (MsgMouseButton _ _ SDL.Pressed _ SDL.ButtonRight _ m) = do
|
|
|
|
ud <- getAffection
|
2018-08-05 02:05:35 +00:00
|
|
|
(V2 rx ry) <- liftIO $ (* V2 640 360) <$> relativizeMouseCoords m
|
|
|
|
let dr = ((ry / 32) / sin (atan 0.5) / 2) + (rx / 64)
|
|
|
|
dc = (rx / 64) - ((ry / 32) / sin (atan 0.5) / 2)
|
2018-08-18 03:01:52 +00:00
|
|
|
(nws, _) <- yieldSystemT (worldState ud) $ do
|
2018-07-22 20:30:17 +00:00
|
|
|
emap allEnts $ do
|
|
|
|
with player
|
|
|
|
with rot
|
|
|
|
rot' <- query rot
|
2018-07-24 23:10:21 +00:00
|
|
|
let ndir = direction (V2 dr dc)
|
2018-07-22 20:30:17 +00:00
|
|
|
return $ unchanged
|
|
|
|
{ rot = Set $ fromMaybe rot' ndir
|
|
|
|
}
|
2019-01-06 02:52:43 +00:00
|
|
|
pdata <- efor allEnts $ do
|
2018-07-22 20:30:17 +00:00
|
|
|
with player
|
|
|
|
with pos
|
|
|
|
with rot
|
|
|
|
pos' <- query pos
|
|
|
|
rot' <- query rot
|
2018-09-12 22:51:22 +00:00
|
|
|
ent <- queryEnt
|
|
|
|
return (pos', rot', ent)
|
2019-01-06 02:52:43 +00:00
|
|
|
let (ppos, pdir, pent) = head pdata
|
2018-07-22 20:30:17 +00:00
|
|
|
mrelEnts <- efor allEnts $ do
|
|
|
|
with pos
|
|
|
|
with objAccess
|
2018-08-10 06:58:26 +00:00
|
|
|
with objType
|
|
|
|
with objState
|
2018-07-22 20:30:17 +00:00
|
|
|
(rel, dir) <- query objAccess
|
|
|
|
pos' <- query pos
|
|
|
|
otype <- query objType
|
2018-08-10 06:58:26 +00:00
|
|
|
ostate <- query objState
|
2018-07-22 20:30:17 +00:00
|
|
|
ent <- queryEnt
|
2018-09-02 08:44:33 +00:00
|
|
|
if ((fmap floor ppos :: V2 Int) == (fmap floor pos' :: V2 Int) ||
|
2018-08-18 03:01:52 +00:00
|
|
|
(fmap floor ppos :: V2 Int) == (fmap floor pos' :: V2 Int) + rel) &&
|
|
|
|
(fmap floor (ppos + V2 dr dc) :: V2 Int) == (fmap floor pos' ::V2 Int) &&
|
2018-07-22 20:30:17 +00:00
|
|
|
pdir == dir
|
2018-08-10 06:58:26 +00:00
|
|
|
then return $ Just (otype, ostate, ent)
|
2018-07-22 20:30:17 +00:00
|
|
|
else return Nothing
|
2018-08-10 06:58:26 +00:00
|
|
|
let relEnts = catMaybes mrelEnts
|
|
|
|
liftIO $ A.logIO A.Debug ("relEnts: " ++ show relEnts)
|
|
|
|
-- liftIO $ A.logIO A.Debug ("dV2: " ++ show (V2 dr dc))
|
|
|
|
mapM_ (\(t, s, e) ->
|
2018-09-12 22:51:22 +00:00
|
|
|
setEntity e =<< objectTransition t s True e (Just pent)
|
2018-08-10 06:58:26 +00:00
|
|
|
) relEnts
|
2018-07-22 20:30:17 +00:00
|
|
|
putAffection ud
|
|
|
|
{ worldState = nws
|
|
|
|
}
|
|
|
|
playerInteract _ = return ()
|
|
|
|
|
2018-10-12 22:07:19 +00:00
|
|
|
playerInteract2 :: ActionMessage -> Affection UserData ()
|
2019-02-11 23:11:53 +00:00
|
|
|
playerInteract2 (ActionMessage ActActivate _) = do
|
2018-10-12 22:07:19 +00:00
|
|
|
ud <- getAffection
|
|
|
|
(nws, _) <- yieldSystemT (worldState ud) $ do
|
2019-01-06 02:52:43 +00:00
|
|
|
pdata <- efor allEnts $ do
|
2018-10-12 22:07:19 +00:00
|
|
|
with player
|
|
|
|
with pos
|
|
|
|
with rot
|
|
|
|
pos' <- query pos
|
|
|
|
rot' <- query rot
|
|
|
|
ent <- queryEnt
|
|
|
|
return (pos', rot', ent)
|
2019-01-06 02:52:43 +00:00
|
|
|
let (ppos, pdir, pent) = head pdata
|
2018-10-12 22:07:19 +00:00
|
|
|
mrelEnts <- efor allEnts $ do
|
|
|
|
with pos
|
|
|
|
with objAccess
|
|
|
|
with objType
|
|
|
|
with objState
|
|
|
|
(rel, dir) <- query objAccess
|
|
|
|
pos' <- query pos
|
|
|
|
otype <- query objType
|
|
|
|
ostate <- query objState
|
|
|
|
ent <- queryEnt
|
|
|
|
if ((fmap floor ppos :: V2 Int) == (fmap floor pos' :: V2 Int) ||
|
|
|
|
(fmap floor ppos :: V2 Int) == (fmap floor pos' :: V2 Int) + rel) &&
|
|
|
|
pdir == dir
|
|
|
|
then return $ Just (otype, ostate, ent)
|
|
|
|
else return Nothing
|
|
|
|
let relEnts = catMaybes mrelEnts
|
|
|
|
liftIO $ A.logIO A.Debug ("relEnts: " ++ show relEnts)
|
|
|
|
-- liftIO $ A.logIO A.Debug ("dV2: " ++ show (V2 dr dc))
|
|
|
|
mapM_ (\(t, s, e) ->
|
|
|
|
setEntity e =<< objectTransition t s True e (Just pent)
|
|
|
|
) relEnts
|
|
|
|
putAffection ud
|
|
|
|
{ worldState = nws
|
|
|
|
}
|
|
|
|
playerInteract2 _ = return ()
|
|
|
|
|
2018-02-17 01:36:06 +00:00
|
|
|
drawMap :: Affection UserData ()
|
|
|
|
drawMap = do
|
|
|
|
ud <- getAffection
|
2018-06-07 22:29:46 +00:00
|
|
|
let ctx = nano ud
|
|
|
|
case stateData ud of
|
|
|
|
None -> liftIO $ do
|
2018-06-08 23:17:03 +00:00
|
|
|
progress <- readMVar (stateProgress ud)
|
|
|
|
drawLoadScreen ud progress
|
2018-06-07 22:29:46 +00:00
|
|
|
_ -> do
|
|
|
|
dt <- getDelta
|
2018-08-10 08:29:12 +00:00
|
|
|
(_, (playerPos, posanims, posActions)) <- yieldSystemT (worldState ud) $ do
|
2019-01-06 02:52:43 +00:00
|
|
|
pc <- efor allEnts $ do
|
2018-06-07 22:29:46 +00:00
|
|
|
with player
|
|
|
|
with pos
|
|
|
|
query pos
|
|
|
|
posanims <- efor allEnts $ do
|
|
|
|
with anim
|
|
|
|
with pos
|
|
|
|
stat <- query anim
|
|
|
|
pos' <- query pos
|
2018-07-21 04:43:26 +00:00
|
|
|
mbnds <- queryMaybe obstacle
|
|
|
|
return (pos', stat, mbnds)
|
2018-08-10 08:29:12 +00:00
|
|
|
posActions <- efor allEnts $ do
|
|
|
|
with objType
|
|
|
|
with objState
|
|
|
|
with objStateTime
|
2018-08-10 09:35:08 +00:00
|
|
|
with objPlayerActivated
|
2018-08-10 08:29:12 +00:00
|
|
|
with pos
|
|
|
|
pos' <- query pos
|
|
|
|
t <- query objType
|
|
|
|
s <- query objState
|
2018-08-10 12:09:07 +00:00
|
|
|
pa <- query objPlayerActivated
|
2018-08-10 08:29:12 +00:00
|
|
|
let maxt = actionTime t s
|
|
|
|
ttl <- query objStateTime
|
2018-08-10 12:09:07 +00:00
|
|
|
return (pos', pa, realToFrac (1 - ttl / maxt))
|
2019-01-06 02:52:43 +00:00
|
|
|
return (head pc, posanims, posActions)
|
2018-06-07 22:29:46 +00:00
|
|
|
let V2 pr pc = playerPos
|
2019-02-09 00:23:38 +00:00
|
|
|
MainData _ _ _ _ gr = stateData ud
|
|
|
|
seekGraph = Types.connects (head gr) ++ tail gr
|
|
|
|
room = Prelude.filter (inBounds (fmap floor playerPos) . bounds) seekGraph
|
2018-06-07 22:29:46 +00:00
|
|
|
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 02:28:39 +00:00
|
|
|
)
|
2018-06-07 22:29:46 +00:00
|
|
|
processList
|
2018-07-21 04:43:26 +00:00
|
|
|
:: [(V2 Double, AnimState, Maybe (Boundaries Double))]
|
2018-06-07 22:29:46 +00:00
|
|
|
-> (Int, Int)
|
2018-07-21 04:43:26 +00:00
|
|
|
-> ( [(V2 Double, AnimState, Maybe (Boundaries Double))]
|
|
|
|
, [(V2 Double, AnimState, Maybe (Boundaries Double))]
|
|
|
|
)
|
2018-07-03 14:19:27 +00:00
|
|
|
processList list (r, c) =
|
2018-07-21 04:43:26 +00:00
|
|
|
let delimiter (V2 nr nc, _, _) =
|
2018-06-07 22:29:46 +00:00
|
|
|
floor nr == r && floor nc == c
|
|
|
|
in L.partition delimiter list
|
2018-09-08 19:40:05 +00:00
|
|
|
liftIO $ do
|
2018-06-07 22:29:46 +00:00
|
|
|
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))
|
2018-08-10 12:09:07 +00:00
|
|
|
mapM_ (\(V2 sr sc, pa, perc) -> when pa $ do
|
2018-08-10 08:29:12 +00:00
|
|
|
let lx = realToFrac $ 640 + ((sc - pc) +
|
|
|
|
(sr - pr)) * (tileWidth / 2) :: CFloat
|
|
|
|
ly = realToFrac $ 360 - (tileHeight / 2) + ((sr - pr) -
|
|
|
|
(sc - pc)) * (tileHeight / 2) :: CFloat
|
|
|
|
fillColor ctx (rgb 0 255 0)
|
|
|
|
strokeColor ctx (rgb 0 255 0)
|
|
|
|
strokeWidth ctx 2
|
|
|
|
beginPath ctx
|
|
|
|
rect ctx (lx - 25) (ly - 50) 50 10
|
|
|
|
stroke ctx
|
|
|
|
closePath ctx
|
|
|
|
beginPath ctx
|
|
|
|
rect ctx (lx - 25 * perc) (ly - 50) (50 * perc) 10
|
|
|
|
fill ctx
|
|
|
|
closePath ctx
|
|
|
|
) posActions
|
2018-06-07 22:29:46 +00:00
|
|
|
fontSize ctx 20
|
|
|
|
fontFace ctx (assetFonts ud Map.! FontBedstead)
|
|
|
|
textAlign ctx (S.fromList [AlignCenter,AlignTop])
|
|
|
|
fillColor ctx (rgb 255 128 0)
|
2019-02-09 00:23:38 +00:00
|
|
|
textBox ctx 0 0 200 (
|
|
|
|
"FPS: "
|
|
|
|
<> T.pack (Prelude.take 5 $ show (1/dt))
|
|
|
|
<> " Clearance: "
|
|
|
|
<> if not (Prelude.null room) then T.pack (show $ clearance $ head room) else "0"
|
|
|
|
)
|
2018-02-17 01:36:06 +00:00
|
|
|
|
2018-05-30 14:20:58 +00:00
|
|
|
drawTile
|
|
|
|
:: UserData
|
|
|
|
-> Context
|
2018-07-21 04:43:26 +00:00
|
|
|
-> [(V2 Double, AnimState, Maybe (Boundaries Double))]
|
2018-05-30 14:20:58 +00: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 15:32:00 +00:00
|
|
|
((realToFrac x :: Double) < 1280 &&
|
|
|
|
(realToFrac (y - (74 - (realToFrac tileHeight :: CFloat))) :: Double) < 720)) $
|
2018-05-30 14:20:58 +00:00
|
|
|
do
|
2018-11-16 11:38:40 +00:00
|
|
|
let (bef, beh) = L.partition delimiter sorted
|
2018-05-30 14:20:58 +00:00
|
|
|
save ctx
|
2018-06-16 09:40:51 +00:00
|
|
|
mapM_ drawAnim beh
|
2018-07-03 00:20:17 +00:00
|
|
|
maybe (return ()) (draw ud x (y - 42) 64 74 fact)
|
2018-07-21 04:43:26 +00:00
|
|
|
((assetImages ud Map.!) <$> case img of
|
2018-07-21 18:37:01 +00:00
|
|
|
Just ImgEmpty -> Nothing
|
2018-07-21 04:43:26 +00:00
|
|
|
_ -> img
|
|
|
|
)
|
2018-06-16 09:40:51 +00:00
|
|
|
mapM_ drawAnim bef
|
2018-05-30 14:20:58 +00:00
|
|
|
restore ctx
|
2018-07-30 13:34:45 +00: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 14:20:58 +00:00
|
|
|
where
|
2018-07-30 12:34:46 +00:00
|
|
|
delimiter (V2 nr nc, as, mbnds) =
|
|
|
|
animFloats (asId as) ||
|
2018-06-16 09:40:51 +00:00
|
|
|
all delimit mb
|
|
|
|
where
|
|
|
|
delimit b
|
2018-08-07 12:04:12 +00:00
|
|
|
| nnr > fst (matmax b) || nnc < snd (matmin b) =
|
|
|
|
True
|
2018-06-16 09:40:51 +00:00
|
|
|
| nnr > fst (matmin b) && nnr < fst (matmax b) =
|
2018-11-16 06:58:15 +00:00
|
|
|
nnc <= snd (matmin b)
|
2018-06-16 09:40:51 +00:00
|
|
|
| nnc > snd (matmin b) && nnc < snd (matmax b) =
|
2018-11-16 06:58:15 +00:00
|
|
|
nnr >= fst (matmax b)
|
2018-06-16 09:40:51 +00:00
|
|
|
| otherwise =
|
2018-08-07 12:04:12 +00:00
|
|
|
False
|
2018-07-21 04:43:26 +00:00
|
|
|
nnr = case mbnds of
|
2018-08-18 03:01:52 +00:00
|
|
|
Just (Boundaries (_, _) (maxr, _)) -> maxr
|
2018-07-21 04:43:26 +00:00
|
|
|
Nothing -> nr - fromIntegral ((floor nr) :: Int) :: Double
|
|
|
|
nnc = case mbnds of
|
2018-08-18 03:01:52 +00:00
|
|
|
Just (Boundaries (_, minc) (_, _)) -> minc
|
2018-07-21 04:43:26 +00:00
|
|
|
Nothing -> nc - fromIntegral ((floor nc) :: Int) :: Double
|
2018-06-16 09:40:51 +00:00
|
|
|
-- any (\m -> nr < fromIntegral (floor nr :: Int) + m) maxrs &&
|
|
|
|
-- any (\m -> nc > fromIntegral (floor nc :: Int) + m) mincs
|
2018-05-30 14:20:58 +00:00
|
|
|
tileWidth = 64 :: Double
|
|
|
|
tileHeight = 32 :: Double
|
2018-07-21 04:43:26 +00:00
|
|
|
sorted = sortOn (\(V2 sr sc, _, mbnds) -> case mbnds of
|
2018-11-16 16:44:57 +00:00
|
|
|
Just (Boundaries (_, _) (maxr, maxc)) -> maxr + (1 - maxc) * 10
|
|
|
|
_ -> (sr - (fromIntegral ((floor sr) :: Int))) +
|
|
|
|
(1 - (sc - (fromIntegral ((floor sc) :: Int)))) * 10
|
2018-07-21 04:43:26 +00:00
|
|
|
) posanims
|
|
|
|
-- sorted = posanims
|
2018-05-31 03:25:08 +00:00
|
|
|
minrs = Prelude.map (fst . matmin) mb
|
2018-05-30 14:20:58 +00: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 =
|
2018-07-30 19:10:42 +00:00
|
|
|
if isWall (fromJust img) &&
|
|
|
|
(pr <= fromIntegral row + minimum maxrs &&
|
|
|
|
pc >= fromIntegral col + maximum mincs)
|
2018-05-30 14:20:58 +00:00
|
|
|
then min 1 dist
|
|
|
|
else 1
|
2018-07-03 00:20:17 +00:00
|
|
|
mb = maybe [] collisionObstacle img
|
2018-07-21 04:43:26 +00:00
|
|
|
drawAnim (V2 nr nc, as, _) = do
|
2018-07-03 00:20:17 +00:00
|
|
|
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 14:20:58 +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-02-18 04:31:34 +00:00
|
|
|
ud <- getAffection
|
2018-09-18 01:13:53 +00:00
|
|
|
-- empty <- liftIO $ isEmptyMVar (stateMVar ud)
|
|
|
|
if stateData ud == None -- && empty
|
2018-06-07 22:29:46 +00:00
|
|
|
then do
|
2018-09-18 01:13:53 +00:00
|
|
|
mstart <- liftIO $ tryTakeMVar (stateMVar ud)
|
|
|
|
case mstart of
|
|
|
|
Just (nws, mendat) -> do
|
|
|
|
putAffection ud
|
|
|
|
{ worldState = nws
|
|
|
|
, stateData = mendat
|
2018-10-12 22:07:19 +00:00
|
|
|
, state = Main WorldMap
|
2018-09-18 01:13:53 +00:00
|
|
|
}
|
|
|
|
updateMap 0.1
|
|
|
|
updateMap 0.1
|
|
|
|
updateMap 0.1
|
|
|
|
updateMap 19
|
|
|
|
liftIO $ logIO A.Debug "Loaded game data"
|
|
|
|
Nothing -> return ()
|
2018-06-07 22:29:46 +00:00
|
|
|
else do
|
2018-08-10 06:58:26 +00:00
|
|
|
(nws, _) <- yieldSystemT (worldState ud) $ do
|
2018-06-07 22:29:46 +00:00
|
|
|
emap allEnts $ do
|
2018-10-12 22:07:19 +00:00
|
|
|
with player
|
|
|
|
with xyvel
|
|
|
|
with vel
|
|
|
|
V2 rx ry <- query xyvel
|
2018-11-13 19:15:29 +00:00
|
|
|
let V2 dr dc = fmap (* 1.5) (V2 rx ry `rotVec` 45)
|
2018-10-12 22:07:19 +00:00
|
|
|
return $ unchanged
|
|
|
|
{ vel = Set $ 2 * V2 dr dc
|
|
|
|
}
|
|
|
|
emap allEnts $ do
|
2018-06-07 22:29:46 +00:00
|
|
|
with anim
|
|
|
|
stat <- query anim
|
|
|
|
let an = assetAnimations ud Map.! asId stat
|
|
|
|
ntime = asElapsedTime stat + dt
|
2018-07-30 12:34:26 +00:00
|
|
|
nstate = if ntime > fromIntegral (asCurrentFrame stat + 1) *
|
2018-06-07 22:29:46 +00:00
|
|
|
(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 20:15:49 +00:00
|
|
|
stat
|
2018-06-07 22:29:46 +00:00
|
|
|
{ asElapsedTime = ntime
|
2018-05-30 20:15:49 +00:00
|
|
|
}
|
2018-06-07 22:29:46 +00:00
|
|
|
return $ unchanged
|
|
|
|
{ anim = Set nstate
|
|
|
|
}
|
2019-02-15 19:02:55 +00:00
|
|
|
obstacleBounds <- efor allEnts $ do
|
|
|
|
with obstacle
|
|
|
|
with pos
|
|
|
|
b <- query obstacle
|
|
|
|
pos' <- query pos
|
|
|
|
return (pos', b)
|
2018-06-07 22:29:46 +00:00
|
|
|
emap allEnts $ do
|
|
|
|
without player
|
|
|
|
with vel
|
|
|
|
with velFact
|
|
|
|
with pos
|
|
|
|
with rot
|
|
|
|
with anim
|
2019-02-15 19:02:55 +00:00
|
|
|
pos'@(V2 pr pc) <- query pos
|
2018-06-07 22:29:46 +00:00
|
|
|
vel' <- query vel
|
|
|
|
rot' <- query rot
|
|
|
|
fact' <- query velFact
|
|
|
|
stat <- query anim
|
|
|
|
let npos = pos' + fmap (* (dt * fact')) vel'
|
2019-02-15 19:02:55 +00:00
|
|
|
dpos@(V2 dpr dpc) = npos - pos'
|
2018-06-07 22:29:46 +00:00
|
|
|
aId = asId stat
|
2019-02-15 19:02:55 +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)])
|
|
|
|
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
|
|
|
|
(fromIntegral $ floor pr + dr)
|
|
|
|
(fromIntegral $ floor pc + dc)
|
|
|
|
(imgMat (stateData ud))))
|
|
|
|
(Prelude.map snd $ Prelude.filter
|
|
|
|
(\((V2 br bc), _) ->
|
|
|
|
floor pr + dr == floor br &&
|
|
|
|
floor pc + dc == floor bc
|
|
|
|
)
|
|
|
|
obstacleBounds)
|
|
|
|
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-07 22:29:46 +00:00
|
|
|
nstat = case aiName aId of
|
|
|
|
"walking"
|
|
|
|
| sqrt (vel' `dot` vel') > 0 ->
|
|
|
|
stat
|
|
|
|
{ asId = aId
|
2018-07-06 15:17:57 +00:00
|
|
|
{ aiDirection = fromMaybe rot' (direction vel')
|
2018-06-07 22:29:46 +00:00
|
|
|
}
|
2018-05-30 20:15:49 +00:00
|
|
|
}
|
2018-06-07 22:29:46 +00:00
|
|
|
| otherwise ->
|
|
|
|
stat
|
|
|
|
{ asId = aId
|
2018-07-06 15:17:57 +00:00
|
|
|
{ aiDirection = fromMaybe rot' (direction vel')
|
2018-06-07 22:29:46 +00:00
|
|
|
, aiName = "standing"
|
|
|
|
}
|
|
|
|
, asCurrentFrame = 0
|
2018-05-30 20:15:49 +00:00
|
|
|
}
|
2018-06-07 22:29:46 +00:00
|
|
|
"standing"
|
|
|
|
| sqrt (vel' `dot` vel') > 0 ->
|
|
|
|
stat
|
|
|
|
{ asId = aId
|
2018-07-06 15:17:57 +00:00
|
|
|
{ aiDirection = fromMaybe rot' (direction vel')
|
2018-06-07 22:29:46 +00:00
|
|
|
, aiName = "walking"
|
|
|
|
}
|
|
|
|
, asCurrentFrame = 0
|
2018-05-30 20:15:49 +00:00
|
|
|
}
|
2018-06-07 22:29:46 +00:00
|
|
|
| otherwise ->
|
|
|
|
stat
|
|
|
|
{ asId = aId
|
2018-07-06 15:17:57 +00:00
|
|
|
{ aiDirection = fromMaybe rot' (direction vel')
|
2018-06-07 22:29:46 +00:00
|
|
|
}
|
2018-05-30 20:15:49 +00:00
|
|
|
}
|
2018-06-07 22:29:46 +00:00
|
|
|
x -> error ("unknown animation name" ++ x)
|
|
|
|
ent = unchanged
|
2019-02-15 19:02:55 +00:00
|
|
|
{ pos = Set $ pos' + colldpos
|
2018-07-06 15:17:57 +00:00
|
|
|
, rot = Set $ fromMaybe rot' (direction vel')
|
2018-06-07 22:29:46 +00: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 15:17:57 +00:00
|
|
|
{ aiDirection = fromMaybe rot' (direction vel')
|
2018-06-07 22:29:46 +00:00
|
|
|
}
|
2018-05-30 20:15:49 +00:00
|
|
|
}
|
2018-06-07 22:29:46 +00:00
|
|
|
| otherwise ->
|
|
|
|
stat
|
|
|
|
{ asId = aId
|
2018-07-06 15:17:57 +00:00
|
|
|
{ aiDirection = fromMaybe rot' (direction vel')
|
2018-06-07 22:29:46 +00:00
|
|
|
, aiName = "standing"
|
|
|
|
}
|
|
|
|
, asCurrentFrame = 0
|
2018-05-30 20:15:49 +00:00
|
|
|
}
|
2018-06-07 22:29:46 +00:00
|
|
|
"standing"
|
|
|
|
| sqrt (colldpos `dot` colldpos) > 0 ->
|
|
|
|
stat
|
|
|
|
{ asId = aId
|
2018-07-06 15:17:57 +00:00
|
|
|
{ aiDirection = fromMaybe rot' (direction vel')
|
2018-06-07 22:29:46 +00:00
|
|
|
, aiName = "walking"
|
|
|
|
}
|
|
|
|
, asCurrentFrame = 0
|
2018-05-30 20:15:49 +00:00
|
|
|
}
|
2018-06-07 22:29:46 +00:00
|
|
|
| otherwise ->
|
|
|
|
stat
|
|
|
|
{ asId = aId
|
2018-07-06 15:17:57 +00:00
|
|
|
{ aiDirection = fromMaybe rot' (direction vel')
|
2018-06-07 22:29:46 +00: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
|
2018-11-16 06:12:27 +00:00
|
|
|
(\acc a ->
|
|
|
|
let ret = checkBoundsCollision2 pos' npos dt acc a
|
2018-06-07 22:29:46 +00:00
|
|
|
in A.log A.Verbose (show ret) ret)
|
|
|
|
(V2 1 1)
|
|
|
|
(
|
|
|
|
concatMap
|
|
|
|
(\(dr, dc) ->
|
2018-07-21 18:37:01 +00:00
|
|
|
let bs = (++)
|
|
|
|
(maybe [] collisionObstacle (fromMaybe Nothing $ M.safeGet
|
|
|
|
(fromIntegral $ floor pr + dr)
|
|
|
|
(fromIntegral $ floor pc + dc)
|
|
|
|
(imgMat (stateData ud))))
|
|
|
|
(Prelude.map snd $ Prelude.filter
|
|
|
|
(\((V2 br bc), _) ->
|
|
|
|
floor pr + dr == floor br &&
|
|
|
|
floor pc + dc == floor bc
|
|
|
|
)
|
|
|
|
obstacleBounds)
|
2018-06-07 22:29:46 +00:00
|
|
|
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 20:04:05 +00:00
|
|
|
)
|
2018-06-07 22:29:46 +00:00
|
|
|
ent = unchanged
|
|
|
|
{ pos = Set $ pos' + colldpos
|
2018-07-06 15:17:57 +00:00
|
|
|
, rot = Set (fromMaybe rot' $ direction vel')
|
2018-06-07 22:29:46 +00:00
|
|
|
, anim = Set nstat
|
|
|
|
}
|
2018-07-21 04:43:26 +00:00
|
|
|
-- liftIO $ A.logIO A.Debug ("player position: " ++ show (pos' + colldpos))
|
2018-06-07 22:29:46 +00:00
|
|
|
return ent
|
2018-08-10 06:58:26 +00:00
|
|
|
tses <- efor allEnts $ do
|
|
|
|
with objType
|
|
|
|
with objState
|
|
|
|
t <- query objType
|
|
|
|
s <- query objState
|
|
|
|
e <- queryEnt
|
|
|
|
return (t, s, e)
|
|
|
|
mapM_ (\(t, s, e) ->
|
|
|
|
objectAction dt t s e
|
|
|
|
) tses
|
2018-08-10 23:12:07 +00:00
|
|
|
(nws2, _) <- yieldSystemT nws $ updateNPCs
|
|
|
|
(imgMat $ stateData ud)
|
2018-09-12 22:51:22 +00:00
|
|
|
nws
|
2018-08-10 23:12:07 +00:00
|
|
|
(Prelude.filter
|
|
|
|
(\p -> pointType p /= RoomExit)
|
|
|
|
(reachPoints $ stateData ud)
|
|
|
|
)
|
|
|
|
dt
|
2018-06-07 22:29:46 +00:00
|
|
|
putAffection ud
|
2018-08-10 23:12:07 +00:00
|
|
|
{ worldState = nws2
|
2018-06-07 22:29:46 +00:00
|
|
|
}
|
2018-02-18 04:31:34 +00:00
|
|
|
|
2019-02-15 19:01:14 +00:00
|
|
|
-- checkBoundsCollision2
|
|
|
|
-- :: V2 Double
|
|
|
|
-- -> V2 Double
|
|
|
|
-- -> Double
|
|
|
|
-- -> V2 Double
|
|
|
|
-- -> Boundaries Double
|
|
|
|
-- -> V2 Double
|
|
|
|
-- checkBoundsCollision2
|
|
|
|
-- pre@(V2 pr pc) nex dt acc (Boundaries (minr, minc) (maxr, maxc))
|
|
|
|
-- | colltr < dt && colltc < dt = V2 0 0
|
|
|
|
-- | colltr < dt = V2 0 0
|
|
|
|
-- | colltc < dt = V2 0 0
|
|
|
|
-- | otherwise = acc
|
|
|
|
-- where
|
|
|
|
-- V2 vr vc = fmap (/ dt) (nex - pre)
|
|
|
|
-- colltr
|
|
|
|
-- | vr > 0 && prr <= maxr && (prc + 0.15 >= minc && prc - 0.15 <= maxc) =
|
|
|
|
-- ((fromIntegral (floor pr :: Int) + minr - 0.15) - pr) / vr
|
|
|
|
-- | vr < 0 && prr >= minr && (prc + 0.15 >= minc && prc - 0.15 <= maxc) =
|
|
|
|
-- ((fromIntegral (floor pr :: Int) + maxr + 0.15) - pr) / vr
|
|
|
|
-- | otherwise = dt
|
|
|
|
-- colltc
|
|
|
|
-- | vc > 0 && prc <= maxc && (prr + 0.15 >= minr && prr - 0.15 <= maxr) =
|
|
|
|
-- ((fromIntegral (floor pc :: Int) + minc - 0.15) - pc) / vc
|
|
|
|
-- | vc < 0 && prc >= minc && (prr + 0.15 >= minr && prr - 0.15 <= maxr) =
|
|
|
|
-- ((fromIntegral (floor pc :: Int) + maxc + 0.15) - pc) / vc
|
|
|
|
-- | otherwise = dt
|
|
|
|
-- prr = pr - fromIntegral (floor pr :: Int)
|
|
|
|
-- prc = pc - fromIntegral (floor pc :: Int)
|