-- |
-- Module      : Aztecs.ECS.Query.Dynamic.Reader.Class
-- 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)
module Aztecs.ECS.Query.Dynamic.Reader.Class (DynamicQueryReaderF (..)) where

import Aztecs.ECS.Component
import Aztecs.ECS.Entity

-- | Dynamic query reader functor.
--
-- @since 0.10
class (Functor f) => DynamicQueryReaderF f where
  -- | Fetch the currently matched `EntityID`.
  --
  -- @since 0.10
  entity :: f EntityID

  -- | Fetch a `Component` by its `ComponentID`.
  --
  -- @since 0.10
  fetchDyn :: (Component a) => ComponentID -> f a

  -- | Try to fetch a `Component` by its `ComponentID`.
  --
  -- @since 0.10
  fetchMaybeDyn :: (Component a) => ComponentID -> f (Maybe a)
  fetchMaybeDyn ComponentID
cId = a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> f a -> f (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ComponentID -> f a
forall a. Component a => ComponentID -> f a
forall (f :: * -> *) a.
(DynamicQueryReaderF f, Component a) =>
ComponentID -> f a
fetchDyn ComponentID
cId