module Swarm.TUI.Editor.Masking where
import Control.Lens hiding (Const, from)
import Data.Maybe (fromMaybe)
import Swarm.Game.Universe
import Swarm.Game.World.Coords
import Swarm.TUI.Editor.Model
import Swarm.TUI.Editor.Util qualified as EU
import Swarm.TUI.Model.UI.Gameplay
shouldHideWorldCell :: UIGameplay -> Coords -> Bool
shouldHideWorldCell :: UIGameplay -> Coords -> Bool
shouldHideWorldCell UIGameplay
ui Coords
coords =
Bool
isOutsideSingleSelectedCorner Bool -> Bool -> Bool
|| Bool
isOutsideMapSaveBounds
where
we :: WorldEditor Name
we = UIGameplay
ui UIGameplay
-> Getting (WorldEditor Name) UIGameplay (WorldEditor Name)
-> WorldEditor Name
forall s a. s -> Getting a s a -> a
^. Getting (WorldEditor Name) UIGameplay (WorldEditor Name)
Lens' UIGameplay (WorldEditor Name)
uiWorldEditor
withinTimeout :: Bool
withinTimeout = UIGameplay
ui UIGameplay -> Getting TimeSpec UIGameplay TimeSpec -> TimeSpec
forall s a. s -> Getting a s a -> a
^. (UITiming -> Const TimeSpec UITiming)
-> UIGameplay -> Const TimeSpec UIGameplay
Lens' UIGameplay UITiming
uiTiming ((UITiming -> Const TimeSpec UITiming)
-> UIGameplay -> Const TimeSpec UIGameplay)
-> ((TimeSpec -> Const TimeSpec TimeSpec)
-> UITiming -> Const TimeSpec UITiming)
-> Getting TimeSpec UIGameplay TimeSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TimeSpec -> Const TimeSpec TimeSpec)
-> UITiming -> Const TimeSpec UITiming
Lens' UITiming TimeSpec
lastFrameTime TimeSpec -> TimeSpec -> Bool
forall a. Ord a => a -> a -> Bool
< WorldEditor Name
we WorldEditor Name
-> Getting TimeSpec (WorldEditor Name) TimeSpec -> TimeSpec
forall s a. s -> Getting a s a -> a
^. (MapEditingBounds -> Const TimeSpec MapEditingBounds)
-> WorldEditor Name -> Const TimeSpec (WorldEditor Name)
forall n (f :: * -> *).
Functor f =>
(MapEditingBounds -> f MapEditingBounds)
-> WorldEditor n -> f (WorldEditor n)
editingBounds ((MapEditingBounds -> Const TimeSpec MapEditingBounds)
-> WorldEditor Name -> Const TimeSpec (WorldEditor Name))
-> ((TimeSpec -> Const TimeSpec TimeSpec)
-> MapEditingBounds -> Const TimeSpec MapEditingBounds)
-> Getting TimeSpec (WorldEditor Name) TimeSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TimeSpec -> Const TimeSpec TimeSpec)
-> MapEditingBounds -> Const TimeSpec MapEditingBounds
Lens' MapEditingBounds TimeSpec
boundsPersistDisplayUntil
isOutsideMapSaveBounds :: Bool
isOutsideMapSaveBounds =
Bool
withinTimeout
Bool -> Bool -> Bool
&& Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe
Bool
False
( do
Cosmic BoundsRectangle
bounds <- WorldEditor Name
we WorldEditor Name
-> Getting
(Maybe (Cosmic BoundsRectangle))
(WorldEditor Name)
(Maybe (Cosmic BoundsRectangle))
-> Maybe (Cosmic BoundsRectangle)
forall s a. s -> Getting a s a -> a
^. (MapEditingBounds
-> Const (Maybe (Cosmic BoundsRectangle)) MapEditingBounds)
-> WorldEditor Name
-> Const (Maybe (Cosmic BoundsRectangle)) (WorldEditor Name)
forall n (f :: * -> *).
Functor f =>
(MapEditingBounds -> f MapEditingBounds)
-> WorldEditor n -> f (WorldEditor n)
editingBounds ((MapEditingBounds
-> Const (Maybe (Cosmic BoundsRectangle)) MapEditingBounds)
-> WorldEditor Name
-> Const (Maybe (Cosmic BoundsRectangle)) (WorldEditor Name))
-> ((Maybe (Cosmic BoundsRectangle)
-> Const
(Maybe (Cosmic BoundsRectangle)) (Maybe (Cosmic BoundsRectangle)))
-> MapEditingBounds
-> Const (Maybe (Cosmic BoundsRectangle)) MapEditingBounds)
-> Getting
(Maybe (Cosmic BoundsRectangle))
(WorldEditor Name)
(Maybe (Cosmic BoundsRectangle))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe (Cosmic BoundsRectangle)
-> Const
(Maybe (Cosmic BoundsRectangle)) (Maybe (Cosmic BoundsRectangle)))
-> MapEditingBounds
-> Const (Maybe (Cosmic BoundsRectangle)) MapEditingBounds
Lens' MapEditingBounds (Maybe (Cosmic BoundsRectangle))
boundsRect
Bool -> Maybe Bool
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ BoundsRectangle -> Coords -> Bool
EU.isOutsideRegion (Cosmic BoundsRectangle
bounds Cosmic BoundsRectangle
-> Getting BoundsRectangle (Cosmic BoundsRectangle) BoundsRectangle
-> BoundsRectangle
forall s a. s -> Getting a s a -> a
^. Getting BoundsRectangle (Cosmic BoundsRectangle) BoundsRectangle
forall a1 a2 (f :: * -> *).
Functor f =>
(a1 -> f a2) -> Cosmic a1 -> f (Cosmic a2)
planar) Coords
coords
)
isOutsideSingleSelectedCorner :: Bool
isOutsideSingleSelectedCorner = Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
False (Maybe Bool -> Bool) -> Maybe Bool -> Bool
forall a b. (a -> b) -> a -> b
$ do
Cosmic SubworldName
_ Coords
cornerCoords <- case WorldEditor Name
we WorldEditor Name
-> Getting
BoundsSelectionStep (WorldEditor Name) BoundsSelectionStep
-> BoundsSelectionStep
forall s a. s -> Getting a s a -> a
^. (MapEditingBounds -> Const BoundsSelectionStep MapEditingBounds)
-> WorldEditor Name -> Const BoundsSelectionStep (WorldEditor Name)
forall n (f :: * -> *).
Functor f =>
(MapEditingBounds -> f MapEditingBounds)
-> WorldEditor n -> f (WorldEditor n)
editingBounds ((MapEditingBounds -> Const BoundsSelectionStep MapEditingBounds)
-> WorldEditor Name
-> Const BoundsSelectionStep (WorldEditor Name))
-> ((BoundsSelectionStep
-> Const BoundsSelectionStep BoundsSelectionStep)
-> MapEditingBounds -> Const BoundsSelectionStep MapEditingBounds)
-> Getting
BoundsSelectionStep (WorldEditor Name) BoundsSelectionStep
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BoundsSelectionStep
-> Const BoundsSelectionStep BoundsSelectionStep)
-> MapEditingBounds -> Const BoundsSelectionStep MapEditingBounds
Lens' MapEditingBounds BoundsSelectionStep
boundsSelectionStep of
LowerRightPending Cosmic Coords
cornerCoords -> Cosmic Coords -> Maybe (Cosmic Coords)
forall a. a -> Maybe a
Just Cosmic Coords
cornerCoords
BoundsSelectionStep
_ -> Maybe (Cosmic Coords)
forall a. Maybe a
Nothing
Bool -> Maybe Bool
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Maybe Bool) -> Bool -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ Coords -> Coords -> Bool
EU.isOutsideTopLeftCorner Coords
cornerCoords Coords
coords