apecs-0.4.0.0: A fast ECS for game engine programming

Safe HaskellNone
LanguageHaskell2010

Apecs.Core

Synopsis

Documentation

newtype Entity Source #

An Entity is just an integer, used to index into a component store.

Constructors

Entity 

Fields

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

type family Elem s Source #

The type of components stored by a Store

Instances

type Elem EntityStore Source # 
type Elem (Identity s) Source # 
type Elem (Identity s) = Identity (Elem s)
type Elem (FilterStore s) Source # 
type Elem (FilterStore s) = Filter (Elem s)
type Elem (MaybeStore s) Source # 
type Elem (MaybeStore s) = Maybe (Elem s)
type Elem (NotStore s) Source # 
type Elem (NotStore s) = Not (Elem s)
type Elem (Global c) Source # 
type Elem (Global c) = c
type Elem (Unique c) Source # 
type Elem (Unique c) = c
type Elem (Map c) Source # 
type Elem (Map c) = c
type Elem (t_0, t_1) Source # 
type Elem (t_0, t_1) = (Elem t_0, Elem t_1)
type Elem (Cache n s) Source # 
type Elem (Cache n s) = Elem s
type Elem (t_0, t_1, t_2) Source # 
type Elem (t_0, t_1, t_2) = (Elem t_0, Elem t_1, Elem t_2)
type Elem (t_0, t_1, t_2, t_3) Source # 
type Elem (t_0, t_1, t_2, t_3) = (Elem t_0, Elem t_1, Elem t_2, Elem t_3)
type Elem (t_0, t_1, t_2, t_3, t_4) Source # 
type Elem (t_0, t_1, t_2, t_3, t_4) = (Elem t_0, Elem t_1, Elem t_2, Elem t_3, Elem t_4)
type Elem (t_0, t_1, t_2, t_3, t_4, t_5) Source # 
type Elem (t_0, t_1, t_2, t_3, t_4, t_5) = (Elem t_0, Elem t_1, Elem t_2, Elem t_3, Elem t_4, Elem t_5)
type Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6) Source # 
type Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6) = (Elem t_0, Elem t_1, Elem t_2, Elem t_3, Elem t_4, Elem t_5, Elem t_6)
type Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) Source # 
type Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) = (Elem t_0, Elem t_1, Elem t_2, Elem t_3, Elem t_4, Elem t_5, Elem t_6, Elem t_7)

class ExplInit s where Source #

Holds components indexed by entities

Minimal complete definition

explInit

Methods

explInit :: IO s Source #

Initialize the store with its initialization arguments.

Instances

Monoid c => ExplInit (Global c) Source # 

Methods

explInit :: IO (Global c) Source #

ExplInit (Unique c) Source # 

Methods

explInit :: IO (Unique c) Source #

ExplInit (Map c) Source # 

Methods

explInit :: IO (Map c) Source #

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

Methods

explInit :: IO (Cache n s) Source #

class ExplGet s where Source #

Stores that support get and exists in the IO monad If existsIO

Minimal complete definition

explGet, explExists

Methods

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

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

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

Returns whether there is a component for the given index

Instances

ExplGet EntityStore Source # 
ExplGet s => ExplGet (Identity s) Source # 
ExplGet s => ExplGet (FilterStore s) Source # 
ExplGet s => ExplGet (MaybeStore s) Source # 
ExplGet s => ExplGet (NotStore s) Source # 
ExplGet (Global c) Source # 

Methods

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

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

ExplGet (Unique c) Source # 

Methods

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

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

ExplGet (Map c) Source # 

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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 #

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

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

Methods

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 #

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

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

Methods

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 #

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

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

Methods

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 #

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

class ExplSet s where Source #

Minimal complete definition

explSet

Methods

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

Writes a component

Instances

ExplSet s => ExplSet (Identity s) Source # 

Methods

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

(ExplDestroy s, ExplSet s) => ExplSet (MaybeStore s) Source # 

Methods

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

ExplDestroy s => ExplSet (NotStore s) Source # 

Methods

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

ExplSet (Global c) Source # 

Methods

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

ExplSet (Unique c) Source # 

Methods

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

ExplSet (Map c) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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 #

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

Methods

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 #

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

Methods

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 #

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

Methods

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 #

class ExplDestroy s where Source #

Minimal complete definition

explDestroy

Methods

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

Destroys the component for a given index.

Instances

ExplDestroy s => ExplDestroy (Identity s) Source # 

Methods

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

ExplDestroy (Unique c) Source # 

Methods

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

ExplDestroy (Map c) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

class ExplMembers s where Source #

Minimal complete definition

explMembers

Methods

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

Returns an unboxed vector of member indices

Instances

ExplMembers s => ExplMembers (Identity s) Source # 
ExplMembers (Unique c) Source # 
ExplMembers (Map c) Source # 

Methods

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

(ExplMembers t_0, ExplGet t_1) => ExplMembers (t_0, t_1) Source # 

Methods

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

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

Methods

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

(ExplMembers t_0, ExplGet t_1, ExplGet t_2) => ExplMembers (t_0, t_1, t_2) Source # 

Methods

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

(ExplMembers t_0, ExplGet t_1, ExplGet t_2, ExplGet t_3) => ExplMembers (t_0, t_1, t_2, t_3) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

type Get w c = (Has w c, ExplGet (Storage c)) Source #

type Set w c = (Has w c, ExplSet (Storage c)) Source #

type Members w c = (Has w c, ExplMembers (Storage c)) Source #

type Destroy w c = (Has w c, ExplDestroy (Storage c)) 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

ExplDestroy s => ExplSet (NotStore s) Source # 

Methods

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

ExplGet s => ExplGet (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 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