| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
System.IO.Streams.ByteString
Description
Stream operations on ByteString.
Synopsis
- countInput :: InputStream ByteString -> IO (InputStream ByteString, IO Int64)
- countOutput :: OutputStream ByteString -> IO (OutputStream ByteString, IO Int64)
- fromByteString :: ByteString -> IO (InputStream ByteString)
- fromLazyByteString :: ByteString -> IO (InputStream ByteString)
- readExactly :: Int -> InputStream ByteString -> IO ByteString
- takeBytesWhile :: (Char -> Bool) -> InputStream ByteString -> IO (Maybe ByteString)
- writeLazyByteString :: ByteString -> OutputStream ByteString -> IO ()
- splitOn :: (Char -> Bool) -> InputStream ByteString -> IO (InputStream ByteString)
- lines :: InputStream ByteString -> IO (InputStream ByteString)
- unlines :: OutputStream ByteString -> IO (OutputStream ByteString)
- words :: InputStream ByteString -> IO (InputStream ByteString)
- unwords :: OutputStream ByteString -> IO (OutputStream ByteString)
- giveBytes :: Int64 -> OutputStream ByteString -> IO (OutputStream ByteString)
- giveExactly :: Int64 -> OutputStream ByteString -> IO (OutputStream ByteString)
- takeBytes :: Int64 -> InputStream ByteString -> IO (InputStream ByteString)
- takeExactly :: Int64 -> InputStream ByteString -> IO (InputStream ByteString)
- throwIfConsumesMoreThan :: Int64 -> OutputStream ByteString -> IO (OutputStream ByteString)
- throwIfProducesMoreThan :: Int64 -> InputStream ByteString -> IO (InputStream ByteString)
- throwIfTooSlow :: IO () -> Double -> Int -> InputStream ByteString -> IO (InputStream ByteString)
- data MatchInfo- = Match !ByteString
- | NoMatch !ByteString
 
- search :: ByteString -> InputStream ByteString -> IO (InputStream MatchInfo)
- data RateTooSlowException
- data ReadTooShortException
- data TooManyBytesReadException
- data TooManyBytesWrittenException
- data TooFewBytesWrittenException
Counting bytes
countInput :: InputStream ByteString -> IO (InputStream ByteString, IO Int64) Source #
Wraps an InputStream, counting the number of bytes produced by the
 stream as a side effect. Produces a new InputStream as well as an IO
 action to retrieve the count of bytes produced.
Strings pushed back to the returned InputStream will be pushed back to the
 original stream, and the count of produced bytes will be subtracted
 accordingly.
