apecs-0.4.1.1: Fast ECS framework for game programming

Safe HaskellNone
LanguageHaskell2010

Apecs.Core

Synopsis

Documentation

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

Defined in Apecs.Core

Methods

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

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

Num Entity Source # 
Instance details

Defined in Apecs.Core

Ord Entity Source # 
Instance details

Defined in Apecs.Core

Show Entity Source # 
Instance details

Defined in Apecs.Core

Component Entity Source # 
Instance details

Defined in Apecs.Core

Associated Types

type Storage Entity :: * Source #

Has w Entity Source # 
Instance details

Defined in Apecs.Core

type Storage Entity Source # 
Instance details

Defined in Apecs.Core

newtype System w a Source #

A System is a newtype around `ReaderT w IO a`, where w is the game world variable. Systems mainly serve to

  • Lift side effects into the IO Monad.
  • Allow type-based lookup of a component's store through getStore.

Constructors

System 

Fields

Instances
Monad (System w) Source # 
Instance details

Defined in Apecs.Core

Methods

(>>=) :: System w a -> (a -> System w b) -> System w b #

(>>) :: System w a -> System w b -> System w b #

return :: a -> System w a #

fail :: String -> System w a #

Functor (System w) Source # 
Instance details

Defined in Apecs.Core

Methods

fmap :: (a -> b) -> System w a -> System w b #

(<$) :: a -> System w b -> System w a #

Applicative (System w) Source # 
Instance details

Defined in Apecs.Core

Methods

pure :: a -> System w a #

(<*>) :: System w (a -> b) -> System w a -> System w b #

liftA2 :: (a -> b -> c) -> System w a -> System w b -> System w c #

(*>) :: System w a -> System w b -> System w b #

(<*) :: System w a -> System w b -> System w a #

MonadIO (System w) Source # 
Instance details

Defined in Apecs.Core

Methods

liftIO :: IO a -> System w a #

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

Defined in Apecs.Core

Associated Types

type Storage () :: * Source #

Component Entity Source # 
Instance details

Defined in Apecs.Core

Associated Types

type Storage Entity :: * Source #

Component EntityCounter Source # 
Instance details

Defined in Apecs.Util

Associated Types

type Storage EntityCounter :: * Source #

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

Defined in Apecs.Core

Associated Types

type Storage (Maybe c) :: * Source #

Component c => Component (Identity c) Source #

Identity component/store. Identity c is equivalent to c, so using it is mostly useless.

Instance details

Defined in Apecs.Core

Associated Types

type Storage (Identity c) :: * Source #

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

Defined in Apecs.Core

Associated Types

type Storage (Filter c) :: * Source #

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

Defined in Apecs.Core

Associated Types

type Storage (Not c) :: * Source #

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

Defined in Apecs.Core

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

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

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

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

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

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

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

Associated Types

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

class Component c => Has w c where Source #

Has w c means that world w can produce a Storage c.

Minimal complete definition

getStore

Methods

getStore :: System w (Storage c) Source #

Instances
Has w Entity Source # 
Instance details

Defined in Apecs.Core

Has w () Source # 
Instance details

Defined in Apecs.Core

Methods

getStore :: System w (Storage ()) Source #

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

Defined in Apecs.Core

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

Defined in Apecs.Core

Methods

getStore :: System w (Storage (Filter c)) Source #

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

Defined in Apecs.Core

Methods

getStore :: System w (Storage (Maybe c)) Source #

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

Defined in Apecs.Core

Methods

getStore :: System w (Storage (Not c)) Source #

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

Defined in Apecs.Core

Methods

getStore :: System w (Storage (Either ca cb)) Source #

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

Defined in Apecs.Core

Methods

getStore :: System w (Storage (t_0, t_1)) Source #

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

Defined in Apecs.Core

Methods

getStore :: System w (Storage (t_0, t_1, t_2)) Source #

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

Defined in Apecs.Core

Methods

getStore :: System w (Storage (t_0, t_1, t_2, t_3)) Source #

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

Defined in Apecs.Core

Methods

getStore :: System w (Storage (t_0, t_1, t_2, t_3, t_4)) Source #

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

Defined in Apecs.Core

Methods

getStore :: System w (Storage (t_0, t_1, t_2, t_3, t_4, t_5)) Source #

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

Defined in Apecs.Core

Methods

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

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

Defined in Apecs.Core

Methods

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

