module Lambdabot.Nick
    ( Nick(..)
    , fmtNick
    , parseNick
    ) where

import Lambdabot.Util

import Data.Char

-- | The type of nicknames isolated from a message.
data Nick = Nick 
    { Nick -> String
nTag  :: !String -- ^ The tag of the server this nick is on
    , Nick -> String
nName :: !String -- ^ The server-specific nickname of this nick
    }

-- This definition of canonicalizeName breaks strict RFC rules, but so does
-- freenode
-- TODO: server-specific rules should have server-specific implementations
canonicalizeName :: String -> String
canonicalizeName :: String -> String
canonicalizeName = forall a. (a -> Bool) -> [a] -> [a]
strip Char -> Bool
isSpace forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper

instance Eq Nick where
  (Nick String
tag String
name) == :: Nick -> Nick -> Bool
== (Nick String
tag2 String
name2) =
     (String -> String
canonicalizeName String
name forall a. Eq a => a -> a -> Bool
== String -> String
canonicalizeName String
name2) Bool -> Bool -> Bool
&& (String
tag forall a. Eq a => a -> a -> Bool
== String
tag2)

instance Ord Nick where
  (Nick String
tag String
name) <= :: Nick -> Nick -> Bool
<= (Nick String
tag2 String
name2) =
     (String
tag, String -> String
canonicalizeName String
name) forall a. Ord a => a -> a -> Bool
<= (String
tag2, String -> String
canonicalizeName String
name2)

-- | Format a nickname for display.  This will automatically omit the server
-- field if it is the same as the server of the provided message.
fmtNick :: String -> Nick -> String
fmtNick :: String -> Nick -> String
fmtNick String
svr Nick
nck
    | Nick -> String
nTag Nick
nck forall a. Eq a => a -> a -> Bool
== String
svr = Nick -> String
nName Nick
nck
    | Bool
otherwise       = Nick -> String
nTag Nick
nck forall a. [a] -> [a] -> [a]
++ Char
':' forall a. a -> [a] -> [a]
: Nick -> String
nName Nick
nck

-- | Parse a nickname received in a message.  If the server field is not
-- provided, it defaults to the same as that of the message.
parseNick :: String -> String -> Nick
parseNick :: String -> String -> Nick
parseNick String
def String
str
    | forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
ac   = String -> String -> Nick
Nick String
def String
str
    | Bool
otherwise = String -> String -> Nick
Nick String
bc String
ac
    where 
        (String
bc, String
ac') = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
==Char
':') String
str
        ac :: String
ac = forall a. Int -> [a] -> [a]
drop Int
1 String
ac'