Safe Haskell | None |
---|---|
Language | Haskell2010 |
Apecs
Description
This module forms the apecs Prelude. It selectively re-exports the user-facing functions from the submodules.
Synopsis
- newtype SystemT w m a = SystemT {}
- type System w a = SystemT w IO a
- class Elem (Storage c) ~ c => Component c where
- type Storage c
- newtype Entity = Entity {}
- class (Monad m, Component c) => Has w m c where
- data Not a = Not
- type Get w m c = (Has w m c, ExplGet m (Storage c))
- type Set w m c = (Has w m c, ExplSet m (Storage c))
- type Destroy w m c = (Has w m c, ExplDestroy m (Storage c))
- type Members w m c = (Has w m c, ExplMembers m (Storage c))
- data Map c
- data Unique c
- data Global c
- data Cache (n :: Nat) s
- explInit :: ExplInit m s => m s
- get :: forall w m c. Get w m c => Entity -> SystemT w m c
- set :: forall w m c. Set w m c => Entity -> c -> SystemT w m ()
- ($=) :: forall w m c. Set w m c => Entity -> c -> SystemT w m ()
- destroy :: forall w m c. Destroy w m c => Entity -> Proxy c -> SystemT w m ()
- exists :: forall w m c. Get w m c => Entity -> Proxy c -> SystemT w m Bool
- modify :: forall w m cx cy. (Get w m cx, Set w m cy) => Entity -> (cx -> cy) -> SystemT w m ()
- ($~) :: forall w m cx cy. (Get w m cx, Set w m cy) => Entity -> (cx -> cy) -> SystemT w m ()
- cmap :: forall w m cx cy. (Get w m cx, Members w m cx, Set w m cy) => (cx -> cy) -> SystemT w m ()
- cmapM :: forall w m cx cy. (Get w m cx, Set w m cy, Members w m cx) => (cx -> SystemT w m cy) -> SystemT w m ()
- cmapM_ :: forall w m c. (Get w m c, Members w m c) => (c -> SystemT w m ()) -> SystemT w m ()
- cfold :: forall w m c a. (Members w m c, Get w m c) => (a -> c -> a) -> a -> SystemT w m a
- cfoldM :: forall w m c a. (Members w m c, Get w m c) => (a -> c -> SystemT w m a) -> a -> SystemT w m a
- cfoldM_ :: forall w m c a. (Members w m c, Get w m c) => (a -> c -> SystemT w m a) -> a -> SystemT w m ()
- runSystem :: SystemT w m a -> w -> m a
- runWith :: w -> SystemT w m a -> m a
- runGC :: System w ()
- data EntityCounter
- newEntity :: (MonadIO m, Set w m c, Get w m EntityCounter) => c -> SystemT w m Entity
- newEntity_ :: (MonadIO m, Set world m component, Get world m EntityCounter) => component -> SystemT world m ()
- global :: Entity
- makeWorld :: String -> [Name] -> Q [Dec]
- makeWorldAndComponents :: String -> [Name] -> Q [Dec]
- asks :: MonadReader r m => (r -> a) -> m a
- ask :: MonadReader r m => m r
- liftIO :: MonadIO m => IO a -> m a
- lift :: (MonadTrans t, Monad m) => m a -> t m a
- data Proxy (t :: k) = Proxy
Core types
newtype SystemT w m a Source #
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) Source # | |
MonadTrans (SystemT w) Source # | |
Defined in Apecs.Core | |
Monad m => Monad (SystemT w m) Source # | |
Functor m => Functor (SystemT w m) Source # | |
Applicative m => Applicative (SystemT w m) Source # | |
Defined in Apecs.Core | |
MonadIO m => MonadIO (SystemT w m) Source # | |
Defined in Apecs.Core | |
MonadThrow m => MonadThrow (SystemT w m) Source # | |
Defined in Apecs.Core | |
MonadCatch m => MonadCatch (SystemT w m) Source # | |
MonadMask m => MonadMask (SystemT w m) Source # | |
Defined in Apecs.Core Methods 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) # |
class Elem (Storage c) ~ c => Component c Source #
A component is defined by specifying how it is stored. The constraint ensures that stores and components are mapped one-to-one.
Instances
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.
class (Monad m, Component c) => Has w m c where Source #
Has w m c
means that world w
can produce a Storage c
.
It is parameterized over m
to allow stores to be foreign.
Instances
Monad m => Has w m Entity Source # | |
Monad m => Has w m () Source # | |
Has w m c => Has w m (Head c) Source # | |
Has w m c => Has w m (Redirect c) Source # | |
Has w m c => Has w m (Identity c) Source # | |
Has w m c => Has w m (Filter c) Source # | |
Has w m c => Has w m (Maybe c) Source # | |
Has w m c => Has w m (Not c) Source # | |
(Storage c ~ Pushdown s c, Has w m c) => Has w m (Stack c) Source # | |
(Has w m ca, Has w m cb) => Has w m (Either ca cb) Source # | |
(Has w m t_0, Has w m t_1) => Has w m (t_0, t_1) Source # | |
(Has w m t_0, Has w m t_1, Has w m t_2) => Has w m (t_0, t_1, t_2) Source # | |
(Has w m t_0, Has w m t_1, Has w m t_2, Has w m t_3) => Has w m (t_0, t_1, t_2, t_3) Source # | |
(Has w m t_0, Has w m t_1, Has w m t_2, Has w m t_3, Has w m t_4) => Has w m (t_0, t_1, t_2, t_3, t_4) Source # | |
(Has w m t_0, Has w m t_1, Has w m t_2, Has w m t_3, Has w m t_4, Has w m t_5) => Has w m (t_0, t_1, t_2, t_3, t_4, t_5) Source # | |
(Has w m t_0, Has w m t_1, Has w m t_2, Has w m t_3, Has w m t_4, Has w m t_5, Has w m t_6) => Has w m (t_0, t_1, t_2, t_3, t_4, t_5, t_6) Source # | |
(Has w m t_0, Has w m t_1, Has w m t_2, Has w m t_3, Has w m t_4, Has w m t_5, Has w m t_6, Has w m t_7) => Has w m (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) Source # | |
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.
Constructors
Not |
Stores
A map based on Strict
. O(log(n)) for most operations.
Instances
MonadIO m => ExplMembers m (Map c) Source # | |
Defined in Apecs.Stores | |
MonadIO m => ExplDestroy m (Map c) Source # | |
Defined in Apecs.Stores Methods explDestroy :: Map c -> Int -> m () Source # | |
MonadIO m => ExplSet m (Map c) Source # | |
(MonadIO m, Typeable c) => ExplGet m (Map c) Source # | |
MonadIO m => ExplInit m (Map c) Source # | |
Defined in Apecs.Stores | |
Cachable (Map s) Source # | |
Defined in Apecs.Stores | |
type Elem (Map c) Source # | |
Defined in Apecs.Stores |
A Unique contains zero or one component.
Writing to it overwrites both the previous component and its owner.
Its main purpose is to be a Map
optimized for when only ever one component inhabits it.
Instances
MonadIO m => ExplMembers m (Unique c) Source # | |
Defined in Apecs.Stores | |
MonadIO m => ExplDestroy m (Unique c) Source # | |
Defined in Apecs.Stores Methods explDestroy :: Unique c -> Int -> m () Source # | |
MonadIO m => ExplSet m (Unique c) Source # | |
(MonadIO m, Typeable c) => ExplGet m (Unique c) Source # | |
MonadIO m => ExplInit m (Unique c) Source # | |
Defined in Apecs.Stores | |
type Elem (Unique c) Source # | |
Defined in Apecs.Stores |
A Global
contains exactly one component.
The initial value is mempty
from the component's Monoid
instance.
Querying a Global
at any Entity yields this one component, effectively sharing the component between all entities.
A Global component can be read with
or get
0
or even get
1
.
The convenience entity get
undefinedglobal
is defined as -1, and can be used to make operations on a global more explicit, i.e. 'Time t <- get global'.
You also can read and write Globals during a cmap
over other components.
data Cache (n :: Nat) s Source #
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, ExplMembers m s) => ExplMembers m (Cache n s) Source # | |
Defined in Apecs.Stores | |
(MonadIO m, ExplDestroy m s) => ExplDestroy m (Cache n s) Source # | |
Defined in Apecs.Stores Methods explDestroy :: Cache n s -> Int -> m () Source # | |
(MonadIO m, ExplSet m s) => ExplSet m (Cache n s) Source # | |
(MonadIO m, ExplGet m s) => ExplGet m (Cache n s) Source # | |
(MonadIO m, ExplInit m s, KnownNat n, Cachable s) => ExplInit m (Cache n s) Source # | |
Defined in Apecs.Stores | |
(KnownNat n, Cachable s) => Cachable (Cache n s) Source # | |
Defined in Apecs.Stores | |
type Elem (Cache n s) Source # | |
Defined in Apecs.Stores |
Systems
set :: forall w m c. Set w m c => Entity -> c -> SystemT w m () Source #
Writes a Component to a given Entity. Will overwrite existing Components.
($=) :: forall w m c. Set w m c => Entity -> c -> SystemT w m () infixr 2 Source #
set
operator
Writes a Component to a given Entity. Will overwrite existing Components.
destroy :: forall w m c. Destroy w m c => Entity -> Proxy c -> SystemT w m () Source #
Destroys component c
for the given entity.
exists :: forall w m c. Get w m c => Entity -> Proxy c -> SystemT w m Bool Source #
Returns whether the given entity has component c
modify :: forall w m cx cy. (Get w m cx, Set w m cy) => Entity -> (cx -> cy) -> SystemT w m () Source #
Applies a function, if possible.
($~) :: forall w m cx cy. (Get w m cx, Set w m cy) => Entity -> (cx -> cy) -> SystemT w m () infixr 2 Source #
modify
operator
Applies a function, if possible.
cmap :: forall w m cx cy. (Get w m cx, Members w m cx, Set w m cy) => (cx -> cy) -> SystemT w m () Source #
Maps a function over all entities with a cx
, and writes their cy
.
cmapM :: forall w m cx cy. (Get w m cx, Set w m cy, Members w m cx) => (cx -> SystemT w m cy) -> SystemT w m () Source #
Monadically iterates over all entites with a cx
, and writes their cy
.
cmapM_ :: forall w m c. (Get w m c, Members w m c) => (c -> SystemT w m ()) -> SystemT w m () Source #
Monadically iterates over all entites with a cx
cfold :: forall w m c a. (Members w m c, Get w m c) => (a -> c -> a) -> a -> SystemT w m a Source #
Fold over the game world; for example, cfold max (minBound :: Foo)
will find the maximum value of Foo
.
Strict in the accumulator.
cfoldM :: forall w m c a. (Members w m c, Get w m c) => (a -> c -> SystemT w m a) -> a -> SystemT w m a Source #
Monadically fold over the game world. Strict in the accumulator.
cfoldM_ :: forall w m c a. (Members w m c, Get w m c) => (a -> c -> SystemT w m a) -> a -> SystemT w m () Source #
Monadically fold over the game world. Strict in the accumulator.
Other
data EntityCounter Source #
Component used by newEntity to track the number of issued entities.
Automatically added to any world created with makeWorld
Instances
Eq EntityCounter Source # | |
Defined in Apecs.Util Methods (==) :: EntityCounter -> EntityCounter -> Bool # (/=) :: EntityCounter -> EntityCounter -> Bool # | |
Show EntityCounter Source # | |
Defined in Apecs.Util Methods showsPrec :: Int -> EntityCounter -> ShowS # show :: EntityCounter -> String # showList :: [EntityCounter] -> ShowS # | |
Semigroup EntityCounter Source # | |
Defined in Apecs.Util Methods (<>) :: EntityCounter -> EntityCounter -> EntityCounter # sconcat :: NonEmpty EntityCounter -> EntityCounter # stimes :: Integral b => b -> EntityCounter -> EntityCounter # | |
Monoid EntityCounter Source # | |
Defined in Apecs.Util Methods mempty :: EntityCounter # mappend :: EntityCounter -> EntityCounter -> EntityCounter # mconcat :: [EntityCounter] -> EntityCounter # | |
Component EntityCounter Source # | |
Defined in Apecs.Util Associated Types type Storage EntityCounter Source # | |
type Storage EntityCounter Source # | |
Defined in Apecs.Util |
newEntity :: (MonadIO m, Set w m c, Get w m EntityCounter) => c -> SystemT w m Entity Source #
Writes the given components to a new entity, and yields that entity. The return value is often ignored.
newEntity_ :: (MonadIO m, Set world m component, Get world m EntityCounter) => component -> SystemT world m () Source #
Writes the given components to a new entity without yelding the result. Used mostly for convenience.
Convenience entity, for use in places where the entity value does not matter, i.e. a global store.
makeWorld :: String -> [Name] -> Q [Dec] Source #
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
makeWorldAndComponents :: String -> [Name] -> Q [Dec] Source #
Calls makeWorld
and makeMapComponents
, i.e. makes a world and also defines Component
instances with a Map
store.
Re-exports
Arguments
:: MonadReader r m | |
=> (r -> a) | The selector function to apply to the environment. |
-> m a |
Retrieves a function of the current environment.
ask :: MonadReader r m => m r #
Retrieves the monad environment.
lift :: (MonadTrans t, Monad m) => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
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
Constructors
Proxy |
Instances
Generic1 (Proxy :: k -> Type) | Since: base-4.6.0.0 |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Foldable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable Methods 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 |
Eq1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Ord1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Bounded (Proxy t) | Since: base-4.7.0.0 |
Enum (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 |
Read (Proxy t) | Since: base-4.7.0.0 |
Show (Proxy s) | Since: base-4.7.0.0 |
Ix (Proxy s) | Since: base-4.7.0.0 |
Defined in Data.Proxy | |
Generic (Proxy t) | Since: base-4.6.0.0 |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Monoid (Proxy s) | Since: base-4.7.0.0 |
type Rep1 (Proxy :: k -> Type) | |
type Rep (Proxy t) | |