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

Apecs

Description

This module forms the apecs Prelude. It selectively re-exports the user-facing functions from the submodules.

Synopsis

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.

Constructors

SystemT 

Fields

Instances

Instances details
Monad m => MonadReader w (SystemT w m) Source # 
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) Source # 
Instance details

Defined in Apecs.Core

Methods

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

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

Defined in Apecs.Core

Methods

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

Applicative m => Applicative (SystemT w m) Source # 
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) Source # 
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) Source # 
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) Source # 
Instance details

Defined in Apecs.Core

Methods

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

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

Defined in Apecs.Core

Methods

mask :: HasCallStack => ((forall a. SystemT w m a -> SystemT w m a) -> SystemT w m b) -> SystemT w m b #

uninterruptibleMask :: HasCallStack => ((forall a. SystemT w m a -> SystemT w m a) -> SystemT w m b) -> SystemT w m b #

generalBracket :: HasCallStack => 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) Source # 
Instance details

Defined in Apecs.Core

Methods

throwM :: (HasCallStack, Exception e) => e -> SystemT w m a #

MonadUnliftIO m => MonadUnliftIO (SystemT w m) Source # 
Instance details

Defined in Apecs.Core

Methods

withRunInIO :: ((forall a. SystemT w m a -> IO a) -> IO b) -> SystemT w m b #

type System w a = SystemT w IO a Source #

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.

Associated Types

type Storage c Source #

Instances

Instances details
Component Entity Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage Entity Source #

Component EntityCounter Source # 
Instance details

Defined in Apecs.Util

Associated Types

type Storage EntityCounter Source #

Component () Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage () Source #

Component c => Component (Filter c) Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (Filter c) Source #

Component c => Component (Not c) Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (Not c) Source #

Component c => Component (Child c) Source # 
Instance details

Defined in Apecs.Experimental.Children

Associated Types

type Storage (Child c) Source #

Component c => Component (ChildList c) Source # 
Instance details

Defined in Apecs.Experimental.Children

Associated Types

type Storage (ChildList c) Source #

Component c => Component (ChildValue c) Source # 
Instance details

Defined in Apecs.Experimental.Children

Associated Types

type Storage (ChildValue c) Source #

Component c => Component (Head c) Source # 
Instance details

Defined in Apecs.Experimental.Components

Associated Types

type Storage (Head c) Source #

Component c => Component (Redirect c) Source # 
Instance details

Defined in Apecs.Experimental.Components

Associated Types

type Storage (Redirect c) Source #

(Storage c ~ Pushdown s c, Component c) => Component (Stack c) Source # 
Instance details

Defined in Apecs.Experimental.Stores

Associated Types

type Storage (Stack c) Source #

Component c => Component (Identity c) Source #

Identity component. Identity c is equivalent to c, so mostly useless.

Instance details

Defined in Apecs.Components

Associated Types

type Storage (Identity c) Source #

Component c => Component (Maybe c) Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (Maybe c) Source #

(Component ca, Component cb) => Component (Either ca cb) Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (Either ca cb) Source #

(Component t_0, Component t_1) => Component (t_0, t_1) Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (t_0, t_1) Source #

(Component t_0, Component t_1, Component t_2) => Component (t_0, t_1, t_2) Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (t_0, t_1, t_2) Source #

(Component t_0, Component t_1, Component t_2, Component t_3) => Component (t_0, t_1, t_2, t_3) Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (t_0, t_1, t_2, t_3) Source #

(Component t_0, Component t_1, Component t_2, Component t_3, Component t_4) => Component (t_0, t_1, t_2, t_3, t_4) Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (t_0, t_1, t_2, t_3, t_4) Source #

(Component t_0, Component t_1, Component t_2, Component t_3, Component t_4, Component t_5) => Component (t_0, t_1, t_2, t_3, t_4, t_5) Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (t_0, t_1, t_2, t_3, t_4, t_5) Source #

(Component t_0, Component t_1, Component t_2, Component t_3, Component t_4, Component t_5, Component t_6) => Component (t_0, t_1, t_2, t_3, t_4, t_5, t_6) Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (t_0, t_1, t_2, t_3, t_4, t_5, t_6) Source #

