Safe Haskell | None |
---|---|
Language | Haskell2010 |
Game.LambdaHack.Client.UI.HandleHelperM
Contents
Description
Helper functions for both inventory management and human commands.
Synopsis
- data FailError
- showFailError :: FailError -> Text
- type MError = Maybe FailError
- mergeMError :: MError -> MError -> MError
- type FailOrCmd a = Either FailError a
- failWith :: MonadClientUI m => Text -> m (FailOrCmd a)
- failSer :: MonadClientUI m => ReqFailure -> m (FailOrCmd a)
- failMsg :: MonadClientUI m => Text -> m MError
- weaveJust :: FailOrCmd a -> Either MError a
- pointmanCycle :: MonadClientUI m => ActorId -> Bool -> Direction -> m MError
- pointmanCycleLevel :: MonadClientUI m => ActorId -> Bool -> Direction -> m MError
- partyAfterLeader :: MonadClientUI m => ActorId -> m [(ActorId, Actor, ActorUI)]
- pickLeader :: MonadClientUI m => Bool -> ActorId -> m Bool
- doLook :: MonadClientUI m => m ()
- pickLeaderWithPointer :: MonadClientUI m => ActorId -> m MError
- itemOverlay :: MonadClientUI m => [(ItemId, ItemQuant)] -> ItemDialogMode -> m OKX
- skillsOverlay :: MonadClientUI m => ActorId -> m OKX
- placesFromState :: ContentData PlaceKind -> Bool -> State -> EnumMap (ContentId PlaceKind) (EnumSet LevelId, Int, Int, Int)
- placesOverlay :: MonadClientUI m => m OKX
- factionsFromState :: ItemRoles -> State -> [(FactionId, Faction)]
- factionsOverlay :: MonadClientUI m => m OKX
- describeMode :: MonadClientUI m => Bool -> ContentId ModeKind -> m (EnumMap DisplayFont Overlay)
- modesOverlay :: MonadClientUI m => m OKX
- pickNumber :: MonadClientUI m => Bool -> Int -> m (Either MError Int)
- guardItemSize :: Actor -> State -> Int
- lookAtItems :: MonadClientUI m => Bool -> Point -> LevelId -> Maybe ActorId -> Maybe (Part, Bool) -> m (Text, Maybe Person)
- lookAtStash :: MonadClientUI m => Point -> LevelId -> m Text
- lookAtPosition :: MonadClientUI m => Point -> LevelId -> m [(MsgClassShow, Text)]
- displayOneMenuItem :: MonadClientUI m => (MenuSlot -> m OKX) -> [KM] -> Int -> MenuSlot -> m KM
- okxItemLoreInline :: MonadClientUI m => (ItemId -> ItemFull -> Int -> Text) -> Int -> ItemDialogMode -> [(ItemId, ItemQuant)] -> Int -> MenuSlot -> m OKX
- okxItemLoreMsg :: MonadClientUI m => (ItemId -> ItemFull -> Int -> Text) -> Int -> ItemDialogMode -> [(ItemId, ItemQuant)] -> MenuSlot -> m OKX
- itemDescOverlays :: MonadClientUI m => Bool -> Int -> ItemDialogMode -> ItemId -> ItemQuant -> ItemFull -> Int -> m (Overlay, Overlay)
- cycleLore :: MonadClientUI m => [m KM] -> [m KM] -> m ()
- spoilsBlurb :: Text -> Int -> Int -> Text
- ppContainerWownW :: MonadClientUI m => (ActorId -> m Part) -> Bool -> Container -> m [Part]
- nxtGameMode :: COps -> Int -> (ContentId ModeKind, ModeKind)
- itemOverlayFromState :: LevelId -> [(ItemId, ItemQuant)] -> Bool -> CCUI -> FactionId -> DiscoveryBenefit -> FontSetup -> State -> OKX
- lookAtTile :: MonadClientUI m => Bool -> Point -> LevelId -> Maybe ActorId -> Maybe Person -> m (Text, Text, [(Int, Part)])
- lookAtActors :: MonadClientUI m => Point -> LevelId -> m (Text, Maybe (Part, Bool), Text)
- guardItemVerbs :: Actor -> State -> [Part]
Documentation
Message describing the cause of failure of human command.
showFailError :: FailError -> Text Source #
failSer :: MonadClientUI m => ReqFailure -> m (FailOrCmd a) Source #
pointmanCycle :: MonadClientUI m => ActorId -> Bool -> Direction -> m MError Source #
Switches current pointman to the previous in the whole dungeon, wrapping.
pointmanCycleLevel :: MonadClientUI m => ActorId -> Bool -> Direction -> m MError Source #
Switches current pointman to the next on the level, if any, wrapping.
partyAfterLeader :: MonadClientUI m => ActorId -> m [(ActorId, Actor, ActorUI)] Source #
pickLeader :: MonadClientUI m => Bool -> ActorId -> m Bool Source #
Select a faction leader. False, if nothing to do.
doLook :: MonadClientUI m => m () Source #
Perform look around in the current position of the xhair. Does nothing outside aiming mode.
pickLeaderWithPointer :: MonadClientUI m => ActorId -> m MError Source #
itemOverlay :: MonadClientUI m => [(ItemId, ItemQuant)] -> ItemDialogMode -> m OKX Source #
skillsOverlay :: MonadClientUI m => ActorId -> m OKX Source #
placesFromState :: ContentData PlaceKind -> Bool -> State -> EnumMap (ContentId PlaceKind) (EnumSet LevelId, Int, Int, Int) Source #
Extract whole-dungeon statistics for each place kind,
counting the number of occurrences of each type of
PlaceEntry
for the given place kind and gathering the set of levels
on which any entry for that place kind can be found.
placesOverlay :: MonadClientUI m => m OKX Source #
factionsOverlay :: MonadClientUI m => m OKX Source #
describeMode :: MonadClientUI m => Bool -> ContentId ModeKind -> m (EnumMap DisplayFont Overlay) Source #
modesOverlay :: MonadClientUI m => m OKX Source #
pickNumber :: MonadClientUI m => Bool -> Int -> m (Either MError Int) Source #
Arguments
:: MonadClientUI m | |
=> Bool | can be seen right now? |
-> Point | position to describe |
-> LevelId | level the position is at |
-> Maybe ActorId | the actor that looks |
-> Maybe (Part, Bool) | pronoun for the big actor at the position, if any, and whether the big actor is alive |
-> m (Text, Maybe Person) |
Produces a textual description of items at a position.
lookAtStash :: MonadClientUI m => Point -> LevelId -> m Text Source #
lookAtPosition :: MonadClientUI m => Point -> LevelId -> m [(MsgClassShow, Text)] Source #
Produces a textual description of everything at the requested level's position.
displayOneMenuItem :: MonadClientUI m => (MenuSlot -> m OKX) -> [KM] -> Int -> MenuSlot -> m KM Source #
okxItemLoreInline :: MonadClientUI m => (ItemId -> ItemFull -> Int -> Text) -> Int -> ItemDialogMode -> [(ItemId, ItemQuant)] -> Int -> MenuSlot -> m OKX Source #
okxItemLoreMsg :: MonadClientUI m => (ItemId -> ItemFull -> Int -> Text) -> Int -> ItemDialogMode -> [(ItemId, ItemQuant)] -> MenuSlot -> m OKX Source #
itemDescOverlays :: MonadClientUI m => Bool -> Int -> ItemDialogMode -> ItemId -> ItemQuant -> ItemFull -> Int -> m (Overlay, Overlay) Source #
ppContainerWownW :: MonadClientUI m => (ActorId -> m Part) -> Bool -> Container -> m [Part] Source #
Internal operations
itemOverlayFromState :: LevelId -> [(ItemId, ItemQuant)] -> Bool -> CCUI -> FactionId -> DiscoveryBenefit -> FontSetup -> State -> OKX Source #
Arguments
:: MonadClientUI m | |
=> Bool | can be seen right now? |
-> Point | position to describe |
-> LevelId | level the position is at |
-> Maybe ActorId | the actor that looks |
-> Maybe Person | grammatical person of the item(s), if any |
-> m (Text, Text, [(Int, Part)]) |
Produces a textual description of the tile at a position.