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.
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
- type Access = AccessT Identity
- runAccessT :: Functor m => AccessT m a -> World -> m (a, World)
- data Bundle
- class Monoid a => MonoidBundle a where
- data DynamicBundle
- class MonoidDynamicBundle a where
- dynBundle :: Component c => ComponentID -> c -> a
- class (Typeable a, Storage a (StorageT a)) => Component a where
- data EntityID
- data Query i o
- class Arrow arr => ArrowQueryReader arr
- class ArrowQueryReader arr => ArrowQuery arr
- class Arrow arr => ArrowDynamicQueryReader arr
- class ArrowDynamicQueryReader arr => ArrowDynamicQuery arr
- data QueryFilter
- with :: forall a. Component a => QueryFilter
- without :: forall a. Component a => QueryFilter
- type System = SystemT Identity
- class Arrow arr => ArrowReaderSystem q arr | arr -> q
- class Arrow arr => ArrowSystem q arr | arr -> q
- class (MonadAccess b m, Arrow arr) => ArrowQueueSystem b m arr | arr -> m
- type Schedule m = ScheduleT (AccessT m)
- class Arrow arr => ArrowReaderSchedule s arr | arr -> s
- class Arrow arr => ArrowSchedule s arr | arr -> s
- class (MonadAccess b m, Arrow arr) => ArrowAccessSchedule b m arr | arr -> m
- reader :: ArrowReaderSchedule s arr => s i o -> arr i o
- system :: ArrowSchedule s arr => s i o -> arr i o
- delay :: Monad m => a -> Schedule m a a
- forever :: Schedule IO i o -> (o -> IO ()) -> Schedule IO i ()
- forever_ :: Schedule IO i o -> Schedule IO i ()
- access :: ArrowAccessSchedule b m arr => (i -> m o) -> arr i o
- runSchedule :: Monad m => Schedule m i o -> World -> i -> m (o, DynamicSchedule m i o, World)
- runSchedule_ :: Monad m => Schedule m () () -> m ()
- data World
Documentation
Bundle of components.
Instances
class Monoid a => MonoidBundle a where Source #
Monoid bundle of components.
Instances
data DynamicBundle Source #
Dynamic bundle of components.
Instances
MonoidDynamicBundle DynamicBundle Source # | |
Defined in Aztecs.ECS.World.Bundle.Dynamic Methods dynBundle :: Component c => ComponentID -> c -> DynamicBundle Source # | |
Monoid DynamicBundle Source # | |
Defined in Aztecs.ECS.World.Bundle.Dynamic Methods mempty :: DynamicBundle # mappend :: DynamicBundle -> DynamicBundle -> DynamicBundle # mconcat :: [DynamicBundle] -> DynamicBundle # | |
Semigroup DynamicBundle Source # | |
Defined in Aztecs.ECS.World.Bundle.Dynamic Methods (<>) :: DynamicBundle -> DynamicBundle -> DynamicBundle # sconcat :: NonEmpty DynamicBundle -> DynamicBundle # stimes :: Integral b => b -> DynamicBundle -> DynamicBundle # |
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
MonoidDynamicBundle Bundle Source # | |
Defined in Aztecs.ECS.World.Bundle | |
MonoidDynamicBundle DynamicBundle Source # | |
Defined in Aztecs.ECS.World.Bundle.Dynamic Methods dynBundle :: Component c => ComponentID -> c -> DynamicBundle Source # |
class (Typeable a, Storage a (StorageT a)) => Component a Source #
Component that can be stored in the World
.
Instances
Entity ID.
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
ArrowQuery Query Source # | |
ArrowDynamicQuery Query Source # | |
Defined in Aztecs.ECS.Query | |
ArrowDynamicQueryReader Query Source # | |
Defined in Aztecs.ECS.Query | |
ArrowQueryReader Query Source # | |
Arrow Query Source # | |
ArrowChoice Query Source # | |
Category Query Source # | |
Monad m => ArrowSystem Query (SystemT m) Source # | |
Applicative (Query i) Source # | |
Functor (Query i) Source # | |
class Arrow arr => ArrowQueryReader arr Source #
Arrow for queries that can read from entities.
Minimal complete definition
Instances
ArrowQueryReader Query Source # | |
ArrowQueryReader QueryReader Source # | |
Defined in Aztecs.ECS.Query.Reader Methods fetch :: Component a => QueryReader () a Source # fetchMaybe :: Component a => QueryReader () (Maybe a) Source # |
class ArrowQueryReader arr => ArrowQuery arr Source #
Arrow for queries that can update entities.
Minimal complete definition
Instances
class Arrow arr => ArrowDynamicQueryReader arr Source #
Instances
ArrowDynamicQueryReader Query Source # | |
Defined in Aztecs.ECS.Query | |
ArrowDynamicQueryReader DynamicQuery Source # | |
Defined in Aztecs.ECS.Query.Dynamic Methods entity :: DynamicQuery () EntityID Source # fetchDyn :: Component a => ComponentID -> DynamicQuery () a Source # fetchMaybeDyn :: Component a => ComponentID -> DynamicQuery () (Maybe a) Source # | |
ArrowDynamicQueryReader DynamicQueryReader Source # | |
Defined in Aztecs.ECS.Query.Dynamic.Reader Methods entity :: DynamicQueryReader () EntityID Source # fetchDyn :: Component a => ComponentID -> DynamicQueryReader () a Source # fetchMaybeDyn :: Component a => ComponentID -> DynamicQueryReader () (Maybe a) Source # | |
ArrowDynamicQueryReader QueryReader Source # | |
Defined in Aztecs.ECS.Query.Reader Methods entity :: QueryReader () EntityID Source # fetchDyn :: Component a => ComponentID -> QueryReader () a Source # fetchMaybeDyn :: Component a => ComponentID -> QueryReader () (Maybe a) Source # |
class ArrowDynamicQueryReader arr => ArrowDynamicQuery arr Source #
Minimal complete definition
Instances
ArrowDynamicQuery Query Source # | |
Defined in Aztecs.ECS.Query | |
ArrowDynamicQuery DynamicQuery Source # | |
Defined in Aztecs.ECS.Query.Dynamic Methods setDyn :: Component a => ComponentID -> DynamicQuery a a Source # |
data QueryFilter Source #
Filter for a Query
.
Instances
Monoid QueryFilter Source # | |
Defined in Aztecs.ECS.Query.Reader Methods mempty :: QueryFilter # mappend :: QueryFilter -> QueryFilter -> QueryFilter # mconcat :: [QueryFilter] -> QueryFilter # | |
Semigroup QueryFilter Source # | |
Defined in Aztecs.ECS.Query.Reader Methods (<>) :: QueryFilter -> QueryFilter -> QueryFilter # sconcat :: NonEmpty QueryFilter -> QueryFilter # stimes :: Integral b => b -> QueryFilter -> QueryFilter # |
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 #
Instances
Monad m => ArrowReaderSystem QueryReader (SystemT m) Source # | |
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 # | |
Defined in Aztecs.ECS.System.Reader Methods all :: QueryReader i a -> ReaderSystemT m i [a] Source # filter :: QueryReader () a -> QueryFilter -> ReaderSystemT m () [a] Source # single :: QueryReader i a -> ReaderSystemT m i a Source # |
class Arrow arr => ArrowSystem q arr | arr -> q Source #
Minimal complete definition
class (MonadAccess b m, Arrow arr) => ArrowQueueSystem b m arr | arr -> m Source #
Minimal complete definition
Instances
ArrowQueueSystem Bundle Access QueueSystem Source # | |
Defined in Aztecs.ECS.System.Queue Methods queue :: (i -> Access ()) -> QueueSystem i () Source # | |
Monad m => ArrowQueueSystem Bundle (AccessT m) (SystemT m) Source # | |
Monad m => ArrowQueueSystem Bundle (AccessT m) (DynamicSystemT m) Source # | |
Defined in Aztecs.ECS.System.Dynamic Methods queue :: (i -> AccessT m ()) -> DynamicSystemT m i () Source # | |
Monad m => ArrowQueueSystem Bundle (AccessT m) (DynamicReaderSystemT m) Source # | |
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 # | |
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
Instances
Monad m => ArrowReaderSchedule (ReaderSystemT m) (Schedule m) Source # | |
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
class (MonadAccess b m, Arrow arr) => ArrowAccessSchedule b m arr | arr -> m Source #
Schedule arrow that provides access to a World
.
Minimal complete definition
Instances
Monad m => ArrowAccessSchedule Bundle (AccessT m) (Schedule m) Source # | |
Monad m => ArrowAccessSchedule Bundle (AccessT m) (AcessSchedule m) Source # | |
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.
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 #
World of entities and their components.
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.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))) |