{- This file is part of funbot. - - Written in 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 - . -} {-# LANGUAGE OverloadedStrings #-} module FunBot.Settings.Sections.Locations ( locationOption , addLocation , removeLocation ) where import Control.Monad (unless, void) import Data.Bool (bool) import Data.Maybe (fromMaybe) import Data.Monoid ((<>)) import Data.Sequence (Seq, (|>), (><), ViewL (..)) import Data.Settings.Section import Data.Settings.Types import FunBot.Settings.MkOption import FunBot.Settings.Persist import FunBot.Types import Network.IRC.Fun.Bot.IrcLog import Network.IRC.Fun.Bot.MsgCount import Network.IRC.Fun.Bot.Nicks import Network.IRC.Fun.Bot.State import Network.IRC.Fun.Types.Base (Channel (..), Nickname (..)) import qualified Data.CaseInsensitive as CI import qualified Data.HashMap.Lazy as M import qualified Data.Sequence as Q import qualified Data.Text as T locationOption l@(LocationLabel t) = let defl = "(?)" getl = maybe defl unLocation . M.lookup l . stLocations setl v sets = let locs = stLocations sets locs' = M.insert l (Location v) locs in sets { stLocations = locs' } in (CI.original t, mkOptionF getl setl defl) -- | Add a new location to settings and tree. Return whether success, i.e. -- whether the location didn't exist and indeed a new one has been created. addLocation :: LocationLabel -> Location -> BotSession Bool addLocation label location = do locs <- fmap stLocations getSettings case M.lookup label locs of Just _ -> return False Nothing -> do let locs' = M.insert label location locs modifySettings $ \ s -> s { stLocations = locs' } saveBotSettings let (t, opt) = locationOption label ins = insertOpt ["locations", t] opt modifyState $ \ s -> s { bsSTree = ins $ bsSTree s } return True -- | Remove a location from settings and tree. Return whether success, i.e. -- whether the location did exist and indeed has been deleted. removeLocation :: LocationLabel -> BotSession Bool removeLocation label = do locs <- fmap stLocations getSettings if M.member label locs then do let locs' = M.delete label locs modifySettings $ \ s -> s { stLocations = locs' } saveBotSettings let path = ["locations", CI.original $ unLocationLabel label] del = deleteOpt path modifyState $ \ s -> s { bsSTree = del $ bsSTree s } return True else return False