{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Aztecs.ECS.System.Dynamic
( DynamicSystem,
DynamicSystemT (..),
ArrowDynamicReaderSystem (..),
ArrowDynamicSystem (..),
ArrowQueueSystem (..),
raceDyn,
fromDynReaderSystem,
)
where
import Aztecs.ECS.Access
import Aztecs.ECS.Query.Dynamic (DynamicQuery (..))
import Aztecs.ECS.Query.Dynamic.Reader (DynamicQueryReader (..))
import Aztecs.ECS.System.Dynamic.Class
import Aztecs.ECS.System.Dynamic.Reader (DynamicReaderSystemT (..))
import Aztecs.ECS.System.Dynamic.Reader.Class
import Aztecs.ECS.System.Queue (ArrowQueueSystem (..))
import Aztecs.ECS.View (View)
import qualified Aztecs.ECS.View as V
import Aztecs.ECS.World.Bundle
import Aztecs.ECS.World.Entities (Entities (..))
import Control.Arrow
import Control.Category
import Control.Monad.Identity
import Control.Parallel (par)
import Data.Maybe (fromMaybe)
import Prelude hiding (id, (.))
type DynamicSystem = DynamicSystemT Identity
newtype DynamicSystemT m i o = DynamicSystem
{
forall (m :: * -> *) i o.
DynamicSystemT m i o
-> Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o)
runSystemDyn :: Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o)
}
deriving ((forall a b.
(a -> b) -> DynamicSystemT m i a -> DynamicSystemT m i b)
-> (forall a b. a -> DynamicSystemT m i b -> DynamicSystemT m i a)
-> Functor (DynamicSystemT m i)
forall a b. a -> DynamicSystemT m i b -> DynamicSystemT m i a
forall a b.
(a -> b) -> DynamicSystemT m i a -> DynamicSystemT m i b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
forall (m :: * -> *) i a b.
a -> DynamicSystemT m i b -> DynamicSystemT m i a
forall (m :: * -> *) i a b.
(a -> b) -> DynamicSystemT m i a -> DynamicSystemT m i b
$cfmap :: forall (m :: * -> *) i a b.
(a -> b) -> DynamicSystemT m i a -> DynamicSystemT m i b
fmap :: forall a b.
(a -> b) -> DynamicSystemT m i a -> DynamicSystemT m i b
$c<$ :: forall (m :: * -> *) i a b.
a -> DynamicSystemT m i b -> DynamicSystemT m i a
<$ :: forall a b. a -> DynamicSystemT m i b -> DynamicSystemT m i a
Functor)
instance (Monad m) => Category (DynamicSystemT m) where
id :: forall a. DynamicSystemT m a a
id = (Entities -> a -> (a, View, AccessT m (), DynamicSystemT m a a))
-> DynamicSystemT m a a
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem ((Entities -> a -> (a, View, AccessT m (), DynamicSystemT m a a))
-> DynamicSystemT m a a)
-> (Entities -> a -> (a, View, AccessT m (), DynamicSystemT m a a))
-> DynamicSystemT m a a
forall a b. (a -> b) -> a -> b
$ \Entities
_ a
i -> (a
i, View
forall a. Monoid a => a
mempty, () -> AccessT m ()
forall a. a -> AccessT m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (), DynamicSystemT m a a
forall a. DynamicSystemT m a a
forall {k} (cat :: k -> k -> *) (a :: k). Category cat => cat a a
id)
DynamicSystem Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c)
f . :: forall b c a.
DynamicSystemT m b c
-> DynamicSystemT m a b -> DynamicSystemT m a c
. DynamicSystem Entities -> a -> (b, View, AccessT m (), DynamicSystemT m a b)
g = (Entities -> a -> (c, View, AccessT m (), DynamicSystemT m a c))
-> DynamicSystemT m a c
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem ((Entities -> a -> (c, View, AccessT m (), DynamicSystemT m a c))
-> DynamicSystemT m a c)
-> (Entities -> a -> (c, View, AccessT m (), DynamicSystemT m a c))
-> DynamicSystemT m a c
forall a b. (a -> b) -> a -> b
$ \Entities
w a
i ->
let (b
b, View
gView, AccessT m ()
gAccess, DynamicSystemT m a b
g') = Entities -> a -> (b, View, AccessT m (), DynamicSystemT m a b)
g Entities
w a
i
(c
a, View
fView, AccessT m ()
fAccess, DynamicSystemT m b c
f') = Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c)
f Entities
w b
b
in (c
a, View
gView View -> View -> View
forall a. Semigroup a => a -> a -> a
<> View
fView, AccessT m ()
gAccess AccessT m () -> AccessT m () -> AccessT m ()
forall a b. AccessT m a -> AccessT m b -> AccessT m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> AccessT m ()
fAccess, DynamicSystemT m b c
f' DynamicSystemT m b c
-> DynamicSystemT m a b -> DynamicSystemT m a c
forall b c a.
DynamicSystemT m b c
-> DynamicSystemT m a b -> DynamicSystemT m a c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. DynamicSystemT m a b
g')
instance (Monad m) => Arrow (DynamicSystemT m) where
arr :: forall b c. (b -> c) -> DynamicSystemT m b c
arr b -> c
f = (Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c))
-> DynamicSystemT m b c
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem ((Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c))
-> DynamicSystemT m b c)
-> (Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c))
-> DynamicSystemT m b c
forall a b. (a -> b) -> a -> b
$ \Entities
_ b
i -> (b -> c
f b
i, View
forall a. Monoid a => a
mempty, () -> AccessT m ()
forall a. a -> AccessT m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (), (b -> c) -> DynamicSystemT m b c
forall b c. (b -> c) -> DynamicSystemT m b c
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr b -> c
f)
first :: forall b c d.
DynamicSystemT m b c -> DynamicSystemT m (b, d) (c, d)
first (DynamicSystem Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c)
f) = (Entities
-> (b, d)
-> ((c, d), View, AccessT m (), DynamicSystemT m (b, d) (c, d)))
-> DynamicSystemT m (b, d) (c, d)
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem ((Entities
-> (b, d)
-> ((c, d), View, AccessT m (), DynamicSystemT m (b, d) (c, d)))
-> DynamicSystemT m (b, d) (c, d))
-> (Entities
-> (b, d)
-> ((c, d), View, AccessT m (), DynamicSystemT m (b, d) (c, d)))
-> DynamicSystemT m (b, d) (c, d)
forall a b. (a -> b) -> a -> b
$ \Entities
w (b
i, d
x) ->
let (c
a, View
v, AccessT m ()
access, DynamicSystemT m b c
f') = Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c)
f Entities
w b
i in ((c
a, d
x), View
v, AccessT m ()
access, DynamicSystemT m b c -> DynamicSystemT m (b, d) (c, d)
forall b c d.
DynamicSystemT m b c -> DynamicSystemT m (b, d) (c, d)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first DynamicSystemT m b c
f')
instance (Monad m) => ArrowChoice (DynamicSystemT m) where
left :: forall b c d.
DynamicSystemT m b c -> DynamicSystemT m (Either b d) (Either c d)
left (DynamicSystem Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c)
f) = (Entities
-> Either b d
-> (Either c d, View, AccessT m (),
DynamicSystemT m (Either b d) (Either c d)))
-> DynamicSystemT m (Either b d) (Either c d)
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem ((Entities
-> Either b d
-> (Either c d, View, AccessT m (),
DynamicSystemT m (Either b d) (Either c d)))
-> DynamicSystemT m (Either b d) (Either c d))
-> (Entities
-> Either b d
-> (Either c d, View, AccessT m (),
DynamicSystemT m (Either b d) (Either c d)))
-> DynamicSystemT m (Either b d) (Either c d)
forall a b. (a -> b) -> a -> b
$ \Entities
w Either b d
i -> case Either b d
i of
Left b
b -> let (c
c, View
v, AccessT m ()
access, DynamicSystemT m b c
f') = Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c)
f Entities
w b
b in (c -> Either c d
forall a b. a -> Either a b
Left c
c, View
v, AccessT m ()
access, DynamicSystemT m b c -> DynamicSystemT m (Either b d) (Either c d)
forall b c d.
DynamicSystemT m b c -> DynamicSystemT m (Either b d) (Either c d)
forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either b d) (Either c d)
left DynamicSystemT m b c
f')
Right d
d -> (d -> Either c d
forall a b. b -> Either a b
Right d
d, View
forall a. Monoid a => a
mempty, () -> AccessT m ()
forall a. a -> AccessT m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (), DynamicSystemT m b c -> DynamicSystemT m (Either b d) (Either c d)
forall b c d.
DynamicSystemT m b c -> DynamicSystemT m (Either b d) (Either c d)
forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either b d) (Either c d)
left ((Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c))
-> DynamicSystemT m b c
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c)
f))
instance (Monad m) => ArrowLoop (DynamicSystemT m) where
loop :: forall b d c.
DynamicSystemT m (b, d) (c, d) -> DynamicSystemT m b c
loop (DynamicSystem Entities
-> (b, d)
-> ((c, d), View, AccessT m (), DynamicSystemT m (b, d) (c, d))
f) = (Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c))
-> DynamicSystemT m b c
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem ((Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c))
-> DynamicSystemT m b c)
-> (Entities -> b -> (c, View, AccessT m (), DynamicSystemT m b c))
-> DynamicSystemT m b c
forall a b. (a -> b) -> a -> b
$ \Entities
w b
b ->
let ((c
c, d
d), View
v, AccessT m ()
access, DynamicSystemT m (b, d) (c, d)
f') = Entities
-> (b, d)
-> ((c, d), View, AccessT m (), DynamicSystemT m (b, d) (c, d))
f Entities
w (b
b, d
d) in (c
c, View
v, AccessT m ()
access, DynamicSystemT m (b, d) (c, d) -> DynamicSystemT m b c
forall b d c.
DynamicSystemT m (b, d) (c, d) -> DynamicSystemT m b c
forall (a :: * -> * -> *) b d c.
ArrowLoop a =>
a (b, d) (c, d) -> a b c
loop DynamicSystemT m (b, d) (c, d)
f')
instance (Monad m) => ArrowDynamicReaderSystem DynamicQueryReader (DynamicSystemT m) where
allDyn :: forall i o.
Set ComponentID -> DynamicQueryReader i o -> DynamicSystemT m i [o]
allDyn Set ComponentID
cIds DynamicQueryReader i o
q = DynamicReaderSystemT m i [o] -> DynamicSystemT m i [o]
forall (m :: * -> *) i o.
DynamicReaderSystemT m i o -> DynamicSystemT m i o
fromDynReaderSystem (DynamicReaderSystemT m i [o] -> DynamicSystemT m i [o])
-> DynamicReaderSystemT m i [o] -> DynamicSystemT m i [o]
forall a b. (a -> b) -> a -> b
$ Set ComponentID
-> DynamicQueryReader i o -> DynamicReaderSystemT m i [o]
forall i o.
Set ComponentID
-> DynamicQueryReader i o -> DynamicReaderSystemT m i [o]
forall (q :: * -> * -> *) (arr :: * -> * -> *) i o.
ArrowDynamicReaderSystem q arr =>
Set ComponentID -> q i o -> arr i [o]
allDyn Set ComponentID
cIds DynamicQueryReader i o
q
filterDyn :: forall i o.
Set ComponentID
-> DynamicQueryReader i o
-> (Node -> Bool)
-> DynamicSystemT m i [o]
filterDyn Set ComponentID
cIds DynamicQueryReader i o
qf Node -> Bool
q = DynamicReaderSystemT m i [o] -> DynamicSystemT m i [o]
forall (m :: * -> *) i o.
DynamicReaderSystemT m i o -> DynamicSystemT m i o
fromDynReaderSystem (DynamicReaderSystemT m i [o] -> DynamicSystemT m i [o])
-> DynamicReaderSystemT m i [o] -> DynamicSystemT m i [o]
forall a b. (a -> b) -> a -> b
$ Set ComponentID
-> DynamicQueryReader i o
-> (Node -> Bool)
-> DynamicReaderSystemT m i [o]
forall i o.
Set ComponentID
-> DynamicQueryReader i o
-> (Node -> Bool)
-> DynamicReaderSystemT m i [o]
forall (q :: * -> * -> *) (arr :: * -> * -> *) i o.
ArrowDynamicReaderSystem q arr =>
Set ComponentID -> q i o -> (Node -> Bool) -> arr i [o]
filterDyn Set ComponentID
cIds DynamicQueryReader i o
qf Node -> Bool
q
instance (Monad m) => ArrowDynamicSystem DynamicQuery (DynamicSystemT m) where
mapDyn :: forall i o.
Set ComponentID -> DynamicQuery i o -> DynamicSystemT m i [o]
mapDyn Set ComponentID
cIds DynamicQuery i o
q = (Entities
-> i -> ([o], View, AccessT m (), DynamicSystemT m i [o]))
-> DynamicSystemT m i [o]
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem ((Entities
-> i -> ([o], View, AccessT m (), DynamicSystemT m i [o]))
-> DynamicSystemT m i [o])
-> (Entities
-> i -> ([o], View, AccessT m (), DynamicSystemT m i [o]))
-> DynamicSystemT m i [o]
forall a b. (a -> b) -> a -> b
$ \Entities
w i
i ->
let !v :: View
v = Set ComponentID -> Archetypes -> View
V.view Set ComponentID
cIds (Archetypes -> View) -> Archetypes -> View
forall a b. (a -> b) -> a -> b
$ Entities -> Archetypes
archetypes Entities
w
([o]
o, View
v') = i -> DynamicQuery i o -> View -> ([o], View)
forall i a. i -> DynamicQuery i a -> View -> ([a], View)
V.allDyn i
i DynamicQuery i o
q View
v
in ([o]
o, View
v', () -> AccessT m ()
forall a. a -> AccessT m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (), Set ComponentID -> DynamicQuery i o -> DynamicSystemT m i [o]
forall i o.
Set ComponentID -> DynamicQuery i o -> DynamicSystemT m i [o]
forall (q :: * -> * -> *) (arr :: * -> * -> *) i o.
ArrowDynamicSystem q arr =>
Set ComponentID -> q i o -> arr i [o]
mapDyn Set ComponentID
cIds DynamicQuery i o
q)
mapSingleDyn :: forall i o.
Set ComponentID -> DynamicQuery i o -> DynamicSystemT m i o
mapSingleDyn Set ComponentID
cIds DynamicQuery i o
q = (Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem ((Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o)
-> (Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
forall a b. (a -> b) -> a -> b
$ \Entities
w i
i ->
let s :: DynamicSystemT m i o
s =
Set ComponentID -> DynamicQuery i o -> DynamicSystemT m i (Maybe o)
forall i o.
Set ComponentID -> DynamicQuery i o -> DynamicSystemT m i (Maybe o)
forall (q :: * -> * -> *) (arr :: * -> * -> *) i o.
ArrowDynamicSystem q arr =>
Set ComponentID -> q i o -> arr i (Maybe o)
mapSingleMaybeDyn Set ComponentID
cIds DynamicQuery i o
q
DynamicSystemT m i (Maybe o)
-> DynamicSystemT m (Maybe o) o -> DynamicSystemT m i o
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> (Maybe o -> o) -> DynamicSystemT m (Maybe o) o
forall b c. (b -> c) -> DynamicSystemT m b c
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr (o -> Maybe o -> o
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> o
forall a. HasCallStack => [Char] -> a
error [Char]
"Expected a single matching entity."))
in DynamicSystemT m i o
-> Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o)
forall (m :: * -> *) i o.
DynamicSystemT m i o
-> Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o)
runSystemDyn DynamicSystemT m i o
s Entities
w i
i
mapSingleMaybeDyn :: forall i o.
Set ComponentID -> DynamicQuery i o -> DynamicSystemT m i (Maybe o)
mapSingleMaybeDyn Set ComponentID
cIds DynamicQuery i o
q = (Entities
-> i
-> (Maybe o, View, AccessT m (), DynamicSystemT m i (Maybe o)))
-> DynamicSystemT m i (Maybe o)
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem ((Entities
-> i
-> (Maybe o, View, AccessT m (), DynamicSystemT m i (Maybe o)))
-> DynamicSystemT m i (Maybe o))
-> (Entities
-> i
-> (Maybe o, View, AccessT m (), DynamicSystemT m i (Maybe o)))
-> DynamicSystemT m i (Maybe o)
forall a b. (a -> b) -> a -> b
$ \Entities
w i
i ->
let !res :: Maybe View
res = Set ComponentID -> Archetypes -> Maybe View
V.viewSingle Set ComponentID
cIds (Archetypes -> Maybe View) -> Archetypes -> Maybe View
forall a b. (a -> b) -> a -> b
$ Entities -> Archetypes
archetypes Entities
w
(Maybe o
res', View
v'') = case Maybe View
res of
Just View
v -> let (Maybe o
o, View
v') = i -> DynamicQuery i o -> View -> (Maybe o, View)
forall i a. i -> DynamicQuery i a -> View -> (Maybe a, View)
V.singleDyn i
i DynamicQuery i o
q View
v in (Maybe o
o, View
v')
Maybe View
Nothing -> (Maybe o
forall a. Maybe a
Nothing, View
forall a. Monoid a => a
mempty)
in (Maybe o
res', View
v'', () -> AccessT m ()
forall a. a -> AccessT m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (), Set ComponentID -> DynamicQuery i o -> DynamicSystemT m i (Maybe o)
forall i o.
Set ComponentID -> DynamicQuery i o -> DynamicSystemT m i (Maybe o)
forall (q :: * -> * -> *) (arr :: * -> * -> *) i o.
ArrowDynamicSystem q arr =>
Set ComponentID -> q i o -> arr i (Maybe o)
mapSingleMaybeDyn Set ComponentID
cIds DynamicQuery i o
q)
filterMapDyn :: forall i o.
Set ComponentID
-> DynamicQuery i o -> (Node -> Bool) -> DynamicSystemT m i [o]
filterMapDyn Set ComponentID
cIds DynamicQuery i o
q Node -> Bool
f = (Entities
-> i -> ([o], View, AccessT m (), DynamicSystemT m i [o]))
-> DynamicSystemT m i [o]
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem ((Entities
-> i -> ([o], View, AccessT m (), DynamicSystemT m i [o]))
-> DynamicSystemT m i [o])
-> (Entities
-> i -> ([o], View, AccessT m (), DynamicSystemT m i [o]))
-> DynamicSystemT m i [o]
forall a b. (a -> b) -> a -> b
$ \Entities
w i
i ->
let !v :: View
v = Set ComponentID -> (Node -> Bool) -> Archetypes -> View
V.filterView Set ComponentID
cIds Node -> Bool
f (Archetypes -> View) -> Archetypes -> View
forall a b. (a -> b) -> a -> b
$ Entities -> Archetypes
archetypes Entities
w
([o]
o, View
v') = i -> DynamicQuery i o -> View -> ([o], View)
forall i a. i -> DynamicQuery i a -> View -> ([a], View)
V.allDyn i
i DynamicQuery i o
q View
v
in ([o]
o, View
v', () -> AccessT m ()
forall a. a -> AccessT m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (), Set ComponentID
-> DynamicQuery i o -> (Node -> Bool) -> DynamicSystemT m i [o]
forall i o.
Set ComponentID
-> DynamicQuery i o -> (Node -> Bool) -> DynamicSystemT m i [o]
forall (q :: * -> * -> *) (arr :: * -> * -> *) i o.
ArrowDynamicSystem q arr =>
Set ComponentID -> q i o -> (Node -> Bool) -> arr i [o]
filterMapDyn Set ComponentID
cIds DynamicQuery i o
q Node -> Bool
f)
instance (Monad m) => ArrowQueueSystem Bundle (AccessT m) (DynamicSystemT m) where
queue :: forall i. (i -> AccessT m ()) -> DynamicSystemT m i ()
queue i -> AccessT m ()
f = (Entities -> i -> ((), View, AccessT m (), DynamicSystemT m i ()))
-> DynamicSystemT m i ()
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem ((Entities -> i -> ((), View, AccessT m (), DynamicSystemT m i ()))
-> DynamicSystemT m i ())
-> (Entities
-> i -> ((), View, AccessT m (), DynamicSystemT m i ()))
-> DynamicSystemT m i ()
forall a b. (a -> b) -> a -> b
$ \Entities
_ i
i -> ((), View
forall a. Monoid a => a
mempty, i -> AccessT m ()
f i
i, (i -> AccessT m ()) -> DynamicSystemT m i ()
forall i. (i -> AccessT m ()) -> DynamicSystemT m i ()
forall b (m :: * -> *) (arr :: * -> * -> *) i.
ArrowQueueSystem b m arr =>
(i -> m ()) -> arr i ()
queue i -> AccessT m ()
f)
raceDyn :: (Monad m) => DynamicSystemT m i a -> DynamicSystemT m i b -> DynamicSystemT m i (a, b)
raceDyn :: forall (m :: * -> *) i a b.
Monad m =>
DynamicSystemT m i a
-> DynamicSystemT m i b -> DynamicSystemT m i (a, b)
raceDyn (DynamicSystem Entities -> i -> (a, View, AccessT m (), DynamicSystemT m i a)
f) (DynamicSystem Entities -> i -> (b, View, AccessT m (), DynamicSystemT m i b)
g) = (Entities
-> i -> ((a, b), View, AccessT m (), DynamicSystemT m i (a, b)))
-> DynamicSystemT m i (a, b)
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem ((Entities
-> i -> ((a, b), View, AccessT m (), DynamicSystemT m i (a, b)))
-> DynamicSystemT m i (a, b))
-> (Entities
-> i -> ((a, b), View, AccessT m (), DynamicSystemT m i (a, b)))
-> DynamicSystemT m i (a, b)
forall a b. (a -> b) -> a -> b
$ \Entities
w i
i ->
let fa :: (a, View, AccessT m (), DynamicSystemT m i a)
fa = Entities -> i -> (a, View, AccessT m (), DynamicSystemT m i a)
f Entities
w i
i
gb :: (b, View, AccessT m (), DynamicSystemT m i b)
gb = Entities -> i -> (b, View, AccessT m (), DynamicSystemT m i b)
g Entities
w i
i
gbPar :: (b, View, AccessT m (), DynamicSystemT m i b)
gbPar = (a, View, AccessT m (), DynamicSystemT m i a)
fa (a, View, AccessT m (), DynamicSystemT m i a)
-> (b, View, AccessT m (), DynamicSystemT m i b)
-> (b, View, AccessT m (), DynamicSystemT m i b)
forall a b. a -> b -> b
`par` (b, View, AccessT m (), DynamicSystemT m i b)
gb
(a
a, View
v, AccessT m ()
fAccess, DynamicSystemT m i a
f') = (a, View, AccessT m (), DynamicSystemT m i a)
fa
(b
b, View
v', AccessT m ()
gAccess, DynamicSystemT m i b
g') = (b, View, AccessT m (), DynamicSystemT m i b)
gbPar
in ((a
a, b
b), View
v View -> View -> View
forall a. Semigroup a => a -> a -> a
<> View
v', AccessT m ()
fAccess AccessT m () -> AccessT m () -> AccessT m ()
forall a b. AccessT m a -> AccessT m b -> AccessT m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> AccessT m ()
gAccess, DynamicSystemT m i a
-> DynamicSystemT m i b -> DynamicSystemT m i (a, b)
forall (m :: * -> *) i a b.
Monad m =>
DynamicSystemT m i a
-> DynamicSystemT m i b -> DynamicSystemT m i (a, b)
raceDyn DynamicSystemT m i a
f' DynamicSystemT m i b
g')
fromDynReaderSystem :: DynamicReaderSystemT m i o -> DynamicSystemT m i o
fromDynReaderSystem :: forall (m :: * -> *) i o.
DynamicReaderSystemT m i o -> DynamicSystemT m i o
fromDynReaderSystem (DynamicReaderSystem Entities -> i -> (o, AccessT m (), DynamicReaderSystemT m i o)
f) = (Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
forall (m :: * -> *) i o.
(Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
DynamicSystem ((Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o)
-> (Entities -> i -> (o, View, AccessT m (), DynamicSystemT m i o))
-> DynamicSystemT m i o
forall a b. (a -> b) -> a -> b
$ \Entities
w i
i ->
let (o
o, AccessT m ()
access, DynamicReaderSystemT m i o
f') = Entities -> i -> (o, AccessT m (), DynamicReaderSystemT m i o)
f Entities
w i
i in (o
o, View
forall a. Monoid a => a
mempty, AccessT m ()
access, DynamicReaderSystemT m i o -> DynamicSystemT m i o
forall (m :: * -> *) i o.
DynamicReaderSystemT m i o -> DynamicSystemT m i o
fromDynReaderSystem DynamicReaderSystemT m i o
f')