tracer/src/Test.hs

206 lines
6 KiB
Haskell
Raw Normal View History

module Test where
2018-02-18 02:11:41 +00:00
import Affection as A hiding (get)
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-02 01:10:35 +00:00
import Control.Monad (when, unless, void)
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-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-02 01:10:35 +00:00
import Data.Maybe (fromJust)
2018-02-18 02:11:41 +00:00
import NanoVG hiding (V2(..))
import Types
import Floorplan
2018-02-18 02:11:41 +00:00
import Linear
import Foreign.C.Types (CFloat(..))
2018-02-18 02:11:41 +00:00
import Debug.Trace
2018-03-02 01:10:35 +00:00
-- internal imports
import Util
loadMap :: Affection UserData ()
loadMap = do
ud <- getAffection
2018-03-03 10:06:38 +00:00
let fc = FloorConfig (20, 20) [(5,5), (35, 35)] (50,75)
2018-02-18 02:11:41 +00:00
(Subsystems _ m) = subsystems ud
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
putAffection ud
2018-02-25 01:03:25 +00:00
{ worldState = nws
2018-02-18 04:31:34 +00:00
, stateData = MenuData
{ mapMat = matrix
2018-03-02 01:10:35 +00:00
, imgMat = convertTileToImg matrix
2018-02-23 12:07:24 +00:00
, initCoords = (0, 500)
}
2018-02-18 02:11:41 +00:00
, uuid = [uu]
}
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
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 ()
drawMap :: Affection UserData ()
drawMap = do
ud <- getAffection
2018-03-01 22:33:08 +00:00
dt <- getDelta
2018-03-03 10:06:38 +00:00
(_, playerPos) <- yieldSystemT (worldState ud) $ do
efor $ \_ -> do
with player
pos' <- E.get pos
pure pos'
let V2 pr pc = head playerPos
matrix = imgMat (stateData ud)
ctx = nano ud
cols = fromIntegral (ncols matrix)
rows = fromIntegral (nrows matrix)
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-03-01 22:33:08 +00:00
liftIO $ do
2018-03-03 10:06:38 +00:00
beginPath ctx
moveTo ctx x y
lineTo ctx
(x + cols * (realToFrac tileWidth / 2))
(y - realToFrac tileHeight / 2 * cols)
lineTo ctx
(x + realToFrac tileWidth / 2 * (cols + rows))
(y + (rows - cols) * (realToFrac tileHeight / 2))
lineTo ctx
(x + realToFrac tileWidth / 2 * rows)
(y + realToFrac tileHeight / 2 * rows)
closePath ctx
fillColor ctx (rgb 255 255 255)
fill ctx
mapM_ (\(i, ls) -> mapM_
(\(j, t) -> drawTile
((mapMat $ stateData ud) M.! (i, j)) (assetImages ud) ctx pr pc i j t)
(reverse $ zip [1..] ls))
(zip [1..] (toLists matrix))
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-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-03-03 10:06:38 +00:00
drawTile :: TileState -> Map ImgId Image -> Context -> Double -> Double -> Int -> Int -> Maybe ImgId -> IO ()
drawTile tile ai ctx pr pc row col img = do
let tileWidth = 64 :: Double
2018-02-24 21:24:48 +00:00
tileHeight = 32 :: Double
2018-03-03 10:06:38 +00:00
save ctx
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)
unless (img == Nothing) $ do
let 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
paint <- imagePattern
ctx x (y - (74 * fact - realToFrac tileHeight)) 64 74 0
(ai Map.! fromJust img)
fact
beginPath ctx
if fact < 1
then do
moveTo ctx x (y + (realToFrac tileHeight - 74 * fact))
lineTo ctx (x + realToFrac tileWidth) (y + (realToFrac tileHeight - 74 * fact))
lineTo ctx (x + realToFrac tileWidth) (y + realToFrac tileHeight / 2)
lineTo ctx (x + realToFrac tileWidth / 2) (y + realToFrac tileHeight)
lineTo ctx x (y + realToFrac tileHeight / 2)
closePath ctx
else
rect ctx x (y - (74 - realToFrac tileHeight)) (realToFrac tileWidth) 74
fillPaint ctx paint
fill ctx
when (floor pr == row && floor pc == col) $ do
beginPath ctx
2018-03-03 10:06:38 +00:00
circle ctx 640 360 5
closePath ctx
2018-03-03 10:06:38 +00:00
fillColor ctx (rgba 0 255 255 255)
fill ctx
2018-03-03 10:06:38 +00:00
restore ctx