apecs-effectful-0.1.0.0: Adaptation of the apecs library for the effectful ecosystem.
Copyright(c) Michael Szvetits 2023
LicenseBSD-3-Clause (see the file LICENSE)
Maintainertypedbyte@qualified.name
Stabilitystable
Portabilityportable
Safe HaskellSafe-Inferred
LanguageGHC2021

Apecs.Effectful

Description

Adaptation of the apecs library for the effectful ecosystem.

Synopsis

Effectful Adaptation

data ECS (w :: Type) :: Effect Source #

Provide the ability to query and manipulate worlds of type w.

Instances

Instances details
type DispatchOf (ECS w) Source # 
Instance details

Defined in Apecs.Effectful

newtype StaticRep (ECS w) Source # 
Instance details

Defined in Apecs.Effectful

newtype StaticRep (ECS w) = ECS w

runECS :: IOE :> es => IO w -> Eff (ECS w ': es) a -> Eff es a Source #

Run the ECS effect using the world initialization function provided by makeWorld or makeWorldAndComponents.

runGC :: forall w es. ECS w :> es => Eff es () Source #

Explicitly invoke the garbage collector.

type Get w c = Get w IO c Source #

Indicates that world w has readable components of type c.

type Set w c = Set w IO c Source #

Indicates that world w has writeable components of type c.

type Destroy w c = Destroy w IO c Source #

Indicates that world w has deletable components of type c.

type Members w c = Members w IO c Source #

Indicates that world w contains components of type c.

newEntity :: forall w c es. (ECS w :> es, Set w c, Get w EntityCounter) => c -> Eff es Entity Source #

Writes the given components to a new entity.

newEntity_ :: forall w c es. (ECS w :> es, Set w c, Get w EntityCounter) => c -> Eff es () Source #

Writes the given components to a new entity.

get :: forall w c es. (ECS w :> es, Get w c) => Entity -> Eff es c Source #

Read a component from an entity.

tryGet :: forall w c es. (ECS w :> es, Get w c) => Entity -> Eff es (Maybe c) Source #

Read a component from an entity, if available.

set :: forall w c es. (ECS w :> es, Set w c) => Entity -> c -> Eff es () Source #

Writes a component to a given entity.

($=) :: forall w c es. (ECS w :> es, Set w c) => Entity -> c -> Eff es () infixr 2 Source #

Writes a component to a given entity.

destroy :: forall c w es. (ECS w :> es, Destroy w c) => Entity -> Eff es () Source #

Destroys component c for the given entity.

exists :: forall c w es. (ECS w :> es, Get w c) => Entity -> Eff es Bool Source #

Returns whether the given entity has component c.

modify :: forall w cx cy es. (ECS w :> es, Get w cx, Set w cy) => Entity -> (cx -> cy) -> Eff es () Source #

Read a component and writes a new component of an entity.

($~) :: forall w cx cy es. (ECS w :> es, Get w cx, Set w cy) => Entity -> (cx -> cy) -> Eff es () infixr 2 Source #

Read the component cx and writes the component cy of an entity.

cmap :: forall w cx cy es. (ECS w :> es, Get w cx, Members w cx, Set w cy) => (cx -> cy) -> Eff es () Source #

Read the component cx and writes the component cy of all entities.

cmapM :: forall w cx cy es. (ECS w :> es, Get w cx, Set w cy, Members w cx) => (cx -> Eff es cy) -> Eff es () Source #

Monadic variant of cmap.

cmapM_ :: forall w c es. (ECS w :> es, Get w c, Members w c) => (c -> Eff es ()) -> Eff es () Source #

Monadic variant of cmap, ignoring the result of the applied function.

cfold :: forall w c a es. (ECS w :> es, Members w c, Get w c) => (a -> c -> a) -> a -> Eff es a Source #

Fold over the components c of the game world.

cfoldM :: forall w c a es. (ECS w :> es, Members w c, Get w c) => (a -> c -> Eff es a) -> a -> Eff es a Source #

Monadic variant of cfold.

cfoldM_ :: forall w c a es. (ECS w :> es, Members w c, Get w c) => (a -> c -> Eff es a) -> a -> Eff es () Source #

Monadic variant of cfold, ignoring the result.

Re-exports

newtype Entity #

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.

Constructors

Entity 

Fields

Instances

Instances details
Enum Entity 
Instance details

Defined in Apecs.Core

Num Entity 
Instance details

Defined in Apecs.Core

Show Entity 
Instance details

Defined in Apecs.Core

Eq Entity 
Instance details

Defined in Apecs.Core

Methods

(==) :: Entity -> Entity -> Bool #

(/=) :: Entity -> Entity -> Bool #

Ord Entity 
Instance details

Defined in Apecs.Core

type Storage Entity 
Instance details

Defined in Apecs.Components

data EntityCounter #

Component used by newEntity to track the number of issued entities. Automatically added to any world created with makeWorld

Instances

Instances details
Component EntityCounter 
Instance details

Defined in Apecs.Util

Associated Types

type Storage EntityCounter #

Monoid EntityCounter 
Instance details

Defined in Apecs.Util

Semigroup EntityCounter 
Instance details

Defined in Apecs.Util

Show EntityCounter 
Instance details

Defined in Apecs.Util

Eq EntityCounter 
Instance details

Defined in Apecs.Util

type Storage EntityCounter 
Instance details

Defined in Apecs.Util

data Not a #

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 

Instances

Instances details
Has w m c => Has w m (Not c) 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage (Not c)) #