type family Elem s Source #

The type of components stored by a store, e.g. Elem (Map c) = c.

Instances
type Elem () Source # 
Instance details

Defined in Apecs.Core

type Elem () = ()
type Elem EntityStore Source # 
Instance details

Defined in Apecs.Core

type Elem (Identity s) Source # 
Instance details

Defined in Apecs.Core

type Elem (Identity s) = Identity (Elem s)
type Elem (FilterStore s) Source # 
Instance details

Defined in Apecs.Core

type Elem (FilterStore s) = Filter (Elem s)
type Elem (MaybeStore s) Source # 
Instance details

Defined in Apecs.Core

type Elem (MaybeStore s) = Maybe (Elem s)
type Elem (NotStore s) Source # 
Instance details

Defined in Apecs.Core

type Elem (NotStore s) = Not (Elem s)
type Elem (Global c) Source # 
Instance details

Defined in Apecs.Stores

type Elem (Global c) = c
type Elem (Unique c) Source # 
Instance details

Defined in Apecs.Stores

type Elem (Unique c) = c
type Elem (Map c) Source # 
Instance details

Defined in Apecs.Stores

type Elem (Map c) = c
type Elem (t_0, t_1) Source # 
Instance details

Defined in Apecs.Core

type Elem (t_0, t_1) = (Elem t_0, Elem t_1)
type Elem (EitherStore sa sb) Source # 
Instance details

Defined in Apecs.Core

type Elem (EitherStore sa sb) = Either (Elem sa) (Elem sb)
type Elem (Cache n s) Source # 
Instance details

Defined in Apecs.Stores

type Elem (Cache n s) = Elem s
type Elem (t_0, t_1, t_2) Source # 
Instance details

Defined in Apecs.Core

type Elem (t_0, t_1, t_2) = (Elem t_0, Elem t_1, Elem t_2)
type Elem (t_0, t_1, t_2, t_3) Source # 
Instance details

Defined in Apecs.Core

type Elem (t_0, t_1, t_2, t_3) = (Elem t_0, Elem t_1, Elem t_2, Elem t_3)
type Elem (t_0, t_1, t_2, t_3, t_4) Source # 
Instance details

Defined in Apecs.Core

type Elem (t_0, t_1, t_2, t_3, t_4) = (Elem t_0, Elem t_1, Elem t_2, Elem t_3, Elem t_4)
type Elem (t_0, t_1, t_2, t_3, t_4, t_5) Source # 
Instance details

Defined in Apecs.Core

type Elem (t_0, t_1, t_2, t_3, t_4, t_5) = (Elem t_0, Elem t_1, Elem t_2, Elem t_3, Elem t_4, Elem t_5)
type Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6) Source # 
Instance details

Defined in Apecs.Core

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

Defined in Apecs.Core

type Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) = (Elem t_0, Elem t_1, Elem t_2, Elem t_3, Elem t_4, Elem t_5, Elem t_6, Elem t_7)

class ExplInit s where Source #

Indicates that the store s can be initialized. Generally, "base" stores like Map c can be initialized, but composite stores like MaybeStore s cannot.

Minimal complete definition

explInit

Methods

explInit :: IO s Source #

Initialize a new empty store.

Instances
Monoid c => ExplInit (Global c) Source # 
Instance details

Defined in Apecs.Stores

Methods

explInit :: IO (Global c) Source #

ExplInit (Unique c) Source # 
Instance details

Defined in Apecs.Stores

Methods

explInit :: IO (Unique c) Source #

