{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Aztecs.ECS.Query.Class (QueryF (..)) where
import Aztecs.ECS.Component
import Control.Monad
class (Applicative g, Functor f) => QueryF g f | f -> g where
adjust :: (Component a) => (b -> a -> a) -> f b -> f a
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
adjustM :: (Component a) => (b -> a -> g a) -> f b -> f a
set :: (Component a) => f a -> f a