Component c => Component (Not c) 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (Not c) #

type Storage (Not c) 
Instance details

Defined in Apecs.Components

type Storage (Not c) = NotStore (Storage c)

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.

Associated Types

type Storage c #

Instances

Instances details
Component EntityCounter 
Instance details

Defined in Apecs.Util

Associated Types

type Storage EntityCounter #

Component c => Component (Filter c) 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (Filter c) #

Component c => Component (Not c) 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (Not c) #

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.

Methods

getStore :: SystemT w m (Storage c) #

Instances

Instances details
Has w m c => Has w m (Filter c) 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage (Filter c)) #

Has w m c => Has w m (Not c) 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage (Not c)) #

data Cache (n :: Nat) s #

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

Instances details
(MonadIO m, ExplDestroy m s) => ExplDestroy m (Cache n s) 
Instance details

Defined in Apecs.Stores

Methods

explDestroy :: Cache n s -> Int -> m () #

(MonadIO m, ExplGet m s) => ExplGet m (Cache n s) 
Instance details

Defined in Apecs.Stores

Methods

explGet :: Cache n s -> Int -> m (Elem (Cache n s)) #

explExists :: Cache n s -> Int -> m Bool #

(MonadIO m, ExplInit m s, KnownNat n, Cachable s) => ExplInit m (Cache n s) 
Instance details

Defined in Apecs.Stores

Methods

explInit :: m (Cache n s) #

(MonadIO m, ExplMembers m s) => ExplMembers m (Cache n s) 
Instance details

Defined in Apecs.Stores

Methods

explMembers :: Cache n s -> m (Vector Int) #

(MonadIO m, ExplSet m s) => ExplSet m (Cache n s) 
Instance details

Defined in Apecs.Stores

Methods

explSet :: Cache n s -> Int -> Elem (Cache n s) -> m () #

(KnownNat n, Cachable s) => Cachable (Cache n s) 
Instance details

Defined in Apecs.Stores

type Elem (Cache n s) 
Instance details

Defined in Apecs.Stores

type Elem (Cache n s) = Elem s

data Global c #

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 get 0 or get 1 or even get undefined. The convenience entity global 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.

Instances

Instances details
MonadIO m => ExplGet m (Global c) 
Instance details

Defined in Apecs.Stores

Methods

explGet :: Global c -> Int -> m (Elem (Global c)) #

explExists :: Global c -> Int -> m Bool #

(Monoid c, MonadIO m) => ExplInit m (Global c) 
Instance details

Defined in Apecs.Stores

Methods

explInit :: m (Global c) #

MonadIO m => ExplSet m (Global c) 
Instance details

Defined in Apecs.Stores

Methods

explSet :: Global c -> Int -> Elem (Global c) -> m () #

type Elem (Global c) 
Instance details

Defined in Apecs.Stores

type Elem (Global c) = c

data Map c #

A map based on Strict. O(log(n)) for most operations.

Instances

Instances details
MonadIO m => ExplDestroy m (Map c) 
Instance details

Defined in Apecs.Stores

Methods

explDestroy :: Map c -> Int -> m () #

(MonadIO m, Typeable c) => ExplGet m (Map c) 
Instance details

Defined in Apecs.Stores

Methods

explGet :: Map c -> Int -> m (Elem (Map c)) #

explExists :: Map c -> Int -> m Bool #

