-- | The default game key-command mapping to be used for UI. Can be overridden
-- via macros in the config file.
module Client.UI.Content.Input
  ( standardKeysAndMouse
#ifdef EXPOSE_INTERNAL
    -- * Internal operations
  , applyTs
#endif
  ) where

import Prelude ()

import Game.LambdaHack.Core.Prelude

import Game.LambdaHack.Client.UI.Content.Input
import Game.LambdaHack.Client.UI.HumanCmd
import Game.LambdaHack.Definition.Defs

-- | Description of default key-command bindings.
--
-- In addition to these commands, mouse and keys have a standard meaning
-- when navigating various menus.
standardKeysAndMouse :: InputContentRaw
standardKeysAndMouse :: InputContentRaw
standardKeysAndMouse = [(KM, CmdTriple)] -> InputContentRaw
InputContentRaw ([(KM, CmdTriple)] -> InputContentRaw)
-> [(KM, CmdTriple)] -> InputContentRaw
forall a b. (a -> b) -> a -> b
$ ((String, CmdTriple) -> (KM, CmdTriple))
-> [(String, CmdTriple)] -> [(KM, CmdTriple)]
forall a b. (a -> b) -> [a] -> [b]
map (String, CmdTriple) -> (KM, CmdTriple)
evalKeyDef ([(String, CmdTriple)] -> [(KM, CmdTriple)])
-> [(String, CmdTriple)] -> [(KM, CmdTriple)]
forall a b. (a -> b) -> a -> b
$
  -- All commands are defined here, except some movement and leader picking
  -- commands. All commands are shown on help screens except debug commands
  -- and macros with empty descriptions.
  -- The order below determines the order on the help screens.
  -- Remember to put commands that show information (e.g., enter aiming
  -- mode) first.

  -- Main menu
  [ ("s", ([CmdCategory
CmdMainMenu], "setup and start new game>", HumanCmd
ChallengeMenu))
  , ("x", ([CmdCategory
CmdMainMenu], "save and exit to desktop", HumanCmd
GameExit))
  , ("v", ([CmdCategory
CmdMainMenu], "tweak convenience settings>", HumanCmd
SettingsMenu))
  , ("t", ([CmdCategory
CmdMainMenu], "toggle autoplay", HumanCmd
AutomateToggle))
  , ("?", ([CmdCategory
CmdMainMenu], "see command help", HumanCmd
Help))
  , ("F12", ([CmdCategory
CmdMainMenu], "switch to dashboard", HumanCmd
Dashboard))
  , ("Escape", ([CmdCategory
CmdMainMenu], "back to playing", HumanCmd
AutomateBack))

  -- Minimal command set, in the desired presentation order.
  -- A lot of these are not necessary, but may be familiar to new players.
  -- Also a few non-minimal item commands to keep proper order.
  , ("I", ( [CmdCategory
CmdMinimal, CmdCategory
CmdItem, CmdCategory
CmdDashboard]
          , "manage the shared inventory stash"
          , ItemDialogMode -> HumanCmd
ChooseItemMenu (CStore -> ItemDialogMode
MStore CStore
CStash) ))
  , ("O", ( [CmdCategory
CmdItem, CmdCategory
CmdDashboard]
          , "manage the equipment outfit of the pointman"
          , ItemDialogMode -> HumanCmd
ChooseItemMenu (CStore -> ItemDialogMode
MStore CStore
CEqp) ))
  , ("g", CmdCategory -> CmdTriple -> CmdTriple
addCmdCategory CmdCategory
CmdMinimal (CmdTriple -> CmdTriple) -> CmdTriple -> CmdTriple
forall a b. (a -> b) -> a -> b
$ Text -> CmdTriple
grabItems "grab item(s)")
  , ("Escape", ( [CmdCategory
CmdMinimal, CmdCategory
CmdAim]
               , "clear messages/open main menu/finish aiming"
               , AimModeCmd -> HumanCmd
ByAimMode $WAimModeCmd :: HumanCmd -> HumanCmd -> AimModeCmd
AimModeCmd
                             { exploration :: HumanCmd
exploration = HumanCmd -> HumanCmd
ExecuteIfClear HumanCmd
MainMenuAutoOff
                             , aiming :: HumanCmd
aiming = HumanCmd
Cancel } ))
  , ("C-Escape", ([], "", HumanCmd
MainMenuAutoOn))
      -- required by frontends; not shown
  , ("Return", ( [CmdCategory
CmdMinimal, CmdCategory
CmdAim]
               , "open dashboard/accept target"
               , AimModeCmd -> HumanCmd
ByAimMode $WAimModeCmd :: HumanCmd -> HumanCmd -> AimModeCmd
AimModeCmd { exploration :: HumanCmd
exploration = HumanCmd
Dashboard
                                      , aiming :: HumanCmd
aiming = HumanCmd
Accept } ))
  , ("space", ( [CmdCategory
CmdMinimal, CmdCategory
CmdAim]
              , "clear messages/show history/cycle detail level"
              , AimModeCmd -> HumanCmd
ByAimMode $WAimModeCmd :: HumanCmd -> HumanCmd -> AimModeCmd
AimModeCmd { exploration :: HumanCmd
exploration = HumanCmd -> HumanCmd
ExecuteIfClear HumanCmd
LastHistory
                                     , aiming :: HumanCmd
aiming = HumanCmd
DetailCycle } ))
  , ("Tab", Direction -> [CmdCategory] -> CmdTriple
memberCycle Direction
Forward [CmdCategory
CmdMinimal, CmdCategory
CmdMove])
      -- listed here to keep proper order of the minimal cheat sheet
  , ("BackTab", Direction -> [CmdCategory] -> CmdTriple
memberCycle Direction
Backward [CmdCategory
CmdMove])
  , ("A-Tab", Direction -> [CmdCategory] -> CmdTriple
memberCycleLevel Direction
Forward [])
  , ("A-BackTab", Direction -> [CmdCategory] -> CmdTriple
memberCycleLevel Direction
Backward [])
  , ("C-Tab", Direction -> [CmdCategory] -> CmdTriple
memberCycleLevel Direction
Forward [CmdCategory
CmdMove])
  , ("C-BackTab", Direction -> [CmdCategory] -> CmdTriple
memberCycleLevel Direction
Backward [CmdCategory
CmdMove])
      -- TODO: the keys are too long to fit in help menu, unless vertically
  , ("*", ( [CmdCategory
CmdMinimal, CmdCategory
CmdAim]
          , "cycle crosshair among enemies"
          , HumanCmd
AimEnemy ))
  , ("/", ([CmdCategory
CmdMinimal, CmdCategory
CmdAim], "cycle crosshair among items", HumanCmd
AimItem))
  , ("m", ([CmdCategory
CmdMove], "modify door by closing it", HumanCmd
CloseDir))
  , ("M", ([CmdCategory
CmdMinimal, CmdCategory
CmdMove], "modify any admissible terrain", HumanCmd
AlterDir))
  , ("%", ([CmdCategory
CmdMinimal, CmdCategory
CmdMeta], "yell or yawn and stop sleeping", HumanCmd
Yell))

  -- Item menu, first part of item use commands
  , ("comma", Text -> CmdTriple
grabItems "")  -- only show extra key, not extra entry
  , ("r", Text -> CmdTriple
dropItems "remove item(s)")
  , ("f", CmdCategory -> CmdTriple -> CmdTriple
addCmdCategory CmdCategory
CmdItemMenu (CmdTriple -> CmdTriple) -> CmdTriple -> CmdTriple
forall a b. (a -> b) -> a -> b
$ [TriggerItem] -> CmdTriple
projectA [TriggerItem]
flingTs)
  , ("C-f", CmdCategory -> CmdTriple -> CmdTriple
addCmdCategory CmdCategory
CmdItemMenu
            (CmdTriple -> CmdTriple) -> CmdTriple -> CmdTriple
forall a b. (a -> b) -> a -> b
$ Text -> CmdTriple -> CmdTriple
replaceDesc "auto-fling and keep choice"
            (CmdTriple -> CmdTriple) -> CmdTriple -> CmdTriple
forall a b. (a -> b) -> a -> b
$ [TriggerItem] -> CmdTriple
projectI [TriggerItem]
flingTs)
  , ("t", CmdCategory -> CmdTriple -> CmdTriple
addCmdCategory CmdCategory
CmdItemMenu (CmdTriple -> CmdTriple) -> CmdTriple -> CmdTriple
forall a b. (a -> b) -> a -> b
$ [TriggerItem] -> CmdTriple
applyI [TriggerItem]
applyTs)
  , ("C-t", CmdCategory -> CmdTriple -> CmdTriple
addCmdCategory CmdCategory
CmdItemMenu
            (CmdTriple -> CmdTriple) -> CmdTriple -> CmdTriple
forall a b. (a -> b) -> a -> b
$ Text -> CmdTriple -> CmdTriple
replaceDesc "trigger item and keep choice" (CmdTriple -> CmdTriple) -> CmdTriple -> CmdTriple
forall a b. (a -> b) -> a -> b
$ [TriggerItem] -> CmdTriple
applyIK [TriggerItem]
applyTs)
  , ("i", Text -> CmdTriple -> CmdTriple
replaceDesc "stash item into shared inventory"
          (CmdTriple -> CmdTriple) -> CmdTriple -> CmdTriple
forall a b. (a -> b) -> a -> b
$ [CStore] -> CStore -> Part -> Bool -> CmdTriple
moveItemTriple [CStore
CGround, CStore
CEqp] CStore
CStash "item" Bool
False)
  , ("o", Text -> CmdTriple -> CmdTriple
replaceDesc "equip item into outfit of the pointman"
          (CmdTriple -> CmdTriple) -> CmdTriple -> CmdTriple
forall a b. (a -> b) -> a -> b
$ [CStore] -> CStore -> Part -> Bool -> CmdTriple
moveItemTriple [CStore
CGround, CStore
CStash] CStore
CEqp "item" Bool
False)

  -- Remaining @ChooseItemMenu@ instances
  , ("G", ( [CmdCategory
CmdItem, CmdCategory
CmdDashboard]
          , "manage items on the ground"
          , ItemDialogMode -> HumanCmd
ChooseItemMenu (CStore -> ItemDialogMode
MStore CStore
CGround) ))
  , ("T", ( [CmdCategory
CmdItem, CmdCategory
CmdDashboard]
          , "manage our total team belongings"
          , ItemDialogMode -> HumanCmd
ChooseItemMenu ItemDialogMode
MOwned ))
  , ("@", ( [CmdCategory
CmdMeta, CmdCategory
CmdDashboard]
          , "describe organs of the pointman"
          , ItemDialogMode -> HumanCmd
ChooseItemMenu ItemDialogMode
MOrgans ))
  , ("#", ( [CmdCategory
CmdMeta, CmdCategory
CmdDashboard]
          , "show skill summary of the pointman"
          , ItemDialogMode -> HumanCmd
ChooseItemMenu ItemDialogMode
MSkills ))
  , ("~", ( [CmdCategory
CmdMeta]
          , "display relevant lore"
          , ItemDialogMode -> HumanCmd
ChooseItemMenu (SLore -> ItemDialogMode
MLore SLore
SItem) ))

  -- Dashboard, in addition to commands marked above
  , ("safeD0", ([CmdCategory
CmdInternal, CmdCategory
CmdDashboard], "", HumanCmd
Cancel))  -- blank line
  ]
  [(String, CmdTriple)]
