{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving #-}
module Game.LambdaHack.Client.UI.Msg
(
Msg, toMsg, toPrompt
, Report, nullReport, consReport, renderReport, findInReport
, History, newReport, emptyHistory, addToReport, archiveReport, lengthHistory
, renderHistory
#ifdef EXPOSE_INTERNAL
, UAttrLine, RepMsgN, uToAttrLine, attrLineToU
, emptyReport, snocReport, renderRepetition, scrapRepetition, renderTimeReport
#endif
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Data.Binary
import Data.Vector.Binary ()
import qualified Data.Vector.Unboxed as U
import Data.Word (Word32)
import GHC.Generics (Generic)
import Game.LambdaHack.Client.UI.Overlay
import qualified Game.LambdaHack.Common.Color as Color
import qualified Game.LambdaHack.Common.RingBuffer as RB
import Game.LambdaHack.Common.Time
type UAttrLine = U.Vector Word32
uToAttrLine :: UAttrLine -> AttrLine
uToAttrLine v = map Color.AttrCharW32 $ U.toList v
attrLineToU :: AttrLine -> UAttrLine
attrLineToU l = U.fromList $ map Color.attrCharW32 l
data Msg = Msg
{ msgLine :: AttrLine
, msgHist :: Bool
}
deriving (Show, Eq, Generic)
instance Binary Msg
toMsg :: AttrLine -> Msg
toMsg l = Msg { msgLine = l
, msgHist = True }
toPrompt :: AttrLine -> Msg
toPrompt l = Msg { msgLine = l
, msgHist = False }
data RepMsgN = RepMsgN {repMsg :: Msg, _repN :: Int}
deriving (Show, Generic)
instance Binary RepMsgN
newtype Report = Report [RepMsgN]
deriving (Show, Binary)
emptyReport :: Report
emptyReport = Report []
nullReport :: Report -> Bool
nullReport (Report l) = null l
snocReport :: Report -> Msg -> Int -> Report
snocReport (Report !r) y n =
if null $ msgLine y then Report r else Report $ RepMsgN y n : r
consReport :: Msg -> Report -> Report
consReport Msg{msgLine=[]} rep = rep
consReport y (Report r) = Report $ r ++ [RepMsgN y 1]
renderReport :: Report -> AttrLine
renderReport (Report []) = []
renderReport (Report (x : xs)) =
renderReport (Report xs) <+:> renderRepetition x
renderRepetition :: RepMsgN -> AttrLine
renderRepetition (RepMsgN s 0) = msgLine s
renderRepetition (RepMsgN s 1) = msgLine s
renderRepetition (RepMsgN s n) = msgLine s ++ stringToAL ("<x" ++ show n ++ ">")
findInReport :: (AttrLine -> Bool) -> Report -> Maybe Msg
findInReport f (Report xns) = find (f . msgLine) $ map repMsg xns
data History = History
{ newReport :: Report
, newTime :: Time
, oldReport :: Report
, oldTime :: Time
, archivedHistory :: RB.RingBuffer UAttrLine }
deriving (Show, Generic)
instance Binary History
emptyHistory :: Int -> History
emptyHistory size = History emptyReport timeZero emptyReport timeZero
$ RB.empty size U.empty
scrapRepetition :: History -> Maybe History
scrapRepetition History{ newReport = Report newMsgs
, oldReport = Report oldMsgs
, .. } =
case newMsgs of
RepMsgN s1 n1 : rest1 ->
let f (RepMsgN s2 _) = s1 == s2
in case break f rest1 of
(_, []) -> case break f oldMsgs of
(_, []) -> Nothing
(noDup, RepMsgN _ n2 : rest2) ->
let newReport = Report $ RepMsgN s1 (n1 + n2) : rest1
oldReport = Report $ noDup ++ rest2
in Just History{..}
(noDup, RepMsgN _ n2 : rest2) ->
let newReport = Report $ noDup ++ RepMsgN s1 (n1 + n2) : rest2
oldReport = Report oldMsgs
in Just History{..}
_ -> Nothing
addToReport :: History -> Msg -> Int -> (History, Bool)
addToReport History{..} msg n =
let newH = History{newReport = snocReport newReport msg n, ..}
in case scrapRepetition newH of
Just scrappedH -> (scrappedH, True)
Nothing -> (newH, False)
archiveReport :: History -> Time -> History
archiveReport History{newReport=Report newMsgs, ..} !newT =
let f (RepMsgN _ n) = n > 0
newReportNon0 = Report $ filter f newMsgs
in if nullReport newReportNon0
then
History emptyReport newT oldReport oldTime archivedHistory
else let lU = map attrLineToU $ renderTimeReport oldTime oldReport
in History emptyReport newT newReportNon0 newTime
$ foldl' (flip RB.cons) archivedHistory (reverse lU)
renderTimeReport :: Time -> Report -> [AttrLine]
renderTimeReport !t (Report r') =
let turns = t `timeFitUp` timeTurn
rep = Report $ filter (msgHist . repMsg) r'
in if nullReport rep
then []
else [stringToAL (show turns ++ ": ") ++ renderReport rep]
lengthHistory :: History -> Int
lengthHistory History{oldReport, archivedHistory} =
RB.length archivedHistory + if nullReport oldReport then 0 else 1
renderHistory :: History -> [AttrLine]
renderHistory History{..} = map uToAttrLine (RB.toList archivedHistory)
++ renderTimeReport oldTime oldReport