-- | -- Module: Data.Enumerator.NetLines -- Copyright: (c) 2010 Ertugrul Soeylemez -- License: BSD3 -- Maintainer: Ertugrul Soeylemez -- Stability: beta -- -- Enumerator tools for working with text-based network protocols. {-# LANGUAGE FlexibleContexts, ScopedTypeVariables #-} module Data.Enumerator.NetLines ( -- * Reexports module Data.Enumerator.NetLines.Error, module Data.Enumerator.NetLines.IO, -- * Iteratees netLine, netLineEmpty, netWord, netWordEmpty, -- * Enumeratees netLines, netLinesEmpty, netWords, netWordsEmpty, -- * General stream splitters netSplitBy, netSplitsBy ) where import Control.ContStuff as Monad import Data.Enumerator as E import Data.Enumerator.NetLines.Class as NL import Data.Enumerator.NetLines.Error import Data.Enumerator.NetLines.IO -- | 'True' for ASCII whitespace. isSpace :: Char -> Bool isSpace n = n == ' ' || (n >= '\t' && n <= '\r') -- | Get the next nonempty line from the stream using 'netLineEmpty'. netLine :: (Monad m, Splittable str) => Int -> Iteratee str m (Maybe str) netLine = nonEmpty . netLineEmpty -- | Get the next line from the stream, length-limited by the given -- 'Int'. This iteratee is error-tolerant by using LF as the line -- terminator and simply ignoring all CR characters. netLineEmpty :: (Monad m, Splittable str) => Int -> Iteratee str m (Maybe str) netLineEmpty = netSplitBy (== '\n') (/= '\r') -- | Convert a raw byte stream to a stream of lines based on 'netLine'. netLines :: (Monad m, Splittable str) => Int -> Enumeratee str str m b netLines = netSplitsBy . netLine -- | Convert a raw byte stream to a stream of lines based on -- 'netLineEmpty'. netLinesEmpty :: (Monad m, Splittable str) => Int -> Enumeratee str str m b netLinesEmpty = netSplitsBy . netLineEmpty -- | Get the next token, where tokens are splitted by the first given -- predicate and filtered by the second. Tokens are length-limited by -- the given 'Int' and are truncated safely in constant space. netSplitBy :: forall m str. (Monad m, Splittable str) => (Char -> Bool) -> (Char -> Bool) -> Int -> Iteratee str m (Maybe str) netSplitBy breakP filterP n = continue (loop NL.empty) where loop :: str -> Stream str -> Iteratee str m (Maybe str) loop line' EOF = yield (if NL.null line' then Nothing else Just line') EOF loop line' (Chunks []) = continue (loop line') loop line' (Chunks (str:strs)) = if NL.null line2' then line `seq` loop line (Chunks strs) else yield (Just line) (Chunks (line2:strs)) where (line1', line2') = NL.break breakP str line1 = NL.filter filterP line1' line2 = NL.tail line2' line = NL.take n $ NL.append line' line1 -- | Split the stream using the supplied iteratee. netSplitsBy :: forall b m str. (Monad m, Splittable str) => Iteratee str m (Maybe str) -> Enumeratee str str m b netSplitsBy getLine = loop where loop :: Enumeratee str str m b loop (Continue k) = do mLine <- getLine case mLine of Just line -> k (Chunks [line]) >>== loop Nothing -> k EOF >>== loop loop step = return step -- | Get the next nonempty word from the stream with the given maximum -- length. Based on 'netWordEmpty'. netWord :: (Monad m, Splittable str) => Int -> Iteratee str m (Maybe str) netWord = nonEmpty . netWordEmpty -- | Get the next word from the stream with the given maximum length. -- This iteratee is error-tolerant by using ASCII whitespace as -- splitting characters. netWordEmpty :: (Monad m, Splittable str) => Int -> Iteratee str m (Maybe str) netWordEmpty = netSplitBy isSpace (const True) -- | Split the raw byte stream into words based on 'netWord'. netWords :: (Monad m, Splittable str) => Int -> Enumeratee str str m b netWords = netSplitsBy . netWord -- | Split the raw byte stream into words based on 'netWords'. netWordsEmpty :: (Monad m, Splittable str) => Int -> Enumeratee str str m b netWordsEmpty = netSplitsBy . netWordEmpty -- | Apply the given iteratee, until it returns a nonempty string. nonEmpty :: forall a m str. (Monad m, Splittable str) => Iteratee a m (Maybe str) -> Iteratee a m (Maybe str) nonEmpty getStr = evalMaybeT loop where loop :: MaybeT r (Iteratee a m) str loop = do line <- liftF getStr if NL.null line then loop else return line