module Swarm.Game.Step.Util.Inspect where
import Control.Carrier.State.Lazy
import Control.Effect.Lens
import Control.Lens hiding (from, use, (%=), (<.>))
import Data.IntMap qualified as IM
import Data.List (find)
import Data.List.Extra (enumerate)
import Data.Text (Text)
import Swarm.Game.Location
import Swarm.Game.Robot
import Swarm.Game.State
import Swarm.Game.State.Robot
import Swarm.Game.Universe
import Swarm.Language.Syntax.Direction
getNeighborLocs :: Cosmic Location -> [Cosmic Location]
getNeighborLocs :: Cosmic Location -> [Cosmic Location]
getNeighborLocs Cosmic Location
loc = (PlanarRelativeDir -> Cosmic Location)
-> [PlanarRelativeDir] -> [Cosmic Location]
forall a b. (a -> b) -> [a] -> [b]
map (Cosmic Location -> V2 Int32 -> Cosmic Location
offsetBy Cosmic Location
loc (V2 Int32 -> Cosmic Location)
-> (PlanarRelativeDir -> V2 Int32)
-> PlanarRelativeDir
-> Cosmic Location
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Direction -> V2 Int32 -> V2 Int32)
-> V2 Int32 -> Direction -> V2 Int32
forall a b c. (a -> b -> c) -> b -> a -> c
flip Direction -> V2 Int32 -> V2 Int32
applyTurn V2 Int32
north (Direction -> V2 Int32)
-> (PlanarRelativeDir -> Direction)
-> PlanarRelativeDir
-> V2 Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelativeDir -> Direction
DRelative (RelativeDir -> Direction)
-> (PlanarRelativeDir -> RelativeDir)
-> PlanarRelativeDir
-> Direction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlanarRelativeDir -> RelativeDir
DPlanar) [PlanarRelativeDir]
forall a. (Enum a, Bounded a) => [a]
enumerate
robotWithID :: (Has (State GameState) sig m) => RID -> m (Maybe Robot)
robotWithID :: forall (sig :: (* -> *) -> * -> *) (m :: * -> *).
Has (State GameState) sig m =>
RID -> m (Maybe Robot)
robotWithID RID
rid = Getting (Maybe Robot) GameState (Maybe Robot) -> m (Maybe Robot)
forall s a (sig :: (* -> *) -> * -> *) (m :: * -> *).
Has (State s) sig m =>
Getting a s a -> m a
use ((Robots -> Const (Maybe Robot) Robots)
-> GameState -> Const (Maybe Robot) GameState
Lens' GameState Robots
robotInfo ((Robots -> Const (Maybe Robot) Robots)
-> GameState -> Const (Maybe Robot) GameState)
-> ((Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> Robots -> Const (Maybe Robot) Robots)
-> Getting (Maybe Robot) GameState (Maybe Robot)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap Robot -> Const (Maybe Robot) (IntMap Robot))
-> Robots -> Const (Maybe Robot) Robots
Lens' Robots (IntMap Robot)
robotMap ((IntMap Robot -> Const (Maybe Robot) (IntMap Robot))
-> Robots -> Const (Maybe Robot) Robots)
-> ((Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> IntMap Robot -> Const (Maybe Robot) (IntMap Robot))
-> (Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> Robots
-> Const (Maybe Robot) Robots
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (IntMap Robot)
-> Lens' (IntMap Robot) (Maybe (IxValue (IntMap Robot)))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at RID
Index (IntMap Robot)
rid)
robotWithName :: (Has (State GameState) sig m) => Text -> m (Maybe Robot)
robotWithName :: forall (sig :: (* -> *) -> * -> *) (m :: * -> *).
Has (State GameState) sig m =>
Text -> m (Maybe Robot)
robotWithName Text
rname = Getting (Maybe Robot) GameState (Maybe Robot) -> m (Maybe Robot)
forall s a (sig :: (* -> *) -> * -> *) (m :: * -> *).
Has (State s) sig m =>
Getting a s a -> m a
use ((Robots -> Const (Maybe Robot) Robots)
-> GameState -> Const (Maybe Robot) GameState
Lens' GameState Robots
robotInfo ((Robots -> Const (Maybe Robot) Robots)
-> GameState -> Const (Maybe Robot) GameState)
-> ((Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> Robots -> Const (Maybe Robot) Robots)
-> Getting (Maybe Robot) GameState (Maybe Robot)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap Robot -> Const (Maybe Robot) (IntMap Robot))
-> Robots -> Const (Maybe Robot) Robots
Lens' Robots (IntMap Robot)
robotMap ((IntMap Robot -> Const (Maybe Robot) (IntMap Robot))
-> Robots -> Const (Maybe Robot) Robots)
-> ((Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> IntMap Robot -> Const (Maybe Robot) (IntMap Robot))
-> (Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> Robots
-> Const (Maybe Robot) Robots
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap Robot -> [Robot])
-> ([Robot] -> Const (Maybe Robot) [Robot])
-> IntMap Robot
-> Const (Maybe Robot) (IntMap Robot)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to IntMap Robot -> [Robot]
forall a. IntMap a -> [a]
IM.elems (([Robot] -> Const (Maybe Robot) [Robot])
-> IntMap Robot -> Const (Maybe Robot) (IntMap Robot))
-> ((Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> [Robot] -> Const (Maybe Robot) [Robot])
-> (Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> IntMap Robot
-> Const (Maybe Robot) (IntMap Robot)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Robot] -> Maybe Robot)
-> (Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> [Robot]
-> Const (Maybe Robot) [Robot]
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ((Robot -> Bool) -> [Robot] -> Maybe Robot
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((Robot -> Bool) -> [Robot] -> Maybe Robot)
-> (Robot -> Bool) -> [Robot] -> Maybe Robot
forall a b. (a -> b) -> a -> b
$ \Robot
r -> Robot
r Robot -> Getting Text Robot Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text Robot Text
Lens' Robot Text
robotName Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
rname))