apecs-0.3.0.2: A fast ECS for game engine programming

Safe HaskellNone
LanguageHaskell2010

Apecs.Core

Synopsis

Documentation

newtype Entity Source #

An Entity is really just an Int in a newtype, used to index into a component store.

Constructors

Entity Int 

newtype System w a Source #

A system is a newtype around `ReaderT w IO a`, where w is the game world variable.

Constructors

System 

Fields

Instances

Monad (System w) Source # 

Methods

(>>=) :: System w a -> (a -> System w b) -> System w b #

(>>) :: System w a -> System w b -> System w b #

return :: a -> System w a #

fail :: String -> System w a #

Functor (System w) Source # 

Methods

fmap :: (a -> b) -> System w a -> System w b #

(<$) :: a -> System w b -> System w a #

Applicative (System w) Source # 

Methods

pure :: a -> System w a #

(<*>) :: System w (a -> b) -> System w a -> System w b #

liftA2 :: (a -> b -> c) -> System w a -> System w b -> System w c #

(*>) :: System w a -> System w b -> System w b #

(<*) :: System w a -> System w b -> System w a #

MonadIO (System w) Source # 

Methods

liftIO :: IO a -> System w a #

class (Elem (Storage c) ~ c, Store (Storage c)) => Component c Source #

A component is defined by the type of its storage The storage in turn supplies runtime types for the component. For the component to be valid, its Storage must be an instance of Store.

Associated Types

type Storage c Source #

Instances

Component Entity Source # 

Associated Types

type Storage Entity :: * Source #

Component EntityCounter Source # 

Associated Types

type Storage EntityCounter :: * Source #

Component c => Component (Maybe c) Source # 

Associated Types

type Storage (Maybe c) :: * Source #

Component c => Component (Identity c) Source # 

Associated Types

type Storage (Identity c) :: * Source #

Component c => Component (Filter c) Source # 

Associated Types

type Storage (Filter c) :: * Source #

Component c => Component (Not c) Source # 

Associated Types

type Storage (Not c) :: * Source #

(Component p, Component q) => Component (Either p q) Source # 

Associated Types

type Storage (Either p q) :: * Source #

(Component t_0, Component t_1) => Component (t_0, t_1) Source # 

Associated Types

type Storage (t_0, t_1) :: * Source #

(Component t_0, Component t_1, Component t_2) => Component (t_0, t_1, t_2) Source # 

Associated Types

type Storage (t_0, t_1, t_2) :: * Source #

(Component t_0, Component t_1, Component t_2, Component t_3) => Component (t_0, t_1, t_2, t_3) Source # 

Associated Types

type Storage (t_0, t_1, t_2, t_3) :: * Source #

(Component t_0, Component t_1, Component t_2, Component t_3, Component t_4) => Component (t_0, t_1, t_2, t_3, t_4) Source # 

Associated Types

type Storage (t_0, t_1, t_2, t_3, t_4) :: * Source #

(Component t_0, Component t_1, Component t_2, Component t_3, Component t_4, Component t_5) => Component (t_0, t_1, t_2, t_3, t_4, t_5) Source # 

Associated Types

type Storage (t_0, t_1, t_2, t_3, t_4, t_5) :: * Source #

(Component t_0, Component t_1, Component t_2, Component t_3, Component t_4, Component t_5, Component t_6) => Component (t_0, t_1, t_2, t_3, t_4, t_5, t_6) Source # 

Associated Types

type Storage (t_0, t_1, t_2, t_3, t_4, t_5, t_6) :: * Source #

(Component t_0, Component t_1, Component t_2, Component t_3, Component t_4, Component t_5, Component t_6, Component t_7) => Component (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) Source # 

Associated Types

type Storage (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) :: * Source #

class Component c => Has w c where Source #

A world Has a component if it can produce its Storage

Minimal complete definition

getStore

Methods

getStore :: System w (Storage c) Source #

Instances

Has w Entity Source # 
Has w c => Has w (Identity c) Source # 
Has w c => Has w (Filter c) Source # 

