{- This file is part of irc-fun-bot.
 -
 - Written in 2015 by fr33domlover <fr33domlover@rel4tion.org>.
 -
 - ♡ 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
 - <http://creativecommons.org/publicdomain/zero/1.0/>.
 -}

module Network.IRC.Fun.Bot.Internal.Chat
    ( disconnect
    --, reconnect
    , quit
    , run
    , login
    , pong
    , joinChannel
    , joinMulti
    , joinConfig
    , partChannel
    , partMulti
    , partAll
    , sendIO
    , sendToUser
    , sendToUserNow
    , sendToChannel
    , sendToChannelNow
    , sendBack
    , sendBackNow
    )
where

import Control.AutoUpdate
import Control.Concurrent.Chan
import Control.Exception (bracket)
import Control.Monad (liftM)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.RWS (asks, gets, runRWST)
import Data.Char (isSpace)
import Data.List (union)
import Network.IRC.Fun.Bot.Internal.History (rememberMsg)
import Network.IRC.Fun.Bot.Internal.MsgCount (recordMsg)
import Network.IRC.Fun.Bot.Internal.Persist
import Network.IRC.Fun.Bot.Internal.State
import Network.IRC.Fun.Bot.Internal.Types
import Network.IRC.Fun.Client.ChannelLogger (logEvent, ChanLogEvent (..))
import Network.IRC.Fun.Client.Commands
import Network.IRC.Fun.Client.IO
import Network.IRC.Fun.Client.Time (currentTimeGetter)
import Network.IRC.Fun.Messages.Types (Message)
import System.Clock

import qualified Data.HashMap.Lazy as M (lookup)
import qualified Data.HashSet as S (toList)

-------------------------------------------------------------------------------
-- Connection Management
-------------------------------------------------------------------------------

-- | Disconnect from IRC by closing the bot's side of the connection. This
-- function is mainly provided for completeness and cases of error. You should
-- probably use the QUIT command of IRC to quit the network in a manner
-- coordinated with the server.
--
-- After disconnection, make sure not to send more IRC commands.
disconnect :: Session e s ()
disconnect = askHandle >>= liftIO . ircDisconnect

-- Disconnect from the IRC server and connect again. This includes
-- identifying with the bot's nickname and joining IRC channels.
--
-- This operation closes the bot session. It opens a new one, and returns it.
--botReconnect :: Session s (Session e s ())
--botReconnect = do
--    disconnect

-- | Finish the IRC session, asking the server to close the connection.
quit :: Maybe String -- ^ Optional message, e.g. the reason for quitting
     -> Session e s ()
quit reason = do
    h <- askHandle
    liftIO $ ircQuit h reason

-------------------------------------------------------------------------------
-- Session Management
-------------------------------------------------------------------------------

-- Run a bot session computation
runSession :: BotEnv e s -> BotState s -> Session e s a -> IO a
runSession bot state session = do
    (a, _, _) <- runRWST session bot state
    return a

-- | Connect to an IRC server and run the bot session
run :: Config        -- ^ IRC configuration
    -> Behavior e s  -- ^ Bot behavior definition
    -> e             -- ^ Custom bot environment (read-only state)
    -> s             -- ^ Initial custom bot state
    -> Session e s a -- ^ Session definition
    -> IO a
run conf beh env state session = do
    timeGetter <- currentTimeGetter
    save <- mkSaveBotState conf
    getMin <- mkAutoUpdate defaultUpdateSettings
        { updateFreq   = 1000000 * 60 -- 60 seconds
        , updateAction = liftM ((`div` 60) . sec) $ getTime Realtime
        }
    mq <- newChan
    putStrLn "Bot: Connecting to IRC server"
    bracket
        (ircConnect $ cfgConnection conf)
        ircDisconnect
        (\ h -> do
            let botEnv = BotEnv conf beh h timeGetter getMin save mq env
            putStrLn "Bot: Loading state from file"
            botState <- loadBotState botEnv state
            runSession botEnv botState session
        )

-- | Log in as an IRC user and identify with the bot's nickname and password.
-- This is the first thing to do after 'botConnect'ing to the server.
login :: Session e s ()
login = do
    h <- askHandle
    conn <- askConfigS cfgConnection
    liftIO $ ircLogin h conn False False

