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-02-18 04:31:34 +00:00
|
|
|
import Control.Monad (when, void)
|
2018-02-17 01:36:06 +00:00
|
|
|
import Control.Monad.IO.Class (liftIO)
|
|
|
|
|
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-02-27 19:35:08 +00:00
|
|
|
import Data.Matrix as M (toLists, (!), Matrix, safeGet)
|
2018-02-18 04:31:34 +00:00
|
|
|
import Data.Ecstasy as E
|
2018-02-17 01:36:06 +00:00
|
|
|
|
2018-02-18 02:11:41 +00:00
|
|
|
import NanoVG hiding (V2(..))
|
2018-02-17 01:36:06 +00:00
|
|
|
|
|
|
|
import Types
|
|
|
|
|
|
|
|
import Floorplan
|
|
|
|
|
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
|
|
|
|
|
|
|
loadMap :: Affection UserData ()
|
|
|
|
loadMap = do
|
|
|
|
ud <- getAffection
|
2018-02-27 19:35:08 +00:00
|
|
|
let fc = FloorConfig (20, 20) [(5,5), (45, 75)] (80,40)
|
2018-02-18 02:11:41 +00:00
|
|
|
(Subsystems _ m) = subsystems ud
|
2018-02-17 01:36:06 +00:00
|
|
|
matrix <- liftIO $ buildHallFloorIO fc
|
2018-02-25 01:03:25 +00:00
|
|
|
(nws, _) <- yieldSystemT (worldState ud) $ do
|
2018-02-18 04:31:34 +00:00
|
|
|
void $ newEntity $ defEntity
|
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)
|
|
|
|
, player = Just True
|
|
|
|
}
|
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-02-17 01:36:06 +00:00
|
|
|
{ mapMat = matrix
|
2018-02-23 12:07:24 +00:00
|
|
|
, initCoords = (0, 500)
|
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 02:11:41 +00:00
|
|
|
relativizeMouseCoords :: V2 Int32 -> IO (V2 Double)
|
|
|
|
relativizeMouseCoords (V2 ix iy) = do
|
2018-02-18 04:31:34 +00:00
|
|
|
(GL.Position vx vy, GL.Size vw vh) <- SDL.get GL.viewport
|
2018-02-18 02:11:41 +00:00
|
|
|
let rx = ix - vx
|
|
|
|
ry = iy - vy
|
|
|
|
hx = fromIntegral vw / 2
|
|
|
|
hy = fromIntegral vh / 2
|
|
|
|
dx = fromIntegral rx - hx
|
|
|
|
dy = fromIntegral ry - hy
|
|
|
|
return $ V2 (dx / hx) (dy / hy)
|
|
|
|
|
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
|
|
|
|
rela@(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-02-25 01:03:25 +00:00
|
|
|
(nws, _) <- yieldSystemT (worldState ud) $ do
|
2018-02-18 04:31:34 +00:00
|
|
|
emap $ do
|
|
|
|
with player
|
2018-02-25 09:30:13 +00:00
|
|
|
pos' <- E.get pos
|
2018-02-18 04:31:34 +00:00
|
|
|
pure $ defEntity'
|
|
|
|
{ vel = Set $ V2 dr dc
|
|
|
|
}
|
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-02-24 14:33:46 +00:00
|
|
|
movePlayer (MsgMouseButton _ _ SDL.Released _ SDL.ButtonLeft _ m) = do
|
2018-02-18 04:31:34 +00:00
|
|
|
ud <- getAffection
|
2018-02-25 01:03:25 +00:00
|
|
|
(nws, _) <- yieldSystemT (worldState ud) $ do
|
2018-02-18 04:31:34 +00:00
|
|
|
emap $ do
|
|
|
|
with player
|
|
|
|
pure $ defEntity'
|
|
|
|
{ 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-02-17 01:36:06 +00:00
|
|
|
let matrix = mapMat (stateData ud)
|
2018-02-27 23:36:54 +00:00
|
|
|
mapM_ (\(i, ls) -> mapM_ (uncurry $ drawTile i) (reverse $ zip [1..] ls))
|
|
|
|
(zip [1..] (toLists matrix))
|
2018-03-01 22:33:08 +00:00
|
|
|
liftIO $ do
|
|
|
|
let ctx = nano ud
|
|
|
|
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-02-18 04:31:34 +00:00
|
|
|
ud <- getAffection
|
2018-02-25 01:03:25 +00:00
|
|
|
let matrix = mapMat $ stateData ud
|
|
|
|
(nws, _) <- yieldSystemT (worldState ud) $ do
|
2018-02-18 04:31:34 +00:00
|
|
|
emap $ do
|
2018-02-25 01:03:25 +00:00
|
|
|
with vel
|
|
|
|
with pos
|
|
|
|
pos'@(V2 or oc) <- E.get pos
|
2018-02-18 04:31:34 +00:00
|
|
|
vel' <- E.get vel
|
2018-02-25 01:03:25 +00:00
|
|
|
let npos@(V2 nr nc) = pos' + fmap (* (4 * dt)) vel'
|
|
|
|
let ent
|
|
|
|
| Wall /= matrix M.! (floor nr, floor nc) =
|
|
|
|
defEntity'
|
|
|
|
{ pos = Set npos
|
|
|
|
}
|
|
|
|
| Wall /= matrix M.! (floor nr, floor oc) =
|
|
|
|
defEntity'
|
|
|
|
{ pos = Set (V2 nr oc)
|
|
|
|
}
|
|
|
|
| Wall /= matrix M.! (floor or, floor nc) =
|
|
|
|
defEntity'
|
|
|
|
{ pos = Set (V2 or nc)
|
|
|
|
}
|
|
|
|
| otherwise =
|
|
|
|
defEntity'
|
2018-02-25 09:30:13 +00:00
|
|
|
return ent
|
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-02-27 19:35:08 +00:00
|
|
|
neighWalls :: Int -> Int -> Matrix TileState -> Int
|
|
|
|
neighWalls row col mat =
|
|
|
|
Prelude.foldl (\acc (ir, ic) ->
|
|
|
|
if M.safeGet (row + ir) (col + ic) mat == Just Wall ||
|
|
|
|
M.safeGet (row + ir) (col + ic) mat == Just Door
|
|
|
|
then acc + 1
|
|
|
|
else acc
|
|
|
|
)
|
|
|
|
0
|
|
|
|
[ (0, -1)
|
|
|
|
, (-1, 0)
|
|
|
|
, (0, 1)
|
|
|
|
, (1, 0)
|
|
|
|
]
|
|
|
|
|
2018-02-17 01:36:06 +00:00
|
|
|
drawTile :: Int -> Int -> TileState -> Affection UserData ()
|
|
|
|
drawTile row col tile = do
|
2018-02-18 02:11:41 +00:00
|
|
|
ud <- getAffection
|
2018-02-24 14:33:46 +00:00
|
|
|
(_, playerPos) <- yieldSystemT (worldState ud) $ do
|
2018-02-18 04:31:34 +00:00
|
|
|
efor $ \_ -> do
|
|
|
|
with player
|
|
|
|
pos' <- E.get pos
|
|
|
|
pure pos'
|
2018-02-24 14:33:46 +00:00
|
|
|
let V2 pr pc = head playerPos
|
2018-02-18 04:31:34 +00:00
|
|
|
ctx = nano ud
|
2018-02-23 12:07:24 +00:00
|
|
|
(xinit, yinit) = initCoords $ stateData ud
|
2018-02-24 21:24:48 +00:00
|
|
|
tileWidth = 64 :: Double
|
|
|
|
tileHeight = 32 :: Double
|
2018-02-17 01:36:06 +00:00
|
|
|
liftIO $ do
|
|
|
|
save ctx
|
|
|
|
beginPath ctx
|
2018-02-27 23:36:54 +00:00
|
|
|
let x = realToFrac $ 640 + ((fromIntegral col - pc) +
|
|
|
|
(fromIntegral row - pr)) * (tileWidth / 2)
|
|
|
|
y = realToFrac $ 360 - (tileHeight / 2) + ((fromIntegral row - pr) -
|
|
|
|
(fromIntegral col - pc)) * (tileHeight / 2)
|
2018-02-17 01:36:06 +00:00
|
|
|
fillColor ctx (case tile of
|
|
|
|
Wall -> rgba 128 128 128 255
|
|
|
|
Door -> rgba 255 128 128 255
|
|
|
|
Hall -> rgba 255 255 255 255
|
|
|
|
Offi -> rgba 0 255 0 255
|
|
|
|
Toil -> rgba 0 0 255 255
|
|
|
|
Kitc -> rgba 255 0 0 255
|
|
|
|
Elev -> rgba 0 0 0 255
|
|
|
|
_ -> rgba 255 255 0 255
|
|
|
|
)
|
2018-02-25 09:30:13 +00:00
|
|
|
moveTo ctx x (y + realToFrac tileHeight / 2)
|
|
|
|
lineTo ctx (x + realToFrac tileWidth / 2) (y + realToFrac tileHeight)
|
|
|
|
lineTo ctx (x + realToFrac tileWidth) (y + realToFrac tileHeight / 2)
|
|
|
|
lineTo ctx (x + realToFrac tileWidth / 2) y
|
2018-02-17 01:36:06 +00:00
|
|
|
closePath ctx
|
|
|
|
fill ctx
|
2018-02-25 09:30:13 +00:00
|
|
|
when (tile == Wall) $ do
|
2018-02-28 20:30:59 +00:00
|
|
|
let img irow icol = case neighWalls irow icol mat of
|
2018-02-27 19:35:08 +00:00
|
|
|
4 ->
|
2018-02-28 20:30:59 +00:00
|
|
|
ImgWallCross
|
2018-02-27 19:35:08 +00:00
|
|
|
3
|
2018-02-28 20:30:59 +00:00
|
|
|
| M.safeGet (irow + 1) icol mat /= Just Wall &&
|
|
|
|
M.safeGet (irow + 1) icol mat /= Just Door ->
|
|
|
|
ImgWallTNW
|
|
|
|
| M.safeGet irow (icol + 1) mat /= Just Wall &&
|
|
|
|
M.safeGet irow (icol + 1) mat /= Just Door ->
|
|
|
|
ImgWallTSW
|
|
|
|
| M.safeGet (irow - 1) icol mat /= Just Wall &&
|
|
|
|
M.safeGet (irow - 1) icol mat /= Just Door ->
|
|
|
|
ImgWallTSE
|
2018-02-27 23:36:54 +00:00
|
|
|
| otherwise ->
|
2018-02-28 20:30:59 +00:00
|
|
|
ImgWallTNE
|
2018-02-27 19:35:08 +00:00
|
|
|
2
|
2018-02-28 20:30:59 +00:00
|
|
|
| (M.safeGet (irow + 1) icol mat == Just Wall ||
|
|
|
|
M.safeGet (irow + 1) icol mat == Just Door) &&
|
|
|
|
(M.safeGet (irow - 1) icol mat == Just Wall ||
|
|
|
|
M.safeGet (irow - 1) icol mat == Just Door) ->
|
|
|
|
ImgWallDesc
|
|
|
|
| (M.safeGet irow (icol + 1) mat == Just Wall ||
|
|
|
|
M.safeGet irow (icol + 1) mat == Just Door) &&
|
|
|
|
(M.safeGet irow (icol - 1) mat == Just Wall ||
|
|
|
|
M.safeGet irow (icol - 1) mat == Just Door) ->
|
|
|
|
ImgWallAsc
|
|
|
|
| (M.safeGet (irow - 1) icol mat == Just Wall ||
|
|
|
|
M.safeGet (irow - 1) icol mat == Just Door) &&
|
|
|
|
(M.safeGet irow (icol - 1) mat == Just Wall ||
|
|
|
|
M.safeGet irow (icol - 1) mat == Just Door) ->
|
|
|
|
ImgWallCornerW
|
|
|
|
| (M.safeGet irow (icol - 1) mat == Just Wall ||
|
|
|
|
M.safeGet irow (icol - 1) mat == Just Door) &&
|
|
|
|
(M.safeGet (irow + 1) icol mat == Just Wall ||
|
|
|
|
M.safeGet (irow + 1) icol mat == Just Door) ->
|
|
|
|
ImgWallCornerS
|
|
|
|
| (M.safeGet (irow + 1) icol mat == Just Wall ||
|
|
|
|
M.safeGet (irow + 1) icol mat == Just Door) &&
|
|
|
|
(M.safeGet irow (icol + 1) mat == Just Wall ||
|
|
|
|
M.safeGet irow (icol + 1) mat == Just Door) ->
|
|
|
|
ImgWallCornerE
|
2018-02-27 23:36:54 +00:00
|
|
|
| otherwise ->
|
2018-02-28 20:30:59 +00:00
|
|
|
ImgWallCornerN
|
2018-02-27 19:35:08 +00:00
|
|
|
1
|
2018-02-28 20:30:59 +00:00
|
|
|
| M.safeGet (irow - 1) icol mat == Just Wall ||
|
|
|
|
M.safeGet (irow - 1) icol mat == Just Door ->
|
|
|
|
ImgWallDesc
|
|
|
|
| M.safeGet (irow + 1) icol mat == Just Wall ||
|
|
|
|
M.safeGet (irow + 1) icol mat == Just Door ->
|
|
|
|
ImgWallDesc
|
|
|
|
| M.safeGet irow (icol + 1) mat == Just Wall ||
|
|
|
|
M.safeGet irow (icol + 1) mat == Just Door ->
|
|
|
|
ImgWallAsc
|
2018-02-27 23:36:54 +00:00
|
|
|
| otherwise ->
|
2018-02-28 20:30:59 +00:00
|
|
|
ImgWallAsc
|
2018-02-27 19:35:08 +00:00
|
|
|
0 ->
|
2018-02-28 20:30:59 +00:00
|
|
|
ImgWallCross
|
2018-02-27 19:35:08 +00:00
|
|
|
_ ->
|
2018-02-27 23:36:54 +00:00
|
|
|
error "unexpected number if neighbouring walls"
|
2018-02-27 19:35:08 +00:00
|
|
|
mat = mapMat (stateData ud)
|
2018-02-28 20:30:59 +00:00
|
|
|
dist = distance (V2 (fromIntegral row) (fromIntegral col))
|
|
|
|
(V2 (realToFrac pr - 0.5) (realToFrac pc + 0.5)) / 4
|
|
|
|
fact = if floor pr <= row && floor pc >= col
|
|
|
|
then min 1 dist
|
|
|
|
else 1
|
2018-02-25 09:30:13 +00:00
|
|
|
paint <- imagePattern
|
2018-02-28 20:30:59 +00:00
|
|
|
ctx x (y - (74 * fact - realToFrac tileHeight)) 64 74 0
|
|
|
|
(assetImages ud Map.! img row col)
|
|
|
|
fact
|
2018-02-25 09:30:13 +00:00
|
|
|
beginPath ctx
|
2018-02-28 20:30:59 +00:00
|
|
|
rect ctx x (y - (74 * fact - realToFrac tileHeight)) 64 74
|
2018-02-25 09:30:13 +00:00
|
|
|
fillPaint ctx paint
|
|
|
|
fill ctx
|
2018-02-27 23:36:54 +00:00
|
|
|
when (floor pr == row && floor pc == col) $ do
|
2018-02-18 02:11:41 +00:00
|
|
|
beginPath ctx
|
|
|
|
circle ctx 640 360 5
|
|
|
|
closePath ctx
|
|
|
|
fillColor ctx (rgba 0 255 255 255)
|
|
|
|
fill ctx
|
2018-02-17 01:36:06 +00:00
|
|
|
restore ctx
|