ohhecs-0.0.2: An Entity-Component-Systems engine core.
Copyright(C) 2020 Sophie Taylor
LicenseAGPL-3.0-or-later
MaintainerSophie Taylor <sophie@spacekitteh.moe>
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageGHC2021

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

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.