LambdaHack-0.2.10.5: A roguelike game engine in early and active development

Safe HaskellNone

Game.LambdaHack.Client.Action

Contents

Description

Game action monads and basic building blocks for human and computer player actions. Has no access to the the main action type. Does not export the liftIO operation nor a few other implementation details.

Synopsis

Action monads

class MonadClient m => MonadClientReadServer c m | m -> c whereSource

Methods

readServer :: m cSource

Instances

class MonadClient m => MonadClientWriteServer d m | m -> d whereSource

Methods

writeServer :: d -> m ()Source

class MonadClient m => MonadClientAbort m whereSource

The bottom of the action monads class semilattice.

Methods

tryWith :: (Msg -> m a) -> m a -> m aSource

abortWith :: Msg -> m aSource

data SessionUI 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.

Constructors

SessionUI 

Fields

sfconn :: !ConnFrontend

connection with the frontend

sbinding :: !Binding

binding of keys to commands

data ConnFrontend Source

Connection method between a client and a frontend.

Constructors

ConnFrontend 

Fields

readConnFrontend :: MonadClientUI m => m KM

read a keystroke received from the frontend

writeConnFrontend :: MonadClientUI m => FrontReq -> m ()

write a UI request to the frontend

Various ways to abort action

abort :: MonadClientAbort m => m aSource

Reset the state and resume from the last backup point, i.e., invoke the failure continuation.

abortIfWith :: MonadClientAbort m => Bool -> Msg -> m aSource

Abort and print the given msg if the condition is true.

neverMind :: MonadClientAbort m => Bool -> m aSource

Abort and conditionally print the fixed message.

Abort exception handlers

tryRepeatedlyWith :: MonadClientAbort m => (Msg -> m ()) -> m () -> m ()Source

Take a handler and a computation. If the computation fails, the handler is invoked and then the computation is retried.

tryIgnore :: MonadClientAbort m => m () -> m ()Source

Try the given computation and silently catch failure.

tryWithSlide :: (MonadClientAbort m, MonadClientUI m) => m a -> WriterT Slideshow m a -> WriterT Slideshow m aSource

Set the current exception handler. Apart of executing it, draw and pass along a slide with the abort message (even if message empty).

Executing actions

mkConfigUI :: Ops RuleKind -> IO ConfigUISource

Read and parse UI config file.

Accessors to the game session Reader and the Perception Reader(-like)

askBinding :: MonadClientUI m => m BindingSource

Get the key binding.

getPerFid :: MonadClient m => LevelId -> m PerceptionSource

Get the current perception of a client.

History and report

msgAdd :: MonadClientUI m => Msg -> m ()Source

Add a message to the current report.

msgReset :: MonadClient m => Msg -> m ()Source

Wipe out and set a new value for the current report.

recordHistory :: MonadClient m => m ()Source

Store current report in the history and reset report.

Key input

getKeyOverlayCommand :: MonadClientUI m => Overlay -> m KMSource

Display an overlay and wait for a human player command.

getInitConfirms :: MonadClientUI m => ColorMode -> [KM] -> Slideshow -> m BoolSource

Display a slideshow, awaiting confirmation for each slide except the last.

Display and key input

displayFrames :: MonadClientUI m => Frames -> m ()Source

Push frames or delays to the frame queue.

displayMore :: MonadClientUI m => ColorMode -> Msg -> m BoolSource

Display a msg with a more prompt. Return value indicates if the player tried to cancel/escape.

displayYesNo :: MonadClientUI m => ColorMode -> Msg -> m BoolSource

Print a yes/no question and return the player's answer. Use black and white colours to turn player's attention to the choice.

displayChoiceUI :: (MonadClientAbort m, MonadClientUI m) => Msg -> Overlay -> [KM] -> m KMSource

Print a prompt and an overlay and wait for a player keypress. If many overlays, scroll screenfuls with SPACE. Do not wrap screenfuls (in some menus ? cycles views, so the user can restart from the top).

Generate slideshows

promptToSlideshow :: MonadClientUI m => Msg -> m SlideshowSource

The prompt is shown after the current message, but not added to history. This is useful, e.g., in targeting mode, not to spam history.

overlayToSlideshow :: MonadClientUI m => Msg -> Overlay -> m SlideshowSource

The prompt is shown after the current message at the top of each slide. Together they may take more than one line. The prompt is not added to history. The portions of overlay that fit on the the rest of the screen are displayed below. As many slides as needed are shown.

Draw frames

drawOverlay :: MonadClientUI m => ColorMode -> Overlay -> m SingleFrameSource

Draw the current level with the overlay on top.

animate :: MonadClientUI m => LevelId -> Animation -> m FramesSource

Render animations on top of the current screen frame.

Assorted primitives

removeServerSave :: MonadClient m => m ()Source

Assuming the client runs on the same machine and for the same user as the server, move the server savegame out of the way.

displayPush :: MonadClientUI m => m ()Source

Push the frame depicting the current level to the frame queue. Only one screenful of the report is shown, the rest is ignored.

rndToAction :: MonadClient m => Rnd a -> m aSource

Invoke pseudo-random computation with the generator kept in the state.

targetToPos :: MonadClientUI m => m (Maybe Point)Source

Calculate the position of leader's target.

partAidLeader :: MonadClient m => ActorId -> m PartSource

The part of speech describing the actor (designated by actor id and present in the dungeon) or a special name if a leader of the observer's faction.

partActorLeader :: MonadClient m => ActorId -> Actor -> m PartSource

The part of speech describing the actor or a special name if a leader of the observer's faction. The actor may not be present in the dungeon.