apecs-0.9.6: Fast Entity-Component-System library for game programming
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Apecs.Experimental.Reactive

Description

This module is experimental, and its API might change between point releases. Use at your own risk.

Adds the Reactive r s store, which when wrapped around store s, will call the react on its r.

Show c => Reactive (Printer c) (Map c) will print a message every time a c value is set.

Enum c => Reactive (EnumMap c) (Map c) allows you to look up entities by component value. Use e.g. withReactive $ enumLookup True to retrieve a list of entities that have a True component.

Reactive (ComponentCounter c) (Map c) tracks the current and max counts of entities with a particular component. Among other things, the max count can be useful in deciding on Cache sizing and the current count can be useful for debugging entity lifecycles. To retrieve the counts, use withReactive readComponentCount.

Synopsis

Documentation

class Monad m => Reacts m r where Source #

Class required by Reactive. Given some r and update information about some component, will run a side-effect in monad m. Note that there are also instances for (,).

Methods

rempty :: m r Source #

react :: Entity -> Maybe (Elem r) -> Maybe (Elem r) -> r -> m () Source #

Instances

Instances details
MonadIO m => Reacts m (ComponentCounter c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

(MonadIO m, Enum c) => Reacts m (EnumMap c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Methods

rempty :: m (EnumMap c) Source #

react :: Entity -> Maybe (Elem (EnumMap c)) -> Maybe (Elem (EnumMap c)) -> EnumMap c -> m () Source #

(MonadIO m, Ix c, Bounded c) => Reacts m (IxMap c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Methods

rempty :: m (IxMap c) Source #

react :: Entity -> Maybe (Elem (IxMap c)) -> Maybe (Elem (IxMap c)) -> IxMap c -> m () Source #

(MonadIO m, Ord c) => Reacts m (OrdMap c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Methods

rempty :: m (OrdMap c) Source #

react :: Entity -> Maybe (Elem (OrdMap c)) -> Maybe (Elem (OrdMap c)) -> OrdMap c -> m () Source #

(MonadIO m, Show c) => Reacts m (Printer c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Methods

rempty :: m (Printer c) Source #

react :: Entity -> Maybe (Elem (Printer c)) -> Maybe (Elem (Printer c)) -> Printer c -> m () Source #

data Reactive r s Source #

Wrapper for reactivity around some store s.

Instances

Instances details
(Reacts m r, ExplDestroy m s, ExplGet m s, Elem s ~ Elem r) => ExplDestroy m (Reactive r s) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Methods

explDestroy :: Reactive r s -> Int -> m () Source #

ExplGet m s => ExplGet m (Reactive r s) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Methods

explGet :: Reactive r s -> Int -> m (Elem (Reactive r s)) Source #

explExists :: Reactive r s -> Int -> m Bool Source #

(Reacts m r, ExplInit m s) => ExplInit m (Reactive r s) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Methods

explInit :: m (Reactive r s) Source #

ExplMembers m s => ExplMembers m (Reactive r s) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Methods

explMembers :: Reactive r s -> m (Vector Int) Source #

(Reacts m r, ExplSet m s, ExplGet m s, Elem s ~ Elem r) => ExplSet m (Reactive r s) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Methods

explSet :: Reactive r s -> Int -> Elem (Reactive r s) -> m () Source #

type Elem (Reactive r s) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

type Elem (Reactive r s) = Elem s

withReactive :: forall w m r s a. (Component (Elem r), Has w m (Elem r), Storage (Elem r) ~ Reactive r s) => (r -> m a) -> SystemT w m a Source #

Performs an action with a reactive state token.

data Printer c Source #

Prints a message to stdout every time a component is updated.

Instances

Instances details
(MonadIO m, Show c) => Reacts m (Printer c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Methods

rempty :: m (Printer c) Source #

react :: Entity -> Maybe (Elem (Printer c)) -> Maybe (Elem (Printer c)) -> Printer c -> m () Source #

type Elem (Printer c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

type Elem (Printer c) = c

data EnumMap c Source #

Allows you to look up entities by component value. Use e.g. withReactive $ enumLookup True to retrieve a list of entities that have a True component. Based on an IntMap IntSet internally.

Instances

Instances details
(MonadIO m, Enum c) => Reacts m (EnumMap c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Methods

rempty :: m (EnumMap c) Source #

react :: Entity -> Maybe (Elem (EnumMap c)) -> Maybe (Elem (EnumMap c)) -> EnumMap c -> m () Source #

type Elem (EnumMap c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

type Elem (EnumMap c) = c

enumLookup :: (MonadIO m, Enum c) => c -> EnumMap c -> m [Entity] Source #

data OrdMap c Source #

Allows you to look up entities by component value. Based on a Map c IntSet internally

Instances

Instances details
(MonadIO m, Ord c) => Reacts m (OrdMap c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Methods

rempty :: m (OrdMap c) Source #

react :: Entity -> Maybe (Elem (OrdMap c)) -> Maybe (Elem (OrdMap c)) -> OrdMap c -> m () Source #

type Elem (OrdMap c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

type Elem (OrdMap c) = c

ordLookup :: (MonadIO m, Ord c) => c -> OrdMap c -> m [Entity] Source #

data IxMap c Source #

Allows you to look up entities by component value. Based on an IOArray c IntSet internally

Instances

Instances details
(MonadIO m, Ix c, Bounded c) => Reacts m (IxMap c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Methods

rempty :: m (IxMap c) Source #

react :: Entity -> Maybe (Elem (IxMap c)) -> Maybe (Elem (IxMap c)) -> IxMap c -> m () Source #

type Elem (IxMap c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

type Elem (IxMap c) = c

ixLookup :: (MonadIO m, Ix c) => c -> IxMap c -> m [Entity] Source #

data ComponentCounter c Source #

Tracks current and max counts of entities with a particular Component.

Note that if this is used in conjunction with a Global store, produced counts will always be 0.

Instances

Instances details
MonadIO m => Reacts m (ComponentCounter c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

type Elem (ComponentCounter c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

type Elem (ComponentCounter c) = c

data ComponentCount c Source #

A snapshot of the current and max counts of entities with a particular Component.

Produced via readComponentCount.

Constructors

ComponentCount 

Fields

  • componentCountCurrent :: !Int

    Represents how many entities existed with the Component assigned at the time the snapshot was produced.

  • componentCountMax :: !Int

    Represents the max number of entities with the Component assigned that coexisted, as observed at any point between system initialization and the time the snapshot was produced.

Instances

Instances details
Show (ComponentCount c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive

Eq (ComponentCount c) Source # 
Instance details

Defined in Apecs.Experimental.Reactive