Copyright | (c) Matt Hunzinger 2025 |
---|---|
License | BSD-style (see the LICENSE file in the distribution) |
Maintainer | matt@hunzinger.me |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Aztecs.ECS.World.Archetypes
Description
Synopsis
- newtype ArchetypeID = ArchetypeID {
- unArchetypeId :: Int
- data Node = Node {
- nodeComponentIds :: !(Set ComponentID)
- nodeArchetype :: !Archetype
- data Archetypes = Archetypes {
- nodes :: !(Map ArchetypeID Node)
- archetypeIds :: !(Map (Set ComponentID) ArchetypeID)
- nextArchetypeId :: !ArchetypeID
- componentIds :: !(Map ComponentID (Set ArchetypeID))
- empty :: Archetypes
- insertArchetype :: Set ComponentID -> Node -> Archetypes -> (ArchetypeID, Archetypes)
- lookupArchetypeId :: Set ComponentID -> Archetypes -> Maybe ArchetypeID
- findArchetypeIds :: Set ComponentID -> Set ComponentID -> Archetypes -> Set ArchetypeID
- lookup :: ArchetypeID -> Archetypes -> Maybe Node
- find :: Set ComponentID -> Set ComponentID -> Archetypes -> Map ArchetypeID Node
- adjustArchetype :: ArchetypeID -> (Archetype -> Archetype) -> Archetypes -> Archetypes
- insert :: EntityID -> ArchetypeID -> Set ComponentID -> DynamicBundle -> Archetypes -> (Maybe ArchetypeID, Archetypes)
- remove :: Component a => EntityID -> ArchetypeID -> ComponentID -> Archetypes -> (Maybe (a, ArchetypeID), Archetypes)
Documentation
newtype ArchetypeID Source #
Archetype
ID.
Since: 0.9
Constructors
ArchetypeID | |
Fields
|
Instances
Show ArchetypeID Source # | |
Defined in Aztecs.ECS.World.Archetypes Methods showsPrec :: Int -> ArchetypeID -> ShowS # show :: ArchetypeID -> String # showList :: [ArchetypeID] -> ShowS # | |
NFData ArchetypeID Source # | |
Defined in Aztecs.ECS.World.Archetypes Methods rnf :: ArchetypeID -> () # | |
Eq ArchetypeID Source # | |
Defined in Aztecs.ECS.World.Archetypes | |
Ord ArchetypeID Source # | |
Defined in Aztecs.ECS.World.Archetypes Methods compare :: ArchetypeID -> ArchetypeID -> Ordering # (<) :: ArchetypeID -> ArchetypeID -> Bool # (<=) :: ArchetypeID -> ArchetypeID -> Bool # (>) :: ArchetypeID -> ArchetypeID -> Bool # (>=) :: ArchetypeID -> ArchetypeID -> Bool # max :: ArchetypeID -> ArchetypeID -> ArchetypeID # min :: ArchetypeID -> ArchetypeID -> ArchetypeID # |
Node in Archetypes
.
Since: 0.9
Constructors
Node | |
Fields
|
Instances
Generic Node Source # | |
Show Node Source # | |
NFData Node Source # | |
Defined in Aztecs.ECS.World.Archetypes | |
type Rep Node Source # | |
Defined in Aztecs.ECS.World.Archetypes type Rep Node = D1 ('MetaData "Node" "Aztecs.ECS.World.Archetypes" "aztecs-0.12.0-GlKmPfHNl6i8JdqwU1RE4N" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "nodeComponentIds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set ComponentID)) :*: S1 ('MetaSel ('Just "nodeArchetype") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Archetype))) |
data Archetypes Source #
Archetype
map.
Constructors
Archetypes | |
Fields
|
Instances
empty :: Archetypes Source #
Empty Archetypes
.
Since: 0.9
insertArchetype :: Set ComponentID -> Node -> Archetypes -> (ArchetypeID, Archetypes) Source #
Insert an archetype by its set of ComponentID
s.
Since: 0.9
lookupArchetypeId :: Set ComponentID -> Archetypes -> Maybe ArchetypeID Source #
Lookup an ArchetypeID
by its set of ComponentID
s.
Since: 0.9
findArchetypeIds :: Set ComponentID -> Set ComponentID -> Archetypes -> Set ArchetypeID Source #
Find ArchetypeID
s containing a set of ComponentID
s.
Since: 0.11
lookup :: ArchetypeID -> Archetypes -> Maybe Node Source #
Lookup an Archetype
by its ArchetypeID
.
Since: 0.9
find :: Set ComponentID -> Set ComponentID -> Archetypes -> Map ArchetypeID Node Source #
Lookup Archetype
s containing a set of ComponentID
s.
Since: 0.9
adjustArchetype :: ArchetypeID -> (Archetype -> Archetype) -> Archetypes -> Archetypes Source #
Adjust an Archetype
by its ArchetypeID
.
Since: 0.9
insert :: EntityID -> ArchetypeID -> Set ComponentID -> DynamicBundle -> Archetypes -> (Maybe ArchetypeID, Archetypes) Source #
Insert a component into an entity with its ComponentID
.
Since: 0.9
remove :: Component a => EntityID -> ArchetypeID -> ComponentID -> Archetypes -> (Maybe (a, ArchetypeID), Archetypes) Source #
Remove a component from an entity with its ComponentID
.
Since: 0.9