{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Aztecs.ECS.World
( World (..),
empty,
spawn,
spawnEmpty,
insert,
lookup,
remove,
removeWithId,
despawn,
)
where
import Aztecs.ECS.Component
import Aztecs.ECS.Entity
import Aztecs.ECS.World.Bundle
import Aztecs.ECS.World.Entities (Entities)
import qualified Aztecs.ECS.World.Entities as E
import Control.DeepSeq
import Data.Dynamic
import Data.IntMap (IntMap)
import GHC.Generics
import Prelude hiding (lookup)
data World = World
{
World -> Entities
entities :: !Entities,
World -> EntityID
nextEntityId :: !EntityID
}
deriving (Int -> World -> ShowS
[World] -> ShowS
World -> String
(Int -> World -> ShowS)
-> (World -> String) -> ([World] -> ShowS) -> Show World
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> World -> ShowS
showsPrec :: Int -> World -> ShowS
$cshow :: World -> String
show :: World -> String
$cshowList :: [World] -> ShowS
showList :: [World] -> ShowS
Show, (forall x. World -> Rep World x)
-> (forall x. Rep World x -> World) -> Generic World
forall x. Rep World x -> World
forall x. World -> Rep World x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. World -> Rep World x
from :: forall x. World -> Rep World x
$cto :: forall x. Rep World x -> World
to :: forall x. Rep World x -> World
Generic, World -> ()
(World -> ()) -> NFData World
forall a. (a -> ()) -> NFData a
$crnf :: World -> ()
rnf :: World -> ()
NFData)
empty :: World
empty :: World
empty =
World
{ entities :: Entities
entities = Entities
E.empty,
nextEntityId :: EntityID
nextEntityId = Int -> EntityID
EntityID Int
0
}
spawn :: Bundle -> World -> (EntityID, World)
spawn :: Bundle -> World -> (EntityID, World)
spawn Bundle
b World
w =
let e :: EntityID
e = World -> EntityID
nextEntityId World
w
in (EntityID
e, World
w {entities = E.spawn e b $ entities w, nextEntityId = EntityID $ unEntityId e + 1})
spawnEmpty :: World -> (EntityID, World)
spawnEmpty :: World -> (EntityID, World)
spawnEmpty World
w = let e :: EntityID
e = World -> EntityID
nextEntityId World
w in (EntityID
e, World
w {nextEntityId = EntityID $ unEntityId e + 1})
insert :: EntityID -> Bundle -> World -> World
insert :: EntityID -> Bundle -> World -> World
insert EntityID
e Bundle
c World
w = World
w {entities = E.insert e c (entities w)}
lookup :: forall a. (Component a) => EntityID -> World -> Maybe a
lookup :: forall a. Component a => EntityID -> World -> Maybe a
lookup EntityID
e World
w = EntityID -> Entities -> Maybe a
forall a. Component a => EntityID -> Entities -> Maybe a
E.lookup EntityID
e (Entities -> Maybe a) -> Entities -> Maybe a
forall a b. (a -> b) -> a -> b
$ World -> Entities
entities World
w
remove :: forall a. (Component a) => EntityID -> World -> (Maybe a, World)
remove :: forall a. Component a => EntityID -> World -> (Maybe a, World)
remove EntityID
e World
w = let (Maybe a
a, Entities
es) = EntityID -> Entities -> (Maybe a, Entities)
forall a.
Component a =>
EntityID -> Entities -> (Maybe a, Entities)
E.remove EntityID
e (World -> Entities
entities World
w) in (Maybe a
a, World
w {entities = es})
removeWithId :: forall a. (Component a) => EntityID -> ComponentID -> World -> (Maybe a, World)
removeWithId :: forall a.
Component a =>
EntityID -> ComponentID -> World -> (Maybe a, World)
removeWithId EntityID
e ComponentID
cId World
w = let (Maybe a
a, Entities
es) = EntityID -> ComponentID -> Entities -> (Maybe a, Entities)
forall a.
Component a =>
EntityID -> ComponentID -> Entities -> (Maybe a, Entities)
E.removeWithId EntityID
e ComponentID
cId (World -> Entities
entities World
w) in (Maybe a
a, World
w {entities = es})
despawn :: EntityID -> World -> (IntMap Dynamic, World)
despawn :: EntityID -> World -> (IntMap Dynamic, World)
despawn EntityID
e World
w = let (IntMap Dynamic
a, Entities
es) = EntityID -> Entities -> (IntMap Dynamic, Entities)
E.despawn EntityID
e (World -> Entities
entities World
w) in (IntMap Dynamic
a, World
w {entities = es})