aztecs-0.8.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. Systems in Aztecs either run in sequence or in parallel automatically based on the components they access.

Systems can access game state in two ways:

Access

An Access can be queued for full access to the World, after a system is complete. Access allows for spawning, inserting, and removing components.

setup :: System  () ()
setup = S.queue . const . A.spawn_ $ bundle (Position 0) <> bundle (Velocity 1)

Queries

A Query can read and write matching components.

move :: System  () ()
move =
 S.map
   ( proc () -> do
       Velocity v <- Q.fetch -< ()
       Position p <- Q.fetch -< ()
       Q.set -< Position $ p + v
   )
   >>> S.run print

Finally, systems can be run on a World to produce a result.

main :: IO ()
main = runSystem_ $ setup >>> S.forever move
Synopsis

Documentation

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

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

data Bundle Source #

Bundle of components.

Instances

Instances details
MonoidBundle Bundle Source # 
Instance details

Defined in Aztecs.ECS.World.Bundle

Methods

bundle :: Component c => c -> Bundle Source #

MonoidDynamicBundle Bundle Source # 
Instance details

Defined in Aztecs.ECS.World.Bundle

Methods

dynBundle :: Component c => ComponentID -> c -> Bundle Source #

Monoid Bundle Source # 
Instance details

Defined in Aztecs.ECS.World.Bundle

Semigroup Bundle Source # 
Instance details

Defined in Aztecs.ECS.World.Bundle

ArrowQueueSystem Bundle Access QueueSystem Source # 
Instance details

Defined in Aztecs.ECS.System.Queue

Methods

queue :: (i -> Access ()) -> QueueSystem i () Source #

Monad m => MonadAccess Bundle (AccessT m) Source # 
Instance details

Defined in Aztecs.ECS.Access

Monad m => ArrowAccessSchedule Bundle (AccessT m) (Schedule m) Source # 
Instance details

Defined in Aztecs.ECS.Schedule

Methods

access :: (i -> AccessT m o) -> Schedule m i o Source #

Monad m => ArrowAccessSchedule Bundle (AccessT m) (AcessSchedule m) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Access

Methods

access :: (i -> AccessT m o) -> AcessSchedule m i o Source #

Monad m => ArrowQueueSystem Bundle (AccessT m) (SystemT m) Source # 
Instance details

Defined in Aztecs.ECS.System

Methods

queue :: (i -> AccessT m ()) -> SystemT m i () Source #

Monad m => ArrowQueueSystem Bundle (AccessT m) (DynamicSystemT m) Source # 
Instance details

Defined in Aztecs.ECS.System.Dynamic

Methods

queue :: (i -> AccessT m ()) -> DynamicSystemT m i () Source #

Monad m => ArrowQueueSystem Bundle (AccessT m) (DynamicReaderSystemT m) Source # 
Instance details

Defined in Aztecs.ECS.System.Dynamic.Reader

Methods

queue :: (i -> AccessT m ()) -> DynamicReaderSystemT m i () Source #

Monad m => ArrowQueueSystem Bundle (AccessT m) (ReaderSystemT m) Source # 
Instance details

Defined in Aztecs.ECS.System.Reader

Methods

queue :: (i -> AccessT m ()) -> ReaderSystemT m i () Source #

class Monoid a => MonoidBundle a where Source #

Monoid bundle of components.

Methods

bundle :: forall c. Component c => c -> a Source #

Add a component to the bundle.

Instances

Instances details
MonoidBundle Bundle Source # 
Instance details

Defined in Aztecs.ECS.World.Bundle

Methods

bundle :: Component c => c -> Bundle Source #

class MonoidDynamicBundle a where Source #

Monoid bundle of dynamic components.

Methods

dynBundle :: Component c => ComponentID -> c -> a Source #

Add a component to the bundle by its ComponentID.

Instances

Instances details
MonoidDynamicBundle Bundle Source # 
Instance details

Defined in Aztecs.ECS.World.Bundle

Methods

dynBundle :: Component c => ComponentID -> c -> Bundle Source #

MonoidDynamicBundle DynamicBundle Source # 
Instance details

