{- 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.Failure
    ( defaultRespondToChan
    , defaultRespondToUser
    , failToChannel
    , failToUser
    , failBack
    )
where

import Data.Char (toLower)
import Data.List (intercalate)
import Network.IRC.Fun.Bot.Internal.Chat (sendToChannel, sendToUser)
import Network.IRC.Fun.Bot.Internal.State (askBehaviorS)
import Network.IRC.Fun.Bot.Internal.Types
import Text.Printf (printf)

-- Get the default response string in case the command isn't found in the sets.
-- This assumes the same response is set both to channels and to users in
-- private conversations, which could change in the future. Right now only
-- channel commands are supported by the bot anyway.
defaultResponse :: Maybe Char             -- Command prefix that was triggered
                -> String                 -- Command name that was triggered
                -> [CommandSet e s]       -- Available command sets
                -> Maybe (CommandSet e s) -- The command set matching the
                                          -- prefix, if one was found
                -> String
defaultResponse Nothing _cname _csets _ =
    "Expected to find a default command prefix, but there’s none."
defaultResponse (Just cpref) _cname csets Nothing =
    printf "Expected to find a command with prefix ‘%v’, but there’s none. \
           \Available prefixes are: ‘%v’."
           cpref $
           intercalate "’, ‘" $ map ((: []) . csetPrefix) csets
defaultResponse (Just cpref) cname _csets (Just cset) =
    printf "The command ‘%v%v’ isn’t available. Available commands for prefix \
           \‘%v’ are: ‘%v’."
           cpref
           cname
           cpref $
           intercalate "’, ‘" $ map (head . cmdNames) $ csetCommands cset

-- | Send the default response to an IRC channel
defaultRespondToChan
    :: String                 -- Target channel
    -> Maybe Char             -- Command prefix that was triggered
    -> String                 -- Command name that was triggered
    -> Maybe (CommandSet e s) -- The command set matching the prefix, if one
                              -- was found
    -> Session e s ()
defaultRespondToChan chan cpref cname cset = do
    csets <- askBehaviorS commandSets
    sendToChannel chan $ defaultResponse cpref cname csets cset

-- | Send the default response to an IRC user
defaultRespondToUser
    :: String                 -- Recipient nickname
    -> Maybe Char             -- Command prefix that was triggered
    -> String                 -- Command name that was triggered
    -> Maybe (CommandSet e s) -- The command set matching the prefix, is one
                              -- was found
    -> Session e s ()
defaultRespondToUser nick cpref cname cset = do
    csets <- askBehaviorS commandSets
    sendToUser nick $ defaultResponse cpref cname csets cset

-- Determine number suffix when counting things
suffix :: Integral a => a -> String
suffix 1 = "st"
suffix 2 = "nd"
suffix 3 = "rd"
suffix _ = "th"

-- Response message to send on failure
failureDescription :: Failure -> String
failureDescription failure =
    case failure of
        WrongNumArgs                               ->
            "Wrong number of arguments"
        WrongNumArgsN Nothing Nothing              ->
            failureDescription WrongNumArgs
        WrongNumArgsN (Just given) Nothing         ->
            printf "Wrong number of arguments: %v given" given
        WrongNumArgsN Nothing (Just expected)      ->
            printf "Wrong number of arguments: %v expected" expected
        WrongNumArgsN (Just given) (Just expected) ->
            printf "Wrong number of arguments: %v given, %v expected"
                   given
                   expected
        InvalidArgs                                -> "Invalid arguments"
        InvalidArg Nothing Nothing                 -> "Invalid argument found"
        InvalidArg (Just pos) Nothing              ->
            printf "The %v%v argument is invalid" pos (suffix pos)
        InvalidArg Nothing (Just param)            ->
            printf "Invalid argument: ‘%v’" param
        InvalidArg (Just pos) (Just param)         ->
            printf "The %v%v argument is invalid: ‘%v’" pos (suffix pos) param
        OtherFail s                                -> "Command failed: " ++ s

-- | Send message explaining a failure to an IRC channel.
failToChannel :: String  -- ^ Target channel
              -> String  -- ^ User to whom to refer
              -> Failure -- ^ Problem indication
              -> Session e s ()
failToChannel chan nick failure =
    let lowerc []     = []
        lowerc (c:cs) = toLower c : cs
    in  sendToChannel chan $
        nick ++ ", " ++ lowerc (failureDescription failure)

-- | Send message explaining a failure to an IRC user.
failToUser :: String  -- ^ Target user
           -> Failure -- ^ Problem indication
           -> Session e s ()
failToUser nick failure =
    sendToUser nick $ failureDescription failure

-- | Send message explaining a failure back to the sender.
failBack :: Maybe String -- ^ Optional target channel, 'Nothing' means private
                         --   message
         -> String       -- ^ Target user nickname
         -> Failure      -- ^ Problem indication
         -> Session e s ()
failBack (Just chan) nick failure = failToChannel chan nick failure
failBack Nothing     nick failure = failToUser nick failure