(Component t_0, Component t_1, Component t_2, Component t_3, Component t_4, Component t_5, Component t_6, Component t_7) => Component (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) Source #

newtype Entity Source #

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
Component Entity Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage Entity Source #

Enum Entity Source # 
Instance details

Defined in Apecs.Core

Num Entity Source # 
Instance details

Defined in Apecs.Core

Show Entity Source # 
Instance details

Defined in Apecs.Core

Eq Entity Source # 
Instance details

Defined in Apecs.Core

Methods

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

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

Ord Entity Source # 
Instance details

Defined in Apecs.Core

Monad m => Has w m Entity Source # 
Instance details

Defined in Apecs.Components

type Storage Entity Source # 
Instance details

Defined in Apecs.Components

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.

Methods

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

Instances

Instances details
Monad m => Has w m Entity Source # 
Instance details

Defined in Apecs.Components

Monad m => Has w m () Source # 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage ()) Source #

Has w m c => Has w m (Filter c) Source # 
Instance details

Defined in Apecs.Components

Methods

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

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

Defined in Apecs.Components

Methods

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

(MonadIO m, Component c, Has w m (Child c)) => Has w m (ChildList c) Source # 
Instance details

Defined in Apecs.Experimental.Children

(MonadIO m, Component c, Has w m (Child c)) => Has w m (ChildValue c) Source # 
Instance details

Defined in Apecs.Experimental.Children

Has w m c => Has w m (Head c) Source # 
Instance details

Defined in Apecs.Experimental.Components

Methods

getStore :: SystemT w m (Storage (Head c)) Source #

Has w m c => Has w m (Redirect c) Source # 
Instance details

Defined in Apecs.Experimental.Components

Methods

getStore :: SystemT w m (Storage (Redirect c)) Source #

(Storage c ~ Pushdown s c, Has w m c) => Has w m (Stack c) Source # 
Instance details

Defined in Apecs.Experimental.Stores

Methods

getStore :: SystemT w m (Storage (Stack c)) Source #

Has w m c => Has w m (Identity c) Source # 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage (Identity c)) Source #

Has w m c => Has w m (Maybe c) Source # 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage (Maybe c)) Source #

(Has w m ca, Has w m cb) => Has w m (Either ca cb) Source # 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage (Either ca cb)) Source #

(Has w m t_0, Has w m t_1) => Has w m (t_0, t_1) Source # 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage (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 # 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage (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 # 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage (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 # 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage (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 # 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage (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 # 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage (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 # 
Instance details

Defined in Apecs.Components

Methods

getStore :: SystemT w m (Storage (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7)) Source #

data Not a 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 

Instances

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

Defined in Apecs.Components

Methods

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

Component c => Component (Not c) Source # 
Instance details

Defined in Apecs.Components

Associated Types

type Storage (Not c) Source #

type Storage (Not c) Source # 
Instance details

Defined in Apecs.Components

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

type Get w m c = (Has w m c, ExplGet m (Storage c)) Source #

type Set w m c = (Has w m c, ExplSet m (Storage c)) Source #

type Destroy w m c = (Has w m c, ExplDestroy m (Storage c)) Source #

type Members w m c = (Has w m c, ExplMembers m (Storage c)) Source #

Stores

data Map c Source #

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

Instances

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

Defined in Apecs.Stores

Methods

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

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

Defined in Apecs.Stores

Methods

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

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

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

Defined in Apecs.Stores

Methods

explInit :: m (Map c) Source #

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

Defined in Apecs.Stores

Methods

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

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

Defined in Apecs.Stores

Methods

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

Cachable (Map s) Source # 
Instance details

Defined in Apecs.Stores

type Elem (Map c) Source # 
Instance details

Defined in Apecs.Stores

type Elem (Map c) = c

data Unique c Source #

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) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

Defined in Apecs.Stores

Methods

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

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

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

Defined in Apecs.Stores

Methods

explInit :: m (Unique c) Source #

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

Defined in Apecs.Stores

Methods

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

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

Defined in Apecs.Stores

Methods

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

type Elem (Unique c) Source # 
Instance details

Defined in Apecs.Stores

