aztecs-0.12.0: A modular game engine and Entity-Component-System (ECS) for Haskell.
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

Documentation

newtype SystemT m a Source #

System to process entities.

Since: 0.11

Constructors

System 

Fields

Instances

Instances details
MonadIO m => MonadIO (SystemT m) Source #

Since: 0.11

Instance details

Defined in Aztecs.ECS.System

Methods

liftIO :: IO a -> SystemT m a #

Monad m => Applicative (SystemT m) Source #

Since: 0.11

Instance details

Defined in Aztecs.ECS.System

Methods

pure :: a -> SystemT m a #

(<*>) :: SystemT m (a -> b) -> SystemT m a -> SystemT m b #

liftA2 :: (a -> b -> c) -> SystemT m a -> SystemT m b -> SystemT m c #

(*>) :: SystemT m a -> SystemT m b -> SystemT m b #

(<*) :: SystemT m a -> SystemT m b -> SystemT m a #

Functor (SystemT m) Source #

Since: 0.11

Instance details

Defined in Aztecs.ECS.System

Methods

fmap :: (a -> b) -> SystemT m a -> SystemT m b #

(<$) :: a -> SystemT m b -> SystemT m a #

Monad m => Monad (SystemT m) Source #

Since: 0.11

Instance details

Defined in Aztecs.ECS.System

Methods

(>>=) :: SystemT m a -> (a -> SystemT m b) -> SystemT m b #

(>>) :: SystemT m a -> SystemT m b -> SystemT m b #

return :: a -> SystemT m a #

data Job t m a where Source #

Job to be interpreted.

Since: 0.11

Constructors

Pure :: a -> Job t m a 
Map :: (a -> b) -> Job t m a -> Job t m b 
Ap :: Job t m (a -> b) -> Job t m a -> Job t m b 
Bind :: Job t m a -> (a -> Job t m b) -> Job t m b 
Once :: Task t m a -> Job t m a 

newtype Task t (m :: Type -> Type) a Source #

System task.

Since: 0.11

Constructors

Task 

Fields

Instances

Instances details
Functor (t m) => Functor (Task t m) Source # 
Instance details

Defined in Aztecs.ECS.System

Methods

fmap :: (a -> b) -> Task t m a -> Task t m b #

(<$) :: a -> Task t m b -> Task t m a #

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

querySingleMaybeDyn :: Monad m => DynamicQuery a -> SystemT m (Maybe a) Source #

Map a single entity with a DynamicQuery.

Since: 0.11

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

fromQuery :: Query a -> SystemT m (DynamicQuery a) Source #

Convert a Query to a SystemT.

Since: 0.11

fromQueryT :: Monad m => QueryT m a -> SystemT m (DynamicQueryT m a) Source #

Convert a QueryT to a SystemT.

Since: 0.11

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

type Query = QueryT Identity Source #

Since: 0.11

newtype QueryT f a Source #

Query for matching entities.

Since: 0.11

Constructors

Query 

Fields

Instances

Instances details
Applicative f => Applicative (QueryT f) Source #

Since: 0.11

Instance details

Defined in Aztecs.ECS.Query

Methods

pure :: a -> QueryT f a #

(<*>) :: QueryT f (a -> b) -> QueryT f a -> QueryT f b #

liftA2 :: (a -> b -> c) -> QueryT f a -> QueryT f b -> QueryT f c #

(*>) :: QueryT f a -> QueryT f b -> QueryT f b #

(<*) :: QueryT f a -> QueryT f b -> QueryT f a #

Functor (QueryT f) Source # 
Instance details

Defined in Aztecs.ECS.Query

Methods

fmap :: (a -> b) -> QueryT f a -> QueryT f b #

(<$) :: a -> QueryT f b -> QueryT f a #

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

entity :: QueryT f EntityID Source #

Fetch the current EntityID.

Since: 0.11

fetch :: forall f a. Component a => QueryT f a Source #

Fetch a component.

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

liftQuery :: (MonadTrans g, Monad (g f), Monad f) => QueryT f a -> QueryT (g f) a Source #

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

type Access = AccessT Identity Source #

Since: 0.9

data AccessT m a Source #

Access into the World.

Since: 0.9

Instances

Instances details
MonadFix m => MonadFix (AccessT m) Source # 
Instance details

