-- |
-- Module:     Network.FastIRC.Users
-- Copyright:  (c) 2010 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez
-- Stability:  experimental
--
-- This module includes parsers for IRC users.

module Network.FastIRC.Users
  ( UserSpec(..),
    showUserSpec,
    userParser )
  where

import qualified Data.ByteString.Char8 as B
import Control.Applicative
import Control.Monad
import Data.Attoparsec.Char8 as P
import Network.FastIRC.ServerSet
import Network.FastIRC.Types
import Network.FastIRC.Utils


-- | IRC user or server.

data UserSpec
  -- | Nickname.
  = Nick NickName
  -- | Nickname, username and hostname.
  | User NickName UserName HostName
  -- | IRC server.
  | Server ServerName
  deriving (Eq, Read, Show)


-- | Turn a 'UserSpec' into a 'B.ByteString' in a format suitable to be
-- sent to the IRC server.

showUserSpec :: UserSpec -> MsgString
showUserSpec (Nick n) = n
showUserSpec (User n u h) = B.concat [ n, B.cons '!' u, B.cons '@' h ]
showUserSpec (Server sh) = sh


-- | A 'Parser' for IRC users and servers.

userParser :: ServerSet -> Parser UserSpec
userParser servers =
  try server <|> try full <|> nickOnly

  where
    server :: Parser UserSpec
    server = do
      srv <- P.takeWhile1 isIRCTokChar
      guard $ srv `isServer` servers
      return (Server srv)

    full :: Parser UserSpec
    full =
      User <$> P.takeWhile1 isNickChar <* char '!'
           <*> P.takeWhile1 isUserChar <* char '@'
           <*> P.takeWhile1 isHostChar

    nickOnly :: Parser UserSpec
    nickOnly = Nick <$> P.takeWhile1 isNickChar