| Copyright | (C) 2020 Sophie Taylor |
|---|---|
| License | AGPL-3.0-or-later |
| Maintainer | Sophie Taylor <sophie@spacekitteh.moe> |
| Stability | experimental |
| Portability | GHC |
| Safe Haskell | None |
| Language | GHC2021 |
Games.ECS
Description
This is the top-level interface to OhhECS. A brief tutorial should probably go here.
import GHC.Generics
import Control.Lens
data Position = Position Int Int
deriving stock (Generic, Eq, Show)
instance Num Position where
(Position a b) + (Position c d) = Position (a + c) (b + d)
(*) = undefined
abs = undefined
signum = undefined
fromInteger = undefined
negate = undefined
instance Component Position where
type CanonicalName Position = "position"
makeHasComponentClass ''Position
data GameWorld s where
GameWorld ::
EntRefField s ->
AComponent "position" s Position ->
GameWorld s
deriving stock (Generic)
deriving instance Show (GameWorld Individual)
deriving instance Show (GameWorld Storing)
deriving instance Eq (GameWorld Individual)
deriving instance Eq (GameWorld Storing)
makeWorld ''GameWorld
data MovementSystem = MovementSystem deriving (Eq, Show, Generic)
instance (UsingPosition worldType Individual, Monad m) => System "MovementSystem" MovementSystem worldType m where
type ComponentFilters "MovementSystem" MovementSystem worldType m = (UsingPosition worldType Individual)
runSystem world = traverseOf (entitiesWith (withPosition)) processCritter world
where
processCritter :: worldType Individual -> m (worldType Individual)
processCritter oldCritter = do
let newCritter = oldCritter & position .~ (Position 1 0)
pure newCritter
someEntity :: GameWorld Individual
someEntity = (createNewEntityWithRef (EntRef 123)) & addPosition .~ Position 4 5
myWorld :: GameWorld Storing
myWorld = newWorld & storeEntity someEntity
changed :: IO (GameWorld Storing)
changed = runSystem @"MovementSystem" myWorld
Synopsis
- type EntityFilter (worldType :: Access -> Type) = IndexedTraversal' Entity (worldType 'Storing) (worldType 'Individual)
- module Games.ECS.Util.Misc
- module Games.ECS.Component
- module Games.ECS.Serialisation
- module Games.ECS.Component.Store
- module Games.ECS.Component.TH
- module Games.ECS.World
- module Games.ECS.World.TH
- module Games.ECS.Entity
- module Games.ECS.SaveLoad
- module Games.ECS.System
- module Games.ECS.Slot
- module Games.ECS.Prototype
- module Games.ECS.Prototype.PrototypeID
- module Games.ECS.Prototype.SpawnedFromPrototype
- module Games.ECS.MessageQueue
Documentation
type EntityFilter (worldType :: Access -> Type) = IndexedTraversal' Entity (worldType 'Storing) (worldType 'Individual) Source #
A filter over entities in a world is just an IndexedTraversal' that preserves the selection predicate.
module Games.ECS.Util.Misc
module Games.ECS.Component
module Games.ECS.Serialisation
module Games.ECS.Component.Store
module Games.ECS.Component.TH
module Games.ECS.World
module Games.ECS.World.TH
module Games.ECS.Entity
module Games.ECS.SaveLoad
module Games.ECS.System
module Games.ECS.Slot
module Games.ECS.Prototype
module Games.ECS.MessageQueue