apecs-0.2.4.1: A fast ECS for game engine programming

Safe HaskellNone
LanguageHaskell2010

Apecs.Types

Synopsis

Documentation

newtype Entity c Source #

An Entity is really just an Int. The type variable is used to keep track of reads and writes, but can be freely cast.

Constructors

Entity 

Fields

Instances

Eq (Entity c) Source # 

Methods

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

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

Ord (Entity c) Source # 

Methods

compare :: Entity c -> Entity c -> Ordering #

(<) :: Entity c -> Entity c -> Bool #

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

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

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

max :: Entity c -> Entity c -> Entity c #

min :: Entity c -> Entity c -> Entity c #

Show (Entity c) Source # 

Methods

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

show :: Entity c -> String #

showList :: [Entity c] -> ShowS #

Cast (Entity a) (Entity b) Source # 

Methods

cast :: Entity a -> Entity b Source #

newtype Slice c Source #

A slice is a list of entities, represented by a Data.Unbox.Vector of Ints.

Constructors

Slice 

Fields

Instances

Show (Slice c) Source # 

Methods

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

show :: Slice c -> String #

showList :: [Slice c] -> ShowS #

Monoid (Slice c) Source # 

Methods

mempty :: Slice c #

mappend :: Slice c -> Slice c -> Slice c #

mconcat :: [Slice c] -> Slice c #

Cast (Slice a) (Slice b) Source # 

Methods

cast :: Slice a -> Slice b Source #

newtype System w a Source #

A system is a newtype around `ReaderT w IO a`, where w is the game world variable.

Constructors

System 

Fields

Instances

Monad (System w) Source # 

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 # 

Methods

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

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

Applicative (System w) Source # 

Methods

pure :: a -> System w a #

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

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

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

MonadIO (System w) Source # 

Methods

liftIO :: IO a -> System w a #

class (Stores (Storage c) ~ c, Store (Storage c)) => Component c Source #

A component is defined by the type of its storage The storage in turn supplies runtime types for the component. For the component to be valid, its Storage must be in instance of Store.

Associated Types

type Storage c Source #

Instances

Component EntityCounter Source # 

Associated Types

type Storage EntityCounter :: * Source #

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

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 # 

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 # 

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 # 

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 # 

Associated Types

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

class Component c => Has w c where Source #

A world Has a component if it can produce its Storage

Minimal complete definition

getStore

Methods

getStore :: System w (Storage c) Source #

Instances

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

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 # 

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 # 

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 # 

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 # 

Methods

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

newtype Safe c Source #

Represents a safe access to c. A safe access is either a read that might fail, or a write that might delete.

Constructors

Safe 

Fields

class Store s where Source #

Holds components indexed by entities

Associated Types

type Stores s Source #

The type of components stored by this Store

type SafeRW s Source #

Return type for safe reads writes to the store

Methods

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

Retrieves a component from the store

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

Writes a component

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

Destroys the component for the given index.

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

Returns whether there is a component for the given index

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

Returns an unboxed vector of member indices

explGetUnsafe :: s -> Int -> IO (Stores s) Source #

Unsafe index to the store. What happens if the component does not exist is left undefined.

explSetMaybe :: s -> Int -> SafeRW s -> IO () Source #

Either writes or deletes a component

initStore :: IO s Source #

explReset :: s -> IO () Source #

Removes all components. Equivalent to calling explDestroy on each member

explImapM_ :: MonadIO m => s -> (Int -> m a) -> m () Source #

Monadically iterates over member indices

explImapM :: MonadIO m => s -> (Int -> m a) -> m [a] Source #

Monadically iterates over member indices

explModify :: s -> Int -> (Stores s -> Stores s) -> IO () Source #

Modifies an element in the store. Equivalent to reading a value, and then writing the result of the function application.

explCmap :: s -> (Stores s -> Stores s) -> IO () Source #

Maps over all elements of this store. Equivalent to getting a list of all entities with this component, and then explModifying each of them.

explCmapM_ :: MonadIO m => s -> (Stores s -> m a) -> m () Source #

explCimapM_ :: MonadIO m => s -> ((Int, Stores s) -> m a) -> m () Source #

explCmapM :: MonadIO m => s -> (Stores s -> m a) -> m [a] Source #

explCimapM :: MonadIO m => s -> ((Int, Stores s) -> m a) -> m [a] Source #

Instances

Monoid c => Store (Global c) Source # 

Associated Types

type Stores (Global c) :: * Source #

type SafeRW (Global c) :: * Source #

Methods

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

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

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

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

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

explGetUnsafe :: Global c -> Int -> IO (Stores (Global c)) Source #