-> [(String, CmdTriple)] -> [(String, CmdTriple)]
forall a. [a] -> [a] -> [a]
++
  ((Int, SLore) -> (String, CmdTriple))
-> [(Int, SLore)] -> [(String, CmdTriple)]
forall a b. (a -> b) -> [a] -> [b]
map (\(k :: Int
k, slore :: SLore
slore) -> ("safeD" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (Int
k :: Int)
                      , ( [CmdCategory
CmdInternal, CmdCategory
CmdDashboard]
                        , "display" Text -> Text -> Text
<+> SLore -> Text
ppSLore SLore
slore Text -> Text -> Text
<+> "lore"
                        , ItemDialogMode -> HumanCmd
ChooseItemMenu (SLore -> ItemDialogMode
MLore SLore
slore) )))
      ([Int] -> [SLore] -> [(Int, SLore)]
forall a b. [a] -> [b] -> [(a, b)]
zip [1..] [SLore
forall a. Bounded a => a
minBound..SLore
forall a. Bounded a => a
maxBound])
  [(String, CmdTriple)]
-> [(String, CmdTriple)] -> [(String, CmdTriple)]
forall a. [a] -> [a] -> [a]
++
  [ ("safeD97", ( [CmdCategory
CmdInternal, CmdCategory
CmdDashboard]
                , "display place lore"
                , ItemDialogMode -> HumanCmd
ChooseItemMenu ItemDialogMode
MPlaces) )
  , ("safeD98", ( [CmdCategory
CmdInternal, CmdCategory
CmdDashboard]
                , "display adventure lore"
                , ItemDialogMode -> HumanCmd
ChooseItemMenu ItemDialogMode
MModes) )
  , ("safeD99", ([CmdCategory
CmdInternal, CmdCategory
CmdDashboard], "", HumanCmd
Cancel))  -- blank line

  -- Terrain exploration and modification
  , ("=", ( [CmdCategory
CmdMove], "select (or deselect) party member", HumanCmd
SelectActor) )
  , ("_", ([CmdCategory
CmdMove], "deselect (or select) all on the level", HumanCmd
SelectNone))
  , ("semicolon", ( [CmdCategory
CmdMove]
                  , "go to crosshair for 25 steps"
                  , [String] -> HumanCmd
Macro ["C-semicolon", "C-quotedbl", "C-v"] ))
  , ("colon", ( [CmdCategory
CmdMove]
              , "run to crosshair collectively for 25 steps"
              , [String] -> HumanCmd
Macro ["C-colon", "C-quotedbl", "C-v"] ))
  , ("[", ( [CmdCategory
CmdMove]
          , "explore nearest unknown spot"
          , HumanCmd
autoexploreCmd ))
  , ("]", ( [CmdCategory
CmdMove]
          , "autoexplore 25 times"
          , HumanCmd
autoexplore25Cmd ))
  , ("R", ([CmdCategory
CmdMove], "rest (wait 25 times)", [String] -> HumanCmd
Macro ["KP_Begin", "C-v"]))
  , ("C-R", ( [CmdCategory
CmdMove], "heed (lurk 0.1 turns 100 times)"
            , [String] -> HumanCmd
Macro ["C-KP_Begin", "A-v"] ))

  -- Aiming
  , ("+", ([CmdCategory
CmdAim], "swerve the aiming line", Direction -> HumanCmd
EpsIncr Direction
Forward))
  , ("-", ([CmdCategory
CmdAim], "unswerve the aiming line", Direction -> HumanCmd
EpsIncr Direction
Backward))
  , ("\\", ([CmdCategory
CmdAim], "cycle aiming modes", HumanCmd
AimFloor))
  , ("C-?", ( [CmdCategory
CmdAim]
            , "set crosshair to nearest unknown spot"
            , HumanCmd
XhairUnknown ))
  , ("C-/", ( [CmdCategory
CmdAim]
            , "set crosshair to nearest item"
            , HumanCmd
XhairItem ))
  , ("C-{", ( [CmdCategory
CmdAim]
            , "aim at nearest upstairs"
            , Bool -> HumanCmd
XhairStair Bool
True ))
  , ("C-}", ( [CmdCategory
CmdAim]
            , "aim at nearest downstairs"
            , Bool -> HumanCmd
XhairStair Bool
False ))
  , ("<", ([CmdCategory
CmdAim], "move aiming one level up" , Int -> HumanCmd
AimAscend 1))
  , ("C-<", ([], "move aiming 10 levels up", Int -> HumanCmd
AimAscend 10))
  , (">", ([CmdCategory
CmdAim], "move aiming one level down", Int -> HumanCmd
AimAscend (-1)))
      -- 'lower' would be misleading in some games, just as 'deeper'
  , ("C->", ([], "move aiming 10 levels down", Int -> HumanCmd
AimAscend (-10)))
  , ("BackSpace" , ( [CmdCategory
CmdAim]
                   , "clear chosen item and crosshair"
                   , HumanCmd -> HumanCmd -> HumanCmd
ComposeUnlessError HumanCmd
ClearTargetIfItemClear HumanCmd
ItemClear))

  -- Assorted (first few cloned from main menu)
  , ("C-g", ([CmdCategory
CmdMeta], "start new game", HumanCmd
GameRestart))
  , ("C-x", ([CmdCategory
CmdMeta], "save and exit to desktop", HumanCmd
GameExit))
  , ("C-q", ([CmdCategory
CmdMeta], "quit game and start autoplay", HumanCmd
GameQuit))
  , ("C-c", ([CmdCategory
CmdMeta], "exit to desktop without saving", HumanCmd
GameDrop))
  , ("?", ([CmdCategory
CmdMeta], "display help", HumanCmd
Hint))
  , ("F1", ([CmdCategory
CmdMeta, CmdCategory
CmdDashboard], "display help immediately", HumanCmd
Help))
  , ("F12", ([CmdCategory
CmdMeta], "open dashboard", HumanCmd
Dashboard))
  , ("v", Int -> [CmdCategory] -> CmdTriple
repeatLastTriple 1 [CmdCategory
CmdMeta])
  , ("C-v", Int -> [CmdCategory] -> CmdTriple
repeatLastTriple 25 [])
  , ("A-v", Int -> [CmdCategory] -> CmdTriple
repeatLastTriple 100 [])
  , ("V", Int -> [CmdCategory] -> CmdTriple
repeatTriple 1 [CmdCategory
CmdMeta])
  , ("C-V", Int -> [CmdCategory] -> CmdTriple
repeatTriple 25 [])
  , ("A-V", Int -> [CmdCategory] -> CmdTriple
repeatTriple 100 [])
  , ("'", ([CmdCategory
CmdMeta], "start recording commands", HumanCmd
Record))
  , ("C-S", ([CmdCategory
CmdMeta], "save game backup", HumanCmd
GameSave))
  , ("C-P", ([CmdCategory
CmdMeta], "print screen", HumanCmd
PrintScreen))

  -- Dashboard, in addition to commands marked above
  , ("safeD101", ([CmdCategory
CmdInternal, CmdCategory
CmdDashboard], "display history", HumanCmd
AllHistory))

  -- Mouse
  , ( "LeftButtonRelease"
    , HumanCmd -> Text -> CmdTriple
mouseLMB HumanCmd
goToCmd
               "go to pointer for 25 steps/fling at enemy" )
  , ( "S-LeftButtonRelease"
    , HumanCmd -> Text -> CmdTriple
mouseLMB HumanCmd
runToAllCmd
               "run to pointer collectively for 25 steps/fling at enemy" )
  , ("RightButtonRelease", CmdTriple
mouseRMB)
  , ("C-LeftButtonRelease", Text -> CmdTriple -> CmdTriple
replaceDesc "" CmdTriple
mouseRMB)  -- Mac convention
  , ( "S-RightButtonRelease"
    , ([CmdCategory
CmdMouse], "modify terrain at pointer", HumanCmd
AlterWithPointer) )
  , ("MiddleButtonRelease", CmdTriple
mouseMMB)
  , ("C-RightButtonRelease", Text -> CmdTriple -> CmdTriple
replaceDesc "" CmdTriple
mouseMMB)
  , ( "C-S-LeftButtonRelease", let (_, _, cmd :: HumanCmd
cmd) = CmdTriple
mouseMMB
                               in ([], "", HumanCmd
cmd) )
  , ("A-MiddleButtonRelease", CmdTriple
mouseMMBMute)
  , ("WheelNorth", ([CmdCategory
CmdMouse], "swerve the aiming line", [String] -> HumanCmd
Macro ["+"]))
  , ("WheelSouth", ([CmdCategory
CmdMouse], "unswerve the aiming line", [String] -> HumanCmd
Macro ["-"]))

  -- Debug and others not to display in help screens
  , ("C-semicolon", ( []
                    , "move one step towards the crosshair"
                    , HumanCmd
MoveOnceToXhair ))
  , ("C-colon", ( []
                , "run collectively one step towards the crosshair"
                , HumanCmd
RunOnceToXhair ))
  , ("C-quotedbl", ( []
                   , "continue towards the crosshair"
                   , HumanCmd
ContinueToXhair ))
  , ("C-comma", ([], "run once ahead", HumanCmd
RunOnceAhead))
  , ("safe1", ( [CmdCategory
CmdInternal]
              , "go to pointer for 25 steps"
              , HumanCmd
goToCmd ))
  , ("safe2", ( [CmdCategory
CmdInternal]
              , "run to pointer collectively"
              , HumanCmd
runToAllCmd ))
  , ("safe3", ( [CmdCategory
CmdInternal]
              , "pick new pointman on screen"
              , HumanCmd
PickLeaderWithPointer ))
  , ("safe4", ( [CmdCategory
CmdInternal]
              , "select party member on screen"
              , HumanCmd
SelectWithPointer ))
  , ("safe5", ( [CmdCategory
CmdInternal]
              , "set crosshair to enemy"
              , HumanCmd
AimPointerEnemy ))
  , ("safe6", ( [CmdCategory
CmdInternal]
              , "fling at enemy under pointer"
              , HumanCmd
aimFlingCmd ))
  , ("safe7", ( [CmdCategory
CmdInternal, CmdCategory
CmdDashboard]
              , "open main menu"
              , HumanCmd
MainMenuAutoOff ))
  , ("safe8", ( [CmdCategory
CmdInternal]
              , "clear msgs and open main menu"
              , HumanCmd -> HumanCmd
ExecuteIfClear HumanCmd
MainMenuAutoOff ))
  , ("safe9", ( [CmdCategory
CmdInternal]
              , "cancel aiming"
              , HumanCmd
Cancel ))
  , ("safe10", ( [CmdCategory
CmdInternal]
               , "accept target"
               , HumanCmd
Accept ))
  , ("safe11", ( [CmdCategory
CmdInternal]
               , "show history"
               , HumanCmd
LastHistory ))
  , ("safe12", ( [CmdCategory
CmdInternal]
               , "wait a turn, bracing for impact"
               , HumanCmd
Wait ))
  , ("safe13", ( [CmdCategory
CmdInternal]
               , "lurk 0.1 of a turn"
               , HumanCmd
Wait10 ))
  , ("safe14", ( [CmdCategory
CmdInternal]
               , "snap crosshair to enemy"
               , HumanCmd
XhairPointerEnemy ))
  ]
  [(String, CmdTriple)]
-> [(String, CmdTriple)] -> [(String, CmdTriple)]
forall a. [a] -> [a] -> [a]
++ (Int -> (String, CmdTriple)) -> [Int] -> [(String, CmdTriple)]
forall a b. (a -> b) -> [a] -> [b]
map Int -> (String, CmdTriple)
defaultHeroSelect [0..9]

applyTs :: [TriggerItem]
applyTs :: [TriggerItem]
applyTs = [$WTriggerItem :: Part -> Part -> String -> TriggerItem
TriggerItem { tiverb :: Part
tiverb = "trigger"
                       , tiobject :: Part
tiobject = "consumable item"
                       , tisymbols :: String
tisymbols = "!,?/" }]