Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module re-exports the apecs prelude with STM versions.
Synopsis
- type System w a = SystemT w STM a
- module Apecs.STM
- makeWorld :: String -> [Name] -> Q [Dec]
- runGC :: System w ()
- newEntity_ :: forall (m :: Type -> Type) world component. (MonadIO m, Set world m component, Get world m EntityCounter) => component -> SystemT world m ()
- newEntity :: forall (m :: Type -> Type) w c. (MonadIO m, Set w m c, Get w m EntityCounter) => c -> SystemT w m Entity
- global :: Entity
- data EntityCounter
- collect :: forall components w (m :: Type -> Type) a. (Get w m components, Members w m components) => (components -> Maybe a) -> SystemT w m [a]
- cfoldM_ :: forall w (m :: Type -> Type) c a. (Members w m c, Get w m c) => (a -> c -> SystemT w m a) -> a -> SystemT w m ()
- cfoldM :: forall w (m :: Type -> Type) c a. (Members w m c, Get w m c) => (a -> c -> SystemT w m a) -> a -> SystemT w m a
- cfold :: forall w (m :: Type -> Type) c a. (Members w m c, Get w m c) => (a -> c -> a) -> a -> SystemT w m a
- cmapM_ :: forall w (m :: Type -> Type) c. (Get w m c, Members w m c) => (c -> SystemT w m ()) -> SystemT w m ()
- cmapM :: forall w (m :: Type -> Type) cx cy. (Get w m cx, Set w m cy, Members w m cx) => (cx -> SystemT w m cy) -> SystemT w m ()
- cmap :: forall w (m :: Type -> Type) cx cy. (Get w m cx, Members w m cx, Set w m cy) => (cx -> cy) -> SystemT w m ()
- ($~) :: forall w (m :: Type -> Type) cx cy. (Get w m cx, Set w m cy) => Entity -> (cx -> cy) -> SystemT w m ()
- modify :: forall w (m :: Type -> Type) cx cy. (Get w m cx, Set w m cy) => Entity -> (cx -> cy) -> SystemT w m ()
- destroy :: forall w (m :: Type -> Type) c. Destroy w m c => Entity -> Proxy c -> SystemT w m ()
- exists :: forall w (m :: Type -> Type) c. Get w m c => Entity -> Proxy c -> SystemT w m Bool
- ($=) :: forall w (m :: Type -> Type) c. Set w m c => Entity -> c -> SystemT w m ()
- set :: forall w (m :: Type -> Type) c. Set w m c => Entity -> c -> SystemT w m ()
- get :: forall w (m :: Type -> Type) c. Get w m c => Entity -> SystemT w m c
- runWith :: w -> SystemT w m a -> m a
- runSystem :: SystemT w m a -> w -> m a
- data Not a = Not
- data Cache (n :: Nat) s
- newtype Entity = Entity {}
- newtype SystemT w (m :: Type -> Type) a = SystemT {}
- type family Storage c
- class Elem (Storage c) ~ c => Component c where
- type Storage c
- class (Monad m, Component c) => Has w (m :: Type -> Type) c where
- explInit :: ExplInit m s => m s
- type Get w (m :: Type -> Type) c = (Has w m c, ExplGet m (Storage c))
- type Set w (m :: Type -> Type) c = (Has w m c, ExplSet m (Storage c))
- type Members w (m :: Type -> Type) c = (Has w m c, ExplMembers m (Storage c))
- type Destroy w (m :: Type -> Type) c = (Has w m c, ExplDestroy m (Storage c))
- asks :: MonadReader r m => (r -> a) -> m a
- data Proxy (t :: k) = Proxy
- liftIO :: MonadIO m => IO a -> m a
- lift :: (MonadTrans t, Monad m) => m a -> t m a
- ask :: MonadReader r m => m r
Documentation
module Apecs.STM
makeWorld :: String -> [Name] -> Q [Dec] #
The typical way to create a world
record, associated Has
instances, and initialization function.
makeWorld "MyWorld" [''Component1, ''Component2, ...]
turns into
data MyWorld = MyWorld Component1 Component2 ... EntityCounter instance MyWorld `Has` Component1 where ... instance MyWorld `Has` Component2 where ... ... instance MyWorld `Has` EntityCounter where ... initMyWorld :: IO MyWorld initMyWorld = MyWorld <$> initStore <*> initStore <*> ... <*> initStore
newEntity_ :: forall (m :: Type -> Type) world component. (MonadIO m, Set world m component, Get world m EntityCounter) => component -> SystemT world m () #
Writes the given components to a new entity without yelding the result. Used mostly for convenience.
newEntity :: forall (m :: Type -> Type) w c. (MonadIO m, Set w m c, Get w m EntityCounter) => c -> SystemT w m Entity #
Writes the given components to a new entity, and yields that entity. The return value is often ignored.
Convenience entity, for use in places where the entity value does not matter, i.e. a global store.
data EntityCounter #
Component used by newEntity to track the number of issued entities.
Automatically added to any world created with makeWorld
Instances
Component EntityCounter | |
Defined in Apecs.Util type Storage EntityCounter # | |
Monoid EntityCounter | |
Defined in Apecs.Util mempty :: EntityCounter # mappend :: EntityCounter -> EntityCounter -> EntityCounter # mconcat :: [EntityCounter] -> EntityCounter # | |
Semigroup EntityCounter | |
Defined in Apecs.Util (<>) :: EntityCounter -> EntityCounter -> EntityCounter # sconcat :: NonEmpty EntityCounter -> EntityCounter # stimes :: Integral b => b -> EntityCounter -> EntityCounter # | |
Show EntityCounter | |
Defined in Apecs.Util showsPrec :: Int -> EntityCounter -> ShowS # show :: EntityCounter -> String # showList :: [EntityCounter] -> ShowS # | |
Eq EntityCounter | |
Defined in Apecs.Util (==) :: EntityCounter -> EntityCounter -> Bool # (/=) :: EntityCounter -> EntityCounter -> Bool # | |
type Storage EntityCounter | |
Defined in Apecs.Util |
collect :: forall components w (m :: Type -> Type) a. (Get w m components, Members w m components) => (components -> Maybe a) -> SystemT w m [a] #
Collect matching components into a list by using the specified test/process function. You can use this to preprocess data before returning. And you can do a test here that depends on data from multiple components. Pass Just to simply collect all the items.
cfoldM_ :: forall w (m :: Type -> Type) c a. (Members w m c, Get w m c) => (a -> c -> SystemT w m a) -> a -> SystemT w m () #
Monadically fold over the game world. Strict in the accumulator.
cfoldM :: forall w (m :: Type -> Type) c a. (Members w m c, Get w m c) => (a -> c -> SystemT w m a) -> a -> SystemT w m a #
Monadically fold over the game world. Strict in the accumulator.
cfold :: forall w (m :: Type -> Type) c a. (Members w m c, Get w m c) => (a -> c -> a) -> a -> SystemT w m a #
Fold over the game world; for example, cfold max (minBound :: Foo)
will find the maximum value of Foo
.
Strict in the accumulator.
cmapM_ :: forall w (m :: Type -> Type) c. (Get w m c, Members w m c) => (c -> SystemT w m ()) -> SystemT w m () #
Monadically iterates over all entites with a cx
cmapM :: forall w (m :: Type -> Type) cx cy. (Get w m cx, Set w m cy, Members w m cx) => (cx -> SystemT w m cy) -> SystemT w m () #
Monadically iterates over all entites with a cx
, and writes their cy
.
cmap :: forall w (m :: Type -> Type) cx cy. (Get w m cx, Members w m cx, Set w m cy) => (cx -> cy) -> SystemT w m () #
Maps a function over all entities with a cx
, and writes their cy
.
($~) :: forall w (m :: Type -> Type) cx cy. (Get w m cx, Set w m cy) => Entity -> (cx -> cy) -> SystemT w m () infixr 2 #
modify
operator
Applies a function, if possible.
modify :: forall w (m :: Type -> Type) cx cy. (Get w m cx, Set w m cy) => Entity -> (cx -> cy) -> SystemT w m () #
Applies a function, if possible.
destroy :: forall w (m :: Type -> Type) c. Destroy w m c => Entity -> Proxy c -> SystemT w m () #
Destroys component c
for the given entity.
exists :: forall w (m :: Type -> Type) c. Get w m c => Entity -> Proxy c -> SystemT w m Bool #
Returns whether the given entity has component c
($=) :: forall w (m :: Type -> Type) c. Set w m c => Entity -> c -> SystemT w m () infixr 2 #
set
operator
Writes a Component to a given Entity. Will overwrite existing Components.
set :: forall w (m :: Type -> Type) c. Set w m c => Entity -> c -> SystemT w m () #
Writes a Component to a given Entity. Will overwrite existing Components.
Pseudocomponent indicating the absence of a
.
Mainly used as e.g. cmap $ (a, Not b) -> c
to iterate over entities with an a
but no b
.
Can also be used to delete components, like cmap $ a -> (Not :: Not a)
to delete every a
component.
A cache around another store. Caches store their members in a fixed-size vector, so read/write operations become O(1). Caches can provide huge performance boosts, especially when working with large numbers of components.
The cache size is given as a type-level argument.
Note that iterating over a cache is linear in cache size, so sparsely populated caches might decrease performance. In general, the exact size of the cache does not matter as long as it reasonably approximates the number of components present.
The cache uses entity (-2) internally to represent missing entities. If you manually manipulate Entity values, be careful that you do not use (-2)
The actual cache is not necessarily the given argument, but the next biggest power of two. This is allows most operations to be expressed as bit masks, for a large potential performance boost.
Instances
(MonadIO m, ExplDestroy m s) => ExplDestroy m (Cache n s) | |
Defined in Apecs.Stores explDestroy :: Cache n s -> Int -> m () # | |
(MonadIO m, ExplGet m s) => ExplGet m (Cache n s) | |
(MonadIO m, ExplInit m s, KnownNat n, Cachable s) => ExplInit m (Cache n s) | |
Defined in Apecs.Stores | |
(MonadIO m, ExplMembers m s) => ExplMembers m (Cache n s) | |
Defined in Apecs.Stores explMembers :: Cache n s -> m (Vector Int) # | |
(MonadIO m, ExplSet m s) => ExplSet m (Cache n s) | |
(KnownNat n, Cachable s) => Cachable (Cache n s) | |
Defined in Apecs.Stores | |
type Elem (Cache n s) | |
Defined in Apecs.Stores |
An Entity is just an integer, used to index into a component store.
In general, use newEntity
, cmap
, and component tags instead of manipulating these directly.
For performance reasons, negative values like (-1) are reserved for stores to represent special values, so avoid using these.
newtype SystemT w (m :: Type -> Type) a #
A SystemT is a newtype around `ReaderT w m a`, where w
is the game world variable.
Systems serve to
- Allow type-based lookup of a component's store through
getStore
. - Lift side effects into their host Monad.
Instances
Monad m => MonadReader w (SystemT w m) | |
MonadTrans (SystemT w) | |
Defined in Apecs.Core | |
MonadIO m => MonadIO (SystemT w m) | |
Defined in Apecs.Core | |
Applicative m => Applicative (SystemT w m) | |
Defined in Apecs.Core | |
Functor m => Functor (SystemT w m) | |
Monad m => Monad (SystemT w m) | |
MonadCatch m => MonadCatch (SystemT w m) | |
MonadMask m => MonadMask (SystemT w m) | |
Defined in Apecs.Core mask :: ((forall a. SystemT w m a -> SystemT w m a) -> SystemT w m b) -> SystemT w m b # uninterruptibleMask :: ((forall a. SystemT w m a -> SystemT w m a) -> SystemT w m b) -> SystemT w m b # generalBracket :: SystemT w m a -> (a -> ExitCase b -> SystemT w m c) -> (a -> SystemT w m b) -> SystemT w m (b, c) # | |
MonadThrow m => MonadThrow (SystemT w m) | |
Defined in Apecs.Core |
Instances
type Storage Entity | |
Defined in Apecs.Components | |
type Storage EntityCounter | |
Defined in Apecs.Util | |
type Storage () | |
Defined in Apecs.Components type Storage () = () | |
type Storage (Filter c) | |
Defined in Apecs.Components | |
type Storage (Not c) | |
Defined in Apecs.Components | |
type Storage (Identity c) | |
Defined in Apecs.Components | |
type Storage (Maybe c) | |
Defined in Apecs.Components | |
type Storage (Either ca cb) | |
Defined in Apecs.Components | |
type Storage (t_0, t_1) | |
Defined in Apecs.Components | |
type Storage (t_0, t_1, t_2) | |
Defined in Apecs.Components | |
type Storage (t_0, t_1, t_2, t_3) | |
type Storage (t_0, t_1, t_2, t_3, t_4) | |
type Storage (t_0, t_1, t_2, t_3, t_4, t_5) | |
type Storage (t_0, t_1, t_2, t_3, t_4, t_5, t_6) | |
type Storage (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) | |
class Elem (Storage c) ~ c => Component c #
A component is defined by specifying how it is stored. The constraint ensures that stores and components are mapped one-to-one.
Instances
Component EntityCounter | |
Defined in Apecs.Util type Storage EntityCounter # | |
Component c => Component (Filter c) | |
Defined in Apecs.Components | |
Component c => Component (Not c) | |
Defined in Apecs.Components |
class (Monad m, Component c) => Has w (m :: Type -> Type) c where #
Has w m c
means that world w
can produce a Storage c
.
It is parameterized over m
to allow stores to be foreign.
:: MonadReader r m | |
=> (r -> a) | The selector function to apply to the environment. |
-> m a |
Retrieves a function of the current environment.
Proxy
is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically,
is a safer alternative to the
Proxy
:: Proxy
a
idiom.undefined
:: a
>>>
Proxy :: Proxy (Void, Int -> Int)
Proxy
Proxy can even hold types of higher kinds,
>>>
Proxy :: Proxy Either
Proxy
>>>
Proxy :: Proxy Functor
Proxy
>>>
Proxy :: Proxy complicatedStructure
Proxy
Instances
Generic1 (Proxy :: k -> Type) | |
Foldable (Proxy :: TYPE LiftedRep -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldMap' :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Hashable1 (Proxy :: Type -> Type) | |
Defined in Data.Hashable.Class | |
Monoid (Proxy s) | Since: base-4.7.0.0 |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Bounded (Proxy t) | Since: base-4.7.0.0 |
Enum (Proxy s) | Since: base-4.7.0.0 |
Generic (Proxy t) | |
Ix (Proxy s) | Since: base-4.7.0.0 |
Defined in Data.Proxy | |
Read (Proxy t) | Since: base-4.7.0.0 |
Show (Proxy s) | Since: base-4.7.0.0 |
Eq (Proxy s) | Since: base-4.7.0.0 |
Ord (Proxy s) | Since: base-4.7.0.0 |
Hashable (Proxy a) | |
Defined in Data.Hashable.Class | |
type Rep1 (Proxy :: k -> Type) | Since: base-4.6.0.0 |
type Rep (Proxy t) | Since: base-4.6.0.0 |
liftIO :: MonadIO m => IO a -> m a #
Lift a computation from the IO
monad.
This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
(i.e. IO
is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted
, we would have ended up with this error:liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO ()
and
.IO
()
Luckily, we know of a function that takes an
and returns an IO
a(m a)
:
,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
lift :: (MonadTrans t, Monad m) => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
ask :: MonadReader r m => m r #
Retrieves the monad environment.