Defined in Aztecs.ECS.World.Bundle.Dynamic

class (Typeable a, Storage a (StorageT a)) => Component a Source #

Component that can be stored in the World.

Associated Types

type StorageT a :: Type Source #

Storage of this component.

type StorageT a = [a]

Instances

Instances details
Component Camera Source # 
Instance details

Defined in Aztecs.Camera

Associated Types

type StorageT Camera Source #

Component CameraTarget Source # 
Instance details

Defined in Aztecs.Camera

Associated Types

type StorageT CameraTarget Source #

Component ChildState Source # 
Instance details

Defined in Aztecs.Hierarchy

Associated Types

type StorageT ChildState Source #

Component Children Source # 
Instance details

Defined in Aztecs.Hierarchy

Associated Types

type StorageT Children Source #

Component Parent Source # 
Instance details

Defined in Aztecs.Hierarchy

Associated Types

type StorageT Parent Source #

Component ParentState Source # 
Instance details

Defined in Aztecs.Hierarchy

Associated Types

type StorageT ParentState Source #

Component KeyboardInput Source # 
Instance details

Defined in Aztecs.Input

Associated Types

type StorageT KeyboardInput Source #

Component MouseInput Source # 
Instance details

Defined in Aztecs.Input

Associated Types

type StorageT MouseInput Source #

Component Time Source # 
Instance details

Defined in Aztecs.Time

Associated Types

type StorageT Time Source #

Component Window Source # 
Instance details

Defined in Aztecs.Window

Associated Types

type StorageT Window Source #

Typeable a => Component (AssetServer a) Source # 
Instance details

Defined in Aztecs.Asset.AssetServer

Associated Types

type StorageT (AssetServer a) Source #

Component (Size (V2 Int)) Source # 
Instance details

Defined in Aztecs.Transform

Associated Types

type StorageT (Size (V2 Int)) Source #

Component (Transform (V2 Int) Int) Source # 
Instance details

Defined in Aztecs.Transform

Associated Types

type StorageT (Transform (V2 Int) Int) Source #

data EntityID Source #

Entity ID.

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.8.0-5YWGoxTs0Vw9iciqZAe9GO" 'True) (C1 ('MetaCons "EntityID" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEntityId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data Query i o Source #

Query for matching entities.

Do notation:

move :: (ArrowQuery arr) => arr () Position
move = proc () -> do
  Velocity v <- Q.fetch -< ()
  Position p <- Q.fetch -< ()
  Q.set -< Position $ p + v

Arrow combinators:

move :: (ArrowQuery arr) => arr () Position
move = Q.fetch &&& Q.fetch >>> arr (\(Position p, Velocity v) -> Position $ p + v) >>> Q.set

Applicative combinators:

move :: (ArrowQuery arr) => arr () Position
move = (,) <$> Q.fetch <*> Q.fetch >>> arr (\(Position p, Velocity v) -> Position $ p + v) >>> Q.set

Instances

Instances details
ArrowQuery Query Source # 
Instance details

Defined in Aztecs.ECS.Query

Methods

set :: Component a => Query a a Source #

ArrowDynamicQuery Query Source # 
Instance details

Defined in Aztecs.ECS.Query

Methods

setDyn :: Component a => ComponentID -> Query a a Source #

ArrowDynamicQueryReader Query Source # 
Instance details

Defined in Aztecs.ECS.Query

ArrowQueryReader Query Source # 
Instance details

Defined in Aztecs.ECS.Query

Methods

fetch :: Component a => Query () a Source #

fetchMaybe :: Component a => Query () (Maybe a) Source #

Arrow Query Source # 
Instance details

Defined in Aztecs.ECS.Query

Methods

arr :: (b -> c) -> Query b c #

first :: Query b c -> Query (b, d) (c, d) #

second :: Query b c -> Query (d, b) (d, c) #

(***) :: Query b c -> Query b' c' -> Query (b, b') (c, c') #

(&&&) :: Query b c -> Query b c' -> Query b (c, c') #

ArrowChoice Query Source # 
Instance details