-- | IRC servers send PING messages at regular intervals to test the presence
-- of an active client, at least if no other activity is detected on the
-- connection. The server closes the connection automatically if a PONG
-- response isn't sent from the client within a certain amount of time.
--
-- Therefore, an IRC client (both human users and bots) usually listens to
-- these PINGs and sends back PONG messages. This function sends a PONG. The
-- parameters should simply be the ones received in the PING message.
pong :: String       -- ^ Server name
     -> Maybe String -- ^ Optional server to forward to
     -> Session e s ()
pong server1 mserver2 = do
    h <- askHandle
    liftIO $ ircPong h server1 mserver2

-------------------------------------------------------------------------------
-- Channels
-------------------------------------------------------------------------------

-- | Join an IRC channel.
joinChannel :: String       -- ^ Channel name
            -> Maybe String -- ^ Optional channel key (password)
            -> Session e s ()
joinChannel channel key = do
    h <- askHandle
    liftIO $ ircJoin h channel key

-- | Join one or more IRC channels.
joinMulti :: [(String, Maybe String)] -- ^ List of channels and optional keys
          -> Session e s ()
joinMulti channels = do
    h <- askHandle
    liftIO $ ircJoinMulti h channels

-- | Join the IRC channels listed for joining in the persistent state and in
-- the configuration, without leaving any other channels the bot already
-- joined.
joinConfig :: Session e s ()
joinConfig = do
    chansC <- askConfigS cfgChannels
    chansP <- liftM S.toList $ gets bsSelChans
    let chans = union chansC chansP
    joinMulti $ map (flip (,) Nothing) chans
    --TODO avoid unnecessary JOINs?

-- | Leave an IRC channel.
partChannel :: String       -- ^ Channel name
            -> Maybe String -- ^ Optional part message, e.g. the reason for
                            --   leaving
            -> Session e s ()
partChannel channel reason = do
    h <- askHandle
    liftIO $ ircPart h channel reason
    removeCurrChan channel

-- | Leave one or more IRC channels.
partMulti :: [String]     -- ^ List of channel names
          -> Maybe String -- ^ Optional part message, e.g. the reason for
                          --   leaving
          -> Session e s ()
partMulti chans reason = do
    h <- askHandle
    liftIO $ ircPartMulti h chans reason

-- | Leave all IRC channels the bot joined.
partAll :: Session e s ()
partAll = do
    askHandle >>= liftIO . ircPartAll
    clearCurrChans

-------------------------------------------------------------------------------
-- Sending Messages
-------------------------------------------------------------------------------

-- Split a string into N-sized substrings, whose concatenation is the original
-- string. The last substring may be shorter than N.
splitN :: Int -> String -> [String]
splitN n s =
    case splitAt n s of
        (l, "") -> [l]
        (l, r)  -> l : splitN n (dropWhile isSpace r)

-- Split a message by newlines and possibly length.
makeLines :: String -> Session e s [String]
makeLines msg = do
    let ls = lines msg
    maybelen <- askConfigS cfgMaxMsgChars
    case maybelen of
        Nothing     -> return ls
        Just maxlen -> return $ concatMap (splitN maxlen) ls

-- Log a channel message event.
logChanMsg :: String -> String -> String -> Session e s ()
logChanMsg nick chan msg = do
    cstates <- gets bsChannels
    case M.lookup chan cstates >>= csLogger of
        Nothing -> return ()
        Just lg -> liftIO $ logEvent lg (MessageChan nick msg)

sendToChannelIO :: Handle -> String -> [String] -> IO ()
sendToChannelIO h chan = mapM_ $ ircSendToChannel h chan

sendToUserIO :: Handle -> String -> [String] -> IO ()
sendToUserIO h nick = mapM_ $ ircSendToUser h nick

sendIO :: Handle -> IrcMsg -> IO ()
sendIO h msg =
    case msgRecip msg of
        Left nick  -> sendToUserIO h nick $ msgLines msg
        Right chan -> sendToChannelIO h chan $ msgLines msg

sendToChannelHere :: String -> [String] -> Session e s ()
sendToChannelHere chan lines = do
    h <- askHandle
    liftIO $ sendToChannelIO h chan lines

sendToUserHere :: String -> [String] -> Session e s ()
sendToUserHere nick lines = do
    h <- askHandle
    liftIO $ sendToUserIO h nick lines

