apecs-0.2.4.3: 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 #

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

Associated Types

type Storage c Source #

Instances

Component EntityCounter Source # 

Associated Types

type Storage EntityCounter :: * 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 #

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

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 #

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 Stores (Map c) :: * Source #

type SafeRW (Map c) :: * Source #

Methods

initStore :: IO (Map c) Source #

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

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

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

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

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

explGetUnsafe :: Map c -> Int -> IO (Stores (Map c)) Source #

explSetMaybe :: Map c -> Int -> SafeRW (Map c) -> IO () Source #

explReset :: Map c -> IO () Source #

explImapM_ :: MonadIO m => Map c -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Map c -> (Int -> m a) -> m [a] Source #

explModify :: Map c -> Int -> (Stores (Map c) -> Stores (Map c)) -> IO () Source #

explCmap :: Map c -> (Stores (Map c) -> Stores (Map c)) -> IO () Source #

explCmapM_ :: MonadIO m => Map c -> (Stores (Map c) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Map c -> ((Int, Stores (Map c)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Map c -> (Stores (Map c) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Map c -> ((Int, Stores (Map c)) -> m a) -> m [a] Source #

Cachable (Map s) Source # 
type Stores (Map c) Source # 
type Stores (Map c) = c
type SafeRW (Map c) Source # 
type SafeRW (Map c) = Maybe c

data Set c Source #

A store that keeps membership, but holds no values. Produces flag runtime values.

Instances

Flag c => Store (Set c) Source # 

Associated Types

type Stores (Set c) :: * Source #

type SafeRW (Set c) :: * Source #

Methods

initStore :: IO (Set c) Source #

explGet :: Set c -> Int -> IO (SafeRW (Set c)) Source #

explSet :: Set c -> Int -> Stores (Set c) -> IO () Source #

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

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

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

explGetUnsafe :: Set c -> Int -> IO (Stores (Set c)) Source #

explSetMaybe :: Set c -> Int -> SafeRW (Set c) -> IO () Source #

explReset :: Set c -> IO () Source #

explImapM_ :: MonadIO m => Set c -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Set c -> (Int -> m a) -> m [a] Source #

explModify :: Set c -> Int -> (Stores (Set c) -> Stores (Set c)) -> IO () Source #

explCmap :: Set c -> (Stores (Set c) -> Stores (Set c)) -> IO () Source #

explCmapM_ :: MonadIO m => Set c -> (Stores (Set c) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Set c -> ((Int, Stores (Set c)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Set c -> (Stores (Set c) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Set c -> ((Int, Stores (Set c)) -> m a) -> m [a] Source #

type Stores (Set c) Source # 
type Stores (Set c) = c
type SafeRW (Set c) Source # 
type SafeRW (Set c) = Bool

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 Stores (Unique c) :: * Source #

type SafeRW (Unique c) :: * Source #

Methods

initStore :: IO (Unique c) Source #

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

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

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

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

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

explGetUnsafe :: Unique c -> Int -> IO (Stores (Unique c)) Source #

explSetMaybe :: Unique c -> Int -> SafeRW (Unique c) -> IO () Source #

explReset :: Unique c -> IO () Source #

explImapM_ :: MonadIO m => Unique c -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Unique c -> (Int -> m a) -> m [a] Source #

explModify :: Unique c -> Int -> (Stores (Unique c) -> Stores (Unique c)) -> IO () Source #

explCmap :: Unique c -> (Stores (Unique c) -> Stores (Unique c)) -> IO () Source #

explCmapM_ :: MonadIO m => Unique c -> (Stores (Unique c) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Unique c -> ((Int, Stores (Unique c)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Unique c -> (Stores (Unique c) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Unique c -> ((Int, Stores (Unique c)) -> m a) -> m [a] Source #

type Stores (Unique c) Source # 
type Stores (Unique c) = c
type SafeRW (Unique c) Source # 
type SafeRW (Unique c) = Maybe c

data Global c Source #

Global value. Initialized with mempty

Instances

Monoid c => GlobalStore (Global c) Source # 
Monoid c => Store (Global c) Source # 

Associated Types

type Stores (Global c) :: * Source #

type SafeRW (Global c) :: * Source #

Methods

initStore :: IO (Global c) Source #

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

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

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

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

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

explGetUnsafe :: Global c -> Int -> IO (Stores (Global c)) Source #

explSetMaybe :: Global c -> Int -> SafeRW (Global c) -> IO () Source #

explReset :: Global c -> IO () Source #

explImapM_ :: MonadIO m => Global c -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Global c -> (Int -> m a) -> m [a] Source #

explModify :: Global c -> Int -> (Stores (Global c) -> Stores (Global c)) -> IO () Source #

explCmap :: Global c -> (Stores (Global c) -> Stores (Global c)) -> IO () Source #

explCmapM_ :: MonadIO m => Global c -> (Stores (Global c) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Global c -> ((Int, Stores (Global c)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Global c -> (Stores (Global c) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Global c -> ((Int, Stores (Global c)) -> m a) -> m [a] Source #

type Stores (Global c) Source # 
type Stores (Global c) = c
type SafeRW (Global c) Source # 
type SafeRW (Global c) = c

class Flag c where Source #

Class for flags, used by Set to yield runtime representations.

Minimal complete definition

flag

Methods

flag :: c Source #

Store wrapper functions

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

Destroys the component c for the given entity

exists :: forall w c. Has w 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 => System w (Slice c) Source #

A slice containing all entities with component c

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

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

get :: forall w 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. Has w c => Entity e -> c -> System w () Source #

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

set' :: forall w 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. 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. Has world c => (c -> c) -> System world () Source #

Maps a pure function over all components

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

mapM version of cmap. Can be used to get a list of entities As the type signature implies, and unlike cmap, the return value is not written to the component store.

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

mapM_ version of cmap

cimapM :: forall w c a. Has w 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 => ((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 r), Store (Storage w)) => (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) => (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, Store (Storage r), Store (Storage w)) => (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 r), Store (Storage w)) => (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 => (c -> Safe c) -> System world () Source #

Maps a function that might delete its components

GlobalRW wrapper functions

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

Reads a global value

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

Writes a global value

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

Modifies a global value

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

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

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.