module Swarm.Game.World.Modify where
import Control.Lens (view)
import Data.Function (on)
import Swarm.Game.Entity (Entity, entityHash)
data CellUpdate e
= NoChange (Maybe e)
| Modified (CellModification e)
getModification :: CellUpdate e -> Maybe (CellModification e)
getModification :: forall e. CellUpdate e -> Maybe (CellModification e)
getModification (NoChange Maybe e
_) = Maybe (CellModification e)
forall a. Maybe a
Nothing
getModification (Modified CellModification e
x) = CellModification e -> Maybe (CellModification e)
forall a. a -> Maybe a
Just CellModification e
x
data CellModification e
=
Swap e e
| Remove e
| Add e
classifyModification ::
Maybe Entity ->
Maybe Entity ->
CellUpdate Entity
classifyModification :: Maybe Entity -> Maybe Entity -> CellUpdate Entity
classifyModification Maybe Entity
Nothing Maybe Entity
Nothing = Maybe Entity -> CellUpdate Entity
forall e. Maybe e -> CellUpdate e
NoChange Maybe Entity
forall a. Maybe a
Nothing
classifyModification Maybe Entity
Nothing (Just Entity
x) = CellModification Entity -> CellUpdate Entity
forall e. CellModification e -> CellUpdate e
Modified (CellModification Entity -> CellUpdate Entity)
-> CellModification Entity -> CellUpdate Entity
forall a b. (a -> b) -> a -> b
$ Entity -> CellModification Entity
forall e. e -> CellModification e
Add Entity
x
classifyModification (Just Entity
x) Maybe Entity
Nothing = CellModification Entity -> CellUpdate Entity
forall e. CellModification e -> CellUpdate e
Modified (CellModification Entity -> CellUpdate Entity)
-> CellModification Entity -> CellUpdate Entity
forall a b. (a -> b) -> a -> b
$ Entity -> CellModification Entity
forall e. e -> CellModification e
Remove Entity
x
classifyModification (Just Entity
x) (Just Entity
y) =
if (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
(/=) (Int -> Int -> Bool) -> (Entity -> Int) -> Entity -> Entity -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Getting Int Entity Int -> Entity -> Int
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Int Entity Int
Getter Entity Int
entityHash) Entity
x Entity
y
then CellModification Entity -> CellUpdate Entity
forall e. CellModification e -> CellUpdate e
Modified (CellModification Entity -> CellUpdate Entity)
-> CellModification Entity -> CellUpdate Entity
forall a b. (a -> b) -> a -> b
$ Entity -> Entity -> CellModification Entity
forall e. e -> e -> CellModification e
Swap Entity
x Entity
y
else Maybe Entity -> CellUpdate Entity
forall e. Maybe e -> CellUpdate e
NoChange (Maybe Entity -> CellUpdate Entity)
-> Maybe Entity -> CellUpdate Entity
forall a b. (a -> b) -> a -> b
$ Entity -> Maybe Entity
forall a. a -> Maybe a
Just Entity
x