Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module forms the apecs Prelude. It selectively re-exports the user-facing functions from the submodules.
- newtype System w a = System {}
- class (Stores (Storage c) ~ c, Store (Storage c)) => Component c where
- type Storage c
- newtype Entity c = Entity Int
- data Slice c
- class Component c => Has w c where
- newtype Safe c = Safe {}
- cast :: Cast a b => a -> b
- data Map c
- data Set c
- data Unique c
- data Global c
- class Flag c where
- initStore :: Store s => IO s
- destroy :: forall w c. Has w c => Entity c -> System w ()
- exists :: forall w c. Has w c => Entity c -> System w Bool
- owners :: forall w c. Has w c => System w (Slice c)
- resetStore :: forall w c p. Has w c => p c -> System w ()
- get :: forall w c. Has w c => Entity c -> System w (Safe c)
- set :: forall w c e. Has w c => Entity e -> c -> System w ()
- set' :: forall w c. Has w c => Entity c -> Safe c -> System w ()
- modify :: forall w c. Has w c => Entity c -> (c -> c) -> System w ()
- cmap :: forall world c. Has world c => (c -> c) -> System world ()
- cmapM :: forall w c a. Has w c => (c -> System w a) -> System w [a]
- cmapM_ :: forall w c. Has w c => (c -> System w ()) -> System w ()
- cimapM :: forall w c a. Has w c => ((Entity c, c) -> System w a) -> System w [a]
- cimapM_ :: forall w c. Has w c => ((Entity c, c) -> System w ()) -> System w ()
- rmap' :: forall world r w. (Has world w, Has world r, Store (Storage r), Store (Storage w)) => (r -> Safe w) -> System world ()
- rmap :: forall world r w. (Has world w, Has world r) => (r -> w) -> System world ()
- wmap :: forall world r w. (Has world w, Has world r, Store (Storage r), Store (Storage w)) => (Safe r -> w) -> System world ()
- wmap' :: forall world r w. (Has world w, Has world r, Store (Storage r), Store (Storage w)) => (Safe r -> Safe w) -> System world ()
- cmap' :: forall world c. Has world c => (c -> Safe c) -> System world ()
- readGlobal :: forall w c. (Has w c, GlobalStore (Storage c)) => System w c
- writeGlobal :: forall w c. (Has w c, GlobalStore (Storage c)) => c -> System w ()
- modifyGlobal :: forall w c. (Has w c, GlobalStore (Storage c)) => (c -> c) -> System w ()
- runSystem :: System w a -> w -> IO a
- runWith :: w -> System w a -> IO a
- runGC :: System w ()
- data EntityCounter
- newEntity :: (Store (Storage c), Has w c, Has w EntityCounter) => c -> System w (Entity c)
- asks :: MonadReader r m => (r -> a) -> m a
- ask :: MonadReader r m => m r
- liftIO :: MonadIO m => forall a. IO a -> m a
- lift :: MonadTrans t => forall m a. Monad m => m a -> t m a
Types
A system is a newtype around `ReaderT w IO a`, where w
is the game world variable.
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.
Component EntityCounter Source # | |
(Component t_0, Component t_1) => Component (t_0, t_1) Source # | |
(Component t_0, Component t_1, Component t_2) => Component (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 # | |
(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 # | |
(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 # | |
An Entity is really just an Int. The type variable is used to keep track of reads and writes, but can be freely cast.
A slice is a list of entities, represented by a Data.Unbox.Vector of Ints.
class Component c => Has w c where Source #
A world Has
a component if it can produce its Storage
(Has w t_0, Has w t_1) => Has w (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 # | |
(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 # | |
(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 # | |
(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 # | |
Represents a safe access to c
. A safe access is either a read that might fail, or a write that might delete.
A map from Data.Intmap.Strict. O(log(n)) for most operations.
Yields safe runtime representations of type Maybe c
.
A store that keeps membership, but holds no values.
Produces flag
runtime values.
A Unique contains exactly one component belonging to some entity. Writing to it overwrites both the previous component and its owner.
Global value.
Initialized with mempty
Class for flags, used by Set
to yield runtime representations.
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
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
data EntityCounter Source #
Secretly just an int in a newtype
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
:: 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.
lift :: MonadTrans t => forall m a. Monad m => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.