Copyright | (C) 2020 Sophie Taylor |
---|---|
License | AGPL-3.0-or-later |
Maintainer | Sophie Taylor <sophie@spacekitteh.moe> |
Stability | experimental |
Portability | GHC |
Safe Haskell | Trustworthy |
Language | GHC2021 |
Games.ECS.World
Description
Infrastructure for defining ECS worlds.
Synopsis
- data Access
- data Props
- class World (w :: Access -> Type) where
- newWorld :: w 'Storing
- createNewEntity :: MonadIO m => m (w 'Individual)
- createNewEntityWithRef :: Entity -> w 'Individual
- entities :: IndexedTraversal' Entity (w 'Storing) (w 'Individual)
- entityReference :: IndexedGetter Entity (w 'Individual) Entity
- unsafeEntityReference :: Lens' (w 'Individual) Entity
- entityReferences :: IndexedFold Entity (w 'Storing) Entity
- lookupEntity :: w 'Storing -> Entity -> Maybe (w 'Individual)
- prototype :: HasPrototypeID p => p -> AffineTraversal' (w 'Storing) (w 'Individual)
- lookupEntities :: forall f p fol. (Indexable Entity p, Applicative f, Foldable fol) => fol Entity -> p (w 'Individual) (f (w 'Individual)) -> w 'Storing -> f (w 'Storing)
- entitiesWith :: forall f p. (Indexable Entity p, Applicative f) => (forall r. Monoid r => Getting r (w 'Storing) IntersectionOfEntities) -> p (w 'Individual) (f (w 'Individual)) -> w 'Storing -> f (w 'Storing)
- storeEntity :: w 'Individual -> w 'Storing -> w 'Storing
- entity :: Entity -> AffineTraversal' (w 'Storing) (w 'Individual)
- type family OpticsFor (name :: Symbol) (hkd :: Access -> Type) (acc :: Access) (p :: Props) a where ...
- type EntRefStoringType = IntSet
- type family EntRefField (acc :: Access) where ...
- type AnAffineTraversal s t a b = ReifiedIndexedTraversal Entity s t a b
- type AnAffineTraversal' s a = AnAffineTraversal s s a a
- type AffineTraversal s t a b = Traversal s t a b
- type AffineTraversal' s a = AffineTraversal s s a a
- affine :: (s -> Either t a) -> (s -> b -> t) -> Traversal s t a b
- affine' :: (s -> Maybe a) -> (s -> a -> s) -> Traversal' s a
- newUniqueEntRef :: IO Entity
Documentation
HKD parameterisation for an ECS.
Constructors
Storing | We are dealing with the entire collection of entities in a world, represented structure-of-array style. |
Individual | We are dealing with a specific individual with specific component values. |
Different arities.
class World (w :: Access -> Type) where Source #
An entity component system, parameterised by its access type.
Minimal complete definition
newWorld, createNewEntityWithRef, entityReference, unsafeEntityReference, entityReferences, lookupEntity, prototype, storeEntity
Methods
newWorld :: w 'Storing Source #
Construct a new world.
createNewEntity :: MonadIO m => m (w 'Individual) Source #
Create a new entity
createNewEntityWithRef :: Entity -> w 'Individual Source #
Create a new entity with a given reference.
entities :: IndexedTraversal' Entity (w 'Storing) (w 'Individual) Source #
Traversal over all entities in the ECS.
default entities :: HasType EntRefStoringType (w 'Storing) => IndexedTraversal' Entity (w 'Storing) (w 'Individual) Source #
entityReference :: IndexedGetter Entity (w 'Individual) Entity Source #
Get the entity reference of an individual
unsafeEntityReference :: Lens' (w 'Individual) Entity Source #
Get and set the entity reference of an individual
entityReferences :: IndexedFold Entity (w 'Storing) Entity Source #
Get all of the entity references stored in the world.
lookupEntity :: w 'Storing -> Entity -> Maybe (w 'Individual) Source #
Check if a given entity exists in the world, and if so, return the individual.
prototype :: HasPrototypeID p => p -> AffineTraversal' (w 'Storing) (w 'Individual) Source #
Get a prototype specification from its name.
lookupEntities :: forall f p fol. (Indexable Entity p, Applicative f, Foldable fol) => fol Entity -> p (w 'Individual) (f (w 'Individual)) -> w 'Storing -> f (w 'Storing) Source #
An IndexedTraversal' which returns the individuals associated to the entities given as input.
entitiesWith :: forall f p. (Indexable Entity p, Applicative f) => (forall r. Monoid r => Getting r (w 'Storing) IntersectionOfEntities) -> p (w 'Individual) (f (w 'Individual)) -> w 'Storing -> f (w 'Storing) Source #
An IndexedTraversal' of individuals matching some constraints. The constraints are included monoidally.
storeEntity :: w 'Individual -> w 'Storing -> w 'Storing Source #
Store an individual in a world, returning the new world.
entity :: Entity -> AffineTraversal' (w 'Storing) (w 'Individual) Source #
Affine traversal for a specified individual from the world.
type family OpticsFor (name :: Symbol) (hkd :: Access -> Type) (acc :: Access) (p :: Props) a where ... Source #
We want to make sure that the API is consistent based on the access type and availability property, so we have a type family to give us the correct optics.
Equations
OpticsFor name hkd 'Individual 'Required a = ReifiedIndexedLens' Entity (hkd 'Individual) a | |
OpticsFor name hkd 'Individual 'Normal a = AnAffineTraversal' (hkd 'Individual) a | |
OpticsFor name hkd 'Individual 'Unique a = AnAffineTraversal' (hkd 'Individual) a | |
OpticsFor name hkd 'Storing 'Unique a = ReifiedIndexedTraversal' Entity (hkd 'Storing) a | |
OpticsFor name hkd 'Storing 'Normal a = ReifiedIndexedTraversal' Entity (hkd 'Storing) a | |
OpticsFor name hkd 'Storing 'Required a = ReifiedIndexedTraversal' Entity (hkd 'Storing) a |
type EntRefStoringType = IntSet Source #
A type which holds a collection of Entity
.
type family EntRefField (acc :: Access) where ... Source #
A type function for simplifying the higher-kinded data implementation.
Equations
EntRefField 'Individual = Entity | |
EntRefField 'Storing = EntRefStoringType |
type AnAffineTraversal s t a b = ReifiedIndexedTraversal Entity s t a b Source #
A reified AffineTraversal
.
type AnAffineTraversal' s a = AnAffineTraversal s s a a Source #
A reified AffineTraversal'
.
type AffineTraversal s t a b = Traversal s t a b Source #
An AffineTraversal
is one which traverses either 0 or 1 elements.
type AffineTraversal' s a = AffineTraversal s s a a Source #
Simplified AffineTraversal
.
affine :: (s -> Either t a) -> (s -> b -> t) -> Traversal s t a b Source #
Construct an AffineTraversal
.
affine' :: (s -> Maybe a) -> (s -> a -> s) -> Traversal' s a Source #
Construct an AffineTraversal'
.
newUniqueEntRef :: IO Entity Source #
Atomically construct a new entity reference.