tracer/src/Types/UserData.hs

146 lines
3.9 KiB
Haskell
Raw Normal View History

2018-02-07 00:18:16 +00:00
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
module Types.UserData where
import Affection
import Control.Concurrent.STM
import qualified SDL
2018-02-07 00:18:16 +00:00
import NanoVG hiding (V2(..), V3(..))
import qualified Data.Map.Strict as M
2018-03-01 22:33:08 +00:00
import qualified Data.Text as T
2018-02-07 00:18:16 +00:00
import Data.Ecstasy
import Control.Concurrent.MVar
import Types.Map
import Types.StateData
import Types.ImgId
import Types.FontId
import Types.Direction
import Types.Animation
2018-02-07 00:18:16 +00:00
data UserData = UserData
2018-05-27 14:03:31 +00:00
{ state :: State
, subsystems :: Subsystems
, assetImages :: M.Map ImgId Image
, assetFonts :: M.Map FontId T.Text
, assetAnimations :: M.Map AnimId Animation
, nano :: Context
, uuid :: [UUID]
, worldState :: SystemState Entity IO
, stateData :: StateData
, stateMVar :: MVar (SystemState Entity IO, StateData)
, stateProgress :: MVar Float
, threadContext :: Maybe SDL.GLContext
, window :: Maybe SDL.Window
2018-02-07 00:18:16 +00:00
}
data State
= Load
2018-06-28 19:07:58 +00:00
| Main SubMain
2018-02-07 00:18:16 +00:00
2018-06-28 19:07:58 +00:00
data SubMain
= WorldMap
| MindMap
2018-02-07 00:18:16 +00:00
data Entity f = Entity
2018-05-27 14:03:31 +00:00
{ pos :: Component f 'Field (V2 Double)
2018-06-28 19:07:58 +00:00
, mmpos :: Component f 'Field (V2 Double)
2018-05-27 14:03:31 +00:00
, gridPos :: Component f 'Field (V2 Int)
, vel :: Component f 'Field (V2 Double)
2018-07-02 16:42:59 +00:00
, mmvel :: Component f 'Field (V2 Double)
2018-05-27 14:03:31 +00:00
, velFact :: Component f 'Field Double
, rot :: Component f 'Field Direction
, obstacle :: Component f 'Field (Boundaries Double)
, player :: Component f 'Unique ()
2018-06-23 22:43:09 +00:00
, npcMoveState :: Component f 'Field NPCMoveState
2018-05-27 14:03:31 +00:00
, anim :: Component f 'Field AnimState
2018-07-06 15:18:12 +00:00
, objAccess :: Component f 'Field (V2 Int)
2018-02-07 00:18:16 +00:00
}
deriving (Generic)
2018-06-23 22:43:09 +00:00
data NPCMoveState
2018-04-14 16:43:05 +00:00
= NPCWalking
{ npcWalkPath :: [V2 Int]
}
| NPCStanding
{ npcStandTime :: Double
, npcFuturePath :: MVar [V2 Int]
2018-04-14 16:43:05 +00:00
}
2018-02-07 00:18:16 +00:00
data Subsystems = Subsystems
2018-06-23 22:42:39 +00:00
{ subWindow :: Window
, subMouse :: Mouse
, subkeyboard :: Keyboard
2018-02-07 00:18:16 +00:00
}
newtype Window = Window (TVar [(UUID, WindowMessage -> Affection UserData())])
newtype Mouse = Mouse (TVar [(UUID, MouseMessage -> Affection UserData ())])
2018-06-23 22:42:39 +00:00
newtype Keyboard = Keyboard (TVar [(UUID, KeyboardMessage -> Affection UserData ())])
2018-02-07 00:18:16 +00:00
instance Participant Window UserData where
type Mesg Window UserData = WindowMessage
partSubscribers (Window t) = generalSubscribers t
partSubscribe (Window t) = generalSubscribe t
partUnSubscribe (Window t) = generalUnSubscribe t
instance SDLSubsystem Window UserData where
consumeSDLEvents = consumeSDLWindowEvents
instance Participant Mouse UserData where
type Mesg Mouse UserData = MouseMessage
partSubscribers (Mouse t) = generalSubscribers t
partSubscribe (Mouse t) = generalSubscribe t
partUnSubscribe (Mouse t) = generalUnSubscribe t
instance SDLSubsystem Mouse UserData where
consumeSDLEvents = consumeSDLMouseEvents
2018-06-23 22:42:39 +00:00
instance Participant Keyboard UserData where
type Mesg Keyboard UserData = KeyboardMessage
partSubscribers (Keyboard t) = generalSubscribers t
partSubscribe (Keyboard t) = generalSubscribe t
partUnSubscribe (Keyboard t) = generalUnSubscribe t
instance SDLSubsystem Keyboard UserData where
consumeSDLEvents = consumeSDLKeyboardEvents
2018-02-07 00:18:16 +00:00
generalSubscribers
:: TVar [(UUID, msg -> Affection UserData ())]
-> Affection UserData [(msg -> Affection UserData ())]
generalSubscribers t = do
subTups <- liftIO $ readTVarIO t
return $ map snd subTups
generalSubscribe
:: TVar [(UUID, msg -> Affection UserData ())]
-> (msg -> Affection UserData ())
-> Affection UserData UUID
generalSubscribe t funct = do
2018-02-18 02:11:41 +00:00
uu <- genUUID
liftIO $ atomically $ modifyTVar' t ((uu, funct) :)
return uu
2018-02-07 00:18:16 +00:00
generalUnSubscribe
:: TVar [(UUID, msg -> Affection UserData ())]
-> UUID
-> Affection UserData ()
2018-02-18 02:11:41 +00:00
generalUnSubscribe t uu =
liftIO $ atomically $ modifyTVar' t (filter (`filterMsg` uu))
2018-02-07 00:18:16 +00:00
where
filterMsg (u, _) p = u /= p