Copyright | (C) 2020 Sophie Taylor |
---|---|
License | AGPL-3.0-or-later |
Maintainer | Sophie Taylor <sophie@spacekitteh.moe> |
Stability | experimental |
Portability | GHC |
Safe Haskell | Trustworthy |
Language | GHC2021 |
Games.ECS.Component.Store
Description
Different components, when stored in bulk, may be suited to different collection types.
Synopsis
- class EntityIndexedTraversable (t :: Type -> Type) c where
- entitiesTraversed :: IndexedTraversal' Entity (t c) c
- data InternedComponentStore c
- data ComponentStore c
- data EntitySet
- theKeys :: forall c f. Functor f => (EntitySet -> f EntitySet) -> ComponentStore c -> f (ComponentStore c)
- theMap :: forall c1 c2 f. Functor f => (IntMap c1 -> f (IntMap c2)) -> ComponentStore c1 -> f (ComponentStore c2)
- theInternedMap :: forall c1 c2 f. Functor f => (IntMap (InternedComponent c1) -> f (IntMap (InternedComponent c2))) -> InternedComponentStore c1 -> f (InternedComponentStore c2)
- data IntersectionOfEntities
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
Methods
entitiesTraversed :: IndexedTraversal' Entity (t c) c Source #
Traverse the collection.
default entitiesTraversed :: TraversableWithIndex Entity t => IndexedTraversal' Entity (t c) c Source #
Instances
EntityIndexedTraversable ComponentStore c Source # | |
Defined in Games.ECS.Component.Store Methods entitiesTraversed :: IndexedTraversal' Entity (ComponentStore c) c Source # | |
Uninternable (InternedComponent c) => EntityIndexedTraversable InternedComponentStore c Source # | |
Defined in Games.ECS.Component.Store Methods entitiesTraversed :: IndexedTraversal' Entity (InternedComponentStore c) c Source # |
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
data ComponentStore c Source #
Instances
Foldable ComponentStore Source # | |||||
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 # | |||||
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 # | |||||
Defined in Games.ECS.Component.Store Methods fmap :: (a -> b) -> ComponentStore a -> ComponentStore b # (<$) :: a -> ComponentStore b -> ComponentStore a # | |||||
Generic1 ComponentStore Source # | |||||
Defined in Games.ECS.Component.Store Associated Types
Methods from1 :: ComponentStore a -> Rep1 ComponentStore a # to1 :: Rep1 ComponentStore a -> ComponentStore a # | |||||
FoldableWithIndex Entity ComponentStore Source # | |||||
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 # | |||||
Defined in Games.ECS.Component.Store Methods imap :: (Entity -> a -> b) -> ComponentStore a -> ComponentStore b # | |||||
TraversableWithIndex Entity ComponentStore Source # | |||||
Defined in Games.ECS.Component.Store Methods itraverse :: Applicative f => (Entity -> a -> f b) -> ComponentStore a -> f (ComponentStore b) # | |||||
EntityIndexedTraversable ComponentStore c Source # | |||||
Defined in Games.ECS.Component.Store Methods entitiesTraversed :: IndexedTraversal' Entity (ComponentStore c) c Source # | |||||
Generic (ComponentStore c) Source # | |||||
Defined in Games.ECS.Component.Store Associated Types
Methods from :: ComponentStore c -> Rep (ComponentStore c) x # to :: Rep (ComponentStore c) x -> ComponentStore c # | |||||
Show c => Show (ComponentStore c) Source # | |||||
Defined in Games.ECS.Component.Store Methods showsPrec :: Int -> ComponentStore c -> ShowS # show :: ComponentStore c -> String # showList :: [ComponentStore c] -> ShowS # | |||||
Eq c => Eq (ComponentStore c) Source # | |||||
Defined in Games.ECS.Component.Store Methods (==) :: ComponentStore c -> ComponentStore c -> Bool # (/=) :: ComponentStore c -> ComponentStore c -> Bool # | |||||
At (ComponentStore c) Source # | |||||
Defined in Games.ECS.Component.Store Methods at :: Index (ComponentStore c) -> Lens' (ComponentStore c) (Maybe (IxValue (ComponentStore c))) # | |||||
Ixed (ComponentStore c) Source # | |||||
Defined in Games.ECS.Component.Store Methods ix :: Index (ComponentStore c) -> Traversal' (ComponentStore c) (IxValue (ComponentStore c)) # | |||||
AsEmpty (ComponentStore c) Source # | |||||
Defined in Games.ECS.Component.Store Methods _Empty :: Prism' (ComponentStore c) () # | |||||
HasEntitySet (ComponentStore c) Source # | |||||
Defined in Games.ECS.Component.Store | |||||
type Rep1 ComponentStore Source # | |||||
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 # | |||||
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 # | |||||
Defined in Games.ECS.Component.Store | |||||
type IxValue (ComponentStore c) Source # | |||||
Defined in Games.ECS.Component.Store |
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.
Instances
Monoid IntersectionOfEntities Source # | |
Defined in Games.ECS.Entity | |
Semigroup IntersectionOfEntities Source # | |
Defined in Games.ECS.Entity Methods (<>) :: IntersectionOfEntities -> IntersectionOfEntities -> IntersectionOfEntities # sconcat :: NonEmpty IntersectionOfEntities -> IntersectionOfEntities # stimes :: Integral b => b -> IntersectionOfEntities -> IntersectionOfEntities # | |
Show IntersectionOfEntities Source # | |
Defined in Games.ECS.Entity Methods showsPrec :: Int -> IntersectionOfEntities -> ShowS # show :: IntersectionOfEntities -> String # showList :: [IntersectionOfEntities] -> ShowS # | |
Eq IntersectionOfEntities Source # | |
Defined in Games.ECS.Entity Methods (==) :: IntersectionOfEntities -> IntersectionOfEntities -> Bool # (/=) :: IntersectionOfEntities -> IntersectionOfEntities -> Bool # | |
HasEntitySet IntersectionOfEntities Source # | |
Defined in Games.ECS.Entity | |
IsEntityStore IntersectionOfEntities Source # | |
Defined in Games.ECS.Entity |