apecs-0.5.0.0: Fast ECS framework for game 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 SystemT w m a Source #

A SystemT is a newtype around `ReaderT w IO a`, where w is the game world variable. Systems mainly serve to

  • Lift side effects into the IO Monad.
  • Allow type-based lookup of a component's store through getStore.

Constructors

SystemT 

Fields

Instances
Monad m => MonadReader w (SystemT w m) Source # 
Instance details

Defined in Apecs.Core

Methods

ask :: SystemT w m w #

local :: (w -> w) -> SystemT w m a -> SystemT w m a #

reader :: (w -> a) -> SystemT w m a #

MonadTrans (SystemT w) Source # 
Instance details

Defined in Apecs.Core

Methods

lift :: Monad m => m a -> SystemT w m a #

Monad m => Monad (SystemT w m) Source # 
Instance details

Defined in Apecs.Core

Methods

(>>=) :: SystemT w m a -> (a -> SystemT w m b) -> SystemT w m b #

(>>) :: SystemT w m a -> SystemT w m b -> SystemT w m b #

return :: a -> SystemT w m a #

fail :: String -> SystemT w m a #

Functor m => Functor (SystemT w m) Source # 
Instance details

Defined in Apecs.Core

Methods

fmap :: (a -> b) -> SystemT w m a -> SystemT w m b #

(<$) :: a -> SystemT w m b -> SystemT w m a #

Applicative m => Applicative (SystemT w m) Source # 
Instance details

Defined in Apecs.Core

Methods

pure :: a -> SystemT w m a #

(<*>) :: SystemT w m (a -> b) -> SystemT w m a -> SystemT w m b #

liftA2 :: (a -> b -> c) -> SystemT w m a -> SystemT w m b -> SystemT w m c #

(*>) :: SystemT w m a -> SystemT w m b -> SystemT w m b #

(<*) :: SystemT w m a -> SystemT w m b -> SystemT w m a #

MonadIO m => MonadIO (SystemT w m) Source # 
Instance details

Defined in Apecs.Core

Methods

liftIO :: IO a -> SystemT w m a #

type System w a = SystemT w IO a Source #

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

A component is defined by specifying how it is stored. The constraint ensures that stores and components are mapped one-to-one.

Associated Types

type Storage c Source #

Instances
Component () Source # 
Instance details

Defined in Apecs.Core

Associated Types

type Storage () :: * Source #

Component Entity Source # 
Instance details

Defined in Apecs.Core

Associated Types

type Storage Entity :: * Source #

Component EntityCounter Source # 
Instance details

Defined in Apecs.Util

Associated Types

type Storage EntityCounter :: * Source #

Component c => Component (Maybe c) Source # 
Instance details

Defined in Apecs.Core

Associated Types

type Storage (Maybe c) :: * Source #

Component c => Component (Identity c) Source #

Identity component/store. Identity c is equivalent to c, so using it is mostly useless.

Instance details

Defined in Apecs.Core

Associated Types

type Storage (Identity c) :: * Source #

Component c => Component (Filter c) Source # 
Instance details

Defined in Apecs.Core

Associated Types

type Storage (Filter c) :: * Source #

Component c => Component (Not c) Source # 
Instance details

Defined in Apecs.Core

Associated Types

type Storage (Not c) :: * Source #

(Component ca, Component cb) => Component (Either ca cb) Source # 
Instance details

Defined in Apecs.Core

Associated Types

type Storage (Either ca cb) :: * Source #

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

Defined in Apecs.Core

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 # 
Instance details

Defined in Apecs.Core

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 # 
Instance details

Defined in Apecs.Core

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 # 
Instance details

Defined in Apecs.Core

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 # 
Instance details

Defined in Apecs.Core

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 # 
Instance details

Defined in Apecs.Core

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 # 
Instance details

Defined in Apecs.Core

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. In general, use newEntity, cmap, and component tags instead of manipulating these directly.

For performance reasons, negative values like (-1) are reserved for stores to represent special values, so avoid using these.

Constructors

Entity 

Fields

Instances
Enum Entity Source # 
Instance details

Defined in Apecs.Core

Eq Entity Source # 
Instance details

Defined in Apecs.Core

Methods

(==) :: Entity -> Entity -> Bool #

(/=) :: Entity -> Entity -> Bool #

Num Entity Source # 
Instance details

Defined in Apecs.Core

Ord Entity Source # 
Instance details

Defined in Apecs.Core

Show Entity Source # 
Instance details

Defined in Apecs.Core

Component Entity Source # 
Instance details

Defined in Apecs.Core

Associated Types

type Storage Entity :: * Source #

Monad m => Has w m Entity Source # 
Instance details

Defined in Apecs.Core

type Storage Entity Source # 
Instance details

Defined in Apecs.Core

class (Monad m, Component c) => Has w m c where Source #

Has w m c means that world w can produce a Storage c.

Minimal complete definition

getStore

Methods

getStore :: SystemT w m (Storage c) Source #

Instances
Monad m => Has w m Entity Source # 
Instance details

Defined in Apecs.Core

Monad m => Has w m () Source # 
Instance details

Defined in Apecs.Core

Methods

getStore :: SystemT w m (Storage ()) Source #

Has w m c => Has w m (Identity c) Source # 
Instance details

Defined in Apecs.Core

Methods

getStore :: SystemT w m (Storage (Identity c)) Source #

Has w m c => Has w m (Filter c) Source # 
Instance details

Defined in Apecs.Core

Methods

getStore :: SystemT w m (Storage (Filter c)) Source #

Has w m c => Has w m (Maybe c) Source # 
Instance details

Defined in Apecs.Core

Methods

getStore :: SystemT w m (Storage (Maybe c)) Source #