Methods

getStore :: System w (Storage (Filter c)) Source #

Has w c => Has w (Maybe c) Source # 

Methods

getStore :: System w (Storage (Maybe c)) Source #

Has w c => Has w (Not c) Source # 

Methods

getStore :: System w (Storage (Not c)) Source #

(Has w p, Has w q) => Has w (Either p q) Source # 

Methods

getStore :: System w (Storage (Either p q)) Source #

(Has w t_0, Has w t_1) => Has w (t_0, t_1) Source # 

Methods

getStore :: System w (Storage (t_0, t_1)) Source #

(Has w t_0, Has w t_1, Has w t_2) => Has w (t_0, t_1, t_2) Source # 

Methods

getStore :: System w (Storage (t_0, t_1, t_2)) Source #

(Has w t_0, Has w t_1, Has w t_2, Has w t_3) => Has w (t_0, t_1, t_2, t_3) Source # 

Methods

getStore :: System w (Storage (t_0, t_1, t_2, t_3)) Source #

(Has w t_0, Has w t_1, Has w t_2, Has w t_3, Has w t_4) => Has w (t_0, t_1, t_2, t_3, t_4) Source # 

Methods

getStore :: System w (Storage (t_0, t_1, t_2, t_3, t_4)) Source #

(Has w t_0, Has w t_1, Has w t_2, Has w t_3, Has w t_4, Has w t_5) => Has w (t_0, t_1, t_2, t_3, t_4, t_5) Source # 

Methods

getStore :: System w (Storage (t_0, t_1, t_2, t_3, t_4, t_5)) Source #

(Has w t_0, Has w t_1, Has w t_2, Has w t_3, Has w t_4, Has w t_5, Has w t_6) => Has w (t_0, t_1, t_2, t_3, t_4, t_5, t_6) Source # 

Methods

getStore :: System w (Storage (t_0, t_1, t_2, t_3, t_4, t_5, t_6)) Source #

(Has w t_0, Has w t_1, Has w t_2, Has w t_3, Has w t_4, Has w t_5, Has w t_6, Has w t_7) => Has w (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) Source # 

Methods

getStore :: System w (Storage (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7)) Source #

class Store s where Source #

Holds components indexed by entities

Laws:

  • For all entities in exmplMembers s, explExists s ety must be true.
  • If for some entity explExists s ety, explGet s ety should safely return a non-bottom value.

Minimal complete definition

initStore, explSet, explGet, explDestroy, explMembers

Associated Types

type Elem s Source #

The type of components stored by this Store

Methods

initStore :: IO s Source #

Initialize the store with its initialization arguments.

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

Writes a component

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

Reads a component from the store. What happens if the component does not exist is left undefined.

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

Destroys the component for a given index.

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

Returns an unboxed vector of member indices

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

Returns whether there is a component for the given index

Instances

Store EntityStore Source # 
Store s => Store (Identity s) Source # 

Associated Types

type Elem (Identity s) :: * Source #

Store s => Store (FilterStore s) Source # 
Store s => Store (MaybeStore s) Source # 
Store s => Store (NotStore s) Source # 

Associated Types

type Elem (NotStore s) :: * Source #

Monoid c => Store (Global c) Source # 

Associated Types

type Elem (Global c) :: * Source #

Store (Unique c) Source # 

Associated Types

type Elem (Unique c) :: * Source #

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 #

(Store t_0, Store t_1) => Store (t_0, t_1) Source # 

Associated Types

type Elem (t_0, t_1) :: * Source #

Methods

initStore :: IO (t_0, t_1) Source #

explSet :: (t_0, t_1) -> Int -> Elem (t_0, t_1) -> IO () Source #

explGet :: (t_0, t_1) -> Int -> IO (Elem (t_0, t_1)) Source #

explDestroy :: (t_0, t_1) -> Int -> IO () Source #

explMembers :: (t_0, t_1) -> IO (Vector Int) Source #

explExists :: (t_0, t_1) -> Int -> IO Bool Source #

