| Stability | experimental |
|---|---|
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
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
- class Monad m => Reacts m r where
- data Reactive r 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
- data Printer c
- data EnumMap c
- enumLookup :: (MonadIO m, Enum c) => c -> EnumMap c -> m [Entity]
- data OrdMap c
- ordLookup :: (MonadIO m, Ord c) => c -> OrdMap c -> m [Entity]
- data IxMap c
- ixLookup :: (MonadIO m, Ix c) => c -> IxMap c -> m [Entity]
- data ComponentCounter c
- readComponentCount :: forall c m. MonadIO m => ComponentCounter c -> m (ComponentCount c)
- data ComponentCount c = ComponentCount {}
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 (,).
Instances
| MonadIO m => Reacts m (ComponentCounter c) Source # | |
Defined in Apecs.Experimental.Reactive Methods rempty :: m (ComponentCounter c) Source # react :: Entity -> Maybe (Elem (ComponentCounter c)) -> Maybe (Elem (ComponentCounter c)) -> ComponentCounter c -> m () Source # | |
| (MonadIO m, Enum c) => Reacts m (EnumMap c) Source # | |
| (MonadIO m, Ix c, Bounded c) => Reacts m (IxMap c) Source # | |
| (MonadIO m, Ord c) => Reacts m (OrdMap c) Source # | |
| (MonadIO m, Show c) => Reacts m (Printer c) Source # | |
Wrapper for reactivity around some store s.
Instances
| (Reacts m r, ExplDestroy m s, ExplGet m s, Elem s ~ Elem r) => ExplDestroy m (Reactive r s) Source # | |
Defined in Apecs.Experimental.Reactive Methods explDestroy :: Reactive r s -> Int -> m () Source # | |
| ExplGet m s => ExplGet m (Reactive r s) Source # | |
| (Reacts m r, ExplInit m s) => ExplInit m (Reactive r s) Source # | |
Defined in Apecs.Experimental.Reactive | |
| ExplMembers m s => ExplMembers m (Reactive r s) Source # | |
Defined in Apecs.Experimental.Reactive | |
| (Reacts m r, ExplSet m s, ExplGet m s, Elem s ~ Elem r) => ExplSet m (Reactive r s) Source # | |
| type Elem (Reactive r s) Source # | |
Defined in Apecs.Experimental.Reactive | |
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.
Prints a message to stdout every time a component is updated.
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.
Allows you to look up entities by component value.
Based on a Map c IntSet internally
Allows you to look up entities by component value.
Based on an IOArray c IntSet internally
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
| MonadIO m => Reacts m (ComponentCounter c) Source # | |
Defined in Apecs.Experimental.Reactive Methods rempty :: m (ComponentCounter c) Source # react :: Entity -> Maybe (Elem (ComponentCounter c)) -> Maybe (Elem (ComponentCounter c)) -> ComponentCounter c -> m () Source # | |
| type Elem (ComponentCounter c) Source # | |
Defined in Apecs.Experimental.Reactive | |
readComponentCount :: forall c m. MonadIO m => ComponentCounter c -> m (ComponentCount c) Source #
data ComponentCount c Source #
A snapshot of the current and max counts of entities with a particular
Component.
Produced via readComponentCount.
Constructors
| ComponentCount | |
Fields
| |
Instances
| Show (ComponentCount c) Source # | |
Defined in Apecs.Experimental.Reactive Methods showsPrec :: Int -> ComponentCount c -> ShowS # show :: ComponentCount c -> String # showList :: [ComponentCount c] -> ShowS # | |
| Eq (ComponentCount c) Source # | |
Defined in Apecs.Experimental.Reactive Methods (==) :: ComponentCount c -> ComponentCount c -> Bool # (/=) :: ComponentCount c -> ComponentCount c -> Bool # | |