-- | Monadic operations on game messages.
module Game.LambdaHack.Client.UI.MsgM
  ( msgAddDuplicate, msgAddDistinct, msgAdd, msgLnAdd
  , promptMainKeys, recordHistory
  ) where

import Prelude ()

import Game.LambdaHack.Core.Prelude

import           Game.LambdaHack.Client.MonadClient
import           Game.LambdaHack.Client.State
import           Game.LambdaHack.Client.UI.EffectDescription
import qualified Game.LambdaHack.Client.UI.HumanCmd as HumanCmd
import qualified Game.LambdaHack.Client.UI.Key as K
import           Game.LambdaHack.Client.UI.MonadClientUI
import           Game.LambdaHack.Client.UI.Msg
import           Game.LambdaHack.Client.UI.SessionUI
import           Game.LambdaHack.Client.UI.UIOptions
import           Game.LambdaHack.Common.ActorState
import           Game.LambdaHack.Common.MonadStateRead
import           Game.LambdaHack.Common.State
import           Game.LambdaHack.Definition.Defs

-- | Add a shared message to the current report. Say if it was a duplicate.
msgAddDuplicate :: (MonadClient m, MonadClientUI m, MsgShared a)
                => a -> Text -> m Bool
msgAddDuplicate :: a -> Text -> m Bool
msgAddDuplicate msgClass :: a
msgClass t :: Text
t = do
  UIOptions
sUIOptions <- (SessionUI -> UIOptions) -> m UIOptions
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> UIOptions
sUIOptions
  Time
time <- (State -> Time) -> m Time
forall (m :: * -> *) a. MonadStateRead m => (State -> a) -> m a
getsState State -> Time
stime
  History
history <- (SessionUI -> History) -> m History
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> History
shistory
  Bool
curTutorial <- (SessionUI -> Bool) -> m Bool
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> Bool
scurTutorial
  Maybe Bool
overrideTut <- (SessionUI -> Maybe Bool) -> m (Maybe Bool)
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> Maybe Bool
soverrideTut
  Set Msg
usedHints <- (SessionUI -> Set Msg) -> m (Set Msg)
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> Set Msg
susedHints
  LevelId
lid <- m LevelId
forall (m :: * -> *). MonadClientUI m => m LevelId
getArenaUI
  Bool
condInMelee <- LevelId -> m Bool
forall (m :: * -> *). MonadClient m => LevelId -> m Bool
condInMeleeM LevelId
lid
  let displayHints :: Bool
displayHints = Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
curTutorial Maybe Bool
overrideTut
      msg :: Msg
msg = [(String, Color)] -> a -> Text -> Msg
forall a. MsgShared a => [(String, Color)] -> a -> Text -> Msg
toMsgShared (UIOptions -> [(String, Color)]
uMessageColors UIOptions
sUIOptions) a
msgClass Text
t
      (nusedHints :: Set Msg
nusedHints, nhistory :: History
nhistory, duplicate :: Bool
duplicate) =
        Set Msg
-> Bool
-> Bool
-> History
-> Msg
-> Time
-> (Set Msg, History, Bool)
addToReport Set Msg
usedHints Bool
displayHints Bool
condInMelee History
history Msg
msg Time
time
  (SessionUI -> SessionUI) -> m ()
forall (m :: * -> *).
MonadClientUI m =>
(SessionUI -> SessionUI) -> m ()
modifySession ((SessionUI -> SessionUI) -> m ())
-> (SessionUI -> SessionUI) -> m ()
forall a b. (a -> b) -> a -> b
$ \sess :: SessionUI
sess -> SessionUI
sess {shistory :: History
shistory = History
nhistory, susedHints :: Set Msg
susedHints = Set Msg
nusedHints}
  Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
duplicate

-- | Add a message comprising of two different texts, one to show, the other
-- to save to messages log, to the current report.
msgAddDistinct :: (MonadClient m, MonadClientUI m)
               => MsgClassDistinct -> (Text, Text) -> m ()
