{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Swarm.TUI.Controller.EventHandlers.Robot (
robotEventHandlers,
handleRobotPanelEvent,
) where
import Brick
import Brick.Keybindings
import Control.Lens as Lens
import Control.Lens.Extras as Lens (is)
import Control.Monad (unless, when)
import Data.Text qualified as T
import Graphics.Vty qualified as V
import Swarm.Game.Entity hiding (empty)
import Swarm.Game.Robot.Concrete
import Swarm.Game.State
import Swarm.Language.Pipeline.QQ (tmQ)
import Swarm.Language.Syntax hiding (Key)
import Swarm.TUI.Controller.Util
import Swarm.TUI.Inventory.Sorting (cycleSortDirection, cycleSortOrder)
import Swarm.TUI.List
import Swarm.TUI.Model
import Swarm.TUI.Model.Event
import Swarm.TUI.Model.Menu
import Swarm.TUI.Model.UI.Gameplay
import Swarm.TUI.View.Util (generateModal)
handleRobotPanelEvent :: BrickEvent Name AppEvent -> EventM Name AppState ()
handleRobotPanelEvent :: BrickEvent Name AppEvent -> EventM Name AppState ()
handleRobotPanelEvent BrickEvent Name AppEvent
bev = do
Maybe Text
search <- Getting (Maybe Text) AppState (Maybe Text)
-> EventM Name AppState (Maybe Text)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting (Maybe Text) AppState (Maybe Text)
-> EventM Name AppState (Maybe Text))
-> Getting (Maybe Text) AppState (Maybe Text)
-> EventM Name AppState (Maybe Text)
forall a b. (a -> b) -> a -> b
$ (PlayState -> Const (Maybe Text) PlayState)
-> AppState -> Const (Maybe Text) AppState
Lens' AppState PlayState
playState ((PlayState -> Const (Maybe Text) PlayState)
-> AppState -> Const (Maybe Text) AppState)
-> ((Maybe Text -> Const (Maybe Text) (Maybe Text))
-> PlayState -> Const (Maybe Text) PlayState)
-> Getting (Maybe Text) AppState (Maybe Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioState -> Const (Maybe Text) ScenarioState)
-> PlayState -> Const (Maybe Text) PlayState
Lens' PlayState ScenarioState
scenarioState ((ScenarioState -> Const (Maybe Text) ScenarioState)
-> PlayState -> Const (Maybe Text) PlayState)
-> ((Maybe Text -> Const (Maybe Text) (Maybe Text))
-> ScenarioState -> Const (Maybe Text) ScenarioState)
-> (Maybe Text -> Const (Maybe Text) (Maybe Text))
-> PlayState
-> Const (Maybe Text) PlayState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UIGameplay -> Const (Maybe Text) UIGameplay)
-> ScenarioState -> Const (Maybe Text) ScenarioState
Lens' ScenarioState UIGameplay
uiGameplay ((UIGameplay -> Const (Maybe Text) UIGameplay)
-> ScenarioState -> Const (Maybe Text) ScenarioState)
-> ((Maybe Text -> Const (Maybe Text) (Maybe Text))
-> UIGameplay -> Const (Maybe Text) UIGameplay)
-> (Maybe Text -> Const (Maybe Text) (Maybe Text))
-> ScenarioState
-> Const (Maybe Text) ScenarioState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UIInventory -> Const (Maybe Text) UIInventory)
-> UIGameplay -> Const (Maybe Text) UIGameplay
Lens' UIGameplay UIInventory
uiInventory ((UIInventory -> Const (Maybe Text) UIInventory)
-> UIGameplay -> Const (Maybe Text) UIGameplay)
-> ((Maybe Text -> Const (Maybe Text) (Maybe Text))
-> UIInventory -> Const (Maybe Text) UIInventory)
-> (Maybe Text -> Const (Maybe Text) (Maybe Text))
-> UIGameplay
-> Const (Maybe Text) UIGameplay
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Text -> Const (Maybe Text) (Maybe Text))
-> UIInventory -> Const (Maybe Text) UIInventory
Lens' UIInventory (Maybe Text)
uiInventorySearch
KeyDispatcher SwarmEvent (EventM Name AppState)
keyHandler <- Getting
(KeyDispatcher SwarmEvent (EventM Name AppState))
AppState
(KeyDispatcher SwarmEvent (EventM Name AppState))
-> EventM
Name AppState (KeyDispatcher SwarmEvent (EventM Name AppState))
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting
(KeyDispatcher SwarmEvent (EventM Name AppState))
AppState
(KeyDispatcher SwarmEvent (EventM Name AppState))
-> EventM
Name AppState (KeyDispatcher SwarmEvent (EventM Name AppState)))
-> Getting
(KeyDispatcher SwarmEvent (EventM Name AppState))
AppState
(KeyDispatcher SwarmEvent (EventM Name AppState))
-> EventM
Name AppState (KeyDispatcher SwarmEvent (EventM Name AppState))
forall a b. (a -> b) -> a -> b
$ (KeyEventHandlingState
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
KeyEventHandlingState)
-> AppState
-> Const (KeyDispatcher SwarmEvent (EventM Name AppState)) AppState
Lens' AppState KeyEventHandlingState
keyEventHandling ((KeyEventHandlingState
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
KeyEventHandlingState)
-> AppState
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState)) AppState)
-> ((KeyDispatcher SwarmEvent (EventM Name AppState)
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
(KeyDispatcher SwarmEvent (EventM Name AppState)))
-> KeyEventHandlingState
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
KeyEventHandlingState)
-> Getting
(KeyDispatcher SwarmEvent (EventM Name AppState))
AppState
(KeyDispatcher SwarmEvent (EventM Name AppState))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SwarmKeyDispatchers
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
SwarmKeyDispatchers)
-> KeyEventHandlingState
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
KeyEventHandlingState
Lens' KeyEventHandlingState SwarmKeyDispatchers
keyDispatchers ((SwarmKeyDispatchers
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
SwarmKeyDispatchers)
-> KeyEventHandlingState
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
KeyEventHandlingState)
-> ((KeyDispatcher SwarmEvent (EventM Name AppState)
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
(KeyDispatcher SwarmEvent (EventM Name AppState)))
-> SwarmKeyDispatchers
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
SwarmKeyDispatchers)
-> (KeyDispatcher SwarmEvent (EventM Name AppState)
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
(KeyDispatcher SwarmEvent (EventM Name AppState)))
-> KeyEventHandlingState
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
KeyEventHandlingState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SwarmKeyDispatchers
-> KeyDispatcher SwarmEvent (EventM Name AppState))
-> (KeyDispatcher SwarmEvent (EventM Name AppState)
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
(KeyDispatcher SwarmEvent (EventM Name AppState)))
-> SwarmKeyDispatchers
-> Const
(KeyDispatcher SwarmEvent (EventM Name AppState))
SwarmKeyDispatchers
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to SwarmKeyDispatchers
-> KeyDispatcher SwarmEvent (EventM Name AppState)
robotDispatcher
case Maybe Text
search of
Just Text
_ -> BrickEvent Name AppEvent -> EventM Name AppState ()
handleInventorySearchEvent BrickEvent Name AppEvent
bev
Maybe Text
Nothing -> case BrickEvent Name AppEvent
bev of
VtyEvent ev :: Event
ev@(V.EvKey Key
k [Modifier]
m) -> do
Bool
handled <- KeyDispatcher SwarmEvent (EventM Name AppState)
-> Key -> [Modifier] -> EventM Name AppState Bool
forall (m :: * -> *) k.
Monad m =>
KeyDispatcher k m -> Key -> [Modifier] -> m Bool
handleKey KeyDispatcher SwarmEvent (EventM Name AppState)
keyHandler Key
k [Modifier]
m
Bool -> EventM Name AppState () -> EventM Name AppState ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
handled (EventM Name AppState () -> EventM Name AppState ())
-> EventM Name AppState () -> EventM Name AppState ()
forall a b. (a -> b) -> a -> b
$
LensLike' (Zoomed (EventM Name UIGameplay) ()) AppState UIGameplay
-> EventM Name UIGameplay () -> EventM Name AppState ()
forall c.
LensLike' (Zoomed (EventM Name UIGameplay) c) AppState UIGameplay
-> EventM Name UIGameplay c -> EventM Name AppState c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
Brick.zoom ((PlayState -> Focusing (StateT (EventState Name) IO) () PlayState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState
Lens' AppState PlayState
playState ((PlayState -> Focusing (StateT (EventState Name) IO) () PlayState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState)
-> ((UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay)
-> PlayState
-> Focusing (StateT (EventState Name) IO) () PlayState)
-> (UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay)
-> AppState
-> Focusing (StateT (EventState Name) IO) () AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> PlayState -> Focusing (StateT (EventState Name) IO) () PlayState
Lens' PlayState ScenarioState
scenarioState ((ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> PlayState
-> Focusing (StateT (EventState Name) IO) () PlayState)
-> ((UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay)
-> ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> (UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay)
-> PlayState
-> Focusing (StateT (EventState Name) IO) () PlayState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay)
-> ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState
Lens' ScenarioState UIGameplay
uiGameplay) (EventM Name UIGameplay () -> EventM Name AppState ())
-> EventM Name UIGameplay () -> EventM Name AppState ()
forall a b. (a -> b) -> a -> b
$
Event -> EventM Name UIGameplay ()
handleInventoryListEvent Event
ev
BrickEvent Name AppEvent
_ -> EventM Name AppState ()
forall n s. EventM n s ()
continueWithoutRedraw
robotEventHandlers :: [KeyEventHandler SwarmEvent (EventM Name AppState)]
robotEventHandlers :: [KeyEventHandler SwarmEvent (EventM Name AppState)]
robotEventHandlers = [KeyEventHandler SwarmEvent (EventM Name AppState)]
forall {k}. [KeyEventHandler k (EventM Name AppState)]
nonCustomizableHandlers [KeyEventHandler SwarmEvent (EventM Name AppState)]
-> [KeyEventHandler SwarmEvent (EventM Name AppState)]
-> [KeyEventHandler SwarmEvent (EventM Name AppState)]
forall a. Semigroup a => a -> a -> a
<> [KeyEventHandler SwarmEvent (EventM Name AppState)]
customizableHandlers
where
nonCustomizableHandlers :: [KeyEventHandler k (EventM Name AppState)]
nonCustomizableHandlers =
[ Key
-> Text
-> EventM Name AppState ()
-> KeyEventHandler k (EventM Name AppState)
forall a (m :: * -> *) k.
ToBinding a =>
a -> Text -> m () -> KeyEventHandler k m
onKey Key
V.KEnter Text
"Show entity description" (EventM Name AppState ()
-> KeyEventHandler k (EventM Name AppState))
-> EventM Name AppState ()
-> KeyEventHandler k (EventM Name AppState)
forall a b. (a -> b) -> a -> b
$ LensLike'
(Zoomed (EventM Name ScenarioState) ()) AppState ScenarioState
-> EventM Name ScenarioState () -> EventM Name AppState ()
forall c.
LensLike'
(Zoomed (EventM Name ScenarioState) c) AppState ScenarioState
-> EventM Name ScenarioState c -> EventM Name AppState c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
Brick.zoom ((PlayState -> Focusing (StateT (EventState Name) IO) () PlayState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState
Lens' AppState PlayState
playState ((PlayState -> Focusing (StateT (EventState Name) IO) () PlayState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState)
-> ((ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> PlayState
-> Focusing (StateT (EventState Name) IO) () PlayState)
-> (ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> AppState
-> Focusing (StateT (EventState Name) IO) () AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> PlayState -> Focusing (StateT (EventState Name) IO) () PlayState
Lens' PlayState ScenarioState
scenarioState) EventM Name ScenarioState ()
showEntityDescription
]
customizableHandlers :: [KeyEventHandler SwarmEvent (EventM Name AppState)]
customizableHandlers = (RobotEvent -> SwarmEvent)
-> (RobotEvent -> (Text, EventM Name AppState ()))
-> [KeyEventHandler SwarmEvent (EventM Name AppState)]
forall e2 e1 s.
(Ord e2, Enum e1, Bounded e1) =>
(e1 -> e2)
-> (e1 -> (Text, EventM Name s ()))
-> [KeyEventHandler e2 (EventM Name s)]
allHandlers RobotEvent -> SwarmEvent
Robot ((RobotEvent -> (Text, EventM Name AppState ()))
-> [KeyEventHandler SwarmEvent (EventM Name AppState)])
-> (RobotEvent -> (Text, EventM Name AppState ()))
-> [KeyEventHandler SwarmEvent (EventM Name AppState)]
forall a b. (a -> b) -> a -> b
$ \case
RobotEvent
MakeEntityEvent -> (Text
"Make the selected entity", LensLike'
(Zoomed (EventM Name ScenarioState) ()) AppState ScenarioState
-> EventM Name ScenarioState () -> EventM Name AppState ()
forall c.
LensLike'
(Zoomed (EventM Name ScenarioState) c) AppState ScenarioState
-> EventM Name ScenarioState c -> EventM Name AppState c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
Brick.zoom ((PlayState -> Focusing (StateT (EventState Name) IO) () PlayState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState
Lens' AppState PlayState
playState ((PlayState -> Focusing (StateT (EventState Name) IO) () PlayState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState)
-> ((ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> PlayState
-> Focusing (StateT (EventState Name) IO) () PlayState)
-> (ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> AppState
-> Focusing (StateT (EventState Name) IO) () AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> PlayState -> Focusing (StateT (EventState Name) IO) () PlayState
Lens' PlayState ScenarioState
scenarioState) EventM Name ScenarioState ()
makeFocusedEntity)
RobotEvent
ShowZeroInventoryEntitiesEvent -> (Text
"Show entities with zero count in inventory", EventM Name UIInventory () -> EventM Name AppState ()
zoomInventory EventM Name UIInventory ()
showZero)
RobotEvent
CycleInventorySortEvent -> (Text
"Cycle inventory sorting type", EventM Name UIInventory () -> EventM Name AppState ()
zoomInventory EventM Name UIInventory ()
cycleSort)
RobotEvent
SwitchInventorySortDirection -> (Text
"Switch ascending/descending inventory sort", EventM Name UIInventory () -> EventM Name AppState ()
zoomInventory EventM Name UIInventory ()
switchSortDirection)
RobotEvent
SearchInventoryEvent -> (Text
"Start inventory search", EventM Name UIInventory () -> EventM Name AppState ()
zoomInventory EventM Name UIInventory ()
searchInventory)
showEntityDescription :: EventM Name ScenarioState ()
showEntityDescription :: EventM Name ScenarioState ()
showEntityDescription = (ScenarioState -> Maybe Entity)
-> EventM Name ScenarioState (Maybe Entity)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets ScenarioState -> Maybe Entity
focusedEntity EventM Name ScenarioState (Maybe Entity)
-> (Maybe Entity -> EventM Name ScenarioState ())
-> EventM Name ScenarioState ()
forall a b.
EventM Name ScenarioState a
-> (a -> EventM Name ScenarioState b)
-> EventM Name ScenarioState b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= EventM Name ScenarioState ()
-> (Entity -> EventM Name ScenarioState ())
-> Maybe Entity
-> EventM Name ScenarioState ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe EventM Name ScenarioState ()
forall n s. EventM n s ()
continueWithoutRedraw Entity -> EventM Name ScenarioState ()
descriptionModal
where
descriptionModal :: Entity -> EventM Name ScenarioState ()
descriptionModal :: Entity -> EventM Name ScenarioState ()
descriptionModal Entity
e = do
ScenarioState
s <- EventM Name ScenarioState ScenarioState
forall s (m :: * -> *). MonadState s m => m s
get
ViewportScroll Name -> EventM Name ScenarioState ()
forall s. ViewportScroll Name -> EventM Name s ()
resetViewport ViewportScroll Name
modalScroll
(UIGameplay -> Identity UIGameplay)
-> ScenarioState -> Identity ScenarioState
Lens' ScenarioState UIGameplay
uiGameplay ((UIGameplay -> Identity UIGameplay)
-> ScenarioState -> Identity ScenarioState)
-> ((Maybe Modal -> Identity (Maybe Modal))
-> UIGameplay -> Identity UIGameplay)
-> (Maybe Modal -> Identity (Maybe Modal))
-> ScenarioState
-> Identity ScenarioState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UIDialogs -> Identity UIDialogs)
-> UIGameplay -> Identity UIGameplay
Lens' UIGameplay UIDialogs
uiDialogs ((UIDialogs -> Identity UIDialogs)
-> UIGameplay -> Identity UIGameplay)
-> ((Maybe Modal -> Identity (Maybe Modal))
-> UIDialogs -> Identity UIDialogs)
-> (Maybe Modal -> Identity (Maybe Modal))
-> UIGameplay
-> Identity UIGameplay
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Modal -> Identity (Maybe Modal))
-> UIDialogs -> Identity UIDialogs
Lens' UIDialogs (Maybe Modal)
uiModal ((Maybe Modal -> Identity (Maybe Modal))
-> ScenarioState -> Identity ScenarioState)
-> Modal -> EventM Name ScenarioState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a (Maybe b) -> b -> m ()
?= ScenarioState -> MidScenarioModalType -> Modal
generateModal ScenarioState
s (Entity -> MidScenarioModalType
DescriptionModal Entity
e)
makeFocusedEntity :: EventM Name ScenarioState ()
makeFocusedEntity :: EventM Name ScenarioState ()
makeFocusedEntity = (ScenarioState -> Maybe Entity)
-> EventM Name ScenarioState (Maybe Entity)
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets ScenarioState -> Maybe Entity
focusedEntity EventM Name ScenarioState (Maybe Entity)
-> (Maybe Entity -> EventM Name ScenarioState ())
-> EventM Name ScenarioState ()
forall a b.
EventM Name ScenarioState a
-> (a -> EventM Name ScenarioState b)
-> EventM Name ScenarioState b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= EventM Name ScenarioState ()
-> (Entity -> EventM Name ScenarioState ())
-> Maybe Entity
-> EventM Name ScenarioState ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe EventM Name ScenarioState ()
forall n s. EventM n s ()
continueWithoutRedraw Entity -> EventM Name ScenarioState ()
makeEntity
where
makeEntity :: Entity -> EventM Name ScenarioState ()
makeEntity :: Entity -> EventM Name ScenarioState ()
makeEntity Entity
e = do
ScenarioState
s <- EventM Name ScenarioState ScenarioState
forall s (m :: * -> *). MonadState s m => m s
get
let name :: Text
name = Entity
e Entity -> Getting Text Entity Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text Entity Text
Lens' Entity Text
entityName
mkT :: Syntax' (Poly q (Fix TypeF))
mkT = [tmQ| make $str:name |]
case Robot -> Bool
isActive (Robot -> Bool) -> Maybe Robot -> Maybe Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ScenarioState
s ScenarioState
-> Getting (First Robot) ScenarioState Robot -> Maybe Robot
forall s a. s -> Getting (First a) s a -> Maybe a
^? (GameState -> Const (First Robot) GameState)
-> ScenarioState -> Const (First Robot) ScenarioState
Lens' ScenarioState GameState
gameState ((GameState -> Const (First Robot) GameState)
-> ScenarioState -> Const (First Robot) ScenarioState)
-> ((Robot -> Const (First Robot) Robot)
-> GameState -> Const (First Robot) GameState)
-> Getting (First Robot) ScenarioState Robot
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Robot -> Const (First Robot) Robot)
-> GameState -> Const (First Robot) GameState
Traversal' GameState Robot
baseRobot) of
Just Bool
False -> Maybe TSyntax -> EventM Name ScenarioState ()
forall (m :: * -> *).
MonadState ScenarioState m =>
Maybe TSyntax -> m ()
runBaseTerm (TSyntax -> Maybe TSyntax
forall a. a -> Maybe a
Just TSyntax
forall {q :: ImplicitQuantification}. Syntax' (Poly q (Fix TypeF))
mkT)
Maybe Bool
_ -> EventM Name ScenarioState ()
forall n s. EventM n s ()
continueWithoutRedraw
showZero :: EventM Name UIInventory ()
showZero :: EventM Name UIInventory ()
showZero = (Bool -> Identity Bool) -> UIInventory -> Identity UIInventory
Lens' UIInventory Bool
uiShowZero ((Bool -> Identity Bool) -> UIInventory -> Identity UIInventory)
-> (Bool -> Bool) -> EventM Name UIInventory ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= Bool -> Bool
not
cycleSort :: EventM Name UIInventory ()
cycleSort :: EventM Name UIInventory ()
cycleSort = (InventorySortOptions -> Identity InventorySortOptions)
-> UIInventory -> Identity UIInventory
Lens' UIInventory InventorySortOptions
uiInventorySort ((InventorySortOptions -> Identity InventorySortOptions)
-> UIInventory -> Identity UIInventory)
-> (InventorySortOptions -> InventorySortOptions)
-> EventM Name UIInventory ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= InventorySortOptions -> InventorySortOptions
cycleSortOrder
switchSortDirection :: EventM Name UIInventory ()
switchSortDirection :: EventM Name UIInventory ()
switchSortDirection = (InventorySortOptions -> Identity InventorySortOptions)
-> UIInventory -> Identity UIInventory
Lens' UIInventory InventorySortOptions
uiInventorySort ((InventorySortOptions -> Identity InventorySortOptions)
-> UIInventory -> Identity UIInventory)
-> (InventorySortOptions -> InventorySortOptions)
-> EventM Name UIInventory ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= InventorySortOptions -> InventorySortOptions
cycleSortDirection
searchInventory :: EventM Name UIInventory ()
searchInventory :: EventM Name UIInventory ()
searchInventory = (Maybe Text -> Identity (Maybe Text))
-> UIInventory -> Identity UIInventory
Lens' UIInventory (Maybe Text)
uiInventorySearch ((Maybe Text -> Identity (Maybe Text))
-> UIInventory -> Identity UIInventory)
-> Maybe Text -> EventM Name UIInventory ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Text -> Maybe Text
forall a. a -> Maybe a
Just Text
""
handleInventoryListEvent :: V.Event -> EventM Name UIGameplay ()
handleInventoryListEvent :: Event -> EventM Name UIGameplay ()
handleInventoryListEvent Event
ev = do
Maybe (GenericList Name Vector InventoryListEntry)
mList <- Getting
(First (GenericList Name Vector InventoryListEntry))
UIGameplay
(GenericList Name Vector InventoryListEntry)
-> EventM
Name
UIGameplay
(Maybe (GenericList Name Vector InventoryListEntry))
forall s (m :: * -> *) a.
MonadState s m =>
Getting (First a) s a -> m (Maybe a)
preuse (Getting
(First (GenericList Name Vector InventoryListEntry))
UIGameplay
(GenericList Name Vector InventoryListEntry)
-> EventM
Name
UIGameplay
(Maybe (GenericList Name Vector InventoryListEntry)))
-> Getting
(First (GenericList Name Vector InventoryListEntry))
UIGameplay
(GenericList Name Vector InventoryListEntry)
-> EventM
Name
UIGameplay
(Maybe (GenericList Name Vector InventoryListEntry))
forall a b. (a -> b) -> a -> b
$ (UIInventory
-> Const
(First (GenericList Name Vector InventoryListEntry)) UIInventory)
-> UIGameplay
-> Const
(First (GenericList Name Vector InventoryListEntry)) UIGameplay
Lens' UIGameplay UIInventory
uiInventory ((UIInventory
-> Const
(First (GenericList Name Vector InventoryListEntry)) UIInventory)
-> UIGameplay
-> Const
(First (GenericList Name Vector InventoryListEntry)) UIGameplay)
-> ((GenericList Name Vector InventoryListEntry
-> Const
(First (GenericList Name Vector InventoryListEntry))
(GenericList Name Vector InventoryListEntry))
-> UIInventory
-> Const
(First (GenericList Name Vector InventoryListEntry)) UIInventory)
-> Getting
(First (GenericList Name Vector InventoryListEntry))
UIGameplay
(GenericList Name Vector InventoryListEntry)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe (Int, GenericList Name Vector InventoryListEntry)
-> Const
(First (GenericList Name Vector InventoryListEntry))
(Maybe (Int, GenericList Name Vector InventoryListEntry)))
-> UIInventory
-> Const
(First (GenericList Name Vector InventoryListEntry)) UIInventory
Lens'
UIInventory
(Maybe (Int, GenericList Name Vector InventoryListEntry))
uiInventoryList ((Maybe (Int, GenericList Name Vector InventoryListEntry)
-> Const
(First (GenericList Name Vector InventoryListEntry))
(Maybe (Int, GenericList Name Vector InventoryListEntry)))
-> UIInventory
-> Const
(First (GenericList Name Vector InventoryListEntry)) UIInventory)
-> ((GenericList Name Vector InventoryListEntry
-> Const
(First (GenericList Name Vector InventoryListEntry))
(GenericList Name Vector InventoryListEntry))
-> Maybe (Int, GenericList Name Vector InventoryListEntry)
-> Const
(First (GenericList Name Vector InventoryListEntry))
(Maybe (Int, GenericList Name Vector InventoryListEntry)))
-> (GenericList Name Vector InventoryListEntry
-> Const
(First (GenericList Name Vector InventoryListEntry))
(GenericList Name Vector InventoryListEntry))
-> UIInventory
-> Const
(First (GenericList Name Vector InventoryListEntry)) UIInventory
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, GenericList Name Vector InventoryListEntry)
-> Const
(First (GenericList Name Vector InventoryListEntry))
(Int, GenericList Name Vector InventoryListEntry))
-> Maybe (Int, GenericList Name Vector InventoryListEntry)
-> Const
(First (GenericList Name Vector InventoryListEntry))
(Maybe (Int, GenericList Name Vector InventoryListEntry))
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just (((Int, GenericList Name Vector InventoryListEntry)
-> Const
(First (GenericList Name Vector InventoryListEntry))
(Int, GenericList Name Vector InventoryListEntry))
-> Maybe (Int, GenericList Name Vector InventoryListEntry)
-> Const
(First (GenericList Name Vector InventoryListEntry))
(Maybe (Int, GenericList Name Vector InventoryListEntry)))
-> ((GenericList Name Vector InventoryListEntry
-> Const
(First (GenericList Name Vector InventoryListEntry))
(GenericList Name Vector InventoryListEntry))
-> (Int, GenericList Name Vector InventoryListEntry)
-> Const
(First (GenericList Name Vector InventoryListEntry))
(Int, GenericList Name Vector InventoryListEntry))
-> (GenericList Name Vector InventoryListEntry
-> Const
(First (GenericList Name Vector InventoryListEntry))
(GenericList Name Vector InventoryListEntry))
-> Maybe (Int, GenericList Name Vector InventoryListEntry)
-> Const
(First (GenericList Name Vector InventoryListEntry))
(Maybe (Int, GenericList Name Vector InventoryListEntry))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector InventoryListEntry
-> Const
(First (GenericList Name Vector InventoryListEntry))
(GenericList Name Vector InventoryListEntry))
-> (Int, GenericList Name Vector InventoryListEntry)
-> Const
(First (GenericList Name Vector InventoryListEntry))
(Int, GenericList Name Vector InventoryListEntry)
forall s t a b. Field2 s t a b => Lens s t a b
Lens
(Int, GenericList Name Vector InventoryListEntry)
(Int, GenericList Name Vector InventoryListEntry)
(GenericList Name Vector InventoryListEntry)
(GenericList Name Vector InventoryListEntry)
_2
case Maybe (GenericList Name Vector InventoryListEntry)
mList of
Maybe (GenericList Name Vector InventoryListEntry)
Nothing -> EventM Name UIGameplay ()
forall n s. EventM n s ()
continueWithoutRedraw
Just GenericList Name Vector InventoryListEntry
l -> do
Bool -> EventM Name UIGameplay () -> EventM Name UIGameplay ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Event -> Bool
isValidListMovement Event
ev) (EventM Name UIGameplay () -> EventM Name UIGameplay ())
-> EventM Name UIGameplay () -> EventM Name UIGameplay ()
forall a b. (a -> b) -> a -> b
$ ViewportScroll Name -> EventM Name UIGameplay ()
forall s. ViewportScroll Name -> EventM Name s ()
resetViewport ViewportScroll Name
infoScroll
GenericList Name Vector InventoryListEntry
l' <- GenericList Name Vector InventoryListEntry
-> EventM Name (GenericList Name Vector InventoryListEntry) ()
-> EventM
Name UIGameplay (GenericList Name Vector InventoryListEntry)
forall a n b s. a -> EventM n a b -> EventM n s a
nestEventM' GenericList Name Vector InventoryListEntry
l (Event
-> (InventoryListEntry -> Bool)
-> EventM Name (GenericList Name Vector InventoryListEntry) ()
forall (t :: * -> *) n e.
(Foldable t, Splittable t, Ord n, Searchable t) =>
Event -> (e -> Bool) -> EventM n (GenericList n t e) ()
handleListEventWithSeparators Event
ev (APrism InventoryListEntry InventoryListEntry Text Text
-> InventoryListEntry -> Bool
forall s t a b. APrism s t a b -> s -> Bool
is APrism InventoryListEntry InventoryListEntry Text Text
Prism' InventoryListEntry Text
_Separator))
(UIInventory -> Identity UIInventory)
-> UIGameplay -> Identity UIGameplay
Lens' UIGameplay UIInventory
uiInventory ((UIInventory -> Identity UIInventory)
-> UIGameplay -> Identity UIGameplay)
-> ((GenericList Name Vector InventoryListEntry
-> Identity (GenericList Name Vector InventoryListEntry))
-> UIInventory -> Identity UIInventory)
-> (GenericList Name Vector InventoryListEntry
-> Identity (GenericList Name Vector InventoryListEntry))
-> UIGameplay
-> Identity UIGameplay
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe (Int, GenericList Name Vector InventoryListEntry)
-> Identity
(Maybe (Int, GenericList Name Vector InventoryListEntry)))
-> UIInventory -> Identity UIInventory
Lens'
UIInventory
(Maybe (Int, GenericList Name Vector InventoryListEntry))
uiInventoryList ((Maybe (Int, GenericList Name Vector InventoryListEntry)
-> Identity
(Maybe (Int, GenericList Name Vector InventoryListEntry)))
-> UIInventory -> Identity UIInventory)
-> ((GenericList Name Vector InventoryListEntry
-> Identity (GenericList Name Vector InventoryListEntry))
-> Maybe (Int, GenericList Name Vector InventoryListEntry)
-> Identity
(Maybe (Int, GenericList Name Vector InventoryListEntry)))
-> (GenericList Name Vector InventoryListEntry
-> Identity (GenericList Name Vector InventoryListEntry))
-> UIInventory
-> Identity UIInventory
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, GenericList Name Vector InventoryListEntry)
-> Identity (Int, GenericList Name Vector InventoryListEntry))
-> Maybe (Int, GenericList Name Vector InventoryListEntry)
-> Identity
(Maybe (Int, GenericList Name Vector InventoryListEntry))
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just (((Int, GenericList Name Vector InventoryListEntry)
-> Identity (Int, GenericList Name Vector InventoryListEntry))
-> Maybe (Int, GenericList Name Vector InventoryListEntry)
-> Identity
(Maybe (Int, GenericList Name Vector InventoryListEntry)))
-> ((GenericList Name Vector InventoryListEntry
-> Identity (GenericList Name Vector InventoryListEntry))
-> (Int, GenericList Name Vector InventoryListEntry)
-> Identity (Int, GenericList Name Vector InventoryListEntry))
-> (GenericList Name Vector InventoryListEntry
-> Identity (GenericList Name Vector InventoryListEntry))
-> Maybe (Int, GenericList Name Vector InventoryListEntry)
-> Identity
(Maybe (Int, GenericList Name Vector InventoryListEntry))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector InventoryListEntry
-> Identity (GenericList Name Vector InventoryListEntry))
-> (Int, GenericList Name Vector InventoryListEntry)
-> Identity (Int, GenericList Name Vector InventoryListEntry)
forall s t a b. Field2 s t a b => Lens s t a b
Lens
(Int, GenericList Name Vector InventoryListEntry)
(Int, GenericList Name Vector InventoryListEntry)
(GenericList Name Vector InventoryListEntry)
(GenericList Name Vector InventoryListEntry)
_2 ((GenericList Name Vector InventoryListEntry
-> Identity (GenericList Name Vector InventoryListEntry))
-> UIGameplay -> Identity UIGameplay)
-> GenericList Name Vector InventoryListEntry
-> EventM Name UIGameplay ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= GenericList Name Vector InventoryListEntry
l'
handleInventorySearchEvent :: BrickEvent Name AppEvent -> EventM Name AppState ()
handleInventorySearchEvent :: BrickEvent Name AppEvent -> EventM Name AppState ()
handleInventorySearchEvent = \case
BrickEvent Name AppEvent
EscapeKey ->
EventM Name UIInventory () -> EventM Name AppState ()
zoomInventory (EventM Name UIInventory () -> EventM Name AppState ())
-> EventM Name UIInventory () -> EventM Name AppState ()
forall a b. (a -> b) -> a -> b
$ (Maybe Text -> Identity (Maybe Text))
-> UIInventory -> Identity UIInventory
Lens' UIInventory (Maybe Text)
uiInventorySearch ((Maybe Text -> Identity (Maybe Text))
-> UIInventory -> Identity UIInventory)
-> Maybe Text -> EventM Name UIInventory ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Maybe Text
forall a. Maybe a
Nothing
Key Key
V.KEnter -> do
EventM Name UIInventory () -> EventM Name AppState ()
zoomInventory (EventM Name UIInventory () -> EventM Name AppState ())
-> EventM Name UIInventory () -> EventM Name AppState ()
forall a b. (a -> b) -> a -> b
$ (Maybe Text -> Identity (Maybe Text))
-> UIInventory -> Identity UIInventory
Lens' UIInventory (Maybe Text)
uiInventorySearch ((Maybe Text -> Identity (Maybe Text))
-> UIInventory -> Identity UIInventory)
-> Maybe Text -> EventM Name UIInventory ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Maybe Text
forall a. Maybe a
Nothing
LensLike'
(Zoomed (EventM Name ScenarioState) ()) AppState ScenarioState
-> EventM Name ScenarioState () -> EventM Name AppState ()
forall c.
LensLike'
(Zoomed (EventM Name ScenarioState) c) AppState ScenarioState
-> EventM Name ScenarioState c -> EventM Name AppState c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
Brick.zoom ((PlayState -> Focusing (StateT (EventState Name) IO) () PlayState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState
Lens' AppState PlayState
playState ((PlayState -> Focusing (StateT (EventState Name) IO) () PlayState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState)
-> ((ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> PlayState
-> Focusing (StateT (EventState Name) IO) () PlayState)
-> (ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> AppState
-> Focusing (StateT (EventState Name) IO) () AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> PlayState -> Focusing (StateT (EventState Name) IO) () PlayState
Lens' PlayState ScenarioState
scenarioState) EventM Name ScenarioState ()
showEntityDescription
CharKey Char
c -> do
ViewportScroll Name -> EventM Name AppState ()
forall s. ViewportScroll Name -> EventM Name s ()
resetViewport ViewportScroll Name
infoScroll
EventM Name UIInventory () -> EventM Name AppState ()
zoomInventory (EventM Name UIInventory () -> EventM Name AppState ())
-> EventM Name UIInventory () -> EventM Name AppState ()
forall a b. (a -> b) -> a -> b
$ (Maybe Text -> Identity (Maybe Text))
-> UIInventory -> Identity UIInventory
Lens' UIInventory (Maybe Text)
uiInventorySearch ((Maybe Text -> Identity (Maybe Text))
-> UIInventory -> Identity UIInventory)
-> (Maybe Text -> Maybe Text) -> EventM Name UIInventory ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= (Text -> Text) -> Maybe Text -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Char -> Text
forall s a. Snoc s s a a => s -> a -> s
`snoc` Char
c)
BrickEvent Name AppEvent
BackspaceKey -> do
EventM Name UIInventory () -> EventM Name AppState ()
zoomInventory (EventM Name UIInventory () -> EventM Name AppState ())
-> EventM Name UIInventory () -> EventM Name AppState ()
forall a b. (a -> b) -> a -> b
$ (Maybe Text -> Identity (Maybe Text))
-> UIInventory -> Identity UIInventory
Lens' UIInventory (Maybe Text)
uiInventorySearch ((Maybe Text -> Identity (Maybe Text))
-> UIInventory -> Identity UIInventory)
-> (Maybe Text -> Maybe Text) -> EventM Name UIInventory ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= (Text -> Text) -> Maybe Text -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Text -> Text
T.dropEnd Int
1)
VtyEvent Event
ev -> LensLike' (Zoomed (EventM Name UIGameplay) ()) AppState UIGameplay
-> EventM Name UIGameplay () -> EventM Name AppState ()
forall c.
LensLike' (Zoomed (EventM Name UIGameplay) c) AppState UIGameplay
-> EventM Name UIGameplay c -> EventM Name AppState c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
Brick.zoom ((PlayState -> Focusing (StateT (EventState Name) IO) () PlayState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState
Lens' AppState PlayState
playState ((PlayState -> Focusing (StateT (EventState Name) IO) () PlayState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState)
-> ((UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay)
-> PlayState
-> Focusing (StateT (EventState Name) IO) () PlayState)
-> (UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay)
-> AppState
-> Focusing (StateT (EventState Name) IO) () AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> PlayState -> Focusing (StateT (EventState Name) IO) () PlayState
Lens' PlayState ScenarioState
scenarioState ((ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> PlayState
-> Focusing (StateT (EventState Name) IO) () PlayState)
-> ((UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay)
-> ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> (UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay)
-> PlayState
-> Focusing (StateT (EventState Name) IO) () PlayState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay)
-> ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState
Lens' ScenarioState UIGameplay
uiGameplay) (EventM Name UIGameplay () -> EventM Name AppState ())
-> EventM Name UIGameplay () -> EventM Name AppState ()
forall a b. (a -> b) -> a -> b
$ Event -> EventM Name UIGameplay ()
handleInventoryListEvent Event
ev
BrickEvent Name AppEvent
_ -> EventM Name AppState ()
forall n s. EventM n s ()
continueWithoutRedraw
zoomInventory :: EventM Name UIInventory () -> EventM Name AppState ()
zoomInventory :: EventM Name UIInventory () -> EventM Name AppState ()
zoomInventory EventM Name UIInventory ()
act = LensLike'
(Zoomed (EventM Name UIInventory) ()) AppState UIInventory
-> EventM Name UIInventory () -> EventM Name AppState ()
forall c.
LensLike' (Zoomed (EventM Name UIInventory) c) AppState UIInventory
-> EventM Name UIInventory c -> EventM Name AppState c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
Brick.zoom ((PlayState -> Focusing (StateT (EventState Name) IO) () PlayState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState
Lens' AppState PlayState
playState ((PlayState -> Focusing (StateT (EventState Name) IO) () PlayState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState)
-> ((UIInventory
-> Focusing (StateT (EventState Name) IO) () UIInventory)
-> PlayState
-> Focusing (StateT (EventState Name) IO) () PlayState)
-> (UIInventory
-> Focusing (StateT (EventState Name) IO) () UIInventory)
-> AppState
-> Focusing (StateT (EventState Name) IO) () AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> PlayState -> Focusing (StateT (EventState Name) IO) () PlayState
Lens' PlayState ScenarioState
scenarioState ((ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> PlayState
-> Focusing (StateT (EventState Name) IO) () PlayState)
-> ((UIInventory
-> Focusing (StateT (EventState Name) IO) () UIInventory)
-> ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> (UIInventory
-> Focusing (StateT (EventState Name) IO) () UIInventory)
-> PlayState
-> Focusing (StateT (EventState Name) IO) () PlayState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay)
-> ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState
Lens' ScenarioState UIGameplay
uiGameplay ((UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay)
-> ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState)
-> ((UIInventory
-> Focusing (StateT (EventState Name) IO) () UIInventory)
-> UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay)
-> (UIInventory
-> Focusing (StateT (EventState Name) IO) () UIInventory)
-> ScenarioState
-> Focusing (StateT (EventState Name) IO) () ScenarioState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UIInventory
-> Focusing (StateT (EventState Name) IO) () UIInventory)
-> UIGameplay
-> Focusing (StateT (EventState Name) IO) () UIGameplay
Lens' UIGameplay UIInventory
uiInventory) (EventM Name UIInventory () -> EventM Name AppState ())
-> EventM Name UIInventory () -> EventM Name AppState ()
forall a b. (a -> b) -> a -> b
$ do
(Bool -> Identity Bool) -> UIInventory -> Identity UIInventory
Lens' UIInventory Bool
uiInventoryShouldUpdate ((Bool -> Identity Bool) -> UIInventory -> Identity UIInventory)
-> Bool -> EventM Name UIInventory ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
True
EventM Name UIInventory ()
act