Skip to content

Commit

Permalink
perf: inline and unpack ReadsWrites
Browse files Browse the repository at this point in the history
  • Loading branch information
matthunz committed Feb 27, 2025
1 parent 113d6ce commit e4dac27
Showing 1 changed file with 8 additions and 8 deletions.
16 changes: 8 additions & 8 deletions src/Aztecs/ECS/Query.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,19 +45,17 @@ module Aztecs.ECS.Query
where

import Aztecs.ECS.Component
import Aztecs.ECS.Query.Class (ArrowQuery (..))
import Aztecs.ECS.Query.Dynamic (DynamicQuery (..), fromDynReader, mapDyn, toDynReader)
import Aztecs.ECS.Query.Dynamic.Class (ArrowDynamicQuery (..))
import Aztecs.ECS.Query.Class
import Aztecs.ECS.Query.Dynamic
import Aztecs.ECS.Query.Dynamic.Reader (allDyn)
import Aztecs.ECS.Query.Dynamic.Reader.Class (ArrowDynamicQueryReader (..))
import Aztecs.ECS.Query.Reader (QueryFilter (..), QueryReader (..), QueryReaderState (..), with, without)
import qualified Aztecs.ECS.Query.Reader as QR
import Aztecs.ECS.Query.Reader.Class (ArrowQueryReader (..))
import Aztecs.ECS.Query.Reader.Class
import Aztecs.ECS.World.Components (Components)
import qualified Aztecs.ECS.World.Components as CS
import Aztecs.ECS.World.Entities (Entities (..))
import Control.Arrow (Arrow (..), ArrowChoice (..))
import Control.Category (Category (..))
import Control.Arrow
import Control.Category
import Data.Set (Set)
import qualified Data.Set as Set
import Prelude hiding (all, id, map, reads, (.))
Expand Down Expand Up @@ -146,15 +144,17 @@ toReader (Query f) = QueryReader $ \cs -> let !(qS, cs') = f cs in (queryStateTo

-- | Reads and writes of a `Query`.
data ReadsWrites = ReadsWrites

Check warning on line 146 in src/Aztecs/ECS/Query.hs

View workflow job for this annotation

GitHub Actions / test

• Ignoring unusable UNPACK pragma

Check warning on line 146 in src/Aztecs/ECS/Query.hs

View workflow job for this annotation

GitHub Actions / build

• Ignoring unusable UNPACK pragma
{ reads :: !(Set ComponentID),
{ reads :: {-# UNPACK #-} !(Set ComponentID),
writes :: !(Set ComponentID)
}
deriving (Show)

instance Semigroup ReadsWrites where
{-# INLINE (<>) #-}
ReadsWrites r1 w1 <> ReadsWrites r2 w2 = ReadsWrites (r1 <> r2) (w1 <> w2)

instance Monoid ReadsWrites where
{-# INLINE mempty #-}
mempty = ReadsWrites mempty mempty

-- | `True` if the reads and writes of two `Query`s overlap.
Expand Down

0 comments on commit e4dac27

Please sign in to comment.