module Swarm.Game.Step.Path.Cache.DistanceLimit (
getDistanceLimitInvalidation,
withinDistance,
) where
import Control.Monad (unless)
import Data.List.NonEmpty (NonEmpty)
import Data.List.NonEmpty qualified as NE
import Swarm.Game.Location
import Swarm.Game.Step.Path.Type
getDistanceLimitInvalidation ::
Location ->
NonEmpty Location ->
Maybe Integer ->
Maybe Integer ->
Either DistanceLimitChange ()
getDistanceLimitInvalidation :: Location
-> NonEmpty Location
-> Maybe Integer
-> Maybe Integer
-> Either DistanceLimitChange ()
getDistanceLimitInvalidation Location
_ NonEmpty Location
_ Maybe Integer
Nothing Maybe Integer
Nothing = () -> Either DistanceLimitChange ()
forall a. a -> Either DistanceLimitChange a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
getDistanceLimitInvalidation Location
_ NonEmpty Location
_ Maybe Integer
Nothing (Just Integer
_) = DistanceLimitChange -> Either DistanceLimitChange ()
forall a b. a -> Either a b
Left DistanceLimitChange
LimitIncreased
getDistanceLimitInvalidation Location
robotLoc NonEmpty Location
pathCells (Just Integer
currLimit) Maybe Integer
Nothing =
Location
-> NonEmpty Location -> Integer -> Either DistanceLimitChange ()
handleLimitDecreased Location
robotLoc NonEmpty Location
pathCells Integer
currLimit
getDistanceLimitInvalidation Location
robotLoc NonEmpty Location
pathCells (Just Integer
currLimit) (Just Integer
prevLimit)
| Integer
currLimit Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
prevLimit = Location
-> NonEmpty Location -> Integer -> Either DistanceLimitChange ()
handleLimitDecreased Location
robotLoc NonEmpty Location
pathCells Integer
currLimit
| Integer
currLimit Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
prevLimit = DistanceLimitChange -> Either DistanceLimitChange ()
forall a b. a -> Either a b
Left DistanceLimitChange
LimitIncreased
| Bool
otherwise = () -> Either DistanceLimitChange ()
forall a. a -> Either DistanceLimitChange a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
handleLimitDecreased ::
Location ->
NonEmpty Location ->
Integer ->
Either DistanceLimitChange ()
handleLimitDecreased :: Location
-> NonEmpty Location -> Integer -> Either DistanceLimitChange ()
handleLimitDecreased Location
robotLoc NonEmpty Location
pathCells Integer
currLimit =
Bool
-> Either DistanceLimitChange () -> Either DistanceLimitChange ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Location -> Bool) -> [Location] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Integer -> Location -> Location -> Bool
withinDistance Integer
currLimit Location
robotLoc) ([Location] -> Bool) -> [Location] -> Bool
forall a b. (a -> b) -> a -> b
$ NonEmpty Location -> [Location]
forall a. NonEmpty a -> [a]
NE.tail NonEmpty Location
pathCells) (Either DistanceLimitChange () -> Either DistanceLimitChange ())
-> Either DistanceLimitChange () -> Either DistanceLimitChange ()
forall a b. (a -> b) -> a -> b
$
DistanceLimitChange -> Either DistanceLimitChange ()
forall a b. a -> Either a b
Left DistanceLimitChange
PathExceededLimit
withinDistance ::
Integer ->
Location ->
Location ->
Bool
withinDistance :: Integer -> Location -> Location -> Bool
withinDistance Integer
distLimit Location
robotLoc = (Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
distLimit) (Integer -> Bool) -> (Location -> Integer) -> Location -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int32 -> Integer) -> (Location -> Int32) -> Location -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Location -> Location -> Int32
manhattan Location
robotLoc