Example:
ghci> is <- Streams.fromList["abc", "def", "ghi"::ByteString] ghci> (is', getCount) <- Streams.countInputis ghci> Streams.readis' Just "abc" ghci> getCount 3 ghci> Streams.unRead"bc" is' ghci> getCount 1 ghci> Streams.peekis Just "bc" ghci> Streams.toListis' ["bc","def","ghi"] ghci> getCount 9
countOutput :: OutputStream ByteString -> IO (OutputStream ByteString, IO Int64) Source #
Wraps an OutputStream, counting the number of bytes consumed by the
 stream as a side effect. Produces a new OutputStream as well as an IO
 action to retrieve the count of bytes consumed.
Example:
ghci> (os :: OutputStream ByteString, getList) <- Streams.listOutputStreamghci> (os', getCount) <- Streams.countOutputos ghci> Streams.fromList["abc", "def", "ghi"] >>= Streams.connectToos' ghci> getList ["abc","def","ghi"] ghci> getCount 9
Treating strings as streams
fromByteString :: ByteString -> IO (InputStream ByteString) Source #
Creates an InputStream from a ByteString.
fromLazyByteString :: ByteString -> IO (InputStream ByteString) Source #
Creates an InputStream from a lazy ByteString.
Input and output
Arguments
| :: Int | number of bytes to read | 
| -> InputStream ByteString | input stream | 
| -> IO ByteString | 
Reads an n-byte ByteString from an input stream. Throws a
 ReadTooShortException if fewer than n bytes were available.
Example:
ghci> Streams.fromList["long string"] >>= Streams.readExactly6 "long s" ghci> Streams.fromList["short"] >>= Streams.readExactly6 *** Exception: Short read, expected 6 bytes
Arguments
| :: (Char -> Bool) | predicate | 
| -> InputStream ByteString | input stream | 
| -> IO (Maybe ByteString) | 
Takes from a stream until the given predicate is no longer satisfied.
 Returns Nothing on end-of-stream, or Just "" if the predicate is never
 satisfied. See takeWhile and takeWhile.
Example:
ghci> Streams.fromList["Hello, world!"] >>= Streams.takeBytesWhile(/= ',') Just "Hello" ghci> import Data.Char ghci> Streams.fromList["7 Samurai"] >>= Streams.takeBytesWhileisAlpha Just "" ghci> Streams.fromList[] >>= Streams.takeBytesWhileisAlpha Nothing
Arguments
| :: ByteString | string to write to output | 
| -> OutputStream ByteString | output stream | 
| -> IO () | 
Writes a lazy ByteString to an OutputStream.
Example:
ghci> Streams.writeLazyByteString"Test\n" Streams.stdoutTest
Stream transformers
Splitting/Joining
Arguments
| :: (Char -> Bool) | predicate used to break the input stream into chunks | 
| -> InputStream ByteString | input stream | 
| -> IO (InputStream ByteString) | 
Splits an InputStream over ByteStrings using a delimiter predicate.
Note that:
- data pushed back with unReadis *not* propagated upstream here.
- the resulting InputStreammay hold an unbounded amount of the bytestring in memory waiting for the function to return true, so this function should not be used in unsafe contexts.
- the delimiter is NOT included in the output.
- consecutive delimiters are not merged.
- if the input ends in the delimiter, a final empty string is not
     emitted. (/Since: 1.5.0.0. Previous versions had the opposite behaviour,
     which was changed to match lines./)
Example:
ghci> Streams.fromList["the quick br", "own fox"::ByteString] >>= Streams.splitOn(== ' ') >>= Streams.toList["the","quick","brown","","fox"]
lines :: InputStream ByteString -> IO (InputStream ByteString) Source #
Splits a bytestring InputStream into lines. See splitOn and
 lines.
Example:
ghci> is <- Streams.fromList["Hello,\n world!"] >>= Streams.linesghci> replicateM 3 (Streams.readis) [Just "Hello", Just ", world!", Nothing]
Note that this may increase the chunk size if the input contains extremely long lines.
unlines :: OutputStream ByteString -> IO (OutputStream ByteString) Source #
Intersperses string chunks sent to the given OutputStream with newlines.
 See intersperse and unlines.
ghci> os <- Streams.unlinesStreams.stdoutghci> Streams.write(Just "Hello,") os Hello ghci> Streams.writeNothing os ghci> Streams.write(Just "world!") os world!
words :: InputStream ByteString -> IO (InputStream ByteString) Source #
Splits a bytestring InputStream into words. See splitOn and
 words.
Example:
ghci> is <- Streams.fromList["Hello, world!"] >>= Streams.wordsghci> replicateM 3 (Streams.readis) [Just "Hello,", Just "world!", Nothing]
Note that this may increase the chunk size if the input contains extremely long words.
unwords :: OutputStream ByteString -> IO (OutputStream ByteString) Source #
Intersperses string chunks sent to the given OutputStream with spaces.
 See intersperse and unwords.
ghci> os <- Streams.unwordsStreams.stdoutghci> forM_ [Just "Hello,", Nothing, Just "world!\n"] $ w -> Streams.writew os Hello, world!
Other
Arguments
| :: Int64 | maximum number of bytes to send to the wrapped stream | 
| -> OutputStream ByteString | output stream to wrap | 
| -> IO (OutputStream ByteString) | 
Wraps an OutputStream, producing a new stream that will pass along at
 most n bytes to the wrapped stream, throwing any subsequent input away.
Example:
ghci> (os :: OutputStream ByteString, getList) <- Streams.listOutputStreamghci> os' <- Streams.giveBytes6 os ghci> Streams.fromList["long ", "string"] >>= Streams.connectToos' ghci> getList ["long ","s"]
giveExactly :: Int64 -> OutputStream ByteString -> IO (OutputStream ByteString) Source #
Wraps an OutputStream, producing a new stream that will pass along
 exactly n bytes to the wrapped stream. If the stream is sent more or fewer
 than the given number of bytes, the resulting stream will throw an exception
 (either TooFewBytesWrittenException or TooManyBytesWrittenException)
 during a call to write.
Example:
ghci> is <- Streams.fromList["ok"] ghci> Streams.outputToList(Streams.giveExactly2 >=> Streams.connectis) ["ok"] ghci> is <- Streams.fromList["ok"] ghci> Streams.outputToList(Streams.giveExactly1 >=> Streams.connectis) *** Exception: Too many bytes written ghci> is <- Streams.fromList["ok"] ghci> Streams.outputToList(Streams.giveExactly3 >=> Streams.connectis) *** Exception: Too few bytes written
Arguments
| :: Int64 | maximum number of bytes to read | 
| -> InputStream ByteString | input stream to wrap | 
| -> IO (InputStream ByteString) | 
Wraps an InputStream, producing a new InputStream that will produce at
 most n bytes, subsequently yielding end-of-stream forever.
Strings pushed back to the returned InputStream will be propagated
 upstream, modifying the count of taken bytes accordingly.
Example:
ghci> is <- Streams.fromList["truncated", " string"::ByteString] ghci> is' <- Streams.takeBytes9 is ghci> Streams.readis' Just "truncated" ghci> Streams.readis' Nothing ghci> Streams.peekis Just " string" ghci> Streams.unRead"cated" is' ghci> Streams.peekis Just "cated" ghci> Streams.peekis' Just "cated" ghci> Streams.readis' Just "cated" ghci> Streams.readis' Nothing ghci> Streams.readis Just " string"
Arguments
| :: Int64 | number of bytes to read | 
| -> InputStream ByteString | input stream to wrap | 
| -> IO (InputStream ByteString) | 
Like Streams., but throws takeBytesReadTooShortException when
 there aren't enough bytes present on the source.
throwIfConsumesMoreThan Source #
Arguments
| :: Int64 | maximum number of bytes to send to the wrapped stream | 
| -> OutputStream ByteString | output stream to wrap | 
| -> IO (OutputStream ByteString) | 
Wraps an OutputStream, producing a new stream that will pass along at
 most n bytes to the wrapped stream. If more than n bytes are sent to the
 outer stream, a TooManyBytesWrittenException will be thrown.
Note: if more than n bytes are sent to the outer stream,
 throwIfConsumesMoreThan will not necessarily send the first n bytes
 through to the wrapped stream before throwing the exception.
Example:
ghci> (os :: OutputStream ByteString, getList) <- Streams.listOutputStreamghci> os' <- Streams.throwIfConsumesMoreThan5 os ghci> Streams.fromList["short"] >>= Streams.connectToos' ghci> getList ["short"] ghci> os'' <- Streams.throwIfConsumesMoreThan5 os ghci> Streams.fromList["long", "string"] >>= Streams.connectToos'' *** Exception: Too many bytes written
throwIfProducesMoreThan Source #
Arguments
| :: Int64 | maximum number of bytes to read | 
| -> InputStream ByteString | input stream | 
| -> IO (InputStream ByteString) | 
Wraps an InputStream. If more than n bytes are produced by this
 stream, read will throw a TooManyBytesReadException.
If a chunk yielded by the input stream would result in more than n bytes
 being produced, throwIfProducesMoreThan will cut the generated string such
 that exactly n bytes are yielded by the returned stream, and the
 subsequent read will throw an exception. Example:
ghci> is <- Streams.fromList["abc", "def", "ghi"] >>= Streams.throwIfProducesMoreThan5 ghci>replicateM2 (readis) [Just "abc",Just "de"] ghci> Streams.readis *** Exception: Too many bytes read
Strings pushed back to the returned InputStream will be propagated
 upstream, modifying the count of taken bytes accordingly. Example:
ghci> is <- Streams.fromList["abc", "def", "ghi"] ghci> is' <- Streams.throwIfProducesMoreThan5 is ghci> Streams.readis' Just "abc" ghci> Streams.unRead"xyz" is' ghci> Streams.peekis Just "xyz" ghci> Streams.readis Just "xyz" ghci> Streams.readis Just "de" ghci> Streams.readis *** Exception: Too many bytes read
Rate limiting
Arguments
| :: IO () | action to bump timeout | 
| -> Double | minimum data rate, in bytes per second | 
| -> Int | amount of time in seconds to wait before data rate calculation takes effect | 
| -> InputStream ByteString | input stream | 
| -> IO (InputStream ByteString) | 
Rate-limits an input stream. If the input stream is not read from faster
 than the given rate, reading from the wrapped stream will throw a
 RateTooSlowException.
Strings pushed back to the returned InputStream will be propagated up to
 the original stream.
String search
MatchInfo provides match information when performing string search.
Constructors
| Match !ByteString | |
| NoMatch !ByteString | 
Arguments
| :: ByteString | "needle" to look for | 
| -> InputStream ByteString | input stream to wrap | 
| -> IO (InputStream MatchInfo) | 
Given a ByteString to look for (the "needle") and an InputStream,
 produces a new InputStream which yields data of type MatchInfo.
Example:
ghci>fromList["food", "oof", "oodles", "ok"] >>=search"foo" >>=toList[Match"foo",NoMatch"d",NoMatch"oo",Match"foo",NoMatch"dlesok"]
Uses the Boyer-Moore-Horspool algorithm (http://en.wikipedia.org/wiki/Boyer%E2%80%93Moore%E2%80%93Horspool_algorithm).
Exception types
data RateTooSlowException Source #
Thrown by throwIfTooSlow if input is not being produced fast enough by
 the given InputStream.
Instances
| Show RateTooSlowException Source # | |
| Defined in System.IO.Streams.ByteString Methods showsPrec :: Int -> RateTooSlowException -> ShowS # show :: RateTooSlowException -> String # showList :: [RateTooSlowException] -> ShowS # | |
| Exception RateTooSlowException Source # | |
| Defined in System.IO.Streams.ByteString Methods toException :: RateTooSlowException -> SomeException # fromException :: SomeException -> Maybe RateTooSlowException # | |
data ReadTooShortException Source #
Thrown by readExactly and takeExactly when not enough bytes were
 available on the input.
Instances
| Show ReadTooShortException Source # | |
| Defined in System.IO.Streams.ByteString Methods showsPrec :: Int -> ReadTooShortException -> ShowS # show :: ReadTooShortException -> String # showList :: [ReadTooShortException] -> ShowS # | |
| Exception ReadTooShortException Source # | |
| Defined in System.IO.Streams.ByteString | |
data TooManyBytesReadException Source #
Thrown by throwIfProducesMoreThan when too many bytes were read from the
 original InputStream.
Instances
| Show TooManyBytesReadException Source # | |
| Defined in System.IO.Streams.ByteString Methods showsPrec :: Int -> TooManyBytesReadException -> ShowS # show :: TooManyBytesReadException -> String # showList :: [TooManyBytesReadException] -> ShowS # | |
| Exception TooManyBytesReadException Source # | |
| Defined in System.IO.Streams.ByteString | |
data TooManyBytesWrittenException Source #
Thrown by throwIfConsumesMoreThan when too many bytes were sent to the
 produced OutputStream.
Instances
| Show TooManyBytesWrittenException Source # | |
| Defined in System.IO.Streams.ByteString Methods showsPrec :: Int -> TooManyBytesWrittenException -> ShowS # show :: TooManyBytesWrittenException -> String # showList :: [TooManyBytesWrittenException] -> ShowS # | |
| Exception TooManyBytesWrittenException Source # | |
data TooFewBytesWrittenException Source #
Thrown by giveExactly when too few bytes were written to the produced
 OutputStream.
Instances
| Show TooFewBytesWrittenException Source # | |
| Defined in System.IO.Streams.ByteString Methods showsPrec :: Int -> TooFewBytesWrittenException -> ShowS # show :: TooFewBytesWrittenException -> String # showList :: [TooFewBytesWrittenException] -> ShowS # | |
| Exception TooFewBytesWrittenException Source # | |