(Store sp, Store sq) => Store (EitherStore sp sq) Source # 

Associated Types

type Elem (EitherStore sp sq) :: * Source #

Methods

initStore :: IO (EitherStore sp sq) Source #

explSet :: EitherStore sp sq -> Int -> Elem (EitherStore sp sq) -> IO () Source #

explGet :: EitherStore sp sq -> Int -> IO (Elem (EitherStore sp sq)) Source #

explDestroy :: EitherStore sp sq -> Int -> IO () Source #

explMembers :: EitherStore sp sq -> IO (Vector Int) Source #

explExists :: EitherStore sp sq -> Int -> IO Bool Source #

(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 #

(Store t_0, Store t_1, Store t_2) => Store (t_0, t_1, t_2) Source # 

Associated Types

type Elem (t_0, t_1, t_2) :: * Source #

Methods

initStore :: IO (t_0, t_1, t_2) Source #

explSet :: (t_0, t_1, t_2) -> Int -> Elem (t_0, t_1, t_2) -> IO () Source #

explGet :: (t_0, t_1, t_2) -> Int -> IO (Elem (t_0, t_1, t_2)) Source #

explDestroy :: (t_0, t_1, t_2) -> Int -> IO () Source #

explMembers :: (t_0, t_1, t_2) -> IO (Vector Int) Source #

explExists :: (t_0, t_1, t_2) -> Int -> IO Bool Source #

(Store t_0, Store t_1, Store t_2, Store t_3) => Store (t_0, t_1, t_2, t_3) Source # 

Associated Types

type Elem (t_0, t_1, t_2, t_3) :: * Source #

Methods

initStore :: IO (t_0, t_1, t_2, t_3) Source #

explSet :: (t_0, t_1, t_2, t_3) -> Int -> Elem (t_0, t_1, t_2, t_3) -> IO () Source #

explGet :: (t_0, t_1, t_2, t_3) -> Int -> IO (Elem (t_0, t_1, t_2, t_3)) Source #

explDestroy :: (t_0, t_1, t_2, t_3) -> Int -> IO () Source #

explMembers :: (t_0, t_1, t_2, t_3) -> IO (Vector Int) Source #

explExists :: (t_0, t_1, t_2, t_3) -> Int -> IO Bool Source #

(Store t_0, Store t_1, Store t_2, Store t_3, Store t_4) => Store (t_0, t_1, t_2, t_3, t_4) Source # 

Associated Types

type Elem (t_0, t_1, t_2, t_3, t_4) :: * Source #

Methods

initStore :: IO (t_0, t_1, t_2, t_3, t_4) Source #

explSet :: (t_0, t_1, t_2, t_3, t_4) -> Int -> Elem (t_0, t_1, t_2, t_3, t_4) -> IO () Source #

explGet :: (t_0, t_1, t_2, t_3, t_4) -> Int -> IO (Elem (t_0, t_1, t_2, t_3, t_4)) Source #

explDestroy :: (t_0, t_1, t_2, t_3, t_4) -> Int -> IO () Source #

explMembers :: (t_0, t_1, t_2, t_3, t_4) -> IO (Vector Int) Source #

explExists :: (t_0, t_1, t_2, t_3, t_4) -> Int -> IO Bool Source #

(Store t_0, Store t_1, Store t_2, Store t_3, Store t_4, Store t_5) => Store (t_0, t_1, t_2, t_3, t_4, t_5) Source # 

Associated Types

type Elem (t_0, t_1, t_2, t_3, t_4, t_5) :: * Source #

Methods

initStore :: IO (t_0, t_1, t_2, t_3, t_4, t_5) Source #

explSet :: (t_0, t_1, t_2, t_3, t_4, t_5) -> Int -> Elem (t_0, t_1, t_2, t_3, t_4, t_5) -> IO () Source #

explGet :: (t_0, t_1, t_2, t_3, t_4, t_5) -> Int -> IO (Elem (t_0, t_1, t_2, t_3, t_4, t_5)) Source #

explDestroy :: (t_0, t_1, t_2, t_3, t_4, t_5) -> Int -> IO () Source #

explMembers :: (t_0, t_1, t_2, t_3, t_4, t_5) -> IO (Vector Int) Source #

explExists :: (t_0, t_1, t_2, t_3, t_4, t_5) -> Int -> IO Bool Source #

(Store t_0, Store t_1, Store t_2, Store t_3, Store t_4, Store t_5, Store t_6) => Store (t_0, t_1, t_2, t_3, t_4, t_5, t_6) Source # 

Associated Types

type Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6) :: * Source #

