{- 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.Logger
    ( newLogger
    , newLogger'
    , removeLogger
    , logLine
    )
where

import Control.Monad (liftM)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.RWS (asks)
import Data.Monoid ((<>))
import Network.IRC.Fun.Bot.Internal.Types
import System.Log.FastLogger

-- | Create a logger in the 'IO' monad.
newLogger :: IO String -- ^ Action which returns a formatted time string. You
          -> FilePath  -- ^ Path of the log file
          -> IO Logger
newLogger getTime path = do
    lset <- newFileLoggerSet defaultBufSize path
    return $ Logger
        { loggerSet     = lset
        , loggerGetTime = getTime
        }

-- | Create a logger inside the bot session.
newLogger' :: FilePath -> Session e s Logger
newLogger' path = do
    timeGetter <- asks beGetTime
    liftIO $ newLogger (liftM snd timeGetter) path

-- | Flush buffers and release resources.
--
-- When the logger is paused for a long period of time (i.e. not momentarily -
-- e.g. by a user disabling channel logging via UI), you can use this to
-- release resources. Later, when logging is needed again, create a fresh new
-- logger.
removeLogger :: Logger -> IO ()
removeLogger logger = rmLoggerSet $ loggerSet logger

formatLine :: ToLogStr s => IO String -> s -> IO LogStr
formatLine getTime line = do
    t <- getTime
    return $ toLogStr t <> toLogStr " " <> toLogStr line

-- | Write a log message.
logLine :: ToLogStr s => Logger -> s -> IO ()
logLine logger str = do
    line <- formatLine (loggerGetTime logger) str
    pushLogStrLn (loggerSet logger) line