apecs-0.2.0.2: A fast ECS for game engine programming

Safe HaskellNone
LanguageHaskell2010

Apecs

Contents

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 #

(*>) :: 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 Initializable (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 in instance of Initializable.

Associated Types

type Storage c = s | s -> c Source #

Instances

Component EntityCounter Source # 

Associated Types

type Storage EntityCounter = (s :: *) Source #

(Component a, Component b) => Component (a, b) Source # 

Associated Types

type Storage (a, b) = (s :: *) Source #

(Component a, Component b, Component c) => Component (a, b, c) Source # 

Associated Types

type Storage (a, b, c) = (s :: *) Source #

newtype Entity c Source #

An Entity is really just an Int. The type variable is used to keep track of reads and writes, but can be freely cast.

Constructors

Entity 

Fields

Instances

Eq (Entity c) Source # 

Methods

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

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

Ord (Entity c) Source # 

Methods

compare :: Entity c -> Entity c -> Ordering #

(<) :: Entity c -> Entity c -> Bool #

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

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

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

max :: Entity c -> Entity c -> Entity c #

min :: Entity c -> Entity c -> Entity c #

Show (Entity c) Source # 

Methods

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

show :: Entity c -> String #

showList :: [Entity c] -> ShowS #

Cast (Entity a) (Entity b) Source # 

Methods

cast :: Entity a -> Entity b Source #

data Slice c Source #

A slice is a list of entities, represented by a Data.Unbox.Vector of Ints.

Instances

Show (Slice c) Source # 

Methods

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

show :: Slice c -> String #

showList :: [Slice c] -> ShowS #

Monoid (Slice c) Source # 

Methods

mempty :: Slice c #

mappend :: Slice c -> Slice c -> Slice c #

mconcat :: [Slice c] -> Slice c #

Cast (Slice a) (Slice b) Source # 

Methods

cast :: Slice a -> Slice b 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 a, Has w b) => Has w (a, b) Source # 

Methods

getStore :: System w (Storage (a, b)) Source #

(Has w a, Has w b, Has w c) => Has w (a, b, c) Source # 

Methods

getStore :: System w (Storage (a, b, c)) Source #

newtype Safe c Source #

Represents a safe access to c. A safe access is either a read that might fail, or a write that might delete.

Constructors

Safe 

Fields

cast :: Cast a b => a -> b Source #

Initializable

HasMembers wrapper functions

destroy :: forall w c. (Has w c, HasMembers (Storage c)) => Entity c -> System w () Source #

Destroys the component c for the given entity

exists :: forall w c. (Has w c, HasMembers (Storage c)) => Entity c -> System w Bool Source #

Returns whether the given entity has component c For composite components, this indicates whether the component has all its constituents

owners :: forall w c. (Has w c, HasMembers (Storage c)) => System w (Slice c) Source #

A slice containing all entities with component c

resetStore :: forall w c p. (Has w c, HasMembers (Storage c)) => p c -> System w () Source #

Removes all components. Equivalent to manually iterating and deleting, but usually optimized.

Store wrapper functions

get :: forall w c. (Store (Storage c), Has w c) => Entity c -> System w (Safe c) Source #

Gets the component for a given entity. This is a safe access, because the entity might not have the requested components.

set :: forall w c e. (Store (Storage c), Stores (Storage c) ~ c, Has w c) => Entity e -> c -> System w () Source #

Writes a component to a given entity. Will overwrite existing components.

setOrDelete :: forall w c. (IsRuntime c, Has w c) => Entity c -> Safe c -> System w () Source #

Same as set, but uses Safe to possibly delete a component

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

Applies a function if possible. Equivalent to reading, mapping, and writing, but stores can provide optimized implementations.

cmap :: forall world c. (IsRuntime c, Has world c) => (c -> c) -> System world () Source #

Maps a pure function over all components

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

mapM version of cmap. Can be used to get a list of entities

cmapM_ :: forall w c. (Has w c, IsRuntime c) => (c -> System w ()) -> System w () Source #

mapM_ version of cmap

cimapM :: forall w c a. (Has w c, IsRuntime c) => ((Entity c, c) -> System w a) -> System w [a] Source #

indexed cmapM, also gives the current entity.

cimapM_ :: forall w c. (Has w c, IsRuntime c) => ((Entity c, c) -> System w ()) -> System w () Source #

indexed cmapM_, also gives the current entity.

rmap' :: forall world r w. (Has world w, Has world r, Store (Storage w), IsRuntime r) => (r -> Safe w) -> System world () Source #

Maps a function over all entities with a r, and writes or deletes their w

rmap :: forall world r w. (Has world w, Has world r, IsRuntime w, IsRuntime r) => (r -> w) -> System world () Source #

Maps a function over all entities with a r, and writes their w

wmap :: forall world r w. (Has world w, Has world r, IsRuntime w, IsRuntime r) => (Safe r -> w) -> System world () Source #

For all entities with a w, this map reads their r and writes their w

wmap' :: forall world r w. (Has world w, Has world r, Store (Storage w), IsRuntime r) => (Safe r -> Safe w) -> System world () Source #

For all entities with a w, this map reads their r and writes or deletes their w

cmap' :: forall world c. (Has world c, IsRuntime c) => (c -> Safe c) -> System world () Source #

Maps a function that might delete its components

GlobalRW wrapper functions

readGlobal :: forall w c. (Has w c, GlobalRW (Storage c) c) => System w c Source #

Reads a global value

writeGlobal :: forall w c. (Has w c, GlobalRW (Storage c) c) => c -> System w () Source #

Writes a global value

modifyGlobal :: forall w c. (Has w c, GlobalRW (Storage c) c) => (c -> c) -> System w () Source #

Modifies a global value

Query

slice :: forall w c q. (Query q (Storage c), Has w c) => q -> System w (Slice c) Source #

Performs a query

data All Source #

Query that returns all members, equivalent to members

Constructors

All 

Instances

HasMembers s => Query All s Source # 

Methods

explSlice :: s -> All -> IO (Vector Int) Source #

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

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.