ExplInit (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

explInit :: IO (Map c) Source #

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

Defined in Apecs.Stores

Methods

explInit :: IO (Cache n s) Source #

class ExplGet s where Source #

Stores that we can read using explGet and explExists. For some entity e, eplGet s e is only guaranteed to be safe if explExists s e returns True.

Minimal complete definition

explGet, explExists

Methods

explGet :: s -> Int -> IO (Elem s) Source #

Reads a component from the store. What happens if the component does not exist is left undefined, and might not necessarily crash.

explExists :: s -> Int -> IO Bool Source #

Returns whether there is a component for the given index.

Instances
ExplGet () Source # 
Instance details

Defined in Apecs.Core

Methods

explGet :: () -> Int -> IO (Elem ()) Source #

explExists :: () -> Int -> IO Bool Source #

ExplGet EntityStore Source # 
Instance details

Defined in Apecs.Core

ExplGet s => ExplGet (Identity s) Source # 
Instance details

Defined in Apecs.Core

ExplGet s => ExplGet (FilterStore s) Source # 
Instance details

Defined in Apecs.Core

ExplGet s => ExplGet (MaybeStore s) Source # 
Instance details

Defined in Apecs.Core

ExplGet s => ExplGet (NotStore s) Source # 
Instance details

Defined in Apecs.Core

ExplGet (Global c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

ExplGet (Unique c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

ExplGet (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

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

Defined in Apecs.Core

Methods

explGet :: (t_0, t_1) -> Int -> IO (Elem (t_0, t_1)) Source #

explExists :: (t_0, t_1) -> Int -> IO Bool Source #

(ExplGet sa, ExplGet sb) => ExplGet (EitherStore sa sb) Source # 
Instance details

Defined in Apecs.Core

Methods

explGet :: EitherStore sa sb -> Int -> IO (Elem (EitherStore sa sb)) Source #

explExists :: EitherStore sa sb -> Int -> IO Bool Source #

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

Defined in Apecs.Stores

Methods

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

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

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

Defined in Apecs.Core

Methods

explGet :: (t_0, t_1, t_2) -> Int -> IO (Elem (t_0, t_1, t_2)) Source #

explExists :: (t_0, t_1, t_2) -> Int -> IO Bool Source #

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

Defined in Apecs.Core

Methods

explGet :: (t_0, t_1, t_2, t_3) -> Int -> IO (Elem (t_0, t_1, t_2, t_3)) Source #

explExists :: (t_0, t_1, t_2, t_3) -> Int -> IO Bool Source #

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

Defined in Apecs.Core

Methods

explGet :: (t_0, t_1, t_2, t_3, t_4) -> Int -> IO (Elem (t_0, t_1, t_2, t_3, t_4)) Source #

explExists :: (t_0, t_1, t_2, t_3, t_4) -> Int -> IO Bool Source #

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

Defined in Apecs.Core

Methods

explGet :: (t_0, t_1, t_2, t_3, t_4, t_5) -> Int -> IO (Elem (t_0, t_1, t_2, t_3, t_4, t_5)) Source #

explExists :: (t_0, t_1, t_2, t_3, t_4, t_5) -> Int -> IO Bool Source #

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

Defined in Apecs.Core

Methods

explGet :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6) -> Int -> IO (Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6)) Source #

explExists :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6) -> Int -> IO Bool Source #

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

Defined in Apecs.Core

Methods

explGet :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) -> Int -> IO (Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7)) Source #

explExists :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) -> Int -> IO Bool Source #

class ExplSet s where Source #

Stores that can be written.

Minimal complete definition

explSet

Methods

explSet :: s -> Int -> Elem s -> IO () Source #

Writes a component to the store.

Instances
ExplSet () Source # 
Instance details

Defined in Apecs.Core

Methods

explSet :: () -> Int -> Elem () -> IO () Source #

ExplSet s => ExplSet (Identity s) Source # 
Instance details

Defined in Apecs.Core

Methods

explSet :: Identity s -> Int -> Elem (Identity s) -> IO () Source #

(ExplDestroy s, ExplSet s) => ExplSet (MaybeStore s) Source # 
Instance details

Defined in Apecs.Core

Methods

explSet :: MaybeStore s -> Int -> Elem (MaybeStore s) -> IO () Source #

ExplDestroy s => ExplSet (NotStore s) Source # 
Instance details

Defined in Apecs.Core

Methods

explSet :: NotStore s -> Int -> Elem (NotStore s) -> IO () Source #

ExplSet (Global c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplSet (Unique c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplSet (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

Defined in Apecs.Core

Methods

explSet :: (t_0, t_1) -> Int -> Elem (t_0, t_1) -> IO () Source #

(ExplSet sa, ExplSet sb) => ExplSet (EitherStore sa sb) Source # 
Instance details

Defined in Apecs.Core

Methods

explSet :: EitherStore sa sb -> Int -> Elem (EitherStore sa sb) -> IO () Source #

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

Defined in Apecs.Stores

Methods

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

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

Defined in Apecs.Core

Methods

explSet :: (t_0, t_1, t_2) -> Int -> Elem (t_0, t_1, t_2) -> IO () Source #

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

Defined in Apecs.Core

Methods

explSet :: (t_0, t_1, t_2, t_3) -> Int -> Elem (t_0, t_1, t_2, t_3) -> IO () Source #

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

Defined in Apecs.Core

Methods

explSet :: (t_0, t_1, t_2, t_3, t_4) -> Int -> Elem (t_0, t_1, t_2, t_3, t_4) -> IO () Source #

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

Defined in Apecs.Core

Methods

explSet :: (t_0, t_1, t_2, t_3, t_4, t_5) -> Int -> Elem (t_0, t_1, t_2, t_3, t_4, t_5) -> IO () Source #

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

Defined in Apecs.Core

Methods

explSet :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6) -> Int -> Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6) -> IO () Source #

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

Defined in Apecs.Core

Methods

explSet :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) -> Int -> Elem (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) -> IO () Source #

