apecs-0.2.3.0: A fast ECS for game engine programming

Safe HaskellNone
LanguageHaskell2010

Apecs.Stores

Synopsis

Documentation

data Map c Source #

A map from Data.Intmap.Strict. O(log(n)) for most operations. Yields safe runtime representations of type Maybe c.

Instances

Store (Map c) Source # 

Associated Types

type Stores (Map c) :: * Source #

type SafeRW (Map c) :: * Source #

Methods

explGet :: Map c -> Int -> IO (SafeRW (Map c)) Source #

explSet :: Map c -> Int -> Stores (Map c) -> IO () Source #

explDestroy :: Map c -> Int -> IO () Source #

explExists :: Map c -> Int -> IO Bool Source #

explMembers :: Map c -> IO (Vector Int) Source #

explGetUnsafe :: Map c -> Int -> IO (Stores (Map c)) Source #

explSetMaybe :: Map c -> Int -> SafeRW (Map c) -> IO () Source #

initStore :: IO (Map c) Source #

explReset :: Map c -> IO () Source #

explImapM_ :: MonadIO m => Map c -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Map c -> (Int -> m a) -> m [a] Source #

explModify :: Map c -> Int -> (Stores (Map c) -> Stores (Map c)) -> IO () Source #

explCmap :: Map c -> (Stores (Map c) -> Stores (Map c)) -> IO () Source #

