Snap Framework type aliases and utilities for iteratees. Note that as a
convenience, this module also exports everything from Data.Iteratee
in the
iteratee
library.
WARNING: Note that all of these types are scheduled to change in the
darcs
head version of the iteratee
library; John Lato et al. are working
on a much improved iteratee formulation.
- type Stream = StreamG WrappedByteString Word8
- type IterV m = IterGV WrappedByteString Word8 m
- type Iteratee m = IterateeG WrappedByteString Word8 m
- type Enumerator m a = Iteratee m a -> m (Iteratee m a)
- module Data.Iteratee
- enumBS :: Monad m => ByteString -> Enumerator m a
- enumLBS :: Monad m => ByteString -> Enumerator m a
- enumFile :: FilePath -> Iteratee IO a -> IO (Iteratee IO a)
- enumFilePartial :: FilePath -> (Int64, Int64) -> Iteratee IO a -> IO (Iteratee IO a)
- data InvalidRangeException
- fromWrap :: WrappedByteString Word8 -> ByteString
- toWrap :: ByteString -> WrappedByteString Word8
- drop' :: (StreamChunk s el, Monad m) => Int64 -> IterateeG s el m ()
- takeExactly :: (StreamChunk s el, Monad m) => Int64 -> EnumeratorN s el s el m a
- takeNoMoreThan :: (StreamChunk s el, Monad m) => Int64 -> EnumeratorN s el s el m a
- countBytes :: Monad m => Iteratee m a -> Iteratee m (a, Int64)
- bufferIteratee :: Iteratee IO a -> IO (Iteratee IO a, IORef Bool)
- mkIterateeBuffer :: IO (ForeignPtr CChar)
- unsafeBufferIterateeWithBuffer :: ForeignPtr CChar -> Iteratee IO a -> IO (Iteratee IO a)
- unsafeBufferIteratee :: Iteratee IO a -> IO (Iteratee IO a)
Convenience aliases around types from Data.Iteratee
type IterV m = IterGV WrappedByteString Word8 mSource
type Iteratee m = IterateeG WrappedByteString Word8 mSource
type Enumerator m a = Iteratee m a -> m (Iteratee m a)Source
Re-export types and functions from Data.Iteratee
module Data.Iteratee
Helper functions
Enumerators
enumBS :: Monad m => ByteString -> Enumerator m aSource
Enumerates a strict bytestring.
enumLBS :: Monad m => ByteString -> Enumerator m aSource
Enumerates a lazy bytestring.
Conversion to/from WrappedByteString
fromWrap :: WrappedByteString Word8 -> ByteStringSource
Converts a wrapped bytestring to a lazy bytestring.
toWrap :: ByteString -> WrappedByteString Word8Source
Converts a lazy bytestring to a wrapped bytestring.
Iteratee utilities
drop' :: (StreamChunk s el, Monad m) => Int64 -> IterateeG s el m ()Source
Skip n elements of the stream, if there are that many This is the Int64 version of the drop function in the iteratee library
takeExactly :: (StreamChunk s el, Monad m) => Int64 -> EnumeratorN s el s el m aSource
Reads n elements from a stream and applies the given iteratee to the stream of the read elements. Reads exactly n elements, and if the stream is short propagates an error.
takeNoMoreThan :: (StreamChunk s el, Monad m) => Int64 -> EnumeratorN s el s el m aSource
Reads up to n elements from a stream and applies the given iteratee to the stream of the read elements. If more than n elements are read, propagates an error.
countBytes :: Monad m => Iteratee m a -> Iteratee m (a, Int64)Source
Wraps an Iteratee
, counting the number of bytes consumed by it.
bufferIteratee :: Iteratee IO a -> IO (Iteratee IO a, IORef Bool)Source
Buffers an iteratee.
Our enumerators produce a lot of little strings; rather than spending all our time doing kernel context switches for 4-byte write() calls, we buffer the iteratee to send 8KB at a time.
The IORef returned can be set to True to cancel buffering. We added this so that transfer-encoding: chunked (which needs its own buffer and therefore doesn't need its output buffered) can switch the outer buffer off.
mkIterateeBuffer :: IO (ForeignPtr CChar)Source
Creates a buffer to be passed into unsafeBufferIterateeWithBuffer
.
unsafeBufferIterateeWithBuffer :: ForeignPtr CChar -> Iteratee IO a -> IO (Iteratee IO a)Source
Buffers an iteratee, "unsafely". Here we use a fixed binary buffer which we'll re-use, meaning that if you hold on to any of the bytestring data passed into your iteratee (instead of, let's say, shoving it right out a socket) it'll get changed out from underneath you, breaking referential transparency. Use with caution!
This version accepts a buffer created by mkIterateeBuffer
.
unsafeBufferIteratee :: Iteratee IO a -> IO (Iteratee IO a)Source
Buffers an iteratee, "unsafely". Here we use a fixed binary buffer which we'll re-use, meaning that if you hold on to any of the bytestring data passed into your iteratee (instead of, let's say, shoving it right out a socket) it'll get changed out from underneath you, breaking referential transparency. Use with caution!