| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Game.LambdaHack.Client.UI.MonadClientUI
Description
Client monad for interacting with a human through UI.
- class MonadClient m => MonadClientUI m where
- getsSession :: (SessionUI -> a) -> m a
- liftIO :: IO a -> m a
- data SessionUI = SessionUI {}
- data ColorMode
- promptGetKey :: MonadClientUI m => [KM] -> SingleFrame -> m KM
- getKeyOverlayCommand :: MonadClientUI m => Bool -> Overlay -> m KM
- getInitConfirms :: MonadClientUI m => ColorMode -> [KM] -> Slideshow -> m Bool
- displayFrame :: MonadClientUI m => Bool -> Maybe SingleFrame -> m ()
- displayDelay :: MonadClientUI m => m ()
- displayFrames :: MonadClientUI m => Frames -> m ()
- displayActorStart :: MonadClientUI m => Actor -> Frames -> m ()
- drawOverlay :: MonadClientUI m => Bool -> ColorMode -> Overlay -> m SingleFrame
- stopPlayBack :: MonadClientUI m => m ()
- stopRunning :: MonadClientUI m => m ()
- askConfig :: MonadClientUI m => m Config
- askBinding :: MonadClientUI m => m Binding
- syncFrames :: MonadClientUI m => m ()
- tryTakeMVarSescMVar :: MonadClientUI m => m Bool
- scoreToSlideshow :: MonadClientUI m => Int -> Status -> m Slideshow
- getLeaderUI :: MonadClientUI m => m ActorId
- getArenaUI :: MonadClientUI m => m LevelId
- viewedLevel :: MonadClientUI m => m LevelId
- targetDescLeader :: MonadClientUI m => ActorId -> m (Text, Maybe Text)
- targetDescCursor :: MonadClientUI m => m (Text, Maybe Text)
- leaderTgtToPos :: MonadClientUI m => m (Maybe Point)
- leaderTgtAims :: MonadClientUI m => m (Either Text Int)
- cursorToPos :: MonadClientUI m => m (Maybe Point)
Client UI monad
class MonadClient m => MonadClientUI m where Source
The information that is constant across a client playing session,
including many consecutive games in a single session,
but is completely disregarded and reset when a new playing session starts.
Auxiliary AI and computer player clients have no sfs nor sbinding.
Display and key input
Color mode for the display.
promptGetKey :: MonadClientUI m => [KM] -> SingleFrame -> m KM Source
getKeyOverlayCommand :: MonadClientUI m => Bool -> Overlay -> m KM Source
Display an overlay and wait for a human player command.
getInitConfirms :: MonadClientUI m => ColorMode -> [KM] -> Slideshow -> m Bool Source
Display a slideshow, awaiting confirmation for each slide except the last.
displayFrame :: MonadClientUI m => Bool -> Maybe SingleFrame -> m () Source
displayDelay :: MonadClientUI m => m () Source
displayFrames :: MonadClientUI m => Frames -> m () Source
Push frames or delays to the frame queue.
displayActorStart :: MonadClientUI m => Actor -> Frames -> m () Source
Push frames or delays to the frame queue. Additionally set sdisplayed.
because animations not always happen after SfxActorStart on the leader's
level (e.g., death can lead to leader change to another level mid-turn,
and there could be melee and animations on that level at the same moment).
drawOverlay :: MonadClientUI m => Bool -> ColorMode -> Overlay -> m SingleFrame Source
Draw the current level with the overlay on top.
Assorted primitives
stopPlayBack :: MonadClientUI m => m () Source
stopRunning :: MonadClientUI m => m () Source
askConfig :: MonadClientUI m => m Config Source
askBinding :: MonadClientUI m => m Binding Source
Get the key binding.
syncFrames :: MonadClientUI m => m () Source
Sync frames display with the frontend.
tryTakeMVarSescMVar :: MonadClientUI m => m Bool Source
scoreToSlideshow :: MonadClientUI m => Int -> Status -> m Slideshow Source
getLeaderUI :: MonadClientUI m => m ActorId Source
getArenaUI :: MonadClientUI m => m LevelId Source
viewedLevel :: MonadClientUI m => m LevelId Source
targetDescLeader :: MonadClientUI m => ActorId -> m (Text, Maybe Text) Source
targetDescCursor :: MonadClientUI m => m (Text, Maybe Text) Source
leaderTgtToPos :: MonadClientUI m => m (Maybe Point) Source
leaderTgtAims :: MonadClientUI m => m (Either Text Int) Source
cursorToPos :: MonadClientUI m => m (Maybe Point) Source