class ExplDestroy s where Source #

Stores that components can be removed from.

Minimal complete definition

explDestroy

Methods

explDestroy :: s -> Int -> IO () Source #

Destroys the component for a given index.

Instances
ExplDestroy () Source # 
Instance details

Defined in Apecs.Core

Methods

explDestroy :: () -> Int -> IO () Source #

ExplDestroy s => ExplDestroy (Identity s) Source # 
Instance details

Defined in Apecs.Core

Methods

explDestroy :: Identity s -> Int -> IO () Source #

ExplDestroy (Unique c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

ExplDestroy (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

Defined in Apecs.Core

Methods

explDestroy :: (t_0, t_1) -> Int -> IO () Source #

ExplDestroy s => ExplDestroy (Cache n s) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

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

Defined in Apecs.Core

Methods

explDestroy :: (t_0, t_1, t_2) -> Int -> IO () Source #

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

Defined in Apecs.Core

Methods

explDestroy :: (t_0, t_1, t_2, t_3) -> Int -> IO () Source #

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

Defined in Apecs.Core

Methods

explDestroy :: (t_0, t_1, t_2, t_3, t_4) -> Int -> IO () Source #

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

Defined in Apecs.Core

Methods

explDestroy :: (t_0, t_1, t_2, t_3, t_4, t_5) -> Int -> IO () Source #

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

Defined in Apecs.Core

Methods

explDestroy :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6) -> Int -> IO () Source #

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

Defined in Apecs.Core

Methods

explDestroy :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) -> Int -> IO () Source #

class ExplMembers s where Source #

Stores that we can request a list of member entities for.

Minimal complete definition

explMembers

Methods

explMembers :: s -> IO (Vector Int) Source #

Returns an unboxed vector of member indices

Instances
ExplMembers s => ExplMembers (Identity s) Source # 
Instance details

Defined in Apecs.Core

ExplMembers s => ExplMembers (FilterStore s) Source # 
Instance details

Defined in Apecs.Core

ExplMembers (Unique c) Source # 
Instance details

Defined in Apecs.Stores

ExplMembers (Map c) Source # 
Instance details

Defined in Apecs.Stores

Methods

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

(ExplMembers t_0, ExplGet t_1) => ExplMembers (t_0, t_1) Source # 
Instance details

Defined in Apecs.Core

Methods

explMembers :: (t_0, t_1) -> IO (Vector Int) Source #

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

Defined in Apecs.Stores

Methods

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

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

Defined in Apecs.Core

Methods

explMembers :: (t_0, t_1, t_2) -> IO (Vector Int) Source #

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

Defined in Apecs.Core

Methods

explMembers :: (t_0, t_1, t_2, t_3) -> IO (Vector Int) Source #

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

Defined in Apecs.Core

Methods

explMembers :: (t_0, t_1, t_2, t_3, t_4) -> IO (Vector Int) Source #

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

Defined in Apecs.Core

Methods

explMembers :: (t_0, t_1, t_2, t_3, t_4, t_5) -> IO (Vector Int) Source #

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

Defined in Apecs.Core

Methods

explMembers :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6) -> IO (Vector Int) Source #

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

Defined in Apecs.Core

Methods

explMembers :: (t_0, t_1, t_2, t_3, t_4, t_5, t_6, t_7) -> IO (Vector Int) Source #

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

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

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

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

data Not a Source #

Psuedocomponent 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
Has w c => Has w (Not c) Source # 
Instance details

Defined in Apecs.Core

Methods

getStore :: System w (Storage (Not c)) Source #

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

Defined in Apecs.Core

Associated Types

type Storage (Not c) :: * Source #