Defined in Aztecs.ECS.Access

Methods

mfix :: (a -> AccessT m a) -> AccessT m a #

MonadIO m => MonadIO (AccessT m) Source # 
Instance details

Defined in Aztecs.ECS.Access

Methods

liftIO :: IO a -> AccessT m a #

Monad m => Applicative (AccessT m) Source # 
Instance details

Defined in Aztecs.ECS.Access

Methods

pure :: a -> AccessT m a #

(<*>) :: AccessT m (a -> b) -> AccessT m a -> AccessT m b #

liftA2 :: (a -> b -> c) -> AccessT m a -> AccessT m b -> AccessT m c #

(*>) :: AccessT m a -> AccessT m b -> AccessT m b #

(<*) :: AccessT m a -> AccessT m b -> AccessT m a #

Functor m => Functor (AccessT m) Source # 
Instance details

Defined in Aztecs.ECS.Access

Methods

fmap :: (a -> b) -> AccessT m a -> AccessT m b #

(<$) :: a -> AccessT m b -> AccessT m a #

Monad m => Monad (AccessT m) Source #

Since: 0.9

Instance details

Defined in Aztecs.ECS.Access

Methods

(>>=) :: AccessT m a -> (a -> AccessT m b) -> AccessT m b #

(>>) :: AccessT m a -> AccessT m b -> AccessT m b #

return :: a -> AccessT m a #

runAccessT :: Functor m => AccessT m a -> World -> m (a, World) Source #

Run an Access on a World, returning the output and updated World.

Since: 0.9

runAccessT_ :: Functor m => AccessT m a -> m a Source #

Run an Access on an empty World.

Since: 0.9

data Bundle Source #

Bundle of components.

Since: 0.9

Instances

Instances details
Monoid Bundle Source #

Since: 0.9

Instance details

Defined in Aztecs.ECS.World.Bundle

Semigroup Bundle Source #

Since: 0.9

Instance details

Defined in Aztecs.ECS.World.Bundle

bundle :: forall a. Component a => a -> Bundle 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

Associated Types

type StorageT a Source #

Storage of this component.

Since: 0.9

type StorageT a = [a]

data EntityID Source #

Unique entity identifier.

Since: 0.9

Instances

Instances details
Generic EntityID Source # 
Instance details

Defined in Aztecs.ECS.Entity

Associated Types

type Rep EntityID :: Type -> Type #

Methods

from :: EntityID -> Rep EntityID x #

to :: Rep EntityID x -> EntityID #

Show EntityID Source # 
Instance details

Defined in Aztecs.ECS.Entity

NFData EntityID Source # 
Instance details

Defined in Aztecs.ECS.Entity

Methods

rnf :: EntityID -> () #

Eq EntityID Source # 
Instance details

Defined in Aztecs.ECS.Entity

Ord EntityID Source # 
Instance details

Defined in Aztecs.ECS.Entity

type Rep EntityID Source # 
Instance details

Defined in Aztecs.ECS.Entity

type Rep EntityID = D1 ('MetaData "EntityID" "Aztecs.ECS.Entity" "aztecs-0.12.0-GlKmPfHNl6i8JdqwU1RE4N" 'True) (C1 ('MetaCons "EntityID" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEntityId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

spawn :: Monad m => Bundle -> AccessT m EntityID Source #

Spawn an entity with a Bundle.

Since: 0.11

system :: Monad m => SystemT m a -> AccessT m a Source #

Run a System.

Since: 0.11

concurrently :: SystemT IO a -> AccessT IO a Source #

Run a System concurrently.

Since: 0.11

data World Source #

World of entities and their components.

Since: 0.9

Instances

Instances details
Generic World Source # 
Instance details

Defined in Aztecs.ECS.World

Associated Types

type Rep World :: Type -> Type #

Methods

from :: World -> Rep World x #

to :: Rep World x -> World #

Show World Source # 
Instance details

Defined in Aztecs.ECS.World

Methods

showsPrec :: Int -> World -> ShowS #

show :: World -> String #

showList :: [World] -> ShowS #

NFData World Source # 
Instance details

Defined in Aztecs.ECS.World

Methods

rnf :: World -> () #

type Rep World Source # 
Instance details

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