module Lambdabot.Plugin.Social.Seen.UserStatus where
import Control.Applicative
import Data.Binary
import qualified Data.ByteString as BS
import Data.List
import Lambdabot.Compat.AltTime
import Lambdabot.Compat.PackedNick
import Lambdabot.Plugin.Social.Seen.StopWatch
type Channel = BS.ByteString
type LastSpoke = Maybe (ClockTime, TimeDiff)
data UserStatus
= Present !LastSpoke [Channel]
| NotPresent !ClockTime !StopWatch [Channel]
| WasPresent !ClockTime !StopWatch !LastSpoke [Channel]
| NewNick !PackedNick
deriving (Show, Read)
instance Binary UserStatus where
put (Present sp ch) = putWord8 0 >> put sp >> put ch
put (NotPresent ct sw ch) = putWord8 1 >> put ct >> put sw >> put ch
put (WasPresent ct sw sp ch) = putWord8 2 >> put ct >> put sw >> put sp >> put ch
put (NewNick n) = putWord8 3 >> put n
get = getWord8 >>= \h -> case h of
0 -> Present <$> get <*> get
1 -> NotPresent <$> get <*> get <*> get
2 -> WasPresent <$> get <*> get <*> get <*> get
3 -> NewNick <$> get
_ -> error "Seen.UserStatus.get"
updateJ :: Maybe ClockTime
-> [Channel]
-> UserStatus
-> UserStatus
updateJ _ c (Present ct cs) = Present ct $ nub (c ++ cs)
updateJ (Just now) cs (WasPresent lastSeen _ (Just (lastSpoke, missed)) channels)
| head channels `elem` cs
= let newMissed = addToClockTime missed now `diffClockTimes` lastSeen
in newMissed `seq` Present (Just (lastSpoke, newMissed)) cs
updateJ _ cs _ = Present Nothing cs
updateNP :: ClockTime -> Channel -> UserStatus -> UserStatus
updateNP now _ (NotPresent ct missed c)
= NotPresent ct (stopWatch now missed) c
updateNP now chan (WasPresent lastSeen missed _ cs)
| head cs == chan = WasPresent lastSeen (stopWatch now missed) Nothing cs
updateNP _ _ status = status