{- | Module : $Header$ Description : Basic NNTP data types Copyright : (c) Maciej Piechotka License : LGPL 3 or later Maintainer : uzytkownik2@gmail.com Stability : none Portability : portable This module contains the parser helpers -} module Network.NNTP.ParserHelpers ( -- * Parser helpers code, integer, iD, groupName, text, line ) where import Control.Applicative import Control.Monad.Error import Data.ByteString.Lazy.Char8 hiding (replicate) import Network.NNTP.Internal hiding (groupName) import Text.Parsec hiding ((<|>)) -- | Parsers 3-digit response code. In some cases it may throw errors such as -- "ServiceDiscontinued" and "NoSuchCommand". It skip to the end of line -- automatically in sych case. code :: Monad m => NntpParser m Int code = (\p -> case p of 400 -> line *> lift (NntpT (throwError ServiceDiscontinued)) 500 -> line *> lift (NntpT (throwError NoSuchCommand)) _ -> return p) =<< read <$> sequence (replicate 3 digit) -- | Parses an integer. integer :: Monad m => NntpParser m Integer integer = read <$> many1 digit -- | Parses an article ID. iD :: Monad m => NntpParser m String iD = (('<':) . (++">")) <$> (string "<" *> many1 (noneOf ">") <* string ">") -- | Parses an group name. groupName :: Monad m => NntpParser m String groupName = (alphaNum <|> char '.') `manyTill` lookAhead space -- | Gets a multiline output. text :: Monad m => NntpParser m ByteString text = pack <$> (anyChar `manyTill` try (string "\r\n.\r\n")) -- | Gets rest of line. line :: Monad m => NntpParser m ByteString line = pack <$> (anyChar `manyTill` try (string "\r\n"))