type Storage (Not c) Source # 
Instance details

Defined in Apecs.Core

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

newtype NotStore s Source #

Pseudostore used to produce values of type Not a, inverts explExists, and destroys instead of explSet.

Constructors

NotStore s 
Instances
ExplDestroy s => ExplSet (NotStore s) Source # 
Instance details

Defined in Apecs.Core

Methods

explSet :: NotStore s -> Int -> Elem (NotStore s) -> IO () Source #

ExplGet s => ExplGet (NotStore s) Source # 
Instance details

Defined in Apecs.Core

type Elem (NotStore s) Source # 
Instance details

Defined in Apecs.Core

type Elem (NotStore s) = Not (Elem s)

newtype MaybeStore s Source #

Pseudostore used to produce values of type Maybe a. Will always return True for explExists. Writing can both set and delete a component using Just and Nothing respectively.

Constructors

MaybeStore s 
Instances
(ExplDestroy s, ExplSet s) => ExplSet (MaybeStore s) Source # 
Instance details

Defined in Apecs.Core

Methods

explSet :: MaybeStore s -> Int -> Elem (MaybeStore s) -> IO () Source #

ExplGet s => ExplGet (MaybeStore s) Source # 
Instance details

Defined in Apecs.Core

type Elem (MaybeStore s) Source # 
Instance details

Defined in Apecs.Core

type Elem (MaybeStore s) = Maybe (Elem s)

data EitherStore sa sb Source #

Used for Either, a logical disjunction between two components. As expected, Either is used to model error values. Getting an Either a b will first attempt to get a b and return it as Right b, or if it does not exist, get an a as Left a. Can also be used to set one of two things.

Constructors

EitherStore sa sb 
Instances
(ExplSet sa, ExplSet sb) => ExplSet (EitherStore sa sb) Source # 
Instance details

Defined in Apecs.Core

Methods

explSet :: EitherStore sa sb -> Int -> Elem (EitherStore sa sb) -> IO () Source #

(ExplGet sa, ExplGet sb) => ExplGet (EitherStore sa sb) Source # 
Instance details

Defined in Apecs.Core

Methods

explGet :: EitherStore sa sb -> Int -> IO (Elem (EitherStore sa sb)) Source #

explExists :: EitherStore sa sb -> Int -> IO Bool Source #

type Elem (EitherStore sa sb) Source # 
Instance details

Defined in Apecs.Core

type Elem (EitherStore sa sb) = Either (Elem sa) (Elem sb)

data Filter c Source #

Pseudocomponent that functions normally for explExists and explMembers, but always return Filter for explGet. Can be used in cmap as cmap $ (Filter :: Filter a) -> b. Since the above can be written more consicely as cmap $ (_ :: a) -> b, it is rarely directly. More interestingly, we can define reusable filters like movables = Filter :: Filter (Position, Velocity).

Constructors

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

Defined in Apecs.Core

Methods

getStore :: System w (Storage (Filter c)) Source #

Eq (Filter c) Source # 
Instance details

Defined in Apecs.Core

Methods

(==) :: Filter c -> Filter c -> Bool #

(/=) :: Filter c -> Filter c -> Bool #

Show (Filter c) Source # 
Instance details

Defined in Apecs.Core

Methods

showsPrec :: Int -> Filter c -> ShowS #

show :: Filter c -> String #

showList :: [Filter c] -> ShowS #

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

Defined in Apecs.Core

Associated Types

type Storage (Filter c) :: * Source #

type Storage (Filter c) Source # 
Instance details

Defined in Apecs.Core

newtype FilterStore s Source #

Constructors

FilterStore s 
Instances
ExplMembers s => ExplMembers (FilterStore s) Source # 
Instance details

Defined in Apecs.Core

ExplGet s => ExplGet (FilterStore s) Source # 
Instance details

Defined in Apecs.Core

type Elem (FilterStore s) Source # 
Instance details

Defined in Apecs.Core

type Elem (FilterStore s) = Filter (Elem s)

data EntityStore Source #

Pseudostore used to produce components of type Entity. Always returns True for explExists, and echoes back the entity argument for explGet. Used in e.g. cmap $ (a, ety :: Entity) -> b to access the current entity.

Constructors

EntityStore 
Instances
ExplGet EntityStore Source # 
Instance details

Defined in Apecs.Core

type Elem EntityStore Source # 
Instance details

Defined in Apecs.Core