ohhecs-0.0.2: An Entity-Component-Systems engine core.
Copyright(C) 2020 Sophie Taylor
LicenseAGPL-3.0-or-later
MaintainerSophie Taylor <sophie@spacekitteh.moe>
Stabilityexperimental
PortabilityGHC
Safe HaskellTrustworthy
LanguageGHC2021

Games.ECS.Component.Store

Description

Different components, when stored in bulk, may be suited to different collection types.

Synopsis

Documentation

class EntityIndexedTraversable (t :: Type -> Type) c where Source #

A class for types which contain objects which are indexed by an Entity.

Minimal complete definition

Nothing

data InternedComponentStore c Source #

Some components may be shared in common among a large number of entities, and may be expensive to compare for equality. This type can be used to store them efficiently by keeping only a single example around.

Instances

Instances details
Generic1 InternedComponentStore Source # 
Instance details

Defined in Games.ECS.Component.Store

Associated Types

type Rep1 InternedComponentStore 
Instance details

Defined in Games.ECS.Component.Store

Uninternable (InternedComponent c) => EntityIndexedTraversable InternedComponentStore c Source # 
Instance details

Defined in Games.ECS.Component.Store

Generic (InternedComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

Associated Types

type Rep (InternedComponentStore c) 
Instance details

Defined in Games.ECS.Component.Store

Show c => Show (InternedComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

Eq (InternedComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

(Eq c, Hashable c) => At (InternedComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

(Eq c, Hashable c) => Ixed (InternedComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

AsEmpty (InternedComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

HasEntitySet (InternedComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

type Rep1 InternedComponentStore Source # 
Instance details

Defined in Games.ECS.Component.Store

type Rep (InternedComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

type Index (InternedComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

type IxValue (InternedComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

data ComponentStore c Source #

An IntMap-based Component store

Instances

Instances details
Foldable ComponentStore Source # 
Instance details

Defined in Games.ECS.Component.Store

Methods

fold :: Monoid m => ComponentStore m -> m #

foldMap :: Monoid m => (a -> m) -> ComponentStore a -> m #

foldMap' :: Monoid m => (a -> m) -> ComponentStore a -> m #

foldr :: (a -> b -> b) -> b -> ComponentStore a -> b #

foldr' :: (a -> b -> b) -> b -> ComponentStore a -> b #

foldl :: (b -> a -> b) -> b -> ComponentStore a -> b #

foldl' :: (b -> a -> b) -> b -> ComponentStore a -> b #

foldr1 :: (a -> a -> a) -> ComponentStore a -> a #

foldl1 :: (a -> a -> a) -> ComponentStore a -> a #

toList :: ComponentStore a -> [a] #

null :: ComponentStore a -> Bool #

length :: ComponentStore a -> Int #

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

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

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

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

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

Traversable ComponentStore Source # 
Instance details

Defined in Games.ECS.Component.Store

Methods

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

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

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

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

Functor ComponentStore Source # 
Instance details

Defined in Games.ECS.Component.Store

Methods

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

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

Generic1 ComponentStore Source # 
Instance details

Defined in Games.ECS.Component.Store

Associated Types

type Rep1 ComponentStore 
Instance details

Defined in Games.ECS.Component.Store

type Rep1 ComponentStore = D1 ('MetaData "ComponentStore" "Games.ECS.Component.Store" "ohhecs-0.0.2-inplace" 'False) (C1 ('MetaCons "ComponentStore" 'PrefixI 'True) (S1 ('MetaSel ('Just "_theMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 IntMap) :*: S1 ('MetaSel ('Just "_theKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EntitySet)))
FoldableWithIndex Entity ComponentStore Source # 
Instance details

Defined in Games.ECS.Component.Store

Methods

ifoldMap :: Monoid m => (Entity -> a -> m) -> ComponentStore a -> m #

ifoldMap' :: Monoid m => (Entity -> a -> m) -> ComponentStore a -> m #

ifoldr :: (Entity -> a -> b -> b) -> b -> ComponentStore a -> b #

ifoldl :: (Entity -> b -> a -> b) -> b -> ComponentStore a -> b #

ifoldr' :: (Entity -> a -> b -> b) -> b -> ComponentStore a -> b #

ifoldl' :: (Entity -> b -> a -> b) -> b -> ComponentStore a -> b #

FunctorWithIndex Entity ComponentStore Source # 
Instance details

Defined in Games.ECS.Component.Store

Methods

imap :: (Entity -> a -> b) -> ComponentStore a -> ComponentStore b #

TraversableWithIndex Entity ComponentStore Source # 
Instance details

Defined in Games.ECS.Component.Store

Methods

itraverse :: Applicative f => (Entity -> a -> f b) -> ComponentStore a -> f (ComponentStore b) #

EntityIndexedTraversable ComponentStore c Source # 
Instance details

Defined in Games.ECS.Component.Store

Generic (ComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

Associated Types

type Rep (ComponentStore c) 
Instance details

Defined in Games.ECS.Component.Store

type Rep (ComponentStore c) = D1 ('MetaData "ComponentStore" "Games.ECS.Component.Store" "ohhecs-0.0.2-inplace" 'False) (C1 ('MetaCons "ComponentStore" 'PrefixI 'True) (S1 ('MetaSel ('Just "_theMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IntMap c)) :*: S1 ('MetaSel ('Just "_theKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EntitySet)))
Show c => Show (ComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

Eq c => Eq (ComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

At (ComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

Ixed (ComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

AsEmpty (ComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

Methods

_Empty :: Prism' (ComponentStore c) () #

HasEntitySet (ComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

type Rep1 ComponentStore Source # 
Instance details

Defined in Games.ECS.Component.Store

type Rep1 ComponentStore = D1 ('MetaData "ComponentStore" "Games.ECS.Component.Store" "ohhecs-0.0.2-inplace" 'False) (C1 ('MetaCons "ComponentStore" 'PrefixI 'True) (S1 ('MetaSel ('Just "_theMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 IntMap) :*: S1 ('MetaSel ('Just "_theKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EntitySet)))
type Rep (ComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

type Rep (ComponentStore c) = D1 ('MetaData "ComponentStore" "Games.ECS.Component.Store" "ohhecs-0.0.2-inplace" 'False) (C1 ('MetaCons "ComponentStore" 'PrefixI 'True) (S1 ('MetaSel ('Just "_theMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IntMap c)) :*: S1 ('MetaSel ('Just "_theKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EntitySet)))
type Index (ComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

type IxValue (ComponentStore c) Source # 
Instance details

Defined in Games.ECS.Component.Store

type IxValue (ComponentStore c) = c

data EntitySet Source #

An efficient storage for a collection of entities.

theKeys :: forall c f. Functor f => (EntitySet -> f EntitySet) -> ComponentStore c -> f (ComponentStore c) Source #

theMap :: forall c1 c2 f. Functor f => (IntMap c1 -> f (IntMap c2)) -> ComponentStore c1 -> f (ComponentStore c2) Source #

theInternedMap :: forall c1 c2 f. Functor f => (IntMap (InternedComponent c1) -> f (IntMap (InternedComponent c2))) -> InternedComponentStore c1 -> f (InternedComponentStore c2) Source #

data IntersectionOfEntities Source #

A helper Monoid for selecting entities which satisfy multiple predicates.