-- |
-- Module:     Network.FastIRC.Messages
-- Copyright:  (c) 2010 Ertugrul Soeylemez
-- License:    BSD3
-- Maintainer: Ertugrul Soeylemez
-- Stability:  experimental
--
-- Parser for IRC messages.

module Network.FastIRC.Messages
  ( -- * IRC messages
    Message(..),
    messageParser,

    -- * IRC commands
    Command(..),
    commandParser
  )
  where

import qualified Data.ByteString.Char8 as B
import Control.Applicative
import Data.Attoparsec.Char8 as P hiding (many)
import Network.FastIRC.ServerSet
import Network.FastIRC.Users
import Network.FastIRC.Utils


-- | Data type for IRC messages.

data Message =
  Message {
    msgOrigin  :: !(Maybe UserSpec), -- ^ Message origin (user/server).
    msgCommand :: !Command           -- ^ Message command or numeric.
  }
  deriving (Eq, Show)


-- | Data type for IRC commands.

data Command
  -- | Arbitrary string command.
  = StringCmd B.ByteString [B.ByteString]

  -- | Arbitrary numeric command.
  | NumericCmd Integer [B.ByteString]

  deriving (Eq, Show)


-- | Parser for IRC commands and their arguments.

commandParser :: Parser Command
commandParser =
  try numCmd <|> stringCmd

  where
    lastArg :: Parser B.ByteString
    lastArg =
      char ':' *>
      P.takeWhile isMessageChar

    cmdArgs :: Parser [B.ByteString]
    cmdArgs =
      many $ do
        skipMany1 (char ' ')
        try lastArg <|> takeWhile1 isIRCTokChar

    stringCmd :: Parser Command
    stringCmd = StringCmd <$> takeWhile1 isCommandChar <*> cmdArgs

    numCmd :: Parser Command
    numCmd = NumericCmd <$> decimal <*> cmdArgs


-- | Parser for IRC messages.

messageParser :: ServerSet -> Parser Message
messageParser servers =
  Message <$> option Nothing (Just <$> try userSpec)
          <*> commandParser

  where
    userSpec :: Parser UserSpec
    userSpec = char ':' *> userParser servers <* skipMany1 (char ' ')