{- This file is part of irc-fun-bot. - - Written in 2015, 2016 by fr33domlover . - - ♡ Copying is an act of love. Please copy, reuse and share. - - The author(s) have dedicated all copyright and related and neighboring - rights to this software to the public domain worldwide. This software is - distributed without any warranty. - - You should have received a copy of the CC0 Public Domain Dedication along - with this software. If not, see - . -} module Network.IRC.Fun.Bot.Internal.Nicks ( channelIsTracked , startTrackingAll , startTrackingChannel , startTrackingChannels , stopTrackingAll , stopTrackingChannel , stopTrackingChannels , isInChannel , presence , addMember , changeNick , addChannel , removeMemberOnce , removeMember , removeChannel , removeChannels ) where import Control.Monad (unless) import Data.Maybe (fromMaybe) import Network.IRC.Fun.Bot.Internal.ChatExt (putIrc) import Network.IRC.Fun.Bot.Internal.Monad import Network.IRC.Fun.Bot.Internal.State import Network.IRC.Fun.Bot.Internal.Types import Network.IRC.Fun.Types import qualified Data.HashMap.Lazy as M import qualified Network.IRC.Fun.Client.NickTracker as NT enable :: ChanState -> ChanState enable cstate = cstate { csTracking = True } disable :: ChanState -> ChanState disable cstate = cstate { csTracking = False } -- | Check whether a given channel is being tracked. channelIsTracked :: Channel -> Session e s Bool channelIsTracked chan = do chans <- getChans return $ fromMaybe False $ fmap csTracking $ M.lookup chan chans -- | Start tracking nicks in all the channels the bot has joined which aren't -- being tracked. startTrackingAll :: Session e s () startTrackingAll = do chans <- getChans let chansD = [chan | (chan, ChanState False _ _ _ _) <- M.toList chans] chansAllE = M.map enable chans putChans chansAllE unless (null chansD) $ putIrc $ NamesMessage chansD Nothing -- | Start tracking nicks in the given channel, if not tracked already. startTrackingChannel :: Channel -> Session e s () startTrackingChannel chan = do chans <- getChans case M.lookup chan chans of Just cstate -> unless (csTracking cstate) $ do let chansE = M.insert chan (cstate { csTracking = True }) chans putChans chansE putIrc $ NamesMessage [chan] Nothing Nothing -> return () -- | Start tracking nicks in the channels not tracked, among the ones given. startTrackingChannels :: [Channel] -> Session e s () startTrackingChannels chans = do chanmapAll <- getChans let given = M.fromList (zip chans (repeat ())) chanmapG = chanmapAll `M.intersection` given chanmapD = M.filter (not . csTracking) chanmapG chansD = M.keys chanmapD chanmapE = M.map enable chanmapD chanmapAllE = chanmapE `M.union` chanmapAll putChans chanmapAllE putIrc $ NamesMessage chansD Nothing -- | Stop tracking nicks in all tracked channels. stopTrackingAll :: Session e s () stopTrackingAll = modify $ \ bstate -> bstate { bsTracker = NT.newNetwork , bsChannels = M.map disable $ bsChannels bstate } -- | Stop tracking nicks in the given channel, if tracked. stopTrackingChannel :: Channel -> Session e s () stopTrackingChannel chan = modify $ \ bstate -> bstate { bsTracker = NT.removeChannel chan $ bsTracker bstate , bsChannels = M.adjust disable chan $ bsChannels bstate } -- | Stop tracking nicks in the tracked channels among the ones given. stopTrackingChannels :: [Channel] -> Session e s () stopTrackingChannels chans = modify $ \ bstate -> bstate { bsTracker = NT.removeChannels chans $ bsTracker bstate , bsChannels = let chanmap = bsChannels bstate chanmapE = M.filter csTracking chanmap chanmapD = M.map disable chanmapE in chanmapD `M.union` chanmap } -- | Check whether a nickname is present in a channel. isInChannel :: Nickname -> Channel -> Session e s Bool nick `isInChannel` chan = do nt <- gets bsTracker return $ NT.isInChannel nick chan nt -- | Check in which channels a nickname is present. presence :: Nickname -> Session e s [Channel] presence nick = do nt <- gets bsTracker return $ NT.presence nick nt -- | Record a nickname being present in a channel. addMember :: Channel -> Nickname -> Session e s () addMember chan nick = modify $ \ s -> s { bsTracker = f $ bsTracker s } where f = NT.addToChannel chan nick -- | Record a nickname change. Remove old nickname from the channels in which -- it's present, and add the new nickname to them. changeNick :: Nickname -> Nickname -> Session e s () changeNick old new = modify $ \ s -> s { bsTracker = f $ bsTracker s } where f = NT.changeNick old new -- | Record a channel with the given present nicknames. addChannel :: Channel -> [Nickname] -> Session e s () addChannel chan nicks = modify $ \ s -> s { bsTracker = f $ bsTracker s } where f = NT.addChannel chan nicks -- | Record a channel not having a given nickname anymore. removeMemberOnce :: Channel -> Nickname -> Session e s () removeMemberOnce chan nick = modify $ \ s -> s { bsTracker = f $ bsTracker s } where f = NT.removeFromChannel chan nick -- | Record a nickname not being present in any channel anymore. removeMember :: Nickname -> Session e s () removeMember nick = modify $ \ s -> s { bsTracker = f $ bsTracker s } where f = NT.removeFromNetwork nick -- | Remove a channel from the records. removeChannel :: Channel -> Session e s () removeChannel chan = modify $ \ s -> s { bsTracker = f $ bsTracker s } where f = NT.removeChannel chan -- | Remove channels from the records. removeChannels :: [Channel] -> Session e s () removeChannels chans = modify $ \ s -> s { bsTracker = f $ bsTracker s } where f = NT.removeChannels chans