apecs-0.3.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

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

newtype Entity Source #

An Entity is really just an Int in a newtype.

Constructors

Entity Int 

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 #

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)

data Map c Source #

A map from Data.Intmap.Strict. O(log(n)) for most operations. Yields safe runtime representations of type Maybe c.

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 Unique c Source #

A Unique contains at most one component. Writing to it overwrites both the previous component and its owner.

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

Instances

Monoid c => Store (Global c) Source # 

Associated Types

type Elem (Global c) :: * Source #

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

Store wrapper functions

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

set :: forall w c. Has 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'

cmap :: forall world cx cy. (Has world cx, Has world cy) => (cx -> cy) -> System world () Source #

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

cmapM :: forall world c a. Has world c => (c -> System world a) -> System world [a] Source #

Monadically iterates over all entites with a cx

cmapM_ :: forall world c a. Has world c => (c -> System world a) -> System world () Source #

Monadically iterates over all entites with a cx

modify :: forall w c. Has w c => Entity -> (c -> c) -> System w () Source #

Applies a function, if possible.

destroy :: forall w c. Has w c => Entity -> 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. Has w c => Entity -> 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

newEntity :: (Store (Storage c), Has w c, Has w EntityCounter) => c -> System w Entity Source #

Writes the given components to a new entity, and yields that entity

proxy :: forall t. t Source #

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

|

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.