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 HaskellNone
LanguageGHC2021

Games.ECS.Entity

Description

In an ECS, an entity is understood in two senses:

  1. An identifying token, used to specify an individual, and
  2. The individual it refers to, that is, the set of components it has.

Here, we implement entities in the first sense.

Synopsis

Documentation

newtype Entity Source #

A reference to an entity in the ECS.

Constructors

EntRef 

Fields

Instances

Instances details
Bounded Entity Source # 
Instance details

Defined in Games.ECS.Entity

Enum Entity Source # 
Instance details

Defined in Games.ECS.Entity

Generic Entity Source # 
Instance details

Defined in Games.ECS.Entity

Associated Types

type Rep Entity 
Instance details

Defined in Games.ECS.Entity

type Rep Entity = D1 ('MetaData "Entity" "Games.ECS.Entity" "ohhecs-0.0.2-inplace" 'True) (C1 ('MetaCons "EntRef" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEntRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

Methods

from :: Entity -> Rep Entity x #

to :: Rep Entity x -> Entity #

Ix Entity Source # 
Instance details

Defined in Games.ECS.Entity

Show Entity Source # 
Instance details

Defined in Games.ECS.Entity

Eq Entity Source # 
Instance details

Defined in Games.ECS.Entity

Methods

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

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

Ord Entity Source # 
Instance details

Defined in Games.ECS.Entity

Hashable Entity Source #

We reverse the byte order, just so there is a bit more variance between hashes.

Instance details

Defined in Games.ECS.Entity

Methods

hashWithSalt :: Int -> Entity -> Int #

hash :: Entity -> Int #

HasEntityReferences Entity Source # 
Instance details

Defined in Games.ECS.Entity

XMLPickleAsAttribute Entity Source # 
Instance details

Defined in Games.ECS.Entity

Unbox Entity Source # 
Instance details

Defined in Games.ECS.Entity

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) #

Vector Vector Entity Source # 
Instance details

Defined in Games.ECS.Entity

MVector MVector Entity Source # 
Instance details

Defined in Games.ECS.Entity

IsEntityStore (HashSet Entity) Source # 
Instance details

Defined in Games.ECS.Entity

XMLPickler [Node] Entity Source # 
Instance details

Defined in Games.ECS.Entity

XMLPickler [Node] v => XMLPickler [Node] (HashMap Entity v) Source # 
Instance details

Defined in Games.ECS.Entity

Methods

xpickle :: PU [Node] (HashMap Entity v) Source #

(Constructor c'', ty ~ M1 C c'' (M1 S c (K1 i Entity :: k -> Type))) => GXmlPickler [Node] (M1 C c'' (M1 S c (K1 i Entity :: Type -> Type))) Source #

An instance for constructors which only contain an entity reference; we put that as an attribute.

Instance details

Defined in Games.ECS.Entity

Methods

gxpicklef :: PU [Node] a -> PU [Node] (M1 C c'' (M1 S c (K1 i Entity :: Type -> Type)) a) Source #

gxpickleContentsf :: PU [Node] a -> PU [Node] (M1 C c'' (M1 S c (K1 i Entity :: Type -> Type)) a) Source #

type Rep Entity Source # 
Instance details

Defined in Games.ECS.Entity

type Rep Entity = D1 ('MetaData "Entity" "Games.ECS.Entity" "ohhecs-0.0.2-inplace" 'True) (C1 ('MetaCons "EntRef" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEntRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
newtype Vector Entity Source # 
Instance details

Defined in Games.ECS.Entity

newtype MVector s Entity Source # 
Instance details

Defined in Games.ECS.Entity

class HasEntityReferences c where Source #

A helper class for finding embedded entity references in components.

Instances

Instances details
HasEntityReferences Entity Source # 
Instance details

Defined in Games.ECS.Entity

HasEntityReferences EntitySet Source # 
Instance details

Defined in Games.ECS.Entity

newtype EntitySet Source #

An efficient storage for a collection of entities.

Constructors

EntitySet IntSet 

theEntitySet :: Iso' EntitySet IntSet Source #

Access the underlying IntSet.

singletonEntitySet :: Entity -> EntitySet Source #

Construct a new EntitySet with a given Entity.

asIntersection :: Iso' IntersectionOfEntities EntitySet Source #

Helper Iso' for selecting entities which satisfy predicates.

newtype IntersectionOfEntities Source #

A helper Monoid for selecting entities which satisfy multiple predicates.

Constructors

Intersect IntSet