{- This file is part of irc-fun-bot. - - Written in 2015 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 , addChannel , removeMemberOnce , removeMember , removeChannel , removeChannels ) where import Control.Monad (unless) import Control.Monad.Trans.RWS import qualified Data.HashMap.Lazy as M import Data.Maybe (fromMaybe) import Network.IRC.Fun.Bot.Internal.Chat (putIrc) import Network.IRC.Fun.Bot.Internal.State import Network.IRC.Fun.Bot.Internal.Types import qualified Network.IRC.Fun.Client.NickTracker as NT import Network.IRC.Fun.Messages.TypeAliases (ChannelName) import Network.IRC.Fun.Messages.Types (Message (NamesMessage)) enable :: ChannelState -> ChannelState enable cstate = cstate { chanTracking = True } disable :: ChannelState -> ChannelState disable cstate = cstate { chanTracking = False } -- | Check whether a given channel is being tracked. channelIsTracked :: String -> Session e s Bool channelIsTracked chan = do chans <- getChans return $ fromMaybe False $ fmap chanTracking $ 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, ChannelState 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 :: String -> Session e s () startTrackingChannel chan = do chans <- getChans case M.lookup chan chans of Just cstate -> unless (chanTracking cstate) $ do let chansE = M.insert chan (cstate { chanTracking = True }) chans putChans chansE putIrc $ NamesMessage [chan] Nothing Nothing -> return () -- | Start tracking nicks in the channels not tracked, among the ones given. startTrackingChannels :: [String] -> Session e s () startTrackingChannels chans = do chanmapAll <- getChans let given = M.fromList (zip chans (repeat ())) chanmapG = chanmapAll `M.intersection` given chanmapD = M.filter (not . chanTracking) 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 { tracker = NT.newNetwork , chanstate = M.map disable $ chanstate bstate } -- | Stop tracking nicks in the given channel, if tracked. stopTrackingChannel :: String -> Session e s () stopTrackingChannel chan = modify $ \ bstate -> bstate { tracker = NT.removeChannel chan $ tracker bstate , chanstate = M.adjust disable chan $ chanstate bstate } -- | Stop tracking nicks in the tracked channels among the ones given. stopTrackingChannels :: [String] -> Session e s () stopTrackingChannels chans = modify $ \ bstate -> bstate { tracker = NT.removeChannels chans $ tracker bstate , chanstate = let chanmap = chanstate bstate chanmapE = M.filter chanTracking chanmap chanmapD = M.map disable chanmapE in chanmapD `M.union` chanmap } -- | Check whether a nickname is present in a channel. isInChannel :: String -> String -> Session e s Bool nick `isInChannel` chan = do nt <- gets tracker return $ NT.isInChannel nick chan nt -- | Check in which channels a nickname is present. presence :: String -> Session e s [ChannelName] presence nick = do nt <- gets tracker return $ NT.presence nick nt -- | Record a nickname being present in a channel. addMember :: String -> String -> Session e s () addMember chan nick = modify $ \ s -> s { tracker = f $ tracker s } where f = NT.addToChannel chan nick -- | Record a channel with the given present nicknames. addChannel :: String -> [String] -> Session e s () addChannel chan nicks = modify $ \ s -> s { tracker = f $ tracker s } where f = NT.addChannel chan nicks -- | Record a channel not having a given nickname anymore. removeMemberOnce :: String -> String -> Session e s () removeMemberOnce chan nick = modify $ \ s -> s { tracker = f $ tracker s } where f = NT.removeFromChannel chan nick -- | Record a nickname not being present in any channel anymore. removeMember :: String -> Session e s () removeMember nick = modify $ \ s -> s { tracker = f $ tracker s } where f = NT.removeFromNetwork nick -- | Remove a channel from the records. removeChannel :: String -> Session e s () removeChannel chan = modify $ \ s -> s { tracker = f $ tracker s } where f = NT.removeChannel chan -- | Remove channels from the records. removeChannels :: [String] -> Session e s () removeChannels chans = modify $ \ s -> s { tracker = f $ tracker s } where f = NT.removeChannels chans