Copyright | (C) 2020 Sophie Taylor |
---|---|
License | AGPL-3.0-or-later |
Maintainer | Sophie Taylor <sophie@spacekitteh.moe> |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | GHC2021 |
Games.ECS.Component
Contents
Description
Components are what hold data in an ECS system.
Synopsis
- class PseudoComponent (c :: k)
- class (AsEmpty (Storage c c), KnownSymbol (CanonicalName c), At (Storage c c), Index (Storage c c) ~ Entity, HasEntitySet (Storage c c)) => Component c where
- type CanonicalName c :: Symbol
- type IsFlag c :: Bool
- type Storage c :: Type -> Type
- type Prop c :: Props
- _ComponentFromXML :: String -> Prism' Element c
- entityKeys :: Fold (Storage c c) EntitySet
- emptyStorage :: Storage c c
- entityHasComponent :: Entity -> IndexedTraversal' Entity (Storage c c) c
- defaultValue :: c
- type ComponentReference (name :: Symbol) c = Component c => TaggedComponent name Entity
- class Component c => CompositeComponent c where
- type SubComponentIndex c
- subComponentReferences :: IndexedFold (SubComponentIndex c) c Entity
- components :: forall p f worldType. (World worldType, Indexable (SubComponentIndex c) p, Applicative f) => c -> p (worldType 'Individual) (f (worldType 'Individual)) -> worldType 'Storing -> f (worldType 'Storing)
- class Component c => SensoryComponent c
- class Component c => EffectorComponent c
- class Component c => AttributeComponent c
- class Component c => FlagComponent c
- class Component c => IntentComponent c
- class Component c => ReferenceComponent c
- class (IntentComponent (Intent c), Component c) => CapabilityComponent c where
- type Intent c
- newtype UniqueStore a = UniqueStore (Maybe (Entity, a))
- data Has (entity :: k) (component :: k1) = Has
- type HasA (component :: k) (entity :: k1) = Has entity component
- data Hasn't (entity :: k) (component :: k1) = Hasn't
- type AComponent (name :: Symbol) (s :: Access) a = Field name s (Prop a) a
- newtype TaggedComponent (name :: k) a = Tagged {
- unTagged :: a
- untag :: forall {k} (name :: k) a. TaggedComponent name a -> a
- type family Field (name :: Symbol) (acc :: Access) (p :: Props) a where ...
- class EntityProperty (name :: Symbol) (hkd :: Access -> Type) (acc :: Access) (p :: Props) a where
- accessor :: OpticsFor name hkd acc p a
- injectToField :: a -> Field name 'Individual p a
- maybeGet :: Field name 'Individual p a -> Maybe a
- injectMaybe :: Maybe a -> Field name 'Individual p a
- defaultField :: Field name 'Individual p a
- defaultStorage :: Field name 'Storing p a
- storage :: Lens' (hkd acc) (Storage a a)
Documentation
class PseudoComponent (c :: k) Source #
class (AsEmpty (Storage c c), KnownSymbol (CanonicalName c), At (Storage c c), Index (Storage c c) ~ Entity, HasEntitySet (Storage c c)) => Component c where Source #
A component represented in the entity component system.
Minimal complete definition
Nothing
Associated Types
type CanonicalName c :: Symbol Source #
What to name accessors if the type name isn't ergonomic.
type IsFlag c :: Bool Source #
Is the type a flag component?
type Storage c :: Type -> Type Source #
What datatype to store all instances of a component in. Allows for a generalisation of
"Structure-of-Arrays". Defaults to HashMap
.
type Storage c = ComponentStore
Arity of the component. Defaults to Normal
.
Methods
_ComponentFromXML :: String -> Prism' Element c Source #
A prism for serialising and deserialising the component as XML.
default _ComponentFromXML :: XMLSerialise c => String -> Prism' Element c Source #
entityKeys :: Fold (Storage c c) EntitySet Source #
The collection of entities held in storage.
emptyStorage :: Storage c c Source #
Construct new storage.
entityHasComponent :: Entity -> IndexedTraversal' Entity (Storage c c) c Source #
default entityHasComponent :: IxValue (Storage c c) ~ c => Entity -> IndexedTraversal' Entity (Storage c c) c Source #
defaultValue :: c Source #
When the component is required, provide a default value.
Instances
type ComponentReference (name :: Symbol) c = Component c => TaggedComponent name Entity Source #
class Component c => CompositeComponent c where Source #
A component comprised of multiple other components.
Minimal complete definition
Associated Types
type SubComponentIndex c Source #
Methods
subComponentReferences :: IndexedFold (SubComponentIndex c) c Entity Source #
Look up the entity references of the subcomponents.
Arguments
:: forall p f worldType. (World worldType, Indexable (SubComponentIndex c) p, Applicative f) | |
=> c | The composite component |
-> p (worldType 'Individual) (f (worldType 'Individual)) | |
-> worldType 'Storing | |
-> f (worldType 'Storing) |
An IndexedTraversal' of the subcomponents of a composite component.
class Component c => SensoryComponent c Source #
Indicates a component behaves like a sensor.
class Component c => EffectorComponent c Source #
Indicates that a component can perform actions in the world.
class Component c => AttributeComponent c Source #
class Component c => FlagComponent c Source #
Indicates whether a component is a simple Boolean flag.
class Component c => IntentComponent c Source #
A component representing an intent to do something.
class Component c => ReferenceComponent c Source #
class (IntentComponent (Intent c), Component c) => CapabilityComponent c Source #
A component which indicates an ability to emit intents.
newtype UniqueStore a Source #
Storage for Unique
components. As a Unique
component will have, at most, a single instance in the world, we only need to store the component and its Entity
naively.
Constructors
UniqueStore (Maybe (Entity, a)) |
Instances
Generic (UniqueStore a) Source # | |||||
Defined in Games.ECS.Component Associated Types
Methods from :: UniqueStore a -> Rep (UniqueStore a) x # to :: Rep (UniqueStore a) x -> UniqueStore a # | |||||
Show a => Show (UniqueStore a) Source # | |||||
Defined in Games.ECS.Component Methods showsPrec :: Int -> UniqueStore a -> ShowS # show :: UniqueStore a -> String # showList :: [UniqueStore a] -> ShowS # | |||||
Eq a => Eq (UniqueStore a) Source # | |||||
Defined in Games.ECS.Component Methods (==) :: UniqueStore a -> UniqueStore a -> Bool # (/=) :: UniqueStore a -> UniqueStore a -> Bool # | |||||
(Index (UniqueStore a) ~ Entity, IxValue (UniqueStore a) ~ a) => At (UniqueStore a) Source # | |||||
Defined in Games.ECS.Component Methods at :: Index (UniqueStore a) -> Lens' (UniqueStore a) (Maybe (IxValue (UniqueStore a))) # | |||||
Ixed (UniqueStore a) Source # | |||||
Defined in Games.ECS.Component Methods ix :: Index (UniqueStore a) -> Traversal' (UniqueStore a) (IxValue (UniqueStore a)) # | |||||
AsEmpty (UniqueStore a) Source # | |||||
Defined in Games.ECS.Component Methods _Empty :: Prism' (UniqueStore a) () # | |||||
HasEntitySet (UniqueStore a) Source # | |||||
Defined in Games.ECS.Component | |||||
type Rep (UniqueStore a) Source # | |||||
Defined in Games.ECS.Component type Rep (UniqueStore a) = D1 ('MetaData "UniqueStore" "Games.ECS.Component" "ohhecs-0.0.2-inplace" 'True) (C1 ('MetaCons "UniqueStore" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Entity, a))))) | |||||
type Index (UniqueStore a) Source # | |||||
Defined in Games.ECS.Component | |||||
type IxValue (UniqueStore a) Source # | |||||
Defined in Games.ECS.Component |
data Has (entity :: k) (component :: k1) Source #
This is an unlawful instance due to entityHasComponent
allowing write-back.
FIXME: Write a valid definition of entityHasComponent, or make it only a psuedocomponent.
instance Component Entity where
type Prop Entity = Required
Constructors
Has |
type AComponent (name :: Symbol) (s :: Access) a = Field name s (Prop a) a Source #
Simplified type signature to use in world definitions.
newtype TaggedComponent (name :: k) a Source #
A component with an arbitrary name tag.
Instances
(Eq a, KnownSymbol name, KnownSymbol (AppendSymbol name "TaggedComponent wrapper"), XMLPickler [Node] a) => XMLPickler [Node] (TaggedComponent name (Maybe a)) Source # | |||||
Defined in Games.ECS.Component | |||||
(KnownSymbol name, KnownSymbol (AppendSymbol name "TaggedComponent wrapper"), XMLPickler [Node] a) => XMLPickler [Node] (TaggedComponent name a) Source # | |||||
Defined in Games.ECS.Component | |||||
(KnownSymbol name, XMLPickler [Node] a, Datatype d, ty ~ M1 D d (M1 C c'' (M1 S c (K1 i a :: k -> Type)))) => GXmlPickler [Node] (M1 D d (M1 C c'' (M1 S c (K1 i (TaggedComponent name (Maybe a)) :: Type -> Type)))) Source # | An instance for wrapper components. Don't bother with the wrapper constructor or fieldname; just the wrapped data. | ||||
Defined in Games.ECS.Component | |||||
Generic a => Generic (TaggedComponent name a) Source # | |||||
Defined in Games.ECS.Component Associated Types
Methods from :: TaggedComponent name a -> Rep (TaggedComponent name a) x # to :: Rep (TaggedComponent name a) x -> TaggedComponent name a # | |||||
Show a => Show (TaggedComponent name (Maybe a)) Source # | |||||
Defined in Games.ECS.Component | |||||
Show a => Show (TaggedComponent name a) Source # | |||||
Defined in Games.ECS.Component Methods showsPrec :: Int -> TaggedComponent name a -> ShowS # show :: TaggedComponent name a -> String # showList :: [TaggedComponent name a] -> ShowS # | |||||
Eq a => Eq (TaggedComponent name a) Source # | |||||
Defined in Games.ECS.Component Methods (==) :: TaggedComponent name a -> TaggedComponent name a -> Bool # (/=) :: TaggedComponent name a -> TaggedComponent name a -> Bool # | |||||
Ord a => Ord (TaggedComponent name a) Source # | |||||
Defined in Games.ECS.Component Methods compare :: TaggedComponent name a -> TaggedComponent name a -> Ordering # (<) :: TaggedComponent name a -> TaggedComponent name a -> Bool # (<=) :: TaggedComponent name a -> TaggedComponent name a -> Bool # (>) :: TaggedComponent name a -> TaggedComponent name a -> Bool # (>=) :: TaggedComponent name a -> TaggedComponent name a -> Bool # max :: TaggedComponent name a -> TaggedComponent name a -> TaggedComponent name a # min :: TaggedComponent name a -> TaggedComponent name a -> TaggedComponent name a # | |||||
type Rep (TaggedComponent name a) Source # | |||||
Defined in Games.ECS.Component |
untag :: forall {k} (name :: k) a. TaggedComponent name a -> a Source #
Get the raw component.
type family Field (name :: Symbol) (acc :: Access) (p :: Props) a where ... Source #
The core mechanics of the higher-kinded representation for the ECS system.
Equations
Field name 'Individual 'Required a = TaggedComponent name a | |
Field name 'Individual 'Normal a = TaggedComponent name (Maybe a) | |
Field name 'Individual 'Unique a = TaggedComponent name (Maybe a) | |
Field name 'Storing 'Unique a = TaggedComponent name (UniqueStore a) | |
Field name 'Storing 'Required a = TaggedComponent name (Storage a a) | |
Field name 'Storing 'Normal a = TaggedComponent name (Storage a a) |
class EntityProperty (name :: Symbol) (hkd :: Access -> Type) (acc :: Access) (p :: Props) a where Source #
Plumbing class for a higher-kinded data representation of a game world. | Generalisation of "Array of Structures" vs "Structure of Arrays".
Minimal complete definition
accessor, injectToField, maybeGet, defaultField, defaultStorage, storage
Methods
accessor :: OpticsFor name hkd acc p a Source #
injectToField :: a -> Field name 'Individual p a Source #
maybeGet :: Field name 'Individual p a -> Maybe a Source #
injectMaybe :: Maybe a -> Field name 'Individual p a Source #
defaultField :: Field name 'Individual p a Source #
defaultStorage :: Field name 'Storing p a Source #
Instances
(HasType (Field name 'Individual 'Normal a) (hkd 'Individual), World hkd, Component a) => EntityProperty name hkd 'Individual 'Normal a Source # | |
Defined in Games.ECS.Component Methods accessor :: OpticsFor name hkd 'Individual 'Normal a Source # injectToField :: a -> Field name 'Individual 'Normal a Source # maybeGet :: Field name 'Individual 'Normal a -> Maybe a Source # injectMaybe :: Maybe a -> Field name 'Individual 'Normal a Source # defaultField :: Field name 'Individual 'Normal a Source # | |
(HasType (Field name 'Individual 'Required a) (hkd 'Individual), World hkd, Component a, Prop a ~ 'Required) => EntityProperty name hkd 'Individual 'Required a Source # | |
Defined in Games.ECS.Component Methods accessor :: OpticsFor name hkd 'Individual 'Required a Source # injectToField :: a -> Field name 'Individual 'Required a Source # maybeGet :: Field name 'Individual 'Required a -> Maybe a Source # injectMaybe :: Maybe a -> Field name 'Individual 'Required a Source # defaultField :: Field name 'Individual 'Required a Source # | |
(HasType (Field name 'Individual 'Unique a) (hkd 'Individual), World hkd, Component a) => EntityProperty name hkd 'Individual 'Unique a Source # | |
Defined in Games.ECS.Component Methods accessor :: OpticsFor name hkd 'Individual 'Unique a Source # injectToField :: a -> Field name 'Individual 'Unique a Source # maybeGet :: Field name 'Individual 'Unique a -> Maybe a Source # injectMaybe :: Maybe a -> Field name 'Individual 'Unique a Source # defaultField :: Field name 'Individual 'Unique a Source # | |
(Storage a a ~ UniqueStore a, HasType (Field name 'Storing 'Unique a) (hkd 'Storing), World hkd, Component a) => EntityProperty name hkd 'Storing 'Unique a Source # | |
Defined in Games.ECS.Component Methods accessor :: OpticsFor name hkd 'Storing 'Unique a Source # injectToField :: a -> Field name 'Individual 'Unique a Source # maybeGet :: Field name 'Individual 'Unique a -> Maybe a Source # injectMaybe :: Maybe a -> Field name 'Individual 'Unique a Source # defaultField :: Field name 'Individual 'Unique a Source # | |
(OpticsFor name hkd 'Storing prop a ~ ReifiedIndexedTraversal' Entity (hkd 'Storing) a, HasType (Field name 'Storing prop a) (hkd 'Storing), EntityIndexedTraversable (Storage a) a, World hkd, Component a, Coercible (Field name 'Storing prop a) (Storage a a), Field name 'Storing prop a ~ TaggedComponent name (Storage a a)) => EntityProperty name hkd 'Storing prop a Source # | |
Defined in Games.ECS.Component Methods accessor :: OpticsFor name hkd 'Storing prop a Source # injectToField :: a -> Field name 'Individual prop a Source # maybeGet :: Field name 'Individual prop a -> Maybe a Source # injectMaybe :: Maybe a -> Field name 'Individual prop a Source # defaultField :: Field name 'Individual prop a Source # defaultStorage :: Field name 'Storing prop a Source # |