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