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.Prototype
Description
Prototypes are exemplar individuals which form a template.
Synopsis
- newtype PrototypeID = PrototypeID {}
- class HasPrototypeID c where
- prototypeID :: Lens' c PrototypeID
- unPrototypeID :: Lens' c Int
- data IsPrototype = IsPrototype {}
- extendsPrototype :: Lens' IsPrototype (Maybe PrototypeID)
- rawIsPrototypeID :: Lens' IsPrototype PrototypeID
- data SpawnedFromPrototype = SpawnedFromPrototype {}
- prototypeEntity :: Lens' SpawnedFromPrototype Entity
- spawnedFromPrototypeID :: Lens' SpawnedFromPrototype (Maybe PrototypeID)
- type UsingIsPrototype (worldType :: Access -> Type) (s :: Access) = (HasIsPrototype worldType, EntityProperty "isPrototype" worldType s (Prop IsPrototype) IsPrototype, OpticsFor "isPrototype" worldType s (Prop IsPrototype) IsPrototype ~ ReifiedIndexedTraversal' Entity (worldType s) IsPrototype)
- class (World worldType, Component IsPrototype, EntityProperty "isPrototype" worldType 'Individual (Prop IsPrototype) IsPrototype, OpticsFor "isPrototype" worldType 'Storing (Prop IsPrototype) IsPrototype ~ ReifiedIndexedTraversal' Entity (worldType 'Storing) IsPrototype) => HasIsPrototype (worldType :: Access -> Type) where
- isPrototype :: forall {s :: Access}. (EntityProperty "isPrototype" worldType s (Prop IsPrototype) IsPrototype, OpticsFor "isPrototype" worldType s (Prop IsPrototype) IsPrototype ~ ReifiedIndexedTraversal' Entity (worldType s) IsPrototype) => IndexedTraversal' Entity (worldType s) IsPrototype
- addIsPrototype :: IndexedSetter' Entity (worldType 'Individual) IsPrototype
- removeIsPrototype :: worldType 'Individual -> worldType 'Individual
- withIsPrototype :: Fold (worldType 'Storing) IntersectionOfEntities
- type UsingSpawnedFromPrototype (worldType :: Access -> Type) (s :: Access) = (HasSpawnedFromPrototype worldType, EntityProperty "spawnedFromPrototype" worldType s (Prop SpawnedFromPrototype) SpawnedFromPrototype, OpticsFor "spawnedFromPrototype" worldType s (Prop SpawnedFromPrototype) SpawnedFromPrototype ~ ReifiedIndexedTraversal' Entity (worldType s) SpawnedFromPrototype)
- class (World worldType, Component SpawnedFromPrototype, EntityProperty "spawnedFromPrototype" worldType 'Individual (Prop SpawnedFromPrototype) SpawnedFromPrototype, OpticsFor "spawnedFromPrototype" worldType 'Storing (Prop SpawnedFromPrototype) SpawnedFromPrototype ~ ReifiedIndexedTraversal' Entity (worldType 'Storing) SpawnedFromPrototype) => HasSpawnedFromPrototype (worldType :: Access -> Type) where
- spawnedFromPrototype :: forall {s :: Access}. (EntityProperty "spawnedFromPrototype" worldType s (Prop SpawnedFromPrototype) SpawnedFromPrototype, OpticsFor "spawnedFromPrototype" worldType s (Prop SpawnedFromPrototype) SpawnedFromPrototype ~ ReifiedIndexedTraversal' Entity (worldType s) SpawnedFromPrototype) => IndexedTraversal' Entity (worldType s) SpawnedFromPrototype
- addSpawnedFromPrototype :: IndexedSetter' Entity (worldType 'Individual) SpawnedFromPrototype
- removeSpawnedFromPrototype :: worldType 'Individual -> worldType 'Individual
- withSpawnedFromPrototype :: Fold (worldType 'Storing) IntersectionOfEntities
- spawnPrototype :: (UsingSpawnedFromPrototype w 'Individual, UsingIsPrototype w 'Individual, MonadIO m) => Entity -> w 'Storing -> m (Maybe (w 'Individual, w 'Storing))
- type PrototypeNameMap = HashMap PrototypeID Entity
- spawnNamedPrototype :: (UsingSpawnedFromPrototype w 'Individual, UsingIsPrototype w 'Individual, MonadIO m) => PrototypeNameMap -> PrototypeID -> w 'Storing -> m (Maybe (w 'Individual, w 'Storing))
- prototypes :: forall (w :: Access -> Type). HasIsPrototype w => IndexedTraversal' Entity (w 'Storing) (w 'Individual)
Documentation
newtype PrototypeID Source #
A prototype's ID is distinct from its entity reference in that it is stable, and in a unique namespace.
Constructors
PrototypeID | |
Fields |
Instances
class HasPrototypeID c where Source #
Minimal complete definition
Instances
HasPrototypeID IsPrototype Source # | |
Defined in Games.ECS.Prototype Methods | |
HasPrototypeID PrototypeID Source # | |
Defined in Games.ECS.Prototype Methods |
data IsPrototype Source #
A component for denoting that an individual is a prototype, to be instantiated later.
Constructors
IsPrototype | |
Fields
|
Instances
Generic IsPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype Associated Types
| |||||||||||||||||
Show IsPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype Methods showsPrec :: Int -> IsPrototype -> ShowS # show :: IsPrototype -> String # showList :: [IsPrototype] -> ShowS # | |||||||||||||||||
Eq IsPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype | |||||||||||||||||
Component IsPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype Associated Types
Methods _ComponentFromXML :: String -> Prism' Element IsPrototype Source # entityKeys :: Fold (Storage IsPrototype IsPrototype) EntitySet Source # emptyStorage :: Storage IsPrototype IsPrototype Source # entityHasComponent :: Entity -> IndexedTraversal' Entity (Storage IsPrototype IsPrototype) IsPrototype Source # | |||||||||||||||||
HasPrototypeID IsPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype Methods | |||||||||||||||||
XMLPickler [Node] IsPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype | |||||||||||||||||
type Rep IsPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype type Rep IsPrototype = D1 ('MetaData "IsPrototype" "Games.ECS.Prototype" "ohhecs-0.0.1-inplace" 'False) (C1 ('MetaCons "IsPrototype" 'PrefixI 'True) (S1 ('MetaSel ('Just "_rawIsPrototypeID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PrototypeID) :*: S1 ('MetaSel ('Just "_extendsPrototype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PrototypeID)))) | |||||||||||||||||
type CanonicalName IsPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype | |||||||||||||||||
type IsFlag IsPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype | |||||||||||||||||
type Prop IsPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype | |||||||||||||||||
type Storage IsPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype |
data SpawnedFromPrototype Source #
Marks an entity as being spawned from a prototype.
Constructors
SpawnedFromPrototype | |
Fields
|
Instances
Generic SpawnedFromPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype Associated Types
Methods from :: SpawnedFromPrototype -> Rep SpawnedFromPrototype x # to :: Rep SpawnedFromPrototype x -> SpawnedFromPrototype # | |||||||||||||||||
Show SpawnedFromPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype Methods showsPrec :: Int -> SpawnedFromPrototype -> ShowS # show :: SpawnedFromPrototype -> String # showList :: [SpawnedFromPrototype] -> ShowS # | |||||||||||||||||
Eq SpawnedFromPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype Methods (==) :: SpawnedFromPrototype -> SpawnedFromPrototype -> Bool # (/=) :: SpawnedFromPrototype -> SpawnedFromPrototype -> Bool # | |||||||||||||||||
Component SpawnedFromPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype Associated Types
Methods _ComponentFromXML :: String -> Prism' Element SpawnedFromPrototype Source # entityKeys :: Fold (Storage SpawnedFromPrototype SpawnedFromPrototype) EntitySet Source # emptyStorage :: Storage SpawnedFromPrototype SpawnedFromPrototype Source # entityHasComponent :: Entity -> IndexedTraversal' Entity (Storage SpawnedFromPrototype SpawnedFromPrototype) SpawnedFromPrototype Source # | |||||||||||||||||
XMLPickler [Node] SpawnedFromPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype | |||||||||||||||||
type Rep SpawnedFromPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype type Rep SpawnedFromPrototype = D1 ('MetaData "SpawnedFromPrototype" "Games.ECS.Prototype" "ohhecs-0.0.1-inplace" 'False) (C1 ('MetaCons "SpawnedFromPrototype" 'PrefixI 'True) (S1 ('MetaSel ('Just "_prototypeEntity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Entity) :*: S1 ('MetaSel ('Just "_spawnedFromPrototypeID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PrototypeID)))) | |||||||||||||||||
type CanonicalName SpawnedFromPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype | |||||||||||||||||
type IsFlag SpawnedFromPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype | |||||||||||||||||
type Prop SpawnedFromPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype | |||||||||||||||||
type Storage SpawnedFromPrototype Source # | |||||||||||||||||
Defined in Games.ECS.Prototype |
type UsingIsPrototype (worldType :: Access -> Type) (s :: Access) = (HasIsPrototype worldType, EntityProperty "isPrototype" worldType s (Prop IsPrototype) IsPrototype, OpticsFor "isPrototype" worldType s (Prop IsPrototype) IsPrototype ~ ReifiedIndexedTraversal' Entity (worldType s) IsPrototype) Source #
class (World worldType, Component IsPrototype, EntityProperty "isPrototype" worldType 'Individual (Prop IsPrototype) IsPrototype, OpticsFor "isPrototype" worldType 'Storing (Prop IsPrototype) IsPrototype ~ ReifiedIndexedTraversal' Entity (worldType 'Storing) IsPrototype) => HasIsPrototype (worldType :: Access -> Type) where Source #
Methods
isPrototype :: forall {s :: Access}. (EntityProperty "isPrototype" worldType s (Prop IsPrototype) IsPrototype, OpticsFor "isPrototype" worldType s (Prop IsPrototype) IsPrototype ~ ReifiedIndexedTraversal' Entity (worldType s) IsPrototype) => IndexedTraversal' Entity (worldType s) IsPrototype Source #
addIsPrototype :: IndexedSetter' Entity (worldType 'Individual) IsPrototype Source #
removeIsPrototype :: worldType 'Individual -> worldType 'Individual Source #
withIsPrototype :: Fold (worldType 'Storing) IntersectionOfEntities Source #
type UsingSpawnedFromPrototype (worldType :: Access -> Type) (s :: Access) = (HasSpawnedFromPrototype worldType, EntityProperty "spawnedFromPrototype" worldType s (Prop SpawnedFromPrototype) SpawnedFromPrototype, OpticsFor "spawnedFromPrototype" worldType s (Prop SpawnedFromPrototype) SpawnedFromPrototype ~ ReifiedIndexedTraversal' Entity (worldType s) SpawnedFromPrototype) Source #
class (World worldType, Component SpawnedFromPrototype, EntityProperty "spawnedFromPrototype" worldType 'Individual (Prop SpawnedFromPrototype) SpawnedFromPrototype, OpticsFor "spawnedFromPrototype" worldType 'Storing (Prop SpawnedFromPrototype) SpawnedFromPrototype ~ ReifiedIndexedTraversal' Entity (worldType 'Storing) SpawnedFromPrototype) => HasSpawnedFromPrototype (worldType :: Access -> Type) where Source #
Methods
spawnedFromPrototype :: forall {s :: Access}. (EntityProperty "spawnedFromPrototype" worldType s (Prop SpawnedFromPrototype) SpawnedFromPrototype, OpticsFor "spawnedFromPrototype" worldType s (Prop SpawnedFromPrototype) SpawnedFromPrototype ~ ReifiedIndexedTraversal' Entity (worldType s) SpawnedFromPrototype) => IndexedTraversal' Entity (worldType s) SpawnedFromPrototype Source #
addSpawnedFromPrototype :: IndexedSetter' Entity (worldType 'Individual) SpawnedFromPrototype Source #
removeSpawnedFromPrototype :: worldType 'Individual -> worldType 'Individual Source #
withSpawnedFromPrototype :: Fold (worldType 'Storing) IntersectionOfEntities Source #
spawnPrototype :: (UsingSpawnedFromPrototype w 'Individual, UsingIsPrototype w 'Individual, MonadIO m) => Entity -> w 'Storing -> m (Maybe (w 'Individual, w 'Storing)) Source #
Spawn a new individual with the given prototype Entity
reference. Returns the new individual, and the new world.
type PrototypeNameMap = HashMap PrototypeID Entity Source #
A dictionary between a PrototypeID
and the characterising Entity
.
spawnNamedPrototype :: (UsingSpawnedFromPrototype w 'Individual, UsingIsPrototype w 'Individual, MonadIO m) => PrototypeNameMap -> PrototypeID -> w 'Storing -> m (Maybe (w 'Individual, w 'Storing)) Source #
Spawns a new individual with a given PrototypeID
, which is looked up in the associated map. Returns the new individual, and the new world.
prototypes :: forall (w :: Access -> Type). HasIsPrototype w => IndexedTraversal' Entity (w 'Storing) (w 'Individual) Source #
All the prototypical individuals in a world.