Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Entity = Entity {}
- newtype System w a = System {}
- class Elem (Storage c) ~ c => Component c where
- type Storage c
- class Component c => Has w c where
- type family Elem s
- class ExplInit s where
- class ExplGet s where
- class ExplSet s where
- class ExplDestroy s where
- class ExplMembers s where
- type Get w c = (Has w c, ExplGet (Storage c))
- type Set w c = (Has w c, ExplSet (Storage c))
- type Members w c = (Has w c, ExplMembers (Storage c))
- type Destroy w c = (Has w c, ExplDestroy (Storage c))
- data Not a = Not
- newtype NotStore s = NotStore s
- newtype MaybeStore s = MaybeStore s
- data EitherStore sa sb = EitherStore sa sb
- data Filter c = Filter
- newtype FilterStore s = FilterStore s
- data EntityStore = EntityStore
Documentation
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.
A System 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
.
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.
Instances
class Component c => Has w c where Source #
Has w c
means that world w
can produce a Storage c
.
Instances
Has w Entity Source # | |
Has w () Source # | |
Has w c => Has w (Identity c) Source # | |
Has w c => Has w (Filter c) Source # | |
Has w c => Has w (Maybe c) Source # | |
Has w c => Has w (Not c) Source # | |
(Has w ca, Has w cb) => Has w (Either ca cb) Source # | |
(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 # | |
(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 # | |
(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 # | |
The type of components stored by a store, e.g. Elem (Map c) = c
.
Instances
type Elem () Source # | |
Defined in Apecs.Core type Elem () = () | |
type Elem EntityStore Source # | |
Defined in Apecs.Core | |
type Elem (Identity s) Source # | |
Defined in Apecs.Core | |
type Elem (FilterStore s) Source # | |
Defined in Apecs.Core | |
type Elem (MaybeStore s) Source # | |
Defined in Apecs.Core | |
type Elem (NotStore s) Source # | |
Defined in Apecs.Core | |
type Elem (Global c) Source # | |
Defined in Apecs.Stores | |
type Elem (Unique c) Source # | |
Defined in Apecs.Stores | |
type Elem (Map c) Source # | |
Defined in Apecs.Stores | |
type Elem (t_0, t_1) Source # | |
Defined in Apecs.Core | |
type Elem (EitherStore sa sb) Source # | |
Defined in Apecs.Core | |
type Elem (Cache n s) Source # | |
Defined in Apecs.Stores | |
type Elem (t_0, t_1, t_2) Source # | |
Defined in Apecs.Core | |
type Elem (t_0, t_1, t_2, t_3) Source # | |
type Elem (t_0, t_1, t_2, t_3, t_4) Source # | |
type Elem (t_0, t_1, t_2, t_3, t_4, t_5) Source # | |
type Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6) Source # | |
type Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) Source # | |
class ExplInit s where Source #
Indicates that the store s
can be initialized.
Generally, "base" stores like Map c
can be initialized, but composite stores like MaybeStore s
cannot.
class ExplGet s where Source #
Stores that we can read using explGet
and explExists
.
For some entity e
, eplGet s e
is only guaranteed to be safe if explExists s e
returns True
.
explGet :: s -> Int -> IO (Elem s) Source #
Reads a component from the store. What happens if the component does not exist is left undefined, and might not necessarily crash.
explExists :: s -> Int -> IO Bool Source #
Returns whether there is a component for the given index.
Instances
class ExplSet s where Source #
Stores that can be written.
Instances
class ExplDestroy s where Source #
Stores that components can be removed from.
explDestroy :: s -> Int -> IO () Source #
Destroys the component for a given index.
Instances
ExplDestroy () Source # | |
Defined in Apecs.Core explDestroy :: () -> Int -> IO () Source # | |
ExplDestroy s => ExplDestroy (Identity s) Source # | |
Defined in Apecs.Core | |
ExplDestroy (Unique c) Source # | |
Defined in Apecs.Stores | |
ExplDestroy (Map c) Source # | |
Defined in Apecs.Stores | |
(ExplDestroy t_0, ExplDestroy t_1) => ExplDestroy (t_0, t_1) Source # | |
Defined in Apecs.Core explDestroy :: (t_0, t_1) -> Int -> IO () Source # | |
ExplDestroy s => ExplDestroy (Cache n s) Source # | |
Defined in Apecs.Stores | |
(ExplDestroy t_0, ExplDestroy t_1, ExplDestroy t_2) => ExplDestroy (t_0, t_1, t_2) Source # | |
Defined in Apecs.Core explDestroy :: (t_0, t_1, t_2) -> Int -> IO () Source # | |
(ExplDestroy t_0, ExplDestroy t_1, ExplDestroy t_2, ExplDestroy t_3) => ExplDestroy (t_0, t_1, t_2, t_3) Source # | |
Defined in Apecs.Core explDestroy :: (t_0, t_1, t_2, t_3) -> Int -> IO () Source # | |
(ExplDestroy t_0, ExplDestroy t_1, ExplDestroy t_2, ExplDestroy t_3, ExplDestroy t_4) => ExplDestroy (t_0, t_1, t_2, t_3, t_4) Source # | |
Defined in Apecs.Core explDestroy :: (t_0, t_1, t_2, t_3, t_4) -> Int -> IO () Source # | |
(ExplDestroy t_0, ExplDestroy t_1, ExplDestroy t_2, ExplDestroy t_3, ExplDestroy t_4, ExplDestroy t_5) => ExplDestroy (t_0, t_1, t_2, t_3, t_4, t_5) Source # | |
Defined in Apecs.Core explDestroy :: (t_0, t_1, t_2, t_3, t_4, t_5) -> Int -> IO () Source # | |
(ExplDestroy t_0, ExplDestroy t_1, ExplDestroy t_2, ExplDestroy t_3, ExplDestroy t_4, ExplDestroy t_5, ExplDestroy t_6) => ExplDestroy (t_0, t_1, t_2, t_3, t_4, t_5, t_6) Source # | |
Defined in Apecs.Core explDestroy :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6) -> Int -> IO () Source # | |
(ExplDestroy t_0, ExplDestroy t_1, ExplDestroy t_2, ExplDestroy t_3, ExplDestroy t_4, ExplDestroy t_5, ExplDestroy t_6, ExplDestroy t_7) => ExplDestroy (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) Source # | |
Defined in Apecs.Core explDestroy :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) -> Int -> IO () Source # |
class ExplMembers s where Source #
Stores that we can request a list of member entities for.
Instances
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.
Pseudostore used to produce values of type Not a
, inverts explExists
, and destroys instead of explSet
.
NotStore s |
newtype MaybeStore s Source #
Pseudostore used to produce values of type Maybe a
.
Will always return True
for explExists
.
Writing can both set and delete a component using Just
and Nothing
respectively.
Instances
(ExplDestroy s, ExplSet s) => ExplSet (MaybeStore s) Source # | |
Defined in Apecs.Core explSet :: MaybeStore s -> Int -> Elem (MaybeStore s) -> IO () Source # | |
ExplGet s => ExplGet (MaybeStore s) Source # | |
Defined in Apecs.Core explGet :: MaybeStore s -> Int -> IO (Elem (MaybeStore s)) Source # explExists :: MaybeStore s -> Int -> IO Bool Source # | |
type Elem (MaybeStore s) Source # | |
Defined in Apecs.Core |
data EitherStore sa sb Source #
Used for Either
, a logical disjunction between two components.
As expected, Either is used to model error values.
Getting an Either a b
will first attempt to get a b
and return it as Right b
, or if it does not exist, get an a
as Left a
.
Can also be used to set one of two things.
EitherStore sa sb |
Instances
(ExplSet sa, ExplSet sb) => ExplSet (EitherStore sa sb) Source # | |
Defined in Apecs.Core explSet :: EitherStore sa sb -> Int -> Elem (EitherStore sa sb) -> IO () Source # | |
(ExplGet sa, ExplGet sb) => ExplGet (EitherStore sa sb) Source # | |
Defined in Apecs.Core explGet :: EitherStore sa sb -> Int -> IO (Elem (EitherStore sa sb)) Source # explExists :: EitherStore sa sb -> Int -> IO Bool Source # | |
type Elem (EitherStore sa sb) Source # | |
Defined in Apecs.Core |
Pseudocomponent that functions normally for explExists
and explMembers
, but always return Filter
for explGet
.
Can be used in cmap as cmap $ (Filter :: Filter a) -> b
.
Since the above can be written more consicely as cmap $ (_ :: a) -> b
, it is rarely directly.
More interestingly, we can define reusable filters like movables = Filter :: Filter (Position, Velocity)
.
newtype FilterStore s Source #
Instances
ExplMembers s => ExplMembers (FilterStore s) Source # | |
Defined in Apecs.Core explMembers :: FilterStore s -> IO (Vector Int) Source # | |
ExplGet s => ExplGet (FilterStore s) Source # | |
Defined in Apecs.Core explGet :: FilterStore s -> Int -> IO (Elem (FilterStore s)) Source # explExists :: FilterStore s -> Int -> IO Bool Source # | |
type Elem (FilterStore s) Source # | |
Defined in Apecs.Core |
data EntityStore Source #
Pseudostore used to produce components of type Entity
.
Always returns True
for explExists
, and echoes back the entity argument for explGet
.
Used in e.g. cmap $ (a, ety :: Entity) -> b
to access the current entity.
Instances
ExplGet EntityStore Source # | |
Defined in Apecs.Core explGet :: EntityStore -> Int -> IO (Elem EntityStore) Source # explExists :: EntityStore -> Int -> IO Bool Source # | |
type Elem EntityStore Source # | |
Defined in Apecs.Core |