explCmapM_ :: MonadIO m => Map c -> (Stores (Map c) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Map c -> ((Int, Stores (Map c)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Map c -> (Stores (Map c) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Map c -> ((Int, Stores (Map c)) -> m a) -> m [a] Source #

Cachable (Map s) Source # 
type Stores (Map c) Source # 
type Stores (Map c) = c
type SafeRW (Map c) Source # 
type SafeRW (Map c) = Maybe c

data Set c Source #

A store that keeps membership, but holds no values. Produces flag runtime values.

Instances

Flag c => Store (Set c) Source # 

Associated Types

type Stores (Set c) :: * Source #

type SafeRW (Set c) :: * Source #

Methods

explGet :: Set c -> Int -> IO (SafeRW (Set c)) Source #

explSet :: Set c -> Int -> Stores (Set c) -> IO () Source #

explDestroy :: Set c -> Int -> IO () Source #

explExists :: Set c -> Int -> IO Bool Source #

explMembers :: Set c -> IO (Vector Int) Source #

explGetUnsafe :: Set c -> Int -> IO (Stores (Set c)) Source #

explSetMaybe :: Set c -> Int -> SafeRW (Set c) -> IO () Source #

initStore :: IO (Set c) Source #

explReset :: Set c -> IO () Source #

explImapM_ :: MonadIO m => Set c -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Set c -> (Int -> m a) -> m [a] Source #

explModify :: Set c -> Int -> (Stores (Set c) -> Stores (Set c)) -> IO () Source #

explCmap :: Set c -> (Stores (Set c) -> Stores (Set c)) -> IO () Source #

explCmapM_ :: MonadIO m => Set c -> (Stores (Set c) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Set c -> ((Int, Stores (Set c)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Set c -> (Stores (Set c) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Set c -> ((Int, Stores (Set c)) -> m a) -> m [a] Source #

type Stores (Set c) Source # 
type Stores (Set c) = c
type SafeRW (Set c) Source # 
type SafeRW (Set c) = Bool

class Flag c where Source #

Class for flags, used by Set to yield runtime representations.

Minimal complete definition

flag

Methods

flag :: c Source #

data Cache n s Source #

A cache around another store. The wrapped store must produce safe representations using Maybe. Note that iterating over a cache is linear in its size, so large, sparsely populated caches will actually decrease performance.

Instances

(KnownNat n, Cachable s) => Store (Cache n s) Source # 

Associated Types

type Stores (Cache n s) :: * Source #

type SafeRW (Cache n s) :: * Source #

Methods

explGet :: Cache n s -> Int -> IO (SafeRW (Cache n s)) Source #

explSet :: Cache n s -> Int -> Stores (Cache n s) -> IO () Source #

explDestroy :: Cache n s -> Int -> IO () Source #

explExists :: Cache n s -> Int -> IO Bool Source #

explMembers :: Cache n s -> IO (Vector Int) Source #

explGetUnsafe :: Cache n s -> Int -> IO (Stores (Cache n s)) Source #

explSetMaybe :: Cache n s -> Int -> SafeRW (Cache n s) -> IO () Source #

initStore :: IO (Cache n s) Source #

explReset :: Cache n s -> IO () Source #

explImapM_ :: MonadIO m => Cache n s -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Cache n s -> (Int -> m a) -> m [a] Source #

explModify :: Cache n s -> Int -> (Stores (Cache n s) -> Stores (Cache n s)) -> IO () Source #

explCmap :: Cache n s -> (Stores (Cache n s) -> Stores (Cache n s)) -> IO () Source #

explCmapM_ :: MonadIO m => Cache n s -> (Stores (Cache n s) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Cache n s -> ((Int, Stores (Cache n s)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Cache n s -> (Stores (Cache n s) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Cache n s -> ((Int, Stores (Cache n s)) -> m a) -> m [a] Source #

(KnownNat n, Cachable s) => Cachable (Cache n s) Source # 
type Stores (Cache n s) Source # 
type Stores (Cache n s) = Stores s
type SafeRW (Cache n s) Source # 
type SafeRW (Cache n s) = SafeRW s

data Unique c Source #

A Unique contains exactly one component belonging to some entity. Writing to it overwrites both the previous component and its owner.

Instances

Store (Unique c) Source # 

Associated Types

type Stores (Unique c) :: * Source #

type SafeRW (Unique c) :: * Source #

Methods

explGet :: Unique c -> Int -> IO (SafeRW (Unique c)) Source #

explSet :: Unique c -> Int -> Stores (Unique c) -> IO () Source #

explDestroy :: Unique c -> Int -> IO () Source #

explExists :: Unique c -> Int -> IO Bool Source #

explMembers :: Unique c -> IO (Vector Int) Source #

explGetUnsafe :: Unique c -> Int -> IO (Stores (Unique c)) Source #

explSetMaybe :: Unique c -> Int -> SafeRW (Unique c) -> IO () Source #

initStore :: IO (Unique c) Source #

explReset :: Unique c -> IO () Source #

explImapM_ :: MonadIO m => Unique c -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Unique c -> (Int -> m a) -> m [a] Source #

explModify :: Unique c -> Int -> (Stores (Unique c) -> Stores (Unique c)) -> IO () Source #

explCmap :: Unique c -> (Stores (Unique c) -> Stores (Unique c)) -> IO () Source #

explCmapM_ :: MonadIO m => Unique c -> (Stores (Unique c) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Unique c -> ((Int, Stores (Unique c)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Unique c -> (Stores (Unique c) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Unique c -> ((Int, Stores (Unique c)) -> m a) -> m [a] Source #

type Stores (Unique c) Source # 
type Stores (Unique c) = c
type SafeRW (Unique c) Source # 
type SafeRW (Unique c) = Maybe c

data Global c Source #

Global value. Initialized with mempty

Instances

Monoid c => GlobalStore (Global c) Source # 
Monoid c => Store (Global c) Source # 

Associated Types

type Stores (Global c) :: * Source #

type SafeRW (Global c) :: * Source #

Methods

explGet :: Global c -> Int -> IO (SafeRW (Global c)) Source #

explSet :: Global c -> Int -> Stores (Global c) -> IO () Source #

explDestroy :: Global c -> Int -> IO () Source #

explExists :: Global c -> Int -> IO Bool Source #

explMembers :: Global c -> IO (Vector Int) Source #

explGetUnsafe :: Global c -> Int -> IO (Stores (Global c)) Source #

explSetMaybe :: Global c -> Int -> SafeRW (Global c) -> IO () Source #

initStore :: IO (Global c) Source #

explReset :: Global c -> IO () Source #

explImapM_ :: MonadIO m => Global c -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Global c -> (Int -> m a) -> m [a] Source #

explModify :: Global c -> Int -> (Stores (Global c) -> Stores (Global c)) -> IO () Source #

explCmap :: Global c -> (Stores (Global c) -> Stores (Global c)) -> IO () Source #

explCmapM_ :: MonadIO m => Global c -> (Stores (Global c) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Global c -> ((Int, Stores (Global c)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Global c -> (Stores (Global c) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Global c -> ((Int, Stores (Global c)) -> m a) -> m [a] Source #

type Stores (Global c) Source # 
type Stores (Global c) = c
type SafeRW (Global c) Source # 
type SafeRW (Global c) = c

class (Store s, SafeRW s ~ Maybe (Stores s)) => Cachable s Source #

Instances