apecs-0.2.0.2: 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(n log(n)) for most operations. Yields safe runtime representations of type Maybe c.

Instances

Store (Map c) Source # 

Associated Types

type SafeRW (Map c) :: * Source #

type Stores (Map c) :: * Source #

Methods

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

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

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

explSetMaybe :: Map c -> Int -> SafeRW (Map c) -> IO () 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 #

HasMembers (Map c) Source # 

Methods

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

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

explMembers :: Map c -> IO (Vector Int) 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 #

Initializable (Map c) Source # 

Associated Types

type InitArgs (Map c) :: * Source #

Methods

initStoreWith :: InitArgs (Map c) -> IO (Map c) Source #

type SafeRW (Map c) Source # 
type SafeRW (Map c) = Maybe c
type Stores (Map c) Source # 
type Stores (Map c) = c
type InitArgs (Map c) Source # 
type InitArgs (Map 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 SafeRW (Set c) :: * Source #

type Stores (Set c) :: * Source #

Methods

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

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

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

explSetMaybe :: Set c -> Int -> SafeRW (Set c) -> IO () 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 #

HasMembers (Set c) Source # 

Methods

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

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

explMembers :: Set c -> IO (Vector Int) 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 #

Initializable (Set c) Source # 

Associated Types

type InitArgs (Set c) :: * Source #

Methods

initStoreWith :: InitArgs (Set c) -> IO (Set c) Source #

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

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

((~) * (SafeRW s) (Maybe (Stores s)), Store s) => Store (Cache n s) Source # 

Associated Types

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

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

Methods

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

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

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

explSetMaybe :: Cache n s -> Int -> SafeRW (Cache n s) -> IO () 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 #

HasMembers s => HasMembers (Cache n s) Source # 

Methods

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

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

explMembers :: Cache n s -> IO (Vector Int) 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 #

(KnownNat n, Initializable s) => Initializable (Cache n s) Source # 

Associated Types

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

Methods

initStoreWith :: InitArgs (Cache n s) -> IO (Cache n s) Source #

type SafeRW (Cache n s) Source # 
type SafeRW (Cache n s) = SafeRW s
type Stores (Cache n s) Source # 
type Stores (Cache n s) = Stores s
type InitArgs (Cache n s) Source # 
type InitArgs (Cache n s) = InitArgs s

data Global c Source #

Global value. Must be given an initial value upon construction.

Instances

Initializable (Global c) Source # 

Associated Types

type InitArgs (Global c) :: * Source #

GlobalRW (Global c) c Source # 

Methods

explGlobalRead :: Global c -> IO c Source #

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

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

type InitArgs (Global c) Source # 
type InitArgs (Global c) = c

data IndexTable s Source #

A table that keeps a hashtable of indices along with its writes. TODO: Benchmark? hashing function as argument?

Instances

((~) * (SafeRW s) (Maybe (Stores s)), ToIndex (Stores s), Store s) => Store (IndexTable s) Source # 

Associated Types

type SafeRW (IndexTable s) :: * Source #

type Stores (IndexTable s) :: * Source #

Methods

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

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

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

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

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

explCmap :: IndexTable s -> (Stores (IndexTable s) -> Stores (IndexTable s)) -> IO () Source #

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

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

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

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

((~) * (SafeRW s) (Maybe (Stores s)), ToIndex (Stores s), Store s) => HasMembers (IndexTable s) Source # 

Methods

explDestroy :: IndexTable s -> Int -> IO () Source #

explExists :: IndexTable s -> Int -> IO Bool Source #

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

explReset :: IndexTable s -> IO () Source #

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

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

(ToIndex (Stores s), Initializable s) => Initializable (IndexTable s) Source # 

Associated Types

type InitArgs (IndexTable s) :: * Source #

((~) * (Stores s) c, ToIndex (Stores s)) => Query (ByComponent c) (IndexTable s) Source # 
((~) * (Stores s) c, ToIndex (Stores s)) => Query (ByIndex c) (IndexTable s) Source # 
type SafeRW (IndexTable s) Source # 
type SafeRW (IndexTable s) = SafeRW s
type Stores (IndexTable s) Source # 
type Stores (IndexTable s) = Stores s
type InitArgs (IndexTable s) Source # 

class Bounded a => ToIndex a where Source #

A component that can be hashed to a table index. minBound must hash to the lowest possible value, maxBound must hash to the highest. For Enums, toIndex = fromEnum

Minimal complete definition

toIndex

Methods

toIndex :: a -> Int Source #

newtype ByIndex a Source #

A query to an IndexTable by an explicit index

Constructors

ByIndex Int 

Instances

((~) * (Stores s) c, ToIndex (Stores s)) => Query (ByIndex c) (IndexTable s) Source # 

newtype ByComponent c Source #

A query to an IndexTable by a reference component

Constructors

ByComponent c 

Instances

((~) * (Stores s) c, ToIndex (Stores s)) => Query (ByComponent c) (IndexTable s) Source #