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.Component

Description

Components are what hold data in an ECS system.

Synopsis

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 IsFlag c = 'False

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 Prop c :: Props Source #

Arity of the component. Defaults to Normal.

type Prop c = 'Normal

Methods

_ComponentFromXML :: String -> Prism' Element c Source #

A prism for serialising and deserialising the component as XML.

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 #

An AffineTraversal lookup of a given Entity's component. This probably should be in hs.

defaultValue :: c Source #

When the component is required, provide a default value.

Instances

Instances details
Component IsPrototype Source # 
Instance details

Defined in Games.ECS.Prototype

Associated Types

type CanonicalName IsPrototype 
Instance details

Defined in Games.ECS.Prototype

type CanonicalName IsPrototype = "isPrototype"
type IsFlag IsPrototype 
Instance details

Defined in Games.ECS.Prototype

type Storage IsPrototype 
Instance details

Defined in Games.ECS.Prototype

type Prop IsPrototype 
Instance details

Defined in Games.ECS.Prototype

Component SpawnedFromPrototype Source # 
Instance details

Defined in Games.ECS.Prototype.SpawnedFromPrototype

class Component c => CompositeComponent c where Source #

A component comprised of multiple other components.

Minimal complete definition

subComponentReferences

Associated Types

type SubComponentIndex c Source #

Methods

subComponentReferences :: IndexedFold (SubComponentIndex c) c Entity Source #

Look up the entity references of the subcomponents.

components Source #

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 => 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 (IntentComponent (Intent c), Component c) => CapabilityComponent c Source #

A component which indicates an ability to emit intents.

Associated Types

type Intent c Source #

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

Instances details
Generic (UniqueStore a) Source # 
Instance details

Defined in Games.ECS.Component

Associated Types

type Rep (UniqueStore a) 
Instance details

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

Methods

from :: UniqueStore a -> Rep (UniqueStore a) x #

to :: Rep (UniqueStore a) x -> UniqueStore a #

Show a => Show (UniqueStore a) Source # 
Instance details

Defined in Games.ECS.Component

Eq a => Eq (UniqueStore a) Source # 
Instance details

Defined in Games.ECS.Component

(Index (UniqueStore a) ~ Entity, IxValue (UniqueStore a) ~ a) => At (UniqueStore a) Source # 
Instance details

Defined in Games.ECS.Component

Ixed (UniqueStore a) Source # 
Instance details

Defined in Games.ECS.Component

AsEmpty (UniqueStore a) Source # 
Instance details

Defined in Games.ECS.Component

Methods

_Empty :: Prism' (UniqueStore a) () #

HasEntitySet (UniqueStore a) Source # 
Instance details

Defined in Games.ECS.Component

type Rep (UniqueStore a) Source # 
Instance details

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 # 
Instance details

Defined in Games.ECS.Component

type IxValue (UniqueStore a) Source # 
Instance details

Defined in Games.ECS.Component

type IxValue (UniqueStore a) = a

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 HasA (component :: k) (entity :: k1) = Has entity component Source #

data Hasn't (entity :: k) (component :: k1) Source #

Constructors

Hasn't 

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.

Constructors

Tagged 

Fields

Instances

Instances details
(Eq a, KnownSymbol name, KnownSymbol (AppendSymbol name "TaggedComponent wrapper"), XMLPickler [Node] a) => XMLPickler [Node] (TaggedComponent name (Maybe a)) Source # 
Instance details

Defined in Games.ECS.Component

Methods

xpickle :: PU [Node] (TaggedComponent name (Maybe a)) Source #

(KnownSymbol name, KnownSymbol (AppendSymbol name "TaggedComponent wrapper"), XMLPickler [Node] a) => XMLPickler [Node] (TaggedComponent name a) Source # 
Instance details

Defined in Games.ECS.Component

Methods

xpickle :: PU [Node] (TaggedComponent name a) Source #

(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.

Instance details

Defined in Games.ECS.Component

Methods

gxpicklef :: PU [Node] a0 -> PU [Node] (M1 D d (M1 C c'' (M1 S c (K1 i (TaggedComponent name (Maybe a)) :: Type -> Type))) a0) Source #

gxpickleContentsf :: PU [Node] a0 -> PU [Node] (M1 D d (M1 C c'' (M1 S c (K1 i (TaggedComponent name (Maybe a)) :: Type -> Type))) a0) Source #

Generic a => Generic (TaggedComponent name a) Source # 
Instance details

Defined in Games.ECS.Component

Associated Types

type Rep (TaggedComponent name a) 
Instance details

Defined in Games.ECS.Component

type Rep (TaggedComponent name a) = Rep a

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 # 
Instance details

Defined in Games.ECS.Component

Methods

showsPrec :: Int -> TaggedComponent name (Maybe a) -> ShowS #

show :: TaggedComponent name (Maybe a) -> String #

showList :: [TaggedComponent name (Maybe a)] -> ShowS #

Show a => Show (TaggedComponent name a) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Games.ECS.Component

type Rep (TaggedComponent name a) = Rep a

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".

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 #

storage :: Lens' (hkd acc) (Storage a a) Source #

Instances

Instances details
(HasType (Field name 'Individual 'Normal a) (hkd 'Individual), World hkd, Component a) => EntityProperty name hkd 'Individual 'Normal a Source # 
Instance details

Defined in Games.ECS.Component

(HasType (Field name 'Individual 'Required a) (hkd 'Individual), World hkd, Component a, Prop a ~ 'Required) => EntityProperty name hkd 'Individual 'Required a Source # 
Instance details

Defined in Games.ECS.Component

(HasType (Field name 'Individual 'Unique a) (hkd 'Individual), World hkd, Component a) => EntityProperty name hkd 'Individual 'Unique a Source # 
Instance details

Defined in Games.ECS.Component

(Storage a a ~ UniqueStore a, HasType (Field name 'Storing 'Unique a) (hkd 'Storing), World hkd, Component a) => EntityProperty name hkd 'Storing 'Unique a Source # 
Instance details

Defined in Games.ECS.Component

(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 # 
Instance details

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 #

storage :: Lens' (hkd 'Storing) (Storage a a) Source #

Orphan instances

(EntityProperty name hkd acc p a, accessorType ~ OpticsFor name hkd acc p a) => IsLabel name accessorType Source # 
Instance details

Methods

fromLabel :: accessorType #