Defined in Aztecs.ECS.Query

Methods

left :: Query b c -> Query (Either b d) (Either c d) #

right :: Query b c -> Query (Either d b) (Either d c) #

(+++) :: Query b c -> Query b' c' -> Query (Either b b') (Either c c') #

(|||) :: Query b d -> Query c d -> Query (Either b c) d #

Category Query Source # 
Instance details

Defined in Aztecs.ECS.Query

Methods

id :: forall (a :: k). Query a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Query b c -> Query a b -> Query a c #

Monad m => ArrowSystem Query (SystemT m) Source # 
Instance details

Defined in Aztecs.ECS.System

Methods

map :: Query i a -> SystemT m i [a] Source #

map_ :: Query i o -> SystemT m i () Source #

filterMap :: Query i a -> QueryFilter -> SystemT m i [a] Source #

mapSingle :: Query i a -> SystemT m i a Source #

mapSingleMaybe :: Query i a -> SystemT m i (Maybe a) Source #

Applicative (Query i) Source # 
Instance details

Defined in Aztecs.ECS.Query

Methods

pure :: a -> Query i a #

(<*>) :: Query i (a -> b) -> Query i a -> Query i b #

liftA2 :: (a -> b -> c) -> Query i a -> Query i b -> Query i c #

(*>) :: Query i a -> Query i b -> Query i b #

(<*) :: Query i a -> Query i b -> Query i a #

Functor (Query i) Source # 
Instance details

Defined in Aztecs.ECS.Query

Methods

fmap :: (a -> b) -> Query i a -> Query i b #

(<$) :: a -> Query i b -> Query i a #

class Arrow arr => ArrowQueryReader arr Source #

Arrow for queries that can read from entities.

Minimal complete definition

fetch

Instances

Instances details
ArrowQueryReader Query Source # 
Instance details

Defined in Aztecs.ECS.Query

Methods

fetch :: Component a => Query () a Source #

fetchMaybe :: Component a => Query () (Maybe a) Source #

ArrowQueryReader QueryReader Source # 
Instance details

Defined in Aztecs.ECS.Query.Reader

class ArrowQueryReader arr => ArrowQuery arr Source #

Arrow for queries that can update entities.

Minimal complete definition

set

Instances

Instances details
ArrowQuery Query Source # 
Instance details

Defined in Aztecs.ECS.Query

Methods

set :: Component a => Query a a Source #

class ArrowDynamicQueryReader arr => ArrowDynamicQuery arr Source #

Minimal complete definition

setDyn

Instances

Instances details
ArrowDynamicQuery Query Source # 
Instance details

Defined in Aztecs.ECS.Query

Methods

setDyn :: Component a => ComponentID -> Query a a Source #

ArrowDynamicQuery DynamicQuery Source # 
Instance details

Defined in Aztecs.ECS.Query.Dynamic

with :: forall a. Component a => QueryFilter Source #

Filter for entities containing this component.

without :: forall a. Component a => QueryFilter Source #

Filter out entities containing this component.

class Arrow arr => ArrowReaderSystem q arr | arr -> q Source #

Minimal complete definition

all, filter

Instances

Instances details
Monad m => ArrowReaderSystem QueryReader (SystemT m) Source # 
Instance details

Defined in Aztecs.ECS.System

Methods

all :: QueryReader i a -> SystemT m i [a] Source #

filter :: QueryReader () a -> QueryFilter -> SystemT m () [a] Source #

single :: QueryReader i a -> SystemT m i a Source #

Monad m => ArrowReaderSystem QueryReader (ReaderSystemT m) Source # 
Instance details

Defined in Aztecs.ECS.System.Reader

class Arrow arr => ArrowSystem q arr | arr -> q Source #

Minimal complete definition

map, filterMap, mapSingle, mapSingleMaybe

Instances

Instances details
Monad m => ArrowSystem Query (SystemT m) Source # 
Instance details

Defined in Aztecs.ECS.System

Methods

map :: Query i a -> SystemT m i [a] Source #

map_ :: Query i o -> SystemT m i () Source #