msgAddDistinct :: MsgClassDistinct -> (Text, Text) -> m ()
msgAddDistinct msgClass :: MsgClassDistinct
msgClass (t1 :: Text
t1, t2 :: Text
t2) = do
  UIOptions
sUIOptions <- (SessionUI -> UIOptions) -> m UIOptions
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> UIOptions
sUIOptions
  Time
time <- (State -> Time) -> m Time
forall (m :: * -> *) a. MonadStateRead m => (State -> a) -> m a
getsState State -> Time
stime
  History
history <- (SessionUI -> History) -> m History
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> History
shistory
  Bool
curTutorial <- (SessionUI -> Bool) -> m Bool
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> Bool
scurTutorial
  Maybe Bool
overrideTut <- (SessionUI -> Maybe Bool) -> m (Maybe Bool)
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> Maybe Bool
soverrideTut
  Set Msg
usedHints <- (SessionUI -> Set Msg) -> m (Set Msg)
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> Set Msg
susedHints
  LevelId
lid <- m LevelId
forall (m :: * -> *). MonadClientUI m => m LevelId
getArenaUI
  Bool
condInMelee <- LevelId -> m Bool
forall (m :: * -> *). MonadClient m => LevelId -> m Bool
condInMeleeM LevelId
lid
  let displayHints :: Bool
displayHints = Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
curTutorial Maybe Bool
overrideTut
      msg :: Msg
msg = [(String, Color)] -> MsgClassDistinct -> Text -> Text -> Msg
toMsgDistinct (UIOptions -> [(String, Color)]
uMessageColors UIOptions
sUIOptions) MsgClassDistinct
msgClass Text
t1 Text
t2
      (nusedHints :: Set Msg
nusedHints, nhistory :: History
nhistory, _) =
        Set Msg
-> Bool
-> Bool
-> History
-> Msg
-> Time
-> (Set Msg, History, Bool)
addToReport Set Msg
usedHints Bool
displayHints Bool
condInMelee History
history Msg
msg Time
time
  (SessionUI -> SessionUI) -> m ()
forall (m :: * -> *).
MonadClientUI m =>
(SessionUI -> SessionUI) -> m ()
modifySession ((SessionUI -> SessionUI) -> m ())
-> (SessionUI -> SessionUI) -> m ()
forall a b. (a -> b) -> a -> b
$ \sess :: SessionUI
sess -> SessionUI
sess {shistory :: History
shistory = History
nhistory, susedHints :: Set Msg
susedHints = Set Msg
nusedHints}

-- | Add a message to the current report.
msgAdd :: (MonadClient m, MonadClientUI m, MsgShared a) => a -> Text -> m ()
msgAdd :: a -> Text -> m ()
msgAdd msgClass :: a
msgClass t :: Text
t = m Bool -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (m Bool -> m ()) -> m Bool -> m ()
forall a b. (a -> b) -> a -> b
$ a -> Text -> m Bool
forall (m :: * -> *) a.
(MonadClient m, MonadClientUI m, MsgShared a) =>
a -> Text -> m Bool
msgAddDuplicate a
msgClass Text
t

-- | Add a message to the current report. End previously collected report,
-- if any, with newline.
msgLnAdd :: (MonadClient m, MonadClientUI m, MsgShared a) => a -> Text -> m ()
msgLnAdd :: a -> Text -> m ()
msgLnAdd msgClass :: a
msgClass t :: Text
t = do
  (SessionUI -> SessionUI) -> m ()
forall (m :: * -> *).
MonadClientUI m =>
(SessionUI -> SessionUI) -> m ()
modifySession ((SessionUI -> SessionUI) -> m ())
-> (SessionUI -> SessionUI) -> m ()
forall a b. (a -> b) -> a -> b
$ \sess :: SessionUI
sess -> SessionUI
sess {shistory :: History
shistory = History -> History
addEolToNewReport (History -> History) -> History -> History
forall a b. (a -> b) -> a -> b
$ SessionUI -> History
shistory SessionUI
sess}
  a -> Text -> m ()
forall (m :: * -> *) a.
(MonadClient m, MonadClientUI m, MsgShared a) =>
a -> Text -> m ()
msgAdd a
msgClass Text
t