MonadIO m => ExplInit m (Map c) 
Instance details

Defined in Apecs.Stores

Methods

explInit :: m (Map c) #

MonadIO m => ExplMembers m (Map c) 
Instance details

Defined in Apecs.Stores

Methods

explMembers :: Map c -> m (Vector Int) #

MonadIO m => ExplSet m (Map c) 
Instance details

Defined in Apecs.Stores

Methods

explSet :: Map c -> Int -> Elem (Map c) -> m () #

Cachable (Map s) 
Instance details

Defined in Apecs.Stores

type Elem (Map c) 
Instance details

Defined in Apecs.Stores

type Elem (Map c) = c

data Unique c #

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

Instances details
MonadIO m => ExplDestroy m (Unique c) 
Instance details

Defined in Apecs.Stores

Methods

explDestroy :: Unique c -> Int -> m () #

(MonadIO m, Typeable c) => ExplGet m (Unique c) 
Instance details

Defined in Apecs.Stores

Methods

explGet :: Unique c -> Int -> m (Elem (Unique c)) #

explExists :: Unique c -> Int -> m Bool #

MonadIO m => ExplInit m (Unique c) 
Instance details

Defined in Apecs.Stores

Methods

explInit :: m (Unique c) #

MonadIO m => ExplMembers m (Unique c) 
Instance details

Defined in Apecs.Stores

Methods

explMembers :: Unique c -> m (Vector Int) #

MonadIO m => ExplSet m (Unique c) 
Instance details

Defined in Apecs.Stores

Methods

explSet :: Unique c -> Int -> Elem (Unique c) -> m () #

type Elem (Unique c) 
Instance details

Defined in Apecs.Stores

type Elem (Unique c) = c

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.

Constructors

SystemT (ReaderT w m a) 

Instances

Instances details
Monad m => MonadReader w (SystemT w m) 
Instance details

Defined in Apecs.Core

Methods

ask :: SystemT w m w #

local :: (w -> w) -> SystemT w m a -> SystemT w m a #

reader :: (w -> a) -> SystemT w m a #

MonadTrans (SystemT w) 
Instance details

Defined in Apecs.Core

Methods

lift :: Monad m => m a -> SystemT w m a #

MonadIO m => MonadIO (SystemT w m) 
Instance details

Defined in Apecs.Core

Methods

liftIO :: IO a -> SystemT w m a #

Applicative m => Applicative (SystemT w m) 
Instance details

Defined in Apecs.Core

Methods

pure :: a -> SystemT w m a #

(<*>) :: SystemT w m (a -> b) -> SystemT w m a -> SystemT w m b #

liftA2 :: (a -> b -> c) -> SystemT w m a -> SystemT w m b -> SystemT w m c #

(*>) :: SystemT w m a -> SystemT w m b -> SystemT w m b #

(<*) :: SystemT w m a -> SystemT w m b -> SystemT w m a #

Functor m => Functor (SystemT w m) 
Instance details

Defined in Apecs.Core

Methods

fmap :: (a -> b) -> SystemT w m a -> SystemT w m b #

(<$) :: a -> SystemT w m b -> SystemT w m a #

Monad m => Monad (SystemT w m) 
Instance details

Defined in Apecs.Core

Methods

(>>=) :: SystemT w m a -> (a -> SystemT w m b) -> SystemT w m b #

(>>) :: SystemT w m a -> SystemT w m b -> SystemT w m b #

return :: a -> SystemT w m a #

MonadCatch m => MonadCatch (SystemT w m) 
Instance details

Defined in Apecs.Core

Methods

catch :: Exception e => SystemT w m a -> (e -> SystemT w m a) -> SystemT w m a #

MonadMask m => MonadMask (SystemT w m) 
Instance details

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) #

MonadThrow m => MonadThrow (SystemT w m) 
Instance details

Defined in Apecs.Core

Methods

throwM :: Exception e => e -> SystemT w m a #

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

makeWorldAndComponents :: String -> [Name] -> Q [Dec] #

Calls makeWorld and makeMapComponents, i.e. makes a world and also defines Component instances with a Map store.

global :: Entity #

Convenience entity, for use in places where the entity value does not matter, i.e. a global store.

explInit :: ExplInit m s => m s #

Initialize a new empty store.

asks #

Arguments

:: MonadReader r m 
=> (r -> a)

The selector function to apply to the environment.

-> m a 

Retrieves a function of the current environment.