Has w m c => Has w m (Not c) Source # 
Instance details

Defined in Apecs.Core

Methods

getStore :: SystemT w m (Storage (Not c)) Source #

(Has w m ca, Has w m cb) => Has w m (Either ca cb) Source # 
Instance details

Defined in Apecs.Core

Methods

getStore :: SystemT w m (Storage (Either ca cb)) Source #

(Has w m t_0, Has w m t_1) => Has w m (t_0, t_1) Source # 
Instance details

Defined in Apecs.Core

Methods

getStore :: SystemT w m (Storage (t_0, t_1)) Source #

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

Defined in Apecs.Core

Methods

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

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

Defined in Apecs.Core

Methods

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

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

Defined in Apecs.Core

Methods

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

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

Defined in Apecs.Core

Methods

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

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

Defined in Apecs.Core

Methods

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

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

Defined in Apecs.Core

Methods

getStore :: SystemT w m (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. Mainly used as e.g. cmap $ (a, Not b) -> c to iterate over entities with an a but no b. Can also be used to delete components, like cmap $ a -> (Not :: Not a) to delete every a component.

Constructors

Not 
Instances
Has w m c => Has w m (Not c) Source # 
Instance details

Defined in Apecs.Core

Methods

getStore :: SystemT w m (Storage (Not c)) Source #

Component c => Component (Not c) Source # 
Instance details

Defined in Apecs.Core

Associated Types

type Storage (Not c) :: * Source #

type Storage (Not c) Source # 
Instance details

Defined in Apecs.Core

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

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

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

type Destroy w m c = (Has w m c, ExplDestroy m (Storage c)) Source #

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

Stores

data Map c Source #

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

Instances
ExplMembers IO (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplMembers STM (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplDestroy IO (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplDestroy STM (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplSet IO (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplSet STM (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplGet IO (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

ExplGet STM (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

ExplInit (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

explInit :: IO (Map c) Source #

Cachable (Map s) Source # 
Instance details

Defined in Apecs.Stores

type Elem (Map c) Source # 
Instance details

Defined in Apecs.Stores

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 IO (Unique c) Source # 
Instance details

Defined in Apecs.Stores

ExplMembers STM (Unique c) Source # 
Instance details

Defined in Apecs.Stores

ExplDestroy IO (Unique c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplDestroy STM (Unique c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplSet IO (Unique c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplSet STM (Unique c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplGet IO (Unique c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

ExplGet STM (Unique c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

ExplInit (Unique c) Source # 
Instance details

Defined in Apecs.Stores

Methods

explInit :: IO (Unique c) Source #

type Elem (Unique c) Source # 
Instance details

Defined in Apecs.Stores

type Elem (Unique c) = c

data Global c Source #

A Global contains exactly one component. The initial value is mempty from the component's Monoid instance.

When operating on a global, any entity arguments are ignored. For example, we can get a global component with get 0 or get 1 or even get undefined.

Instances
ExplSet IO (Global c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplSet STM (Global c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplGet IO (Global c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

ExplGet STM (Global c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

Monoid c => ExplInit (Global c) Source # 
Instance details

Defined in Apecs.Stores

Methods

explInit :: IO (Global c) Source #

type Elem (Global c) Source # 
Instance details

Defined in Apecs.Stores

type Elem (Global c) = c

data Cache (n :: Nat) s Source #

A cache around another store. Caches store their members in a fixed-size vector, so operations run in O(1). Caches can provide huge performance boosts, especially for large numbers of components. The cache size is given as a type-level argument.

Note that iterating over a cache is linear in cache size, so sparsely populated caches might actually decrease performance. In general, the exact size of the cache does not matter as long as it reasonably approximates the number of components present.

The cache uses entity (-1) to internally represent missing entities, so be wary when manually manipulating entities.

Instances
ExplMembers IO s => ExplMembers IO (Cache n s) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplDestroy IO s => ExplDestroy IO (Cache n s) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplSet IO s => ExplSet IO (Cache n s) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplGet IO s => ExplGet IO (Cache n s) Source # 
Instance details

Defined in Apecs.Stores

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 # 
Instance details

Defined in Apecs.Stores

Methods

explInit :: IO (Cache n s) Source #

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

Defined in Apecs.Stores

type Elem (Cache n s) Source # 
Instance details

Defined in Apecs.Stores

type Elem (Cache n s) = Elem s

explInit :: ExplInit s => IO s Source #

Initialize a new empty store.

Systems

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

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

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

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

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

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

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

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

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

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

Monadically iterates over all entites with a cx

cfold :: forall w m c a. (Members w m c, Get w m c) => (a -> c -> a) -> a -> SystemT w m a Source #

Fold over the game world; for example, cfold max (minBound :: Foo) will find the maximum value of Foo. Strict in the accumulator.

cfoldM :: forall w m c a. (Members w m c, Get w m c) => (a -> c -> SystemT w m a) -> a -> SystemT w m a Source #

Monadically fold over the game world. Strict in the accumulator.

cfoldM_ :: forall w m c a. (Members w m c, Get w m c) => (a -> c -> SystemT w m a) -> a -> SystemT w m () Source #

Monadically fold over the game world. Strict in the accumulator.

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

Applies a function, if possible.

destroy :: forall w m c. Destroy w m c => Entity -> Proxy c -> SystemT w m () 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 m c. Get w m c => Entity -> Proxy c -> SystemT w m 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 :: SystemT w m a -> w -> m a Source #

Run a system with a game world

runWith :: w -> SystemT w m a -> m 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 m c, Get w m EntityCounter, Set w m EntityCounter) => c -> SystemT w m 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, for use in places where the 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 => IO a -> m a #

Lift a computation from the IO monad.

lift :: (MonadTrans t, Monad m) => m a -> t m a #

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