sendToChannelDefer :: String -> [String] -> Session e s ()
sendToChannelDefer chan lines = do
    q <- asks beMsgQueue
    let msg = IrcMsg
            { msgRecip = Right chan
            , msgLines = lines
            }
    liftIO $ writeChan q msg

sendToUserDefer :: String -> [String] -> Session e s ()
sendToUserDefer nick lines = do
    q <- asks beMsgQueue
    let msg = IrcMsg
            { msgRecip = Left nick
            , msgLines = lines
            }
    liftIO $ writeChan q msg

sendToChannelImpl :: (String -> [String] -> Session e s ())
                  -> String
                  -> String
                  -> Session e s ()
sendToChannelImpl send chan msg = do
    msgs <- makeLines msg
    send chan msgs
    self <- askConfigS $ connNick . cfgConnection
    let remember s = do
            rememberMsg chan self s False
            recordMsg chan
            logChanMsg self chan s
    mapM_ remember msgs

sendToUserImpl :: (String -> [String] -> Session e s ())
               -> String
               -> String
               -> Session e s ()
sendToUserImpl send nick msg = do
    msgs <- makeLines msg
    send nick msgs

-- | Send a message to an IRC channel.
--
-- This usually requires that the bot joins the channel first, because many
-- channels have the +n flag set. This flag forbids sending a messages into
-- a channel from outside it.
--
-- This function doesn't instantly send the message, but instead queues it for
-- sending by the sending scheduler thread, which adds delay to avoid flood. If
-- you want to send instantly, see 'sendToChannelNow'.
sendToChannel
    :: String -- ^ The channel name
    -> String -- ^ The message to send. It may contain newlines, in which case
              -- it will be split into multiple messages and sent sequentially.
    -> Session e s ()
sendToChannel = sendToChannelImpl sendToChannelDefer

-- | A variant of 'sendToChannel' which sends instantly, without any delay.
sendToChannelNow
    :: String -- ^ The channel name
    -> String -- ^ The message to send. It may contain newlines, in which case
              -- it will be split into multiple messages and sent sequentially.
    -> Session e s ()
sendToChannelNow = sendToChannelImpl sendToChannelHere

-- | Send a private message to an IRC user.
--
-- This function doesn't instantly send the message, but instead queues it for
-- sending by the sending scheduler thread, which adds delay to avoid flood. If
-- you want to send instantly, see 'sendToUserNow'.
sendToUser :: String -- ^ The user's nickname
           -> String -- ^ The message to send. It may contain newlines, in
                     --   which case it will be split into multiple messages
                     --   and sent sequentially.
           -> Session e s ()
sendToUser = sendToUserImpl sendToUserDefer

-- | A variant of 'sendToUser' which sends instantly, without any delay.
sendToUserNow :: String -- ^ The user's nickname
              -> String -- ^ The message to send. It may contain newlines, in
                        --   which case it will be split into multiple messages
                        --   and sent sequentially.
              -> Session e s ()
sendToUserNow = sendToUserImpl sendToUserHere

-- | Send a message back to the sender. If a channel is specified, send to the
-- channel. If not, send a private message.
sendBack :: Maybe String -- ^ Channel name, specify if replying to a message
                         --   sent in a channel. Otherwise pass 'Nothing'.
         -> String       -- ^ The sender user's nickname
         -> String       -- ^ The message to send. It may contain newlines, in
                         --   which case it will be split into multiple
                         --   messages and sent sequentially.
         -> Session e s ()
sendBack (Just chan) _nick msg = sendToChannel chan msg
sendBack Nothing     nick  msg = sendToUser nick msg

-- | A variant of 'sendBack' which sends instantly, without any delay.
sendBackNow
    :: Maybe String -- ^ Channel name, specify if replying to a message sent in
                    --   a channel. Otherwise pass 'Nothing'.
    -> String       -- ^ The sender user's nickname
    -> String       -- ^ The message to send. It may contain newlines, in which
                    --   case it will be split into multiple messages and sent
                    --   sequentially.
    -> Session e s ()
sendBackNow (Just chan) _nick msg = sendToChannelNow chan msg
sendBackNow Nothing     nick  msg = sendToUserNow nick msg

-------------------------------------------------------------------------------
-- Other Utilities
-------------------------------------------------------------------------------

-- See the ChatExt module.