Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Aztecs.ECS
Description
Aztecs is a type-safe and friendly ECS for games and more.
An ECS is a modern approach to organizing your application state as a database, providing patterns for data-oriented design and parallel processing.
The ECS architecture is composed of three main concepts:
Entities
An entity is an object comprised of zero or more components.
In Aztecs, entities are represented by their EntityID
, a unique identifier.
Components
A Component
holds the data for a particular aspect of an entity.
For example, a zombie entity might have a Health
and a Transform
component.
newtype Position = Position Int deriving (Show) instance Component Position newtype Velocity = Velocity Int deriving (Show) instance Component Velocity
Systems
A System
is a pipeline that processes entities and their components.
Synopsis
- type System = SystemT Identity
- newtype SystemT m a = System {
- unSystem :: forall t. (MonadTrans t, Monad (t m)) => Job t m a
- data Job t m a where
- newtype Task t (m :: Type -> Type) a = Task {}
- query :: Monad m => Query a -> SystemT m [a]
- querySingleMaybe :: Monad m => Query a -> SystemT m (Maybe a)
- readQuery :: Monad m => Query a -> SystemT m [a]
- readQueryEntities :: Monad m => [EntityID] -> Query a -> SystemT m [a]
- runSystemT :: (MonadTrans t, Monad (t m), Monad m) => SystemT m a -> ((Entities -> Entities) -> t m Entities) -> t m a
- queryDyn :: Monad m => DynamicQuery a -> SystemT m [a]
- readQueryDyn :: Monad m => DynamicQuery a -> SystemT m [a]
- querySingleMaybeDyn :: Monad m => DynamicQuery a -> SystemT m (Maybe a)
- readQueryEntitiesDyn :: Monad m => [EntityID] -> DynamicQuery a -> SystemT m [a]
- readQueryT :: Monad m => QueryT m a -> SystemT m [a]
- readQueryEntitiesT :: Monad m => [EntityID] -> QueryT m a -> SystemT m [a]
- queryT :: Monad m => QueryT m a -> SystemT m [a]
- querySingleMaybeT :: Monad m => QueryT m a -> SystemT m (Maybe a)
- fromQuery :: Query a -> SystemT m (DynamicQuery a)
- fromQueryT :: Monad m => QueryT m a -> SystemT m (DynamicQueryT m a)
- readQueryDynT :: Monad m => DynamicQueryT m a -> SystemT m [a]
- readQueryEntitiesDynT :: Monad m => [EntityID] -> DynamicQueryT m a -> SystemT m [a]
- queryDynT :: Monad m => DynamicQueryT m a -> SystemT m [a]
- querySingleMaybeDynT :: Monad m => DynamicQueryT m a -> SystemT m (Maybe a)
- type Query = QueryT Identity
- newtype QueryT f a = Query {
- runQuery :: Components -> (Components, DynamicQueryT f a)
- with :: forall f a. Component a => QueryT f ()
- fromDyn :: DynamicQueryT f a -> QueryT f a
- entity :: QueryT f EntityID
- fetch :: forall f a. Component a => QueryT f a
- fetchMaybe :: forall f a. Component a => QueryT f (Maybe a)
- fetchMap :: forall f a. Component a => (a -> a) -> QueryT f a
- fetchMapM :: forall f a. (Monad f, Component a) => (a -> f a) -> QueryT f a
- zipFetchMap :: forall f a b. Component a => (b -> a -> a) -> QueryT f b -> QueryT f a
- zipFetchMapAccum :: forall f a b c. Component a => (b -> a -> (c, a)) -> QueryT f b -> QueryT f (c, a)
- zipFetchMapM :: forall f a b. (Monad f, Component a) => (b -> a -> f a) -> QueryT f b -> QueryT f a
- zipFetchMapAccumM :: forall f a b c. (Monad f, Component a) => (b -> a -> f (c, a)) -> QueryT f b -> QueryT f (c, a)
- without :: forall f a. Component a => QueryT f ()
- liftQuery :: (MonadTrans g, Monad (g f), Monad f) => QueryT f a -> QueryT (g f) a
- queryEntities :: Monad m => [EntityID] -> QueryT m a -> Entities -> m ([a], Entities)
- readQuerySingle :: (HasCallStack, Applicative f) => QueryT f a -> Entities -> f (a, Entities)
- readQuerySingleMaybe :: Applicative f => QueryT f a -> Entities -> f (Maybe a, Entities)
- type Access = AccessT Identity
- data AccessT m a
- runAccessT :: Functor m => AccessT m a -> World -> m (a, World)
- runAccessT_ :: Functor m => AccessT m a -> m a
- data Bundle
- bundle :: forall a. Component a => a -> Bundle
- fromDynBundle :: DynamicBundle -> Bundle
- data DynamicBundle
- dynBundle :: Component a => ComponentID -> a -> DynamicBundle
- class (Typeable a, Storage a (StorageT a)) => Component a where
- type StorageT a
- data EntityID
- spawn :: Monad m => Bundle -> AccessT m EntityID
- system :: Monad m => SystemT m a -> AccessT m a
- concurrently :: SystemT IO a -> AccessT IO a
- data World
Documentation
System to process entities.
Since: 0.11
Constructors
System | |
Fields
|
Job to be interpreted.
Since: 0.11
query :: Monad m => Query a -> SystemT m [a] Source #
Match and update all entities with a QueryT
.
Since: 0.11
querySingleMaybe :: Monad m => Query a -> SystemT m (Maybe a) Source #
Match and update a single entity with a Query
, or Nothing
.
Since: 0.11
readQuery :: Monad m => Query a -> SystemT m [a] Source #
Match all entities with a Query
.
Since: 0.11
readQueryEntities :: Monad m => [EntityID] -> Query a -> SystemT m [a] Source #
Match entities with a QueryT
.
Since: 0.11
runSystemT :: (MonadTrans t, Monad (t m), Monad m) => SystemT m a -> ((Entities -> Entities) -> t m Entities) -> t m a Source #
queryDyn :: Monad m => DynamicQuery a -> SystemT m [a] Source #
Map all entities with a DynamicQuery
.
Since: 0.11
readQueryDyn :: Monad m => DynamicQuery a -> SystemT m [a] Source #
querySingleMaybeDyn :: Monad m => DynamicQuery a -> SystemT m (Maybe a) Source #
Map a single entity with a DynamicQuery
.
Since: 0.11
readQueryEntitiesDyn :: Monad m => [EntityID] -> DynamicQuery a -> SystemT m [a] Source #
readQueryT :: Monad m => QueryT m a -> SystemT m [a] Source #
Match all entities with a QueryT
.
Since: 0.11
readQueryEntitiesT :: Monad m => [EntityID] -> QueryT m a -> SystemT m [a] Source #
Match entities with a QueryT
.
Since: 0.11
queryT :: Monad m => QueryT m a -> SystemT m [a] Source #
Match and update all entities with a QueryT
.
Since: 0.11
querySingleMaybeT :: Monad m => QueryT m a -> SystemT m (Maybe a) Source #
Match and update a single entity with a QueryT
, or Nothing
.
Since: 0.11
fromQueryT :: Monad m => QueryT m a -> SystemT m (DynamicQueryT m a) Source #
readQueryDynT :: Monad m => DynamicQueryT m a -> SystemT m [a] Source #
readQueryEntitiesDynT :: Monad m => [EntityID] -> DynamicQueryT m a -> SystemT m [a] Source #
queryDynT :: Monad m => DynamicQueryT m a -> SystemT m [a] Source #
Map all entities with a DynamicQueryT
.
Since: 0.11
querySingleMaybeDynT :: Monad m => DynamicQueryT m a -> SystemT m (Maybe a) Source #
Map a single entity with a DynamicQueryT
.
Since: 0.11
Query for matching entities.
Since: 0.11
Constructors
Query | |
Fields
|
Instances
Applicative f => Applicative (QueryT f) Source # | Since: 0.11 |
Functor (QueryT f) Source # | |
with :: forall f a. Component a => QueryT f () Source #
Filter for entities with a component.
Since: 0.11
fromDyn :: DynamicQueryT f a -> QueryT f a Source #
Convert a DynamicQueryT
to a QueryT
.
Since: 0.11
fetchMaybe :: forall f a. Component a => QueryT f (Maybe a) Source #
Fetch a component, or Nothing
.
Since: 0.12
fetchMap :: forall f a. Component a => (a -> a) -> QueryT f a Source #
Fetch a component and map it, storing the result.
Since: 0.11
fetchMapM :: forall f a. (Monad f, Component a) => (a -> f a) -> QueryT f a Source #
Fetch a component and map it with a monadic function, storing the result.
Since: 0.11
zipFetchMap :: forall f a b. Component a => (b -> a -> a) -> QueryT f b -> QueryT f a Source #
Fetch a component and map it with some input, storing the result.
Since: 0.11
zipFetchMapAccum :: forall f a b c. Component a => (b -> a -> (c, a)) -> QueryT f b -> QueryT f (c, a) Source #
Fetch a component and map it with some input, storing the result and returning some output.
Since: 0.11
zipFetchMapM :: forall f a b. (Monad f, Component a) => (b -> a -> f a) -> QueryT f b -> QueryT f a Source #
Fetch a component and map it with some input and a monadic function, storing the result.
Since: 0.11
zipFetchMapAccumM :: forall f a b c. (Monad f, Component a) => (b -> a -> f (c, a)) -> QueryT f b -> QueryT f (c, a) Source #
Fetch a component and map it with some input and a monadic function, storing the result and returning some output.
Since: 0.11
without :: forall f a. Component a => QueryT f () Source #
Filter for entities without a component.
Since: 0.11
queryEntities :: Monad m => [EntityID] -> QueryT m a -> Entities -> m ([a], Entities) Source #
Match and update the specified entities.
Since: 0.12
readQuerySingle :: (HasCallStack, Applicative f) => QueryT f a -> Entities -> f (a, Entities) Source #
Match a single entity.
Since: 0.12
readQuerySingleMaybe :: Applicative f => QueryT f a -> Entities -> f (Maybe a, Entities) Source #
Match a single entity, or Nothing
.
Since: 0.12
Access into the World
.
Since: 0.9
Bundle of components.
Since: 0.9
fromDynBundle :: DynamicBundle -> Bundle Source #
data DynamicBundle Source #
Dynamic bundle of components.
Since: 0.9
Instances
Monoid DynamicBundle Source # | Since: 0.9 |
Defined in Aztecs.ECS.World.Bundle.Dynamic Methods mempty :: DynamicBundle # mappend :: DynamicBundle -> DynamicBundle -> DynamicBundle # mconcat :: [DynamicBundle] -> DynamicBundle # | |
Semigroup DynamicBundle Source # | Since: 0.9 |
Defined in Aztecs.ECS.World.Bundle.Dynamic Methods (<>) :: DynamicBundle -> DynamicBundle -> DynamicBundle # sconcat :: NonEmpty DynamicBundle -> DynamicBundle # stimes :: Integral b => b -> DynamicBundle -> DynamicBundle # |
dynBundle :: Component a => ComponentID -> a -> DynamicBundle Source #
Since: 0.11
class (Typeable a, Storage a (StorageT a)) => Component a Source #
Component that can be stored in the World
.
Since: 0.9
Unique entity identifier.
Since: 0.9
World of entities and their components.
Since: 0.9
Instances
Generic World Source # | |
Show World Source # | |
NFData World Source # | |
Defined in Aztecs.ECS.World | |
type Rep World Source # | |
Defined in Aztecs.ECS.World type Rep World = D1 ('MetaData "World" "Aztecs.ECS.World" "aztecs-0.12.0-GlKmPfHNl6i8JdqwU1RE4N" 'False) (C1 ('MetaCons "World" 'PrefixI 'True) (S1 ('MetaSel ('Just "entities") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Entities) :*: S1 ('MetaSel ('Just "nextEntityId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EntityID))) |