explSetMaybe :: Global c -> Int -> SafeRW (Global c) -> IO () Source #

initStore :: IO (Global c) Source #

explReset :: Global c -> IO () Source #

explImapM_ :: MonadIO m => Global c -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Global c -> (Int -> m a) -> m [a] Source #

explModify :: Global c -> Int -> (Stores (Global c) -> Stores (Global c)) -> IO () Source #

explCmap :: Global c -> (Stores (Global c) -> Stores (Global c)) -> IO () Source #

explCmapM_ :: MonadIO m => Global c -> (Stores (Global c) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Global c -> ((Int, Stores (Global c)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Global c -> (Stores (Global c) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Global c -> ((Int, Stores (Global c)) -> m a) -> m [a] Source #

Store (Unique c) Source # 

Associated Types

type Stores (Unique c) :: * Source #

type SafeRW (Unique c) :: * Source #

Methods

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

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

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

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

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

explGetUnsafe :: Unique c -> Int -> IO (Stores (Unique c)) Source #

explSetMaybe :: Unique c -> Int -> SafeRW (Unique c) -> IO () Source #

initStore :: IO (Unique c) Source #

explReset :: Unique c -> IO () Source #

explImapM_ :: MonadIO m => Unique c -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Unique c -> (Int -> m a) -> m [a] Source #

explModify :: Unique c -> Int -> (Stores (Unique c) -> Stores (Unique c)) -> IO () Source #

explCmap :: Unique c -> (Stores (Unique c) -> Stores (Unique c)) -> IO () Source #

explCmapM_ :: MonadIO m => Unique c -> (Stores (Unique c) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Unique c -> ((Int, Stores (Unique c)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Unique c -> (Stores (Unique c) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Unique c -> ((Int, Stores (Unique c)) -> m a) -> m [a] Source #

Flag c => Store (Set c) Source # 

Associated Types

type Stores (Set c) :: * Source #

type SafeRW (Set c) :: * Source #

Methods

explGet :: Set c -> Int -> IO (SafeRW (Set c)) Source #

explSet :: Set c -> Int -> Stores (Set c) -> IO () Source #

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

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

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

explGetUnsafe :: Set c -> Int -> IO (Stores (Set c)) Source #

explSetMaybe :: Set c -> Int -> SafeRW (Set c) -> IO () Source #

initStore :: IO (Set c) Source #

explReset :: Set c -> IO () Source #

explImapM_ :: MonadIO m => Set c -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Set c -> (Int -> m a) -> m [a] Source #

explModify :: Set c -> Int -> (Stores (Set c) -> Stores (Set c)) -> IO () Source #

explCmap :: Set c -> (Stores (Set c) -> Stores (Set c)) -> IO () Source #

explCmapM_ :: MonadIO m => Set c -> (Stores (Set c) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Set c -> ((Int, Stores (Set c)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Set c -> (Stores (Set c) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Set c -> ((Int, Stores (Set c)) -> m a) -> m [a] Source #

Store (Map c) Source # 

Associated Types

type Stores (Map c) :: * Source #

type SafeRW (Map c) :: * Source #

Methods

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

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

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

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

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

explGetUnsafe :: Map c -> Int -> IO (Stores (Map c)) Source #

explSetMaybe :: Map c -> Int -> SafeRW (Map c) -> IO () Source #

initStore :: IO (Map c) Source #

explReset :: Map c -> IO () Source #

explImapM_ :: MonadIO m => Map c -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Map c -> (Int -> m a) -> m [a] Source #

explModify :: Map c -> Int -> (Stores (Map c) -> Stores (Map c)) -> IO () Source #

explCmap :: Map c -> (Stores (Map c) -> Stores (Map c)) -> IO () Source #

explCmapM_ :: MonadIO m => Map c -> (Stores (Map c) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Map c -> ((Int, Stores (Map c)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Map c -> (Stores (Map c) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Map c -> ((Int, Stores (Map c)) -> m a) -> m [a] Source #

(Store t_0, Store t_1) => Store (t_0, t_1) Source # 

Associated Types

type Stores (t_0, t_1) :: * Source #

type SafeRW (t_0, t_1) :: * Source #

Methods

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

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

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

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

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

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

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

initStore :: IO (t_0, t_1) Source #

explReset :: (t_0, t_1) -> IO () Source #

explImapM_ :: MonadIO m => (t_0, t_1) -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => (t_0, t_1) -> (Int -> m a) -> m [a] Source #

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

explCmap :: (t_0, t_1) -> (Stores (t_0, t_1) -> Stores (t_0, t_1)) -> IO () Source #

explCmapM_ :: MonadIO m => (t_0, t_1) -> (Stores (t_0, t_1) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => (t_0, t_1) -> ((Int, Stores (t_0, t_1)) -> m a) -> m () Source #

explCmapM :: MonadIO m => (t_0, t_1) -> (Stores (t_0, t_1) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => (t_0, t_1) -> ((Int, Stores (t_0, t_1)) -> m a) -> m [a] Source #

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

Associated Types

type Stores (Cache n s) :: * Source #

type SafeRW (Cache n s) :: * Source #

Methods

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

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

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

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

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

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

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

initStore :: IO (Cache n s) Source #

explReset :: Cache n s -> IO () Source #

explImapM_ :: MonadIO m => Cache n s -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Cache n s -> (Int -> m a) -> m [a] Source #

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

explCmap :: Cache n s -> (Stores (Cache n s) -> Stores (Cache n s)) -> IO () Source #

explCmapM_ :: MonadIO m => Cache n s -> (Stores (Cache n s) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Cache n s -> ((Int, Stores (Cache n s)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Cache n s -> (Stores (Cache n s) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Cache n s -> ((Int, Stores (Cache n s)) -> m a) -> m [a] Source #

(Log l (Stores s), Cachable s) => Store (Logger l s) Source # 

Associated Types

type Stores (Logger l s) :: * Source #

type SafeRW (Logger l s) :: * Source #

Methods

explGet :: Logger l s -> Int -> IO (SafeRW (Logger l s)) Source #

explSet :: Logger l s -> Int -> Stores (Logger l s) -> IO () Source #

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

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

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

explGetUnsafe :: Logger l s -> Int -> IO (Stores (Logger l s)) Source #

explSetMaybe :: Logger l s -> Int -> SafeRW (Logger l s) -> IO () Source #

initStore :: IO (Logger l s) Source #

explReset :: Logger l s -> IO () Source #

explImapM_ :: MonadIO m => Logger l s -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => Logger l s -> (Int -> m a) -> m [a] Source #

explModify :: Logger l s -> Int -> (Stores (Logger l s) -> Stores (Logger l s)) -> IO () Source #

explCmap :: Logger l s -> (Stores (Logger l s) -> Stores (Logger l s)) -> IO () Source #

explCmapM_ :: MonadIO m => Logger l s -> (Stores (Logger l s) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => Logger l s -> ((Int, Stores (Logger l s)) -> m a) -> m () Source #

explCmapM :: MonadIO m => Logger l s -> (Stores (Logger l s) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => Logger l s -> ((Int, Stores (Logger l s)) -> m a) -> m [a] Source #

(Store t_0, Store t_1, Store t_2) => Store (t_0, t_1, t_2) Source # 

Associated Types

type Stores (t_0, t_1, t_2) :: * Source #

type SafeRW (t_0, t_1, t_2) :: * Source #

Methods

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

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

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

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

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

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

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

initStore :: IO (t_0, t_1, t_2) Source #

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

explImapM_ :: MonadIO m => (t_0, t_1, t_2) -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => (t_0, t_1, t_2) -> (Int -> m a) -> m [a] Source #

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

explCmap :: (t_0, t_1, t_2) -> (Stores (t_0, t_1, t_2) -> Stores (t_0, t_1, t_2)) -> IO () Source #

explCmapM_ :: MonadIO m => (t_0, t_1, t_2) -> (Stores (t_0, t_1, t_2) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => (t_0, t_1, t_2) -> ((Int, Stores (t_0, t_1, t_2)) -> m a) -> m () Source #

explCmapM :: MonadIO m => (t_0, t_1, t_2) -> (Stores (t_0, t_1, t_2) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => (t_0, t_1, t_2) -> ((Int, Stores (t_0, t_1, t_2)) -> m a) -> m [a] Source #

(Store t_0, Store t_1, Store t_2, Store t_3) => Store (t_0, t_1, t_2, t_3) Source # 

Associated Types

type Stores (t_0, t_1, t_2, t_3) :: * Source #

type SafeRW (t_0, t_1, t_2, t_3) :: * Source #

Methods

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

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

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

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

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

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

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

initStore :: IO (t_0, t_1, t_2, t_3) Source #

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

explImapM_ :: MonadIO m => (t_0, t_1, t_2, t_3) -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => (t_0, t_1, t_2, t_3) -> (Int -> m a) -> m [a] Source #

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

explCmap :: (t_0, t_1, t_2, t_3) -> (Stores (t_0, t_1, t_2, t_3) -> Stores (t_0, t_1, t_2, t_3)) -> IO () Source #

explCmapM_ :: MonadIO m => (t_0, t_1, t_2, t_3) -> (Stores (t_0, t_1, t_2, t_3) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => (t_0, t_1, t_2, t_3) -> ((Int, Stores (t_0, t_1, t_2, t_3)) -> m a) -> m () Source #

explCmapM :: MonadIO m => (t_0, t_1, t_2, t_3) -> (Stores (t_0, t_1, t_2, t_3) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => (t_0, t_1, t_2, t_3) -> ((Int, Stores (t_0, t_1, t_2, t_3)) -> m a) -> m [a] Source #

(Store t_0, Store t_1, Store t_2, Store t_3, Store t_4) => Store (t_0, t_1, t_2, t_3, t_4) Source # 

Associated Types

type Stores (t_0, t_1, t_2, t_3, t_4) :: * Source #

type SafeRW (t_0, t_1, t_2, t_3, t_4) :: * Source #

Methods

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

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

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

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

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

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

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

initStore :: IO (t_0, t_1, t_2, t_3, t_4) Source #

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

explImapM_ :: MonadIO m => (t_0, t_1, t_2, t_3, t_4) -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => (t_0, t_1, t_2, t_3, t_4) -> (Int -> m a) -> m [a] Source #

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

explCmap :: (t_0, t_1, t_2, t_3, t_4) -> (Stores (t_0, t_1, t_2, t_3, t_4) -> Stores (t_0, t_1, t_2, t_3, t_4)) -> IO () Source #

explCmapM_ :: MonadIO m => (t_0, t_1, t_2, t_3, t_4) -> (Stores (t_0, t_1, t_2, t_3, t_4) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => (t_0, t_1, t_2, t_3, t_4) -> ((Int, Stores (t_0, t_1, t_2, t_3, t_4)) -> m a) -> m () Source #

explCmapM :: MonadIO m => (t_0, t_1, t_2, t_3, t_4) -> (Stores (t_0, t_1, t_2, t_3, t_4) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => (t_0, t_1, t_2, t_3, t_4) -> ((Int, Stores (t_0, t_1, t_2, t_3, t_4)) -> m a) -> m [a] Source #

(Store t_0, Store t_1, Store t_2, Store t_3, Store t_4, Store t_5) => Store (t_0, t_1, t_2, t_3, t_4, t_5) Source # 

Associated Types

type Stores (t_0, t_1, t_2, t_3, t_4, t_5) :: * Source #

type SafeRW (t_0, t_1, t_2, t_3, t_4, t_5) :: * Source #

Methods

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

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

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

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

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

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

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

initStore :: IO (t_0, t_1, t_2, t_3, t_4, t_5) Source #

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

explImapM_ :: MonadIO m => (t_0, t_1, t_2, t_3, t_4, t_5) -> (Int -> m a) -> m () Source #

explImapM :: MonadIO m => (t_0, t_1, t_2, t_3, t_4, t_5) -> (Int -> m a) -> m [a] Source #

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

explCmap :: (t_0, t_1, t_2, t_3, t_4, t_5) -> (Stores (t_0, t_1, t_2, t_3, t_4, t_5) -> Stores (t_0, t_1, t_2, t_3, t_4, t_5)) -> IO () Source #

explCmapM_ :: MonadIO m => (t_0, t_1, t_2, t_3, t_4, t_5) -> (Stores (t_0, t_1, t_2, t_3, t_4, t_5) -> m a) -> m () Source #

explCimapM_ :: MonadIO m => (t_0, t_1, t_2, t_3, t_4, t_5) -> ((Int, Stores (t_0, t_1, t_2, t_3, t_4, t_5)) -> m a) -> m () Source #

explCmapM :: MonadIO m => (t_0, t_1, t_2, t_3, t_4, t_5) -> (Stores (t_0, t_1, t_2, t_3, t_4, t_5) -> m a) -> m [a] Source #

explCimapM :: MonadIO m => (t_0, t_1, t_2, t_3, t_4, t_5) -> ((Int, Stores (t_0, t_1, t_2, t_3, t_4, t_5)) -> m a) -> m [a] Source #

class (SafeRW s ~ Stores s, Store s) => GlobalStore s Source #

Class of storages for global values

class Cast a b where Source #

Casts for entities and slices

Minimal complete definition

cast

Methods

cast :: a -> b Source #

Instances

Cast (Slice a) (Slice b) Source # 

Methods

cast :: Slice a -> Slice b Source #

Cast (Entity a) (Entity b) Source # 

Methods

cast :: Entity a -> Entity b Source #