Safe Haskell | None |
---|
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.
- class MonadActionRO m => MonadClient m where
- getClient :: m StateClient
- getsClient :: (StateClient -> a) -> m a
- modifyClient :: (StateClient -> StateClient) -> m ()
- putClient :: StateClient -> m ()
- saveClient :: m ()
- class MonadClient m => MonadClientUI m
- class MonadClient m => MonadClientReadServer c m | m -> c where
- readServer :: m c
- class MonadClient m => MonadClientWriteServer d m | m -> d where
- writeServer :: d -> m ()
- class MonadClient m => MonadClientAbort m where
- data SessionUI = SessionUI {
- sfconn :: !ConnFrontend
- sbinding :: !Binding
- data ConnFrontend = ConnFrontend {
- readConnFrontend :: MonadClientUI m => m KM
- writeConnFrontend :: MonadClientUI m => FrontReq -> m ()
- connFrontend :: FactionId -> ChanFrontend -> ConnFrontend
- abort :: MonadClientAbort m => m a
- abortIfWith :: MonadClientAbort m => Bool -> Msg -> m a
- neverMind :: MonadClientAbort m => Bool -> m a
- tryRepeatedlyWith :: MonadClientAbort m => (Msg -> m ()) -> m () -> m ()
- tryIgnore :: MonadClientAbort m => m () -> m ()
- tryWithSlide :: (MonadClientAbort m, MonadClientUI m) => m a -> WriterT Slideshow m a -> WriterT Slideshow m a
- mkConfigUI :: Ops RuleKind -> IO ConfigUI
- askBinding :: MonadClientUI m => m Binding
- getPerFid :: MonadClient m => LevelId -> m Perception
- msgAdd :: MonadClientUI m => Msg -> m ()
- msgReset :: MonadClient m => Msg -> m ()
- recordHistory :: MonadClient m => m ()
- getKeyOverlayCommand :: MonadClientUI m => Overlay -> m KM
- getInitConfirms :: MonadClientUI m => ColorMode -> [KM] -> Slideshow -> m Bool
- displayFrames :: MonadClientUI m => Frames -> m ()
- displayMore :: MonadClientUI m => ColorMode -> Msg -> m Bool
- displayYesNo :: MonadClientUI m => ColorMode -> Msg -> m Bool
- displayChoiceUI :: (MonadClientAbort m, MonadClientUI m) => Msg -> Overlay -> [KM] -> m KM
- promptToSlideshow :: MonadClientUI m => Msg -> m Slideshow
- overlayToSlideshow :: MonadClientUI m => Msg -> Overlay -> m Slideshow
- drawOverlay :: MonadClientUI m => ColorMode -> Overlay -> m SingleFrame
- animate :: MonadClientUI m => LevelId -> Animation -> m Frames
- restoreGame :: MonadClient m => m (Maybe (State, StateClient))
- removeServerSave :: MonadClient m => m ()
- displayPush :: MonadClientUI m => m ()
- scoreToSlideshow :: MonadClientUI m => Int -> Status -> m Slideshow
- rndToAction :: MonadClient m => Rnd a -> m a
- getArenaUI :: MonadClientUI m => m LevelId
- getLeaderUI :: MonadClientUI m => m ActorId
- targetToPos :: MonadClientUI m => m (Maybe Point)
- partAidLeader :: MonadClient m => ActorId -> m Part
- partActorLeader :: MonadClient m => ActorId -> Actor -> m Part
- debugPrint :: MonadClient m => Text -> m ()
Action monads
class MonadActionRO m => MonadClient m where
getClient :: m StateClient
getsClient :: (StateClient -> a) -> m a
modifyClient :: (StateClient -> StateClient) -> m ()
putClient :: StateClient -> m ()
saveClient :: m ()
(Monoid a, MonadClient m) => MonadClient (WriterT a m) | |
MonadClient (ActionCli c d) |
class MonadClient m => MonadClientUI m
(Monoid a, MonadClientUI m) => MonadClientUI (WriterT a m) | |
MonadClientUI (ActionCli c d) |
class MonadClient m => MonadClientReadServer c m | m -> c where
readServer :: m c
MonadClientReadServer c (ActionCli c d) |
class MonadClient m => MonadClientWriteServer d m | m -> d where
writeServer :: d -> m ()
MonadClientWriteServer d (ActionCli c d) |
class MonadClient m => MonadClientAbort m where
The bottom of the action monads class semilattice.
(Monoid a, MonadClientAbort m) => MonadClientAbort (WriterT a m) | |
MonadClientAbort (ActionCli c d) |
data SessionUI
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
.
SessionUI | |
|
data ConnFrontend
Connection method between a client and a frontend.
ConnFrontend | |
|
connFrontend :: FactionId -> ChanFrontend -> ConnFrontend
Various ways to abort action
abort :: MonadClientAbort m => m a
Reset the state and resume from the last backup point, i.e., invoke the failure continuation.
abortIfWith :: MonadClientAbort m => Bool -> Msg -> m a
Abort and print the given msg if the condition is true.
neverMind :: MonadClientAbort m => Bool -> m a
Abort and conditionally print the fixed message.
Abort exception handlers
tryRepeatedlyWith :: MonadClientAbort m => (Msg -> m ()) -> m () -> m ()
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 ()
Try the given computation and silently catch failure.
tryWithSlide :: (MonadClientAbort m, MonadClientUI m) => m a -> WriterT Slideshow m a -> WriterT Slideshow m a
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 ConfigUI
Read and parse UI config file.
Accessors to the game session Reader and the Perception Reader(-like)
askBinding :: MonadClientUI m => m Binding
Get the key binding.
getPerFid :: MonadClient m => LevelId -> m Perception
Get the current perception of a client.
History and report
msgAdd :: MonadClientUI m => Msg -> m ()
Add a message to the current report.
msgReset :: MonadClient m => Msg -> m ()
Wipe out and set a new value for the current report.
recordHistory :: MonadClient m => m ()
Store current report in the history and reset report.
Key input
getKeyOverlayCommand :: MonadClientUI m => Overlay -> m KM
Display an overlay and wait for a human player command.
getInitConfirms :: MonadClientUI m => ColorMode -> [KM] -> Slideshow -> m Bool
Display a slideshow, awaiting confirmation for each slide except the last.
Display and key input
displayFrames :: MonadClientUI m => Frames -> m ()
Push frames or delays to the frame queue.
displayMore :: MonadClientUI m => ColorMode -> Msg -> m Bool
Display a msg with a more
prompt. Return value indicates if the player
tried to cancel/escape.
displayYesNo :: MonadClientUI m => ColorMode -> Msg -> m Bool
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 KM
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 Slideshow
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 Slideshow
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 SingleFrame
Draw the current level with the overlay on top.
animate :: MonadClientUI m => LevelId -> Animation -> m Frames
Render animations on top of the current screen frame.
Assorted primitives
restoreGame :: MonadClient m => m (Maybe (State, StateClient))
removeServerSave :: MonadClient m => m ()
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 ()
Push the frame depicting the current level to the frame queue. Only one screenful of the report is shown, the rest is ignored.
scoreToSlideshow :: MonadClientUI m => Int -> Status -> m Slideshow
rndToAction :: MonadClient m => Rnd a -> m a
Invoke pseudo-random computation with the generator kept in the state.
getArenaUI :: MonadClientUI m => m LevelId
getLeaderUI :: MonadClientUI m => m ActorId
targetToPos :: MonadClientUI m => m (Maybe Point)
Calculate the position of leader's target.
partAidLeader :: MonadClient m => ActorId -> m Part
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 Part
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.
debugPrint :: MonadClient m => Text -> m ()