-- | Add a prompt with basic keys description.
promptMainKeys :: (MonadClient m, MonadClientUI m) => m ()
promptMainKeys :: m ()
promptMainKeys = do
  FactionId
side <- (StateClient -> FactionId) -> m FactionId
forall (m :: * -> *) a.
MonadClientRead m =>
(StateClient -> a) -> m a
getsClient StateClient -> FactionId
sside
  [(ActorId, Actor)]
ours <- (State -> [(ActorId, Actor)]) -> m [(ActorId, Actor)]
forall (m :: * -> *) a. MonadStateRead m => (State -> a) -> m a
getsState ((State -> [(ActorId, Actor)]) -> m [(ActorId, Actor)])
-> (State -> [(ActorId, Actor)]) -> m [(ActorId, Actor)]
forall a b. (a -> b) -> a -> b
$ FactionId -> State -> [(ActorId, Actor)]
fidActorNotProjGlobalAssocs FactionId
side
  HumanCmd -> KM
revCmd <- m (HumanCmd -> KM)
forall (m :: * -> *). MonadClientUI m => m (HumanCmd -> KM)
revCmdMap
  let kmHelp :: KM
kmHelp = HumanCmd -> KM
revCmd HumanCmd
HumanCmd.Hint
      kmViewStash :: KM
kmViewStash = HumanCmd -> KM
revCmd (ItemDialogMode -> HumanCmd
HumanCmd.ChooseItemMenu (CStore -> ItemDialogMode
MStore CStore
CStash))
      kmItemStash :: KM
kmItemStash = HumanCmd -> KM
revCmd ([CStore] -> CStore -> Maybe Text -> Bool -> HumanCmd
HumanCmd.MoveItem [CStore
CGround, CStore
CEqp] CStore
CStash
                                              Maybe Text
forall a. Maybe a
Nothing Bool
False)
      kmXhairPointerFloor :: KM
kmXhairPointerFloor = HumanCmd -> KM
revCmd HumanCmd
HumanCmd.XhairPointerFloor
  Maybe AimMode
saimMode <- (SessionUI -> Maybe AimMode) -> m (Maybe AimMode)
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> Maybe AimMode
saimMode
  UIOptions{Bool
uVi :: UIOptions -> Bool
uVi :: Bool
uVi, Bool
uLeftHand :: UIOptions -> Bool
uLeftHand :: Bool
uLeftHand} <- (SessionUI -> UIOptions) -> m UIOptions
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> UIOptions
sUIOptions
  Maybe Target
xhair <- (SessionUI -> Maybe Target) -> m (Maybe Target)
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> Maybe Target
sxhair
  -- The silly "axwdqezc" name of keys is chosen to match "hjklyubn",
  -- which the usual way of writing them.
  let moveKeys :: Text
moveKeys | Bool
uVi Bool -> Bool -> Bool
&& Bool
uLeftHand = "keypad or axwdqezc or hjklyubn"
               | Bool
uLeftHand = "keypad or axwdqezc"
               | Bool
uVi = "keypad or hjklyubn"
               | Bool
otherwise = "keypad"
      manyTeammates :: Bool
manyTeammates = [(ActorId, Actor)] -> Int
forall a. [a] -> Int
length [(ActorId, Actor)]
ours Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 1
      detailAtDefault :: Bool
detailAtDefault = (AimMode -> DetailLevel
detailLevel (AimMode -> DetailLevel) -> Maybe AimMode -> Maybe DetailLevel
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe AimMode
saimMode) Maybe DetailLevel -> Maybe DetailLevel -> Bool
forall a. Eq a => a -> a -> Bool
== DetailLevel -> Maybe DetailLevel
forall a. a -> Maybe a
Just DetailLevel
defaultDetailLevel
      -- @Tab@ here is not a button, which we would write consistently
      -- as @TAB@, just as in our internal in-game key naming, but a key name
      -- as written on the keyboard, hence most useful to a newbie.
      keepTab :: Text
