| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Apecs.Types
- newtype Entity c = Entity Int
- newtype Slice c = Slice {}
- newtype System w a = System {}
- class Initializable (Storage c) => Component c where- type Storage c = s | s -> c
 
- class Component c => Has w c where
- class Initializable s where- type InitArgs s
 
- class HasMembers s where
- newtype Safe c = Safe {}
- class HasMembers s => Store s where
- type IsRuntime c = (Store (Storage c), Stores (Storage c) ~ c)
- class GlobalRW s c where
- class Cast a b where
Documentation
An Entity is really just an Int. The type variable is used to keep track of reads and writes, but can be freely cast.
A slice is a list of entities, represented by a Data.Unbox.Vector of Ints.
A system is a newtype around `ReaderT w IO a`, where w is the game world variable.
class Initializable (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 Initializable.
class Component c => Has w c where Source #
A world Has a component if it can produce its Storage
Minimal complete definition
class Initializable s where Source #
Common for every storage. Represents a container that can be initialized.
Minimal complete definition
Methods
initStoreWith :: InitArgs s -> IO s Source #
Instances
| Initializable (Global c) Source # | |
| Initializable (Unique c) Source # | |
| Initializable (Set c) Source # | |
| Initializable (Map c) Source # | |
| (Initializable a, Initializable b) => Initializable (a, b) Source # | |
| (KnownNat n, Cachable s) => Initializable (Cache n s) Source # | |
| (Log l (Stores s), Cachable s) => Initializable (Logger l s) Source # | |
| (Initializable a, Initializable b, Initializable c) => Initializable (a, b, c) Source # | |
class HasMembers s where Source #
A store that is indexed by entities.
Minimal complete definition
Methods
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
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
Instances
| HasMembers (Unique c) Source # | |
| HasMembers (Set c) Source # | |
| HasMembers (Map c) Source # | |
| (HasMembers a, HasMembers b) => HasMembers (a, b) Source # | |
| Cachable s => HasMembers (Cache n s) Source # | |
| (Log l (Stores s), Cachable s) => HasMembers (Logger l s) Source # | |
| (HasMembers a, HasMembers b, HasMembers c) => HasMembers (a, b, c) Source # | |
Represents a safe access to c. A safe access is either a read that might fail, or a write that might delete.
class HasMembers s => Store s where Source #
Class of storages that associates components with entities.
Minimal complete definition
Associated Types
Return type for safe reads writes to the store
The type of components stored by this Store
Methods
explGetUnsafe :: s -> Int -> IO (Stores s) Source #
Unsafe index to the store. Undefined if the component does not exist
explGet :: s -> Int -> IO (SafeRW s) Source #
Retrieves a component from the store
explSet :: s -> Int -> Stores s -> IO () Source #
Writes a component
explSetMaybe :: s -> Int -> SafeRW s -> IO () Source #
Either writes or deletes a component
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 #
type IsRuntime c = (Store (Storage c), Stores (Storage c) ~ c) Source #
A constraint that indicates that the runtime representation of c is c
   This will almost always be the case, but it _might_ not be so we need this constraint.
class GlobalRW s c where Source #
Class of storages for global values
Minimal complete definition
Methods
explGlobalRead :: s -> IO c Source #
explGlobalWrite :: s -> c -> IO () Source #
explGlobalModify :: s -> (c -> c) -> IO () Source #