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

Aztecs.ECS.Query

Synopsis

Queries

newtype 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

Constructors

Query 

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 where Source #

Arrow for queries that can read from entities.

Minimal complete definition

fetch

Methods

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

Fetch a Component by its type.

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

Fetch a Component by its type, returning Nothing if it doesn't exist.

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 where Source #

Arrow for queries that can update entities.

Methods

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

Set a Component by its type.

Instances

Instances details
ArrowQuery Query Source # 
Instance details

Defined in Aztecs.ECS.Query

Methods

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

class Arrow arr => ArrowDynamicQueryReader arr where Source #

Minimal complete definition

entity, fetchDyn

Methods

entity :: arr () EntityID Source #

Fetch the currently matched EntityID.

fetchDyn :: Component a => ComponentID -> arr () a Source #

Fetch a Component by its ComponentID.

fetchMaybeDyn :: Component a => ComponentID -> arr () (Maybe a) Source #

Try to fetch a Component by its ComponentID.

class ArrowDynamicQueryReader arr => ArrowDynamicQuery arr where Source #

Methods

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

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

Running

all :: i -> Query i a -> Entities -> ([a], Entities) Source #

Match all entities.

map :: i -> Query i a -> Entities -> ([a], Entities) Source #

Map all matched entities.

Conversion

Filters

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.

Reads and writes

data ReadsWrites Source #

Reads and writes of a Query.

Constructors

ReadsWrites 

Fields

disjoint :: ReadsWrites -> ReadsWrites -> Bool Source #

True if the reads and writes of two Querys overlap.