pulsar/src/Overseer.hs

70 lines
3.0 KiB
Haskell

--{-# LANGUAGE TypeFamilyDependencies #-}
module Overseer(
) where
import Data.Sequence(Seq)
import Data.Sequence qualified as S
import Data.IntMap.Strict qualified as IMS
import Lib
import Structure
import Material
{-| The Overseer module handles disseminating and redirecting events between the relavent parties. Overall, this means that the Overseer for a type will have the full list of all UIDs in that type. For types with sub-types (such as the Creature -> BodyPart -> Sense relation), the Overseer carries the highest parent type.
-- An efficient data structure for searching is required, as there will be many searches per tick. A BST is ideal, however this requires restructuring the UID type to be indicative of position (i.e. it should not be monotonically increasing unless the tree is self-balancing)
-- Signalling success/failure back is important. Obviously, a bunch of events can be queued, however, there are race conditions. E.g. if two creatures attempt to pick up the same item in the same tick. In this case, we should use some deterministic mechanism to solve who gets priority. The other creature should be informed that they failed.
-- In this system, a list of Actions will be compiled at each tick, and the GameState will fold over them for each Overseer, applying each to its relevant member.
|-}
---- GameState and Action Definitions -----------------------------------------------------------------------------------------------------
-- TODO: Figure out how to structure actions and event queues
-- This will likely require some kind of type-level list
data GameState where
GameStateMk :: {
overseers :: [Has Overseer]
} -> GameState
-- TODO: Is Partial a desired state?
data Status = Failure | Partial | Success deriving (Eq, Ord, Show, Read)
data Result k u = ResultMk {
originatior :: (IsUID u) => u,
status :: Status
}
data Event k u = EventMk {
action :: k -> k,
actor :: (IsUID u) => u,
precedence :: Int -- ^Precedence is a secondary sorting order for each actor
}
data Overseer k where
OverseerI :: {
itemsI :: Seq k,
eventsI :: Seq (Has (Event k)), -- ^Using sequence for consistency, list is fine here since we operate the list in order
resultsI :: Seq (Has (Result k)), -- ^The use of sequences lets us share results as required with cheap concat
oUID :: OverseerUID
} -> Overseer k
OverseerU :: { -- ^Overseers for 'case class' style definitions of parameters that do are not expected to change - they are defined strictly
itemsU :: IMS.IntMap k,
oUID :: OverseerUID
} -> Overseer k
class OverseerType k o t | k -> o, o -> k, k -> t where
-- Where k is the Subject, and i is the UID
items :: (Traversable t) => o -> t k
events :: (Traversable t) => Maybe (t (Event k u))
results :: (Traversable t) => Maybe (t (Result k u))
overseerUID :: o -> OverseerUID
instance OverseerType Material (Overseer Material) IMS.IntMap where
items = itemsU
events = Nothing
results = Nothing
overseerUID = oUID