Methods

initStore :: IO (t_0, t_1, t_2, t_3, t_4, t_5, t_6) Source #

explSet :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6) -> Int -> Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6) -> IO () Source #

explGet :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6) -> Int -> IO (Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6)) Source #

explDestroy :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6) -> Int -> IO () Source #

explMembers :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6) -> IO (Vector Int) Source #

explExists :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6) -> Int -> IO Bool Source #

(Store t_0, Store t_1, Store t_2, Store t_3, Store t_4, Store t_5, Store t_6, Store t_7) => Store (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) Source # 

Associated Types

type Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) :: * Source #

Methods

initStore :: IO (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) Source #

explSet :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) -> Int -> Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) -> IO () Source #

explGet :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) -> Int -> IO (Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7)) Source #

explDestroy :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) -> Int -> IO () Source #

explMembers :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) -> IO (Vector Int) Source #

explExists :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) -> Int -> IO Bool Source #

data Not a Source #

Psuedocomponent indicating the absence of a.

Constructors

Not 

Instances

Has w c => Has w (Not c) Source # 

Methods

getStore :: System w (Storage (Not c)) Source #

Component c => Component (Not c) Source # 

Associated Types

type Storage (Not c) :: * Source #

type Storage (Not c) Source # 
type Storage (Not c) = NotStore (Storage c)

newtype NotStore s Source #

Pseudostore used to produce values of type Not a

Constructors

NotStore s 

Instances

Store s => Store (NotStore s) Source # 

Associated Types

type Elem (NotStore s) :: * Source #

type Elem (NotStore s) Source # 
type Elem (NotStore s) = Not (Elem s)

newtype MaybeStore s Source #

Pseudostore used to produce values of type Maybe a

Constructors

MaybeStore s 

Instances

data EitherStore sp sq Source #

Pseudostore used to produce values of type Either p q

Constructors

EitherStore sp sq 

Instances

(Store sp, Store sq) => Store (EitherStore sp sq) Source # 

Associated Types

type Elem (EitherStore sp sq) :: * Source #

Methods

initStore :: IO (EitherStore sp sq) Source #

explSet :: EitherStore sp sq -> Int -> Elem (EitherStore sp sq) -> IO () Source #

explGet :: EitherStore sp sq -> Int -> IO (Elem (EitherStore sp sq)) Source #

explDestroy :: EitherStore sp sq -> Int -> IO () Source #

explMembers :: EitherStore sp sq -> IO (Vector Int) Source #

explExists :: EitherStore sp sq -> Int -> IO Bool Source #

type Elem (EitherStore sp sq) Source # 
type Elem (EitherStore sp sq) = Either (Elem sp) (Elem sq)

data Filter c Source #

Constructors

Filter 

Instances

Has w c => Has w (Filter c) Source # 

Methods

getStore :: System w (Storage (Filter c)) Source #

Eq (Filter c) Source # 

Methods

(==) :: Filter c -> Filter c -> Bool #

(/=) :: Filter c -> Filter c -> Bool #

Show (Filter c) Source # 

Methods

showsPrec :: Int -> Filter c -> ShowS #

show :: Filter c -> String #

showList :: [Filter c] -> ShowS #

Component c => Component (Filter c) Source # 

Associated Types

type Storage (Filter c) :: * Source #

type Storage (Filter c) Source # 

newtype FilterStore s Source #

Constructors

FilterStore s 

data EntityStore Source #

Pseudostore used to produce components of type Entity

Constructors

EntityStore