apecs-0.3.0.1: A fast ECS for game engine programming

Safe HaskellNone
LanguageHaskell2010

Apecs.Stores

Synopsis

Documentation

data Map c Source #

A map based on Data.Intmap.Strict. O(log(n)) for most operations.

Instances

Store (Map c) Source # 

Associated Types

type Elem (Map c) :: * Source #

Methods

initStore :: IO (Map c) Source #

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

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

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

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

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

Cachable (Map s) Source # 
type Elem (Map c) Source # 
type Elem (Map c) = c

data Cache (n :: Nat) s Source #

A cache around another store. Note that iterating over a cache is linear in cache size, so sparsely populated caches might actually decrease performance.

Instances

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

Associated Types

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

Methods

initStore :: IO (Cache n s) Source #

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

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

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

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

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

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

data Unique c Source #

A Unique contains zero or one component. Writing to it overwrites both the previous component and its owner. Its main purpose is to be a Map optimized for when only ever one component inhabits it.

Instances

Store (Unique c) Source # 

Associated Types

type Elem (Unique c) :: * Source #

type Elem (Unique c) Source # 
type Elem (Unique c) = c

data Global c Source #

A Global contains exactly one component. Initialized with mempty The store will return true for every existence check, but only ever gives (-1) as its inhabitant. The entity argument is ignored when setting/getting a global.

Instances

Monoid c => Store (Global c) Source # 

Associated Types

type Elem (Global c) :: * Source #

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

class Store s => Cachable s Source #

An empty type class indicating that the store behaves like a regular map, and can therefore safely be cached.

Instances