apecs-0.4.0.0: A fast ECS for game engine programming

Safe HaskellNone
LanguageHaskell2010

Apecs

Contents

Description

This module forms the apecs Prelude. It selectively re-exports the user-facing functions from the submodules.

Synopsis

Documentation

module Data.Proxy

Core types

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 #

newtype Entity Source #

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

Constructors

Entity 

Fields

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 #

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)

Stores

data Map c Source #

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

Instances

ExplMembers (Map c) Source # 

Methods

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

ExplDestroy (Map c) Source # 

Methods

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

ExplSet (Map c) Source # 

Methods

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

ExplGet (Map c) Source # 

Methods

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

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

ExplInit (Map c) Source # 

Methods

explInit :: IO (Map c) Source #

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

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

ExplMembers (Unique c) Source # 
ExplDestroy (Unique c) Source # 

Methods

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

ExplSet (Unique c) Source # 

Methods

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

ExplGet (Unique c) Source # 

Methods

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

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

ExplInit (Unique c) Source # 

Methods

explInit :: IO (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

ExplSet (Global c) Source # 

Methods

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

ExplGet (Global c) Source # 

Methods

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

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

Monoid c => ExplInit (Global c) Source # 

Methods

explInit :: IO (Global c) Source #

type Elem (Global c) Source # 
type Elem (Global 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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

explInit :: IO (Cache n s) Source #

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

explInit :: ExplInit s => IO s Source #

Initialize the store with its initialization arguments.

Systems

get :: forall w c. Get w c => Entity -> System w c Source #

set :: forall w c. Set w c => Entity -> c -> System w () Source #

Writes a component to a given entity. Will overwrite existing components. The type was originally 'Entity c -> c -> System w ()', but is relaxed to 'Entity e' so you don't always have to write 'set . cast'

getAll :: forall w c. (Get w c, Members w c) => System w [c] Source #

Get all components c. Call as [(c,Entity)] to read the entity/index.

cmap :: forall w cx cy. (Get w cx, Members w cx, Set w cy) => (cx -> cy) -> System w () Source #

Maps a function over all entities with a cx, and writes their cy

cmapM :: forall w cx cy. (Get w cx, Set w cy, Members w cx) => (cx -> System w cy) -> System w () Source #

Monadically iterates over all entites with a cx, and writes their cy

cmapM_ :: forall w c a. (Get w c, Members w c) => (c -> System w a) -> System w () Source #

Monadically iterates over all entites with a cx

modify :: forall w c. (Get w c, Set w c) => Entity -> (c -> c) -> System w () Source #

Applies a function, if possible.

destroy :: forall w c. Destroy w c => Entity -> Proxy c -> System w () Source #

Destroys component c for the given entity. Note that c is a phantom argument, used only to convey the type of the entity to be destroyed.

exists :: forall w c. Get w c => Entity -> Proxy c -> System w Bool Source #

Returns whether the given entity has component c Note that c is a phantom argument, used only to convey the type of the entity to be queried.

Other

runSystem :: System w a -> w -> IO a Source #

Run a system with a game world

runWith :: w -> System w a -> IO a Source #

Run a system with a game world

runGC :: System w () Source #

Explicitly invoke the garbage collector

data EntityCounter Source #

Component used by newEntity to track the number of issued entities. Automatically added to any world created with makeWorld

newEntity :: (Set w c, Get w EntityCounter, Set w EntityCounter) => c -> System w Entity Source #

Writes the given components to a new entity, and yields that entity. The return value is often ignored.

global :: Entity Source #

Convenience entity (-1), used in places where the exact entity value does not matter, i.e. a global store.

makeWorld :: String -> [Name] -> Q [Dec] Source #

makeWorld "WorldName" [''Component1, ''Component2, ...]

turns into

data WorldName = WorldName Component1 Component2 ... EntityCounter
instance WorldName `Has` Component1 where ...
instance WorldName `Has` Component2 where ...
...
instance WorldName `Has` EntityCounter where ...

initWorldName :: IO WorldName
initWorldName = WorldName <$> initStore <*> initStore <*> ... <*> initStore

|

makeWorldAndComponents :: String -> [Name] -> Q [Dec] Source #

Same as makeWorld, but also makes a component instance:

Re-exports

asks #

Arguments

:: MonadReader r m 
=> (r -> a)

The selector function to apply to the environment.

-> m a 

Retrieves a function of the current environment.

ask :: MonadReader r m => m r #

Retrieves the monad environment.

liftIO :: MonadIO m => forall a. IO a -> m a #

Lift a computation from the IO monad.

lift :: MonadTrans t => forall (m :: * -> *) a. Monad m => m a -> t m a #

Lift a computation from the argument monad to the constructed monad.