| License | BSD-3-Clause |
|---|---|
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Swarm.TUI.Controller.Util
Description
Synopsis
- pattern Key :: Key -> BrickEvent n e
- pattern CharKey :: Char -> BrickEvent n e
- pattern ControlChar :: Char -> BrickEvent n e
- pattern MetaChar :: Char -> BrickEvent n e
- pattern ShiftKey :: Key -> BrickEvent n e
- pattern MetaKey :: Key -> BrickEvent n e
- pattern EscapeKey :: BrickEvent n e
- pattern BackspaceKey :: BrickEvent n e
- pattern FKey :: Int -> BrickEvent n e
- openModal :: ModalType -> EventM Name AppState ()
- isRunningModal :: ModalType -> Bool
- safeTogglePause :: EventM Name AppState ()
- safeAutoUnpause :: EventM Name AppState ()
- toggleModal :: ModalType -> EventM Name AppState ()
- setFocus :: FocusablePanel -> EventM Name AppState ()
- immediatelyRedrawWorld :: EventM Name AppState ()
- loadVisibleRegion :: EventM Name AppState ()
- mouseLocToWorldCoords :: Location -> EventM Name GameState (Maybe (Cosmic Coords))
- hasDebugCapability :: Bool -> AppState -> Bool
- resetViewport :: ViewportScroll Name -> EventM Name AppState ()
- zoomGameState :: (MonadState AppState m, MonadIO m) => StateC GameState (TimeIOC (LiftC IO)) a -> m a
- onlyCreative :: MonadState AppState m => m () -> m ()
- allHandlers :: (Ord e2, Enum e1, Bounded e1) => (e1 -> e2) -> (e1 -> (Text, EventM Name AppState ())) -> [KeyEventHandler e2 (EventM Name AppState)]
- runBaseTerm :: MonadState AppState m => Maybe TSyntax -> m ()
- modifyResetREPL :: Text -> REPLPrompt -> REPLState -> REPLState
- resetREPL :: MonadState AppState m => Text -> REPLPrompt -> m ()
- addREPLHistItem :: MonadState AppState m => REPLHistItem -> m ()
Documentation
pattern Key :: Key -> BrickEvent n e Source #
Pattern synonyms to simplify brick event handler
pattern CharKey :: Char -> BrickEvent n e Source #
pattern ControlChar :: Char -> BrickEvent n e Source #
pattern MetaChar :: Char -> BrickEvent n e Source #
pattern ShiftKey :: Key -> BrickEvent n e Source #
pattern MetaKey :: Key -> BrickEvent n e Source #
pattern EscapeKey :: BrickEvent n e Source #
pattern BackspaceKey :: BrickEvent n e Source #
pattern FKey :: Int -> BrickEvent n e Source #
isRunningModal :: ModalType -> Bool Source #
The running modals do not autopause the game.
safeTogglePause :: EventM Name AppState () Source #
Set the game to Running if it was (auto) paused otherwise to paused.
Also resets the last frame time to now. If we are pausing, it doesn't matter; if we are unpausing, this is critical to ensure the next frame doesn't think it has to catch up from whenever the game was paused!
safeAutoUnpause :: EventM Name AppState () Source #
Only unpause the game if leaving autopaused modal.
Note that the game could have been paused before opening the modal, in that case, leave the game paused.
loadVisibleRegion :: EventM Name AppState () Source #
Make sure all tiles covering the visible part of the world are loaded.
resetViewport :: ViewportScroll Name -> EventM Name AppState () Source #
Resets the viewport scroll position
zoomGameState :: (MonadState AppState m, MonadIO m) => StateC GameState (TimeIOC (LiftC IO)) a -> m a Source #
Modifies the game state using a fused-effect state action.
onlyCreative :: MonadState AppState m => m () -> m () Source #
allHandlers :: (Ord e2, Enum e1, Bounded e1) => (e1 -> e2) -> (e1 -> (Text, EventM Name AppState ())) -> [KeyEventHandler e2 (EventM Name AppState)] Source #
Create a list of handlers with embedding events and using pattern matching.
runBaseTerm :: MonadState AppState m => Maybe TSyntax -> m () Source #
modifyResetREPL :: Text -> REPLPrompt -> REPLState -> REPLState Source #
Set the REPL to the given text and REPL prompt type.
resetREPL :: MonadState AppState m => Text -> REPLPrompt -> m () Source #
Reset the REPL state to the given text and REPL prompt type.
addREPLHistItem :: MonadState AppState m => REPLHistItem -> m () Source #
Add an item to the REPL history.