keepTab = if Bool
manyTeammates
                then "Switch to another teammate with Tab, while all others auto-melee foes, if adjacent, but normally don't chase them."
                else ""
      describePos :: Text
describePos = if Bool
describeIsNormal
                    then "Describe map position with MMB or RMB."
                    else ""
      viewEquip :: Text
viewEquip = if Bool
stashKeysAreNormal
                  then "View shared 'I'nventory stash and stash items into the 'i'nventory."
                  else ""
      moreHelp :: Text
moreHelp = "Press '" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> KM -> Text
forall a. Show a => a -> Text
tshow KM
kmHelp Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "' for more help."
      describeIsNormal :: Bool
describeIsNormal = KM
kmXhairPointerFloor KM -> KM -> Bool
forall a. Eq a => a -> a -> Bool
== KM
K.middleButtonReleaseKM
      stashKeysAreNormal :: Bool
stashKeysAreNormal = KM
kmViewStash KM -> KM -> Bool
forall a. Eq a => a -> a -> Bool
== Char -> KM
K.mkChar 'I'
                           Bool -> Bool -> Bool
&& KM
kmItemStash KM -> KM -> Bool
forall a. Eq a => a -> a -> Bool
== Char -> KM
K.mkChar 'i'
      keys :: Text
keys | Maybe AimMode -> Bool
forall a. Maybe a -> Bool
isNothing Maybe AimMode
saimMode =
        "Explore with" Text -> Text -> Text
<+> Text
moveKeys Text -> Text -> Text
<+> "or mouse."
        Text -> Text -> Text
<+> Text
describePos
        Text -> Text -> Text
<+> Text
viewEquip
        Text -> Text -> Text
<+> Text
keepTab
        Text -> Text -> Text
<+> Text
moreHelp
           | Bool
otherwise =
        (if Bool
detailAtDefault then "" else Text
miniHintAimingBare)
        Text -> Text -> Text
<+> Maybe Target -> Text
tgtKindVerb Maybe Target
xhair
        Text -> Text -> Text
<+> "with" Text -> Text -> Text
<+> Text
moveKeys Text -> Text -> Text
<+> "keys or mouse."
        Text -> Text -> Text
<+> Text
keepTab
        Text -> Text -> Text
<+> Text
moreHelp
  m () -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ MsgClassShow -> Text -> m ()
forall (m :: * -> *) a.
(MonadClient m, MonadClientUI m, MsgShared a) =>
a -> Text -> m ()
msgAdd MsgClassShow
MsgPromptGeneric Text
keys

tgtKindVerb :: Maybe Target -> Text
tgtKindVerb :: Maybe Target -> Text
tgtKindVerb mtgt :: Maybe Target
mtgt = case Maybe Target
mtgt of
  Just TEnemy{} -> "Aim at enemy"
  Just TNonEnemy{} -> "Aim at non-enemy"
  Just TPoint{} -> "Aim at position"
  Just TVector{} -> "Indicate a move vector"
  Nothing -> "Start aiming"

-- | Store new report in the history and archive old report.
recordHistory :: MonadClientUI m => m ()
recordHistory :: m ()
recordHistory = do
  UIOptions{Bool
uHistory1PerLine :: UIOptions -> Bool
uHistory1PerLine :: Bool
uHistory1PerLine} <- (SessionUI -> UIOptions) -> m UIOptions
forall (m :: * -> *) a. MonadClientUI m => (SessionUI -> a) -> m a
getsSession SessionUI -> UIOptions
sUIOptions
  (SessionUI -> SessionUI) -> m ()
forall (m :: * -> *).
MonadClientUI m =>
(SessionUI -> SessionUI) -> m ()
modifySession ((SessionUI -> SessionUI) -> m ())
-> (SessionUI -> SessionUI) -> m ()
forall a b. (a -> b) -> a -> b
$ \sess :: SessionUI
sess ->
    SessionUI
sess {shistory :: History
shistory = Bool -> History -> History
archiveReport Bool
uHistory1PerLine (History -> History) -> History -> History
forall a b. (a -> b) -> a -> b
$ SessionUI -> History
shistory SessionUI
sess}