Skip to content

Commit

Permalink
doc: add docs
Browse files Browse the repository at this point in the history
  • Loading branch information
matthunz committed Feb 27, 2025
1 parent 954ed1a commit 08d3483
Show file tree
Hide file tree
Showing 3 changed files with 15 additions and 7 deletions.
3 changes: 1 addition & 2 deletions src/Aztecs/ECS/World.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,13 +30,12 @@ import qualified Aztecs.ECS.World.Entities as E
import Control.DeepSeq
import Data.Dynamic
import Data.IntMap (IntMap)
import Data.Map (Map)
import GHC.Generics
import Prelude hiding (lookup)

-- | World of entities and their components.
data World = World
{ entities :: Entities,
{ entities :: !Entities,
nextEntityId :: !EntityID
}
deriving (Show, Generic, NFData)
Expand Down
15 changes: 12 additions & 3 deletions src/Aztecs/Hierarchy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,8 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeApplications #-}

-- | Hierarchical relationships.
-- A `Children` component forms a one-to-many relationship with `Parent` components.
module Aztecs.Hierarchy
( Parent (..),
Children (..),
Expand Down Expand Up @@ -35,6 +37,7 @@ import Data.Set (Set)
import qualified Data.Set as Set
import GHC.Generics (Generic)

-- | Parent component.
newtype Parent = Parent {unParent :: EntityID}
deriving (Eq, Ord, Show, Generic, NFData)

Expand All @@ -45,6 +48,7 @@ newtype ParentState = ParentState {unParentState :: EntityID}

instance Component ParentState

-- | Children component.
newtype Children = Children {unChildren :: Set EntityID}
deriving (Eq, Ord, Show, Semigroup, Monoid, Generic, NFData)

Expand All @@ -55,6 +59,7 @@ newtype ChildState = ChildState {unChildState :: Set EntityID}

instance Component ChildState

-- | Update the parent-child relationships.
update ::
( ArrowQueryReader qr,
ArrowDynamicQueryReader qr,
Expand Down Expand Up @@ -126,6 +131,7 @@ update = proc () -> do
-<
(parents, children)

-- | Hierarchy of entities.
data Hierarchy a = Node
{ nodeEntityId :: EntityID,
nodeEntity :: a,
Expand All @@ -137,7 +143,8 @@ instance Foldable Hierarchy where
foldMap f n = f (nodeEntity n) <> foldMap (foldMap f) (nodeChildren n)

instance Traversable Hierarchy where
traverse f n = Node (nodeEntityId n) <$> f (nodeEntity n) <*> traverse (traverse f) (nodeChildren n)
traverse f n =
Node (nodeEntityId n) <$> f (nodeEntity n) <*> traverse (traverse f) (nodeChildren n)

toList :: Hierarchy a -> [(EntityID, a)]
toList n = (nodeEntityId n, nodeEntity n) : concatMap toList (nodeChildren n)
Expand All @@ -146,12 +153,14 @@ foldWithKey :: (EntityID -> a -> b -> b) -> Hierarchy a -> b -> b
foldWithKey f n b = f (nodeEntityId n) (nodeEntity n) (foldr (foldWithKey f) b (nodeChildren n))

mapWithKey :: (EntityID -> a -> b) -> Hierarchy a -> Hierarchy b
mapWithKey f n = Node (nodeEntityId n) (f (nodeEntityId n) (nodeEntity n)) (map (mapWithKey f) (nodeChildren n))
mapWithKey f n =
Node (nodeEntityId n) (f (nodeEntityId n) (nodeEntity n)) (map (mapWithKey f) (nodeChildren n))

mapWithAccum :: (EntityID -> a -> b -> (c, b)) -> b -> Hierarchy a -> Hierarchy c
mapWithAccum f b n = case f (nodeEntityId n) (nodeEntity n) b of
(c, b') -> Node (nodeEntityId n) c (map (mapWithAccum f b') (nodeChildren n))

-- | System to read a hierarchy of parents to children with the given query.
hierarchy ::
(ArrowQueryReader q, ArrowDynamicQueryReader q, ArrowReaderSystem q arr) =>
EntityID ->
Expand All @@ -171,7 +180,7 @@ hierarchy e q = proc i -> do
let childMap = Map.fromList children
returnA -< hierarchy' e childMap

-- | Build all hierarchies of parents to children with the given query.
-- | Build all hierarchies of parents to children, joined with the given query.
hierarchies ::
(ArrowQueryReader q, ArrowDynamicQueryReader q, ArrowReaderSystem q arr) =>
q i a ->
Expand Down
4 changes: 2 additions & 2 deletions src/Aztecs/Transform.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,8 +37,8 @@ import qualified Aztecs.ECS.System as S
import Aztecs.Hierarchy (Hierarchy, hierarchies, mapWithAccum, toList)
import Control.Arrow (Arrow (..), (>>>))
import Control.DeepSeq
import GHC.Generics (Generic)
import Linear (V2 (..))
import GHC.Generics
import Linear

-- | Transform component.
data Transform v r = Transform
Expand Down

0 comments on commit 08d3483

Please sign in to comment.