tracer/src/Load.hs

566 lines
19 KiB
Haskell
Raw Normal View History

module Load where
import Affection as A
import qualified SDL
import Graphics.Rendering.OpenGL.GL.FlushFinish (finish)
import Control.Concurrent (forkIO)
import Control.Concurrent.MVar
2020-05-05 09:13:39 +02:00
import Control.Monad
import qualified Data.Map as M
2018-07-19 04:51:07 +02:00
import qualified Data.Text as T
import Data.Ecstasy
import Data.Maybe
2019-10-28 18:20:34 +01:00
import Data.String
import System.Exit (exitFailure)
import NanoVG hiding (V2(..))
-- internal imports
2018-10-12 14:26:06 +02:00
import Menu.Connect
import Types
import Util
2020-05-05 09:13:39 +02:00
loadLoad :: UserData -> Affection ()
loadLoad ud = do
2018-07-06 17:17:12 +02:00
ad <- A.get
2020-05-05 09:13:39 +02:00
wState <- liftIO $ readMVar (worldState ud)
curWin <- liftIO $ readMVar (window ud)
tContext <- liftIO $ readMVar (threadContext ud)
let progress = (0, "Starting up")
2020-05-05 10:26:16 +02:00
void $ liftIO $ putMVar (stateProgress ud) progress
_ <- liftIO $ createFont (nano ud) "bedstead"
(FileName "assets/font/Bedstead-Semicondensed.ttf")
_ <- liftIO $ forkIO $
loadFork
2020-05-05 09:13:39 +02:00
wState
(fromJust curWin)
(fromJust tContext)
(nano ud)
2020-05-05 09:13:39 +02:00
(stateMVar ud)
(stateProgress ud)
SDL.glMakeCurrent (fromJust curWin) (snd $ head $ glContext ad)
void $ liftIO $ swapMVar (state ud) Load
void $ liftIO $ swapMVar (assetFonts ud) (M.fromList
[ (FontBedstead, "bedstead")
]
)
loadFork
2020-05-05 09:13:39 +02:00
:: SystemState Entity (AffectionState (AffectionData) IO)
2018-07-03 16:19:27 +02:00
-> SDL.Window
-> SDL.GLContext
-> Context
2018-08-10 08:58:26 +02:00
-> MVar
2020-05-05 09:13:39 +02:00
( SystemState Entity (AffectionState (AffectionData) IO)
2018-08-10 08:58:26 +02:00
, StateData
)
2018-07-19 04:51:07 +02:00
-> MVar (Float, T.Text)
-> IO ()
2018-07-03 16:19:27 +02:00
loadFork ws win glc nvg future progress = do
2019-02-14 22:31:00 +01:00
let stateSteps = 57
increment = 1 / stateSteps
SDL.glMakeCurrent win glc
2018-10-08 23:36:52 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading icon \"conntroller_blue\""
)))
mcontrblue <- createImage nvg (FileName "assets/icons/controller_blue.png") 0
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
2019-02-11 16:11:27 +01:00
, "Loading icon \"controller_blue\""
2018-10-08 23:36:52 +02:00
)))
mcontrgreen <- createImage nvg (FileName "assets/icons/controller_green.png") 0
2018-10-12 14:26:06 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
2019-02-11 16:11:27 +01:00
, "Loading icon \"controller_green\""
)))
2019-02-12 00:11:53 +01:00
mkbdblue <- createImage nvg (FileName "assets/icons/keyboard_blue.png") 0
2019-02-11 16:11:27 +01:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading icon \"keyboard_blue\""
)))
2019-02-12 00:11:53 +01:00
mkbdgreen <- createImage nvg (FileName "assets/icons/keyboard_green.png") 0
2019-02-11 16:11:27 +01:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading icon \"keyboard_green\""
2018-10-12 14:26:06 +02:00
)))
marrow <- createImage nvg (FileName "assets/icons/arrow.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"wall_asc\""
)))
mwallasc <- createImage nvg (FileName "assets/walls/wall_asc.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"wall_desc\""
)))
mwalldesc <- createImage nvg (FileName "assets/walls/wall_desc.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"wall_corner_n\""
)))
mwallcornern <- createImage nvg (FileName "assets/walls/wall_corner_n.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"wall_corner_e\""
)))
mwallcornere <- createImage nvg (FileName "assets/walls/wall_corner_e.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"wall_corner_s\""
)))
mwallcorners <- createImage nvg (FileName "assets/walls/wall_corner_s.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"wall_corner_w\""
)))
mwallcornerw <- createImage nvg (FileName "assets/walls/wall_corner_w.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"wall_t_ne\""
)))
mwalltne <- createImage nvg (FileName "assets/walls/wall_t_ne.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"wall_t_se\""
)))
mwalltse <- createImage nvg (FileName "assets/walls/wall_t_se.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"wall_t_sw\""
)))
mwalltsw <- createImage nvg (FileName "assets/walls/wall_t_sw.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"wall_t_nw\""
)))
mwalltnw <- createImage nvg (FileName "assets/walls/wall_t_nw.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"wall_cross\""
)))
mwallcross <- createImage nvg (FileName "assets/walls/wall_cross.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"box1\""
)))
mmiscbox1 <- createImage nvg (FileName "assets/misc/box1.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"tableSW\""
2018-07-19 04:51:07 +02:00
)))
mtableSW <- createImage nvg (FileName "assets/table/tableSW.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"tableSE\""
2018-07-19 04:51:07 +02:00
)))
mtableSE <- createImage nvg (FileName "assets/table/tableSE.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"tableNE\""
2018-07-19 04:51:07 +02:00
)))
mtableNE <- createImage nvg (FileName "assets/table/tableNE.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"tableNW\""
2018-07-19 04:51:07 +02:00
)))
mtableNW <- createImage nvg (FileName "assets/table/tableNW.png") 0
2018-07-30 21:10:42 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"tableC1\""
)))
2018-07-31 13:30:17 +02:00
mtablec1 <- createImage nvg (FileName "assets/table/tablec1.png") 0
2018-07-30 21:10:42 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"tableC2\""
)))
2018-07-31 13:30:17 +02:00
mtablec2 <- createImage nvg (FileName "assets/table/tablec2.png") 0
2018-07-30 21:10:42 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"tableC3\""
)))
2018-07-31 13:30:17 +02:00
mtablec3 <- createImage nvg (FileName "assets/table/tablec3.png") 0
2018-07-30 21:10:42 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"tableC4\""
)))
2018-07-31 13:30:17 +02:00
mtablec4 <- createImage nvg (FileName "assets/table/tablec4.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"tableCorner\""
)))
2018-07-31 13:30:17 +02:00
mtableC <- createImage nvg (FileName "assets/table/tableCorner.png") 0
2018-07-30 15:34:45 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"flipchart\""
)))
mmiscFlipchart <- createImage nvg (FileName "assets/misc/flipchart.png") 0
2018-07-31 13:30:17 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"plant1\""
)))
mmiscPlant1 <- createImage nvg (FileName "assets/misc/plant1.png") 0
2018-07-31 22:59:25 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"plant2\""
)))
mmiscPlant2 <- createImage nvg (FileName "assets/misc/plant2.png") 0
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
2018-08-07 14:04:49 +02:00
, "Loading asset \"watercooler\""
2018-07-19 04:51:07 +02:00
)))
2018-08-07 14:04:49 +02:00
mmiscWatercooler <- createImage nvg (FileName "assets/misc/watercooler.png") 0
2019-01-10 18:31:36 +01:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"vending machine\""
)))
mmiscVending <- createImage nvg (FileName "assets/misc/vending.png") 0
2019-01-14 04:00:34 +01:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
2019-01-15 05:28:09 +01:00
, "Loading asset \"Cabinet with Coffee machine SW\""
2019-01-14 04:00:34 +01:00
)))
2019-01-15 05:28:09 +01:00
mcabCoffeeSW <- createImage nvg (FileName "assets/cabinet/cabCoffeeSW.png") 0
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"Cabinet with Coffee machine SE\""
)))
mcabCoffeeSE <- createImage nvg (FileName "assets/cabinet/cabCoffeeSE.png") 0
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"Cabinet with sink SW\""
)))
mcabSinkSW <- createImage nvg (FileName "assets/cabinet/cabSinkSW.png") 0
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"Cabinet with sink SE\""
)))
mcabSinkSE <- createImage nvg (FileName "assets/cabinet/cabSinkSE.png") 0
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"Cabinet with stove SW\""
)))
mcabStoveSW <- createImage nvg (FileName "assets/cabinet/cabStoveSW.png") 0
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"Cabinet with stove SE\""
)))
mcabStoveSE <- createImage nvg (FileName "assets/cabinet/cabStoveSE.png") 0
2019-01-14 04:00:34 +01:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"cabinet SW\""
)))
2019-01-15 05:28:09 +01:00
mcabinetSW <- createImage nvg (FileName "assets/cabinet/cabinetSW.png") 0
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"cabinet SE\""
)))
mcabinetSE <- createImage nvg (FileName "assets/cabinet/cabinetSE.png") 0
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading asset \"cabinet corner\""
)))
mcabinetCorner <- createImage nvg (FileName "assets/cabinet/cabinetCorner.png") 0
2018-10-08 23:36:52 +02:00
let micons =
2019-02-12 00:11:53 +01:00
[ mcontrblue, mcontrgreen, mkbdblue, mkbdgreen, marrow
2018-10-08 23:36:52 +02:00
]
when (any isNothing micons) $ do
liftIO $logIO Error "Failed to load icon assets"
exitFailure
2018-08-07 14:04:49 +02:00
let mimgs =
[ mwallasc, mwalldesc
, mwallcornern, mwallcornere, mwallcorners, mwallcornerw
, mwalltne, mwalltse, mwalltsw, mwalltnw, mwallcross
, mmiscbox1
, mtableSW, mtableNW, mtableNE, mtableSE, mtableC
2018-08-07 14:04:49 +02:00
, mtablec1, mtablec2, mtablec3, mtablec4
, mmiscFlipchart
, mmiscPlant1, mmiscPlant2
2019-01-10 18:31:36 +01:00
, mmiscWatercooler, mmiscVending
2019-01-18 19:02:45 +01:00
, mcabCoffeeSW, mcabCoffeeSE
2019-01-15 05:28:09 +01:00
, mcabSinkSW, mcabSinkSE
, mcabStoveSW, mcabStoveSE
, mcabinetSW, mcabinetSE, mcabinetCorner
]
when (any isNothing mimgs) $ do
liftIO $logIO Error "Failed to load image assets"
exitFailure
2018-08-07 14:04:49 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"intruder: standing\""
)))
-- playerImgs <- loadPlayerSprite "assets/intruder.png" 64 74 nvg
-- (zipWith (\a b -> (a, [b])) [0..] $ [ImgIntrE .. ImgIntrN] ++ [ImgIntrNE])
2018-07-21 06:43:26 +02:00
let imgs = zipWith (\a b -> (a, fromJust b))
[ ImgWallAsc
2019-01-15 05:28:09 +01:00
.. ImgCabinetCorner
2018-07-21 06:43:26 +02:00
]
mimgs
2018-10-08 23:36:52 +02:00
icons = zipWith (\a b -> (a, fromJust b))
[ IconContrBlue
2018-10-12 14:26:06 +02:00
.. IconArrow
2018-10-08 23:36:52 +02:00
]
micons
directions = [E .. N] ++ [NE]
standIds var = map (AnimId var "standing") directions
walkIds var = map (AnimId var "walking") directions
standConfigs = map
2018-07-21 06:43:26 +02:00
(\i -> AnimationConfig (0, i * 74) (64, 74) (64, 0) 1 0 APLoop)
2019-02-14 22:31:00 +01:00
[0 .. length (standIds AnimIntruder) - 1]
walkConfigs = map
2018-07-21 06:43:26 +02:00
(\i -> AnimationConfig (64, i * 74) (64, 74) (64, 0) 6 1.5 APLoop)
2019-02-14 22:31:00 +01:00
[0 .. length (walkIds AnimIntruder) - 1]
playerStanding <- loadAnimationSprites "assets/intruder.png" nvg
2019-02-14 22:31:00 +01:00
(zip (standIds AnimIntruder) standConfigs)
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"intruder: walking\""
)))
playerWalking <- loadAnimationSprites "assets/intruder.png" nvg
2019-02-14 22:31:00 +01:00
(zip (walkIds AnimIntruder) walkConfigs)
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"jdoem: standing\""
)))
jdoemStanding <- loadAnimationSprites "assets/jdoem.png" nvg
2019-02-14 22:31:00 +01:00
(zip (standIds AnimJDoeM) standConfigs)
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"jdoem: walking\""
)))
jdoemWalking <- loadAnimationSprites "assets/jdoem.png" nvg
2019-02-14 22:31:00 +01:00
(zip (walkIds AnimJDoeM) walkConfigs)
2020-01-26 18:07:40 +01:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"policem: standing\""
)))
policemStanding <- loadAnimationSprites "assets/policem.png" nvg
(zip (standIds AnimPoliceM) standConfigs)
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"policem: walking\""
)))
policemWalking <- loadAnimationSprites "assets/policem.png" nvg
(zip (walkIds AnimPoliceM) walkConfigs)
2018-07-21 06:43:26 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"copier: stand\""
)))
copierStand <- loadAnimationSprites "assets/misc/copier.png" nvg $ zip
2019-02-14 22:31:00 +01:00
(map (\name -> AnimId AnimCopier name N) ["closed", "open"])
2018-07-21 06:43:26 +02:00
(map
(\i -> AnimationConfig (0, i * 74) (64, 74) (0, 0) 1 0 APLoop)
[0, 1]
)
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"copier: copy\""
)))
2018-07-30 14:34:46 +02:00
copierCopy <- loadAnimationSprites "assets/misc/copier.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimCopier "copy" N
, AnimationConfig (64, 0) (64, 74) (64, 0) 4 1 APLoop
2018-07-21 06:43:26 +02:00
)
]
2018-07-30 14:34:46 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
2019-02-09 15:19:16 +01:00
, "Loading Animation \"cornerComputer: off\""
2018-07-30 14:34:46 +02:00
)))
2019-02-09 15:19:16 +01:00
cornerComputerOff <- loadAnimationSprites "assets/misc/tableCornerComputer.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimComputer "off" N
2018-07-30 14:34:46 +02:00
, AnimationConfig (0, 0) (64, 74) (64, 0) 2 2 APLoop
)
]
2018-08-12 06:28:31 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
2019-02-09 15:19:16 +01:00
, "Loading Animation \"cornerComputer: on\""
2018-08-12 06:28:31 +02:00
)))
2019-02-09 15:19:16 +01:00
cornerComputerOn <- loadAnimationSprites "assets/misc/tableCornerComputer.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimComputer "on" N
2018-08-12 06:28:31 +02:00
, AnimationConfig (128, 0) (64, 74) (0, 0) 1 0 APLoop
)
]
2018-08-11 11:51:20 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
2019-02-09 15:19:16 +01:00
, "Loading Animation \"cornerComputer: hack\""
2018-08-11 11:51:20 +02:00
)))
2019-02-09 15:19:16 +01:00
cornerComputerHack <- loadAnimationSprites "assets/misc/tableCornerComputer.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimComputer "hack" N
2018-08-11 11:51:20 +02:00
, AnimationConfig (0, 74) (64, 74) (64, 0) 4 2 APLoop
)
]
2019-02-09 15:19:16 +01:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"neComputer: off\""
)))
neComputerOff <- loadAnimationSprites "assets/misc/tableSWComputer.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimComputer "off" NE
2019-02-09 15:19:16 +01:00
, AnimationConfig (0, 0) (64, 74) (64, 0) 2 2 APLoop
)
]
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"neComputer: on\""
)))
neComputerOn <- loadAnimationSprites "assets/misc/tableSWComputer.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimComputer "on" NE
2019-02-09 15:19:16 +01:00
, AnimationConfig (128, 0) (64, 74) (0, 0) 1 0 APLoop
)
]
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"neComputer: hack\""
)))
neComputerHack <- loadAnimationSprites "assets/misc/tableSWComputer.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimComputer "hack" NE
2019-02-09 15:19:16 +01:00
, AnimationConfig (0, 74) (64, 74) (64, 0) 4 2 APLoop
)
]
2019-02-09 22:39:42 +01:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"nwComputer: off\""
)))
nwComputerOff <- loadAnimationSprites "assets/misc/tableSEComputer.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimComputer "off" NW
2019-02-09 22:39:42 +01:00
, AnimationConfig (0, 0) (64, 74) (64, 0) 2 2 APLoop
)
]
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"nwComputer: on\""
)))
nwComputerOn <- loadAnimationSprites "assets/misc/tableSEComputer.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimComputer "on" NW
2019-02-09 22:39:42 +01:00
, AnimationConfig (128, 0) (64, 74) (0, 0) 1 0 APLoop
)
]
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"nwComputer: hack\""
)))
nwComputerHack <- loadAnimationSprites "assets/misc/tableSEComputer.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimComputer "hack" NW
2019-02-09 22:39:42 +01:00
, AnimationConfig (0, 74) (64, 74) (64, 0) 4 2 APLoop
)
]
2018-07-31 22:59:25 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"toilet: free\""
)))
toiletFree <- loadAnimationSprites "assets/misc/toilet.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimToilet "free" N
2018-07-31 22:59:25 +02:00
, AnimationConfig (0, 0) (64, 74) (0, 0) 1 0 APLoop
)
]
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"toilet: occupied\""
)))
toiletOccupied <- loadAnimationSprites "assets/misc/toilet.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimToilet "occupied" N
2018-07-31 22:59:25 +02:00
, AnimationConfig (64, 0) (64, 74) (0, 0) 1 0 APLoop
)
]
2019-02-16 20:38:00 +01:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"neDoor0: open\""
)))
neDoor0open <- loadAnimationSprites "assets/doors/door_desc_0.png" nvg
[ ( AnimId AnimDoor0 "open" NE
2019-02-18 19:14:41 +01:00
, AnimationConfig (0, 0) (64, 74) (0, 74) 5 0.25 APOnce
2019-02-16 20:38:00 +01:00
)
]
2019-02-14 22:31:00 +01:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"neDoor0: shut\""
)))
2019-02-16 20:38:00 +01:00
neDoor0shut <- loadAnimationSprites "assets/doors/door_desc_0.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimDoor0 "shut" NE
2019-02-18 19:14:41 +01:00
, AnimationConfig (0, 4*74) (64, 74) (0, -74) 5 0.25 APOnce
2019-02-16 20:38:00 +01:00
)
]
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"nwDoor0: open\""
)))
nwDoor0open <- loadAnimationSprites "assets/doors/door_asc_0.png" nvg
[ ( AnimId AnimDoor0 "open" NW
2019-02-18 19:14:41 +01:00
, AnimationConfig (0, 0) (64, 74) (0, 74) 5 0.25 APOnce
2019-02-14 22:31:00 +01:00
)
]
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Loading Animation \"nwDoor0: shut\""
)))
2019-02-16 20:38:00 +01:00
nwDoor0shut <- loadAnimationSprites "assets/doors/door_asc_0.png" nvg
2019-02-14 22:31:00 +01:00
[ ( AnimId AnimDoor0 "shut" NW
2019-02-18 19:14:41 +01:00
, AnimationConfig (0, 4*74) (64, 74) (0, -74) 5 0.25 APOnce
2019-02-14 22:31:00 +01:00
)
]
2018-07-19 04:51:07 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
2020-05-05 10:26:16 +02:00
, "GL_Finish"
2018-07-19 04:51:07 +02:00
)))
finish
2020-05-05 10:26:16 +02:00
modifyMVar_ progress (return . (\(p, _) ->
( p + increment
, "Handing over"
)))
putMVar future
( ws
, LoadData
{ loadAssetImages = M.fromList imgs
, loadAssetAnims = M.fromList
2018-07-21 06:43:26 +02:00
( playerStanding ++
playerWalking ++
jdoemStanding ++
jdoemWalking ++
2020-01-26 18:07:40 +01:00
policemStanding ++
policemWalking ++
2018-07-21 06:43:26 +02:00
copierStand ++
2018-07-30 14:34:46 +02:00
copierCopy ++
2019-02-09 15:19:16 +01:00
cornerComputerOff ++
cornerComputerOn ++
cornerComputerHack ++
neComputerOff ++
neComputerOn ++
neComputerHack ++
2019-02-09 22:39:42 +01:00
nwComputerOff ++
nwComputerOn ++
nwComputerHack ++
2018-07-31 22:59:25 +02:00
toiletFree ++
2019-02-14 22:31:00 +01:00
toiletOccupied ++
neDoor0shut ++
2019-02-16 20:38:00 +01:00
neDoor0open ++
nwDoor0shut ++
nwDoor0open
2018-07-21 06:43:26 +02:00
)
2018-10-08 23:36:52 +02:00
, loadAssetIcons = M.fromList icons
}
)
2020-05-05 09:13:39 +02:00
drawLoad :: UserData -> Affection ()
drawLoad ud = do
progress <- liftIO $ readMVar (stateProgress ud)
liftIO $ do
2019-10-28 18:20:34 +01:00
logIO A.Verbose ("LoadProgress: " <> fromString (show progress))
drawLoadScreen ud progress
2020-05-05 09:13:39 +02:00
updateLoad :: UserData -> Double -> Affection ()
updateLoad ud _ = do
mwsld <- liftIO $ tryTakeMVar (stateMVar ud)
case mwsld of
Just (_, ld) -> do
liftIO $ logIO A.Debug "loaded assets, entering menu"
2020-05-05 09:13:39 +02:00
void $ liftIO $ swapMVar (assetImages ud) (loadAssetImages ld)
void $ liftIO $ swapMVar (assetAnimations ud) (loadAssetAnims ld)
void $ liftIO $ swapMVar (assetIcons ud) (loadAssetIcons ld)
void $ liftIO $ swapMVar (stateData ud) None
2018-10-08 23:36:52 +02:00
-- loadMap
2020-05-05 09:13:39 +02:00
loadMenu ud
2018-07-03 16:19:27 +02:00
Nothing ->
return ()