filterMap :: Query i a -> QueryFilter -> SystemT m i [a] Source #

mapSingle :: Query i a -> SystemT m i a Source #

mapSingleMaybe :: Query i a -> SystemT m i (Maybe a) Source #

class (MonadAccess b m, Arrow arr) => ArrowQueueSystem b m arr | arr -> m Source #

Minimal complete definition

queue

Instances

Instances details
ArrowQueueSystem Bundle Access QueueSystem Source # 
Instance details

Defined in Aztecs.ECS.System.Queue

Methods

queue :: (i -> Access ()) -> QueueSystem i () Source #

Monad m => ArrowQueueSystem Bundle (AccessT m) (SystemT m) Source # 
Instance details

Defined in Aztecs.ECS.System

Methods

queue :: (i -> AccessT m ()) -> SystemT m i () Source #

Monad m => ArrowQueueSystem Bundle (AccessT m) (DynamicSystemT m) Source # 
Instance details

Defined in Aztecs.ECS.System.Dynamic

Methods

queue :: (i -> AccessT m ()) -> DynamicSystemT m i () Source #

Monad m => ArrowQueueSystem Bundle (AccessT m) (DynamicReaderSystemT m) Source # 
Instance details

Defined in Aztecs.ECS.System.Dynamic.Reader

Methods

queue :: (i -> AccessT m ()) -> DynamicReaderSystemT m i () Source #

Monad m => ArrowQueueSystem Bundle (AccessT m) (ReaderSystemT m) Source # 
Instance details

Defined in Aztecs.ECS.System.Reader

Methods

queue :: (i -> AccessT m ()) -> ReaderSystemT m i () Source #

class Arrow arr => ArrowReaderSchedule s arr | arr -> s Source #

Schedule arrow that runs read-only systems.

Minimal complete definition

reader

Instances

Instances details
Monad m => ArrowReaderSchedule (ReaderSystemT m) (Schedule m) Source # 
Instance details

Defined in Aztecs.ECS.Schedule

Methods

reader :: ReaderSystemT m i o -> Schedule m i o Source #

class Arrow arr => ArrowSchedule s arr | arr -> s Source #

Schedule arrow that runs systems.

Minimal complete definition

system

Instances

Instances details
Monad m => ArrowSchedule (SystemT m) (Schedule m) Source # 
Instance details

Defined in Aztecs.ECS.Schedule

Methods

system :: SystemT m i o -> Schedule m i o Source #

class (MonadAccess b m, Arrow arr) => ArrowAccessSchedule b m arr | arr -> m Source #

Schedule arrow that provides access to a World.

Minimal complete definition

access

Instances

Instances details
Monad m => ArrowAccessSchedule Bundle (AccessT m) (Schedule m) Source # 
Instance details

Defined in Aztecs.ECS.Schedule

Methods

access :: (i -> AccessT m o) -> Schedule m i o Source #

Monad m => ArrowAccessSchedule Bundle (AccessT m) (AcessSchedule m) Source # 
Instance details

Defined in Aztecs.ECS.Schedule.Access

Methods

access :: (i -> AccessT m o) -> AcessSchedule m i o Source #

reader :: ArrowReaderSchedule s arr => s i o -> arr i o Source #

Schedule a reader system.

system :: ArrowSchedule s arr => s i o -> arr i o Source #

Schedule a system.

delay :: Monad m => a -> Schedule m a a Source #

forever :: Schedule IO i o -> (o -> IO ()) -> Schedule IO i () Source #

access :: ArrowAccessSchedule b m arr => (i -> m o) -> arr i o Source #

Access the World.

runSchedule :: Monad m => Schedule m i o -> World -> i -> m (o, DynamicSchedule m i o, World) Source #

runSchedule_ :: Monad m => Schedule m () () -> m () Source #

data World Source #

World of entities and their components.

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.8.0-5YWGoxTs0Vw9iciqZAe9GO" 'False) (C1 ('MetaCons "World" 'PrefixI 'True) (S1 ('MetaSel ('Just "entities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Entities) :*: S1 ('MetaSel ('Just "nextEntityId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EntityID)))