LambdaHack-0.6.1.0: A game engine library for roguelike dungeon crawlers

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Client.UI.HumanCmd

Description

Abstract syntax human player commands.

Synopsis

Documentation

data CmdCategory Source #

Instances

Eq CmdCategory Source # 
Read CmdCategory Source # 
Show CmdCategory Source # 
Generic CmdCategory Source # 

Associated Types

type Rep CmdCategory :: * -> * #

Binary CmdCategory Source # 
NFData CmdCategory Source # 

Methods

rnf :: CmdCategory -> () #

type Rep CmdCategory Source # 
type Rep CmdCategory = D1 * (MetaData "CmdCategory" "Game.LambdaHack.Client.UI.HumanCmd" "LambdaHack-0.6.1.0-HURqEs4cFyW7LJywblRLqn" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CmdMainMenu" PrefixI False) (U1 *)) (C1 * (MetaCons "CmdItemMenu" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CmdMove" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CmdItem" PrefixI False) (U1 *)) (C1 * (MetaCons "CmdAim" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "CmdMeta" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CmdMouse" PrefixI False) (U1 *)) (C1 * (MetaCons "CmdInternal" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "CmdNoHelp" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CmdDebug" PrefixI False) (U1 *)) (C1 * (MetaCons "CmdMinimal" PrefixI False) (U1 *))))))

data CmdArea Source #

Instances

Eq CmdArea Source # 

Methods

(==) :: CmdArea -> CmdArea -> Bool #

(/=) :: CmdArea -> CmdArea -> Bool #

Ord CmdArea Source # 
Read CmdArea Source # 
Show CmdArea Source # 
Generic CmdArea Source # 

Associated Types

type Rep CmdArea :: * -> * #

Methods

from :: CmdArea -> Rep CmdArea x #

to :: Rep CmdArea x -> CmdArea #

Binary CmdArea Source # 

Methods

put :: CmdArea -> Put #

get :: Get CmdArea #

putList :: [CmdArea] -> Put #

NFData CmdArea Source # 

Methods

rnf :: CmdArea -> () #

type Rep CmdArea Source # 
type Rep CmdArea = D1 * (MetaData "CmdArea" "Game.LambdaHack.Client.UI.HumanCmd" "LambdaHack-0.6.1.0-HURqEs4cFyW7LJywblRLqn" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CaMessage" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CaMapLeader" PrefixI False) (U1 *)) (C1 * (MetaCons "CaMapParty" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "CaMap" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CaLevelNumber" PrefixI False) (U1 *)) (C1 * (MetaCons "CaArenaName" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "CaPercentSeen" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CaXhairDesc" PrefixI False) (U1 *)) (C1 * (MetaCons "CaSelected" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "CaCalmGauge" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CaHPGauge" PrefixI False) (U1 *)) (C1 * (MetaCons "CaTargetDesc" PrefixI False) (U1 *))))))

data HumanCmd Source #

Abstract syntax of player commands.

Instances

Eq HumanCmd Source # 
Ord HumanCmd Source # 
Read HumanCmd Source # 
Show HumanCmd Source # 
Generic HumanCmd Source # 

Associated Types

type Rep HumanCmd :: * -> * #

Methods

from :: HumanCmd -> Rep HumanCmd x #

to :: Rep HumanCmd x -> HumanCmd #

Binary HumanCmd Source # 

Methods

put :: HumanCmd -> Put #

get :: Get HumanCmd #

putList :: [HumanCmd] -> Put #

NFData HumanCmd Source # 

Methods

rnf :: HumanCmd -> () #

type Rep HumanCmd Source # 
type Rep HumanCmd = D1 * (MetaData "HumanCmd" "Game.LambdaHack.Client.UI.HumanCmd" "LambdaHack-0.6.1.0-HURqEs4cFyW7LJywblRLqn" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Macro" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [String]))) (C1 * (MetaCons "ByArea" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [(CmdArea, HumanCmd)])))) ((:+:) * (C1 * (MetaCons "ByAimMode" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "exploration") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HumanCmd)) (S1 * (MetaSel (Just Symbol "aiming") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HumanCmd)))) (C1 * (MetaCons "ByItemMode" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "ts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Trigger])) ((:*:) * (S1 * (MetaSel (Just Symbol "notChosen") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HumanCmd)) (S1 * (MetaSel (Just Symbol "chosen") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HumanCmd))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "ComposeIfLocal" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HumanCmd)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HumanCmd)))) (C1 * (MetaCons "ComposeUnlessError" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HumanCmd)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HumanCmd))))) ((:+:) * (C1 * (MetaCons "Compose2ndLocal" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HumanCmd)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HumanCmd)))) ((:+:) * (C1 * (MetaCons "LoopOnNothing" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HumanCmd))) (C1 * (MetaCons "Wait" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Wait10" PrefixI False) (U1 *)) (C1 * (MetaCons "MoveDir" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Vector)))) ((:+:) * (C1 * (MetaCons "RunDir" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Vector))) (C1 * (MetaCons "RunOnceAhead" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "MoveOnceToXhair" PrefixI False) (U1 *)) (C1 * (MetaCons "RunOnceToXhair" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ContinueToXhair" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "MoveItem" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [CStore])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * CStore))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Part))) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool))))) (C1 * (MetaCons "Project" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Trigger])))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Apply" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Trigger]))) (C1 * (MetaCons "AlterDir" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Trigger])))) ((:+:) * (C1 * (MetaCons "AlterWithPointer" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Trigger]))) (C1 * (MetaCons "Help" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "ItemMenu" PrefixI False) (U1 *)) (C1 * (MetaCons "MainMenu" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "GameDifficultyIncr" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "GameWolfToggle" PrefixI False) (U1 *)) (C1 * (MetaCons "GameFishToggle" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "GameScenarioIncr" PrefixI False) (U1 *)) (C1 * (MetaCons "GameRestart" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "GameExit" PrefixI False) (U1 *)) (C1 * (MetaCons "GameSave" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Tactic" PrefixI False) (U1 *)) (C1 * (MetaCons "Automate" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Clear" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SortSlots" PrefixI False) (U1 *)) (C1 * (MetaCons "ChooseItem" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ItemDialogMode))))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ChooseItemMenu" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ItemDialogMode))) (C1 * (MetaCons "ChooseItemProject" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Trigger])))) ((:+:) * (C1 * (MetaCons "ChooseItemApply" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [Trigger]))) (C1 * (MetaCons "PickLeader" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int))))) ((:+:) * ((:+:) * (C1 * (MetaCons "PickLeaderWithPointer" PrefixI False) (U1 *)) (C1 * (MetaCons "MemberCycle" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "MemberBack" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SelectActor" PrefixI False) (U1 *)) (C1 * (MetaCons "SelectNone" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "SelectWithPointer" PrefixI False) (U1 *)) (C1 * (MetaCons "Repeat" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)))) ((:+:) * (C1 * (MetaCons "Record" PrefixI False) (U1 *)) (C1 * (MetaCons "History" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "MarkVision" PrefixI False) (U1 *)) (C1 * (MetaCons "MarkSmell" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "MarkSuspect" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SettingsMenu" PrefixI False) (U1 *)) (C1 * (MetaCons "ChallengesMenu" PrefixI False) (U1 *))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Cancel" PrefixI False) (U1 *)) (C1 * (MetaCons "Accept" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TgtClear" PrefixI False) (U1 *)) (C1 * (MetaCons "ItemClear" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "MoveXhair" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Vector)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)))) (C1 * (MetaCons "AimTgt" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "AimFloor" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "AimEnemy" PrefixI False) (U1 *)) (C1 * (MetaCons "AimItem" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "AimAscend" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int))) (C1 * (MetaCons "EpsIncr" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool)))) ((:+:) * (C1 * (MetaCons "XhairUnknown" PrefixI False) (U1 *)) (C1 * (MetaCons "XhairItem" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "XhairStair" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool))) (C1 * (MetaCons "XhairPointerFloor" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "XhairPointerEnemy" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "AimPointerFloor" PrefixI False) (U1 *)) (C1 * (MetaCons "AimPointerEnemy" PrefixI False) (U1 *)))))))))

noRemoteHumanCmd :: HumanCmd -> Bool Source #

Commands that are forbidden on a remote level, because they would usually take time when invoked on one, but not necessarily do what the player expects. Note that some commands that normally take time are not included, because they don't take time in aiming mode or their individual sanity conditions include a remote level check.

data Trigger Source #

Constructors

ApplyItem 

Fields

AlterFeature 

Fields

Instances

Eq Trigger Source # 

Methods

(==) :: Trigger -> Trigger -> Bool #

(/=) :: Trigger -> Trigger -> Bool #

Ord Trigger Source # 
Read Trigger Source # 
Show Trigger Source # 
Generic Trigger Source # 

Associated Types

type Rep Trigger :: * -> * #

Methods

from :: Trigger -> Rep Trigger x #

to :: Rep Trigger x -> Trigger #

Binary Trigger Source # 

Methods

put :: Trigger -> Put #

get :: Get Trigger #

putList :: [Trigger] -> Put #

NFData Trigger Source # 

Methods

rnf :: Trigger -> () #

type Rep Trigger Source #