type Elem (Unique c) = c

data Global c Source #

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) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

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

Defined in Apecs.Stores

Methods

explInit :: m (Global c) Source #

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

Defined in Apecs.Stores

Methods

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

type Elem (Global c) Source # 
Instance details

Defined in Apecs.Stores

type Elem (Global c) = c

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

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

Defined in Apecs.Stores

Methods

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

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

Defined in Apecs.Stores

Methods

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

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

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

Defined in Apecs.Stores

Methods

explInit :: m (Cache n s) Source #

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

Defined in Apecs.Stores

Methods

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

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

Defined in Apecs.Stores

Methods

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

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

Defined in Apecs.Stores

type Elem (Cache n s) Source # 
Instance details

Defined in Apecs.Stores

type Elem (Cache n s) = Elem s

explInit :: ExplInit m s => m s Source #

Initialize a new empty store.

Systems

get :: forall w m c. Get w m c => Entity -> SystemT w m c Source #

Read a Component

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.

cmapIf :: forall w m cp cx cy. (Get w m cx, Get w m cp, Members w m cx, Set w m cy) => (cp -> Bool) -> (cx -> cy) -> SystemT w m () Source #

Conditional cmap, that first tests whether the argument satisfies some property. The entity needs to have both a cx and cp component.

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.

collect :: forall components w m a. (Get w m components, Members w m components) => (components -> Maybe a) -> SystemT w m [a] Source #

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.

Performance

When using cmap or cfold over a tuple of components, keep in mind the ordering of the tuple can have performance implications!

For tuples, the way the cmap and cfold work under the hood is by iterating over the component in the first position, and then for each entity that has that component, checking whether the entity also has the components in the remaining positions. Therefore, the first component will typically be the most determining factor for performance, and a good rule of thumb is to, when iterating over a tuple, put the rarest component in first position.

Let's take a look at an example. Consider a simple 2D rendering system built on top of cmapM_:

cmapM_ $ \(Sprite sprite, Visible) -> do
  renderSprite sprite

While this rendering system works, it could be made more efficient by leveraging knowledge of how the library handles reading of tupled components. The usage of cmapM_ here (or any of the other map/fold functions) will iterate over all entities with a Sprite component and filter out any of these entities that do not have a Visible component. Depending on the game, it is reasonable to assume that there are more sprites active in the game's world than sprites that are visible to the game's camera.

Swapping the component ordering in the tuple is likely to be more efficient:

cmapM_ $ \(Visible, Sprite sprite) -> do
  renderSprite sprite

Now the system iterates over just those entities that are visible to the game's camera and filters out any that do not have a Sprite component.

While putting the rarest component first is an excellent rule of thumb, to get the best possible performance, always consider how maps and folds are executed under the hood, and how you can order your components to optimize that process.

Other

runSystem :: SystemT w m a -> w -> m a Source #

Run a system in a game world

runWith :: w -> SystemT w m a -> m a Source #

Run a system in a game world

runGC :: MonadIO m => SystemT w m () Source #

Explicitly invoke the garbage collector

data EntityCounter Source #

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

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.

global :: Entity Source #

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

asks #

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.

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

Expand
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 liftIO, we would have ended up with this error:

• 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 IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> 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.

data Proxy (t :: k) #

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, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

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

Instances details
Generic1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: forall (a :: k0). Proxy a -> Rep1 Proxy a #

to1 :: forall (a :: k0). Rep1 Proxy a -> Proxy a #

Foldable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

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 #

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

elem :: Eq a => a -> Proxy a -> Bool #

maximum :: Ord a => Proxy a -> a #

minimum :: Ord a => Proxy a -> a #

sum :: Num a => Proxy a -> a #

product :: Num a => Proxy a -> a #

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) #

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

(*>) :: Proxy a -> Proxy b -> Proxy b #

(<*) :: Proxy a -> Proxy b -> Proxy a #

Functor (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b #

(<$) :: a -> Proxy b -> Proxy a #

Monad (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b #

(>>) :: Proxy a -> Proxy b -> Proxy b #

return :: a -> Proxy a #

MonadPlus (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int #

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

type Rep1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))
type Rep (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))