{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- |
-- Module      : Aztecs.ECS.Query.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.Class (QueryF (..)) where

import Aztecs.ECS.Component
import Control.Monad

-- | Query functor.
--
-- @since 0.10
class (Applicative g, Functor f) => QueryF g f | f -> g where
  -- | Adjust a `Component` by its type.
  --
  -- @since 0.10
  adjust :: (Component a) => (b -> a -> a) -> f b -> f a

  -- | Adjust a `Component` by its type, ignoring any output.
  --
  -- @since 0.10
  adjust_ :: (Component a) => (b -> a -> a) -> f b -> f ()
  adjust_ b -> a -> a
f = f a -> f ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (f a -> f ()) -> (f b -> f a) -> f b -> f ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (b -> a -> a) -> f b -> f a
forall a b. Component a => (b -> a -> a) -> f b -> f a
forall (g :: * -> *) (f :: * -> *) a b.
(QueryF g f, Component a) =>
(b -> a -> a) -> f b -> f a
adjust b -> a -> a
f

  -- | Adjust a `Component` by its type with some `Monad` @m@.
  --
  -- @since 0.10
  adjustM :: (Component a) => (b -> a -> g a) -> f b -> f a

  -- | Set a `Component` by its type.
  --
  -- @since 0.10
  set :: (Component a) => f a -> f a