This module contains basic iteratees and enumerators for working
with strings, ListLike
objects, file handles, and stream and
datagram sockets.
- putI :: (ChunkData t, Monad m) => (t -> Iter t m a) -> Iter t m b -> Iter t m ()
- sendI :: (Show t, Monad m) => (t -> Iter [t] m a) -> Iter [t] m ()
- headLI :: (Show a, Monad m) => Iter [a] m a
- safeHeadLI :: (Show a, Monad m) => Iter [a] m (Maybe a)
- headI :: (ChunkData t, ListLike t e, Monad m) => Iter t m e
- safeHeadI :: (ChunkData t, ListLike t e, Monad m) => Iter t m (Maybe e)
- lineI :: (Monad m, ChunkData t, ListLike t e, Eq t, Enum e, Eq e) => Iter t m t
- safeLineI :: (ChunkData t, Monad m, ListLike t e, Eq t, Enum e, Eq e) => Iter t m (Maybe t)
- dataMaxI :: (ChunkData t, ListLike t e, Monad m) => Int -> Iter t m t
- data0MaxI :: (ChunkData t, ListLike t e, Monad m) => Int -> Iter t m t
- takeI :: (ChunkData t, ListLike t e, Monad m) => Int -> Iter t m t
- handleI :: (MonadIO m, ChunkData t, ListLikeIO t e) => Handle -> Iter t m ()
- sockDgramI :: (MonadIO m, SendRecvString t) => Socket -> Maybe SockAddr -> Iter [t] m ()
- sockStreamI :: (ChunkData t, SendRecvString t, MonadIO m) => Socket -> Iter t m ()
- stdoutI :: (ListLikeIO t e, ChunkData t, MonadIO m) => Iter t m ()
- data SeekMode
- data SizeC = SizeC
- data SeekC = SeekC !SeekMode !Integer
- data TellC = TellC
- fileCtl :: (ChunkData t, ListLike t e, MonadIO m) => Handle -> CtlHandler (Iter () m) t m a
- data GetSocketC = GetSocketC
- socketCtl :: (ChunkData t, MonadIO m) => Socket -> CtlHandler (Iter () m) t m a
- enumDgram :: (MonadIO m, SendRecvString t) => Socket -> Onum [t] m a
- enumDgramFrom :: (MonadIO m, SendRecvString t) => Socket -> Onum [(t, SockAddr)] m a
- enumStream :: (MonadIO m, ChunkData t, SendRecvString t) => Socket -> Onum t m a
- enumHandle :: (MonadIO m, ChunkData t, ListLikeIO t e) => Handle -> Onum t m a
- enumHandle' :: MonadIO m => Handle -> Onum ByteString m a
- enumNonBinHandle :: (MonadIO m, ChunkData t, ListLikeIO t e) => Handle -> Onum t m a
- enumFile :: (MonadIO m, ChunkData t, ListLikeIO t e) => FilePath -> Onum t m a
- enumFile' :: MonadIO m => FilePath -> Onum ByteString m a
- enumStdin :: (MonadIO m, ChunkData t, ListLikeIO t e) => Onum t m a
- inumMax :: (ChunkData t, ListLike t e, Monad m) => Int -> Inum t t m a
- inumTakeExact :: (ChunkData t, ListLike t e, Monad m) => Int -> Inum t t m a
- inumLog :: (MonadIO m, ChunkData t, ListLikeIO t e) => FilePath -> Bool -> Inum t t m a
- inumhLog :: (MonadIO m, ChunkData t, ListLikeIO t e) => Handle -> Inum t t m a
- inumStderr :: (MonadIO m, ChunkData t, ListLikeIO t e) => Inum t t m a
- inumLtoS :: Monad m => Inum ByteString ByteString m a
- inumStoL :: Monad m => Inum ByteString ByteString m a
- pairFinalizer :: (ChunkData t, ChunkData t1, ChunkData t2, MonadIO m, MonadIO m1) => Iter t m a -> Inum t1 t2 m1 b -> IO () -> IO (Iter t m a, Inum t1 t2 m1 b)
- iterHandle :: (ListLikeIO t e, ChunkData t, MonadIO m) => Handle -> IO (Iter t m (), Onum t m a)
- iterStream :: (SendRecvString t, ChunkData t, MonadIO m) => Socket -> IO (Iter t m (), Onum t m a)
Iteratees
sendI :: (Show t, Monad m) => (t -> Iter [t] m a) -> Iter [t] m ()Source
Send datagrams using a supplied function. The datagrams are fed
as a list of packets, where each element of the list should be a
separate datagram. For example, to create an Iter
from a
connected UDP socket:
udpI :: (SendRecvString
s,MonadIO
m) =>Socket
->Iter
s m () udpI sock = sendI $liftIO
.genSend
sock
headLI :: (Show a, Monad m) => Iter [a] m aSource
Return the first element when the Iteratee data type is a list.
safeHeadI :: (ChunkData t, ListLike t e, Monad m) => Iter t m (Maybe e)Source
Like safeHeadLI
, but works for any ListLike
data type.
lineI :: (Monad m, ChunkData t, ListLike t e, Eq t, Enum e, Eq e) => Iter t m tSource
Return a line delimited by \r, \n, or \r\n.
dataMaxI :: (ChunkData t, ListLike t e, Monad m) => Int -> Iter t m tSource
Return ListLike
data that is at most the number of elements
specified by the first argument, and at least one element (as long
as a positive number is requested). Throws an exception if a
positive number of items is requested and an EOF is encountered.
takeI :: (ChunkData t, ListLike t e, Monad m) => Int -> Iter t m tSource
Return the next len
elements of a ListLike
data stream,
unless an EOF is encountered, in which case fewer may be returned.
Note the difference from data0MaxI
:
will keep
reading input until it has accumulated takeI
nn
elements or seen an EOF,
then return the data;
will keep reading only until
it has received any non-empty amount of data, even if the amount
received is less than data0MaxI
nn
elements and there is no EOF.
handleI :: (MonadIO m, ChunkData t, ListLikeIO t e) => Handle -> Iter t m ()Source
Puts strings (or ListLikeIO
data) to a file Handle
, then
writes an EOF to the handle.
Note that this does not put the handle into binary mode. To do
this, you may need to call
on the
handle before using it with hSetBinaryMode
h True
handleI
. Otherwise, Haskell by
default will treat the data as UTF-8. (On the other hand, if the
Handle
corresponds to a socket and the socket is being read in
another thread, calling hSetBinaryMode
can cause deadlock, so in
this case it is better to have the thread handling reads call
hSetBinaryMode
.)
Also note that Haskell by default buffers data written to
Handle
s. For many network protocols this is a problem. Don't
forget to call
before passing a
handle to hSetBuffering
h NoBuffering
handleI
.
sockDgramI :: (MonadIO m, SendRecvString t) => Socket -> Maybe SockAddr -> Iter [t] m ()Source
Sends a list of packets to a datagram socket.
sockStreamI :: (ChunkData t, SendRecvString t, MonadIO m) => Socket -> Iter t m ()Source
Sends output to a stream socket. Calls shutdown (e.g., to send a TCP FIN packet) upon receiving EOF.
Control requests
data SeekMode
A mode that determines the effect of hSeek
hdl mode i
.
AbsoluteSeek | the position of |
RelativeSeek | the position of |
SeekFromEnd | the position of |
A control command (issued with
) requesting the
size of the current file being enumerated.
ctlI
SizeC
A control command for seeking within a file, when a file is being enumerated. Flushes the residual input data.
A control command for determining the current offset within a file. Note that this subtracts the size of the residual input data from the offset in the file. Thus, it will only be accurate when all left-over input data is from the current file.
fileCtl :: (ChunkData t, ListLike t e, MonadIO m) => Handle -> CtlHandler (Iter () m) t m aSource
A handler function for the SizeC
, SeekC
, and TellC
control
requests. fileCtl
is used internally by enumFile
and
enumHandle
, and is exposed for similar enumerators to use.
data GetSocketC Source
A control request that returns the Socket
from an enclosing
socket enumerator.
socketCtl :: (ChunkData t, MonadIO m) => Socket -> CtlHandler (Iter () m) t m aSource
A handler for the GetSocketC
control request.
Onums
enumDgram :: (MonadIO m, SendRecvString t) => Socket -> Onum [t] m aSource
Read datagrams (of up to 64KiB in size) from a socket and feed a list of strings (one for each datagram) into an Iteratee.
enumDgramFrom :: (MonadIO m, SendRecvString t) => Socket -> Onum [(t, SockAddr)] m aSource
Read datagrams from a socket and feed a list of (Bytestring, SockAddr) pairs (one for each datagram) into an Iteratee.
enumStream :: (MonadIO m, ChunkData t, SendRecvString t) => Socket -> Onum t m aSource
Read data from a stream (e.g., TCP) socket.
enumHandle :: (MonadIO m, ChunkData t, ListLikeIO t e) => Handle -> Onum t m aSource
Puts a handle into binary mode with hSetBinaryMode
, then
enumerates data read from the handle to feed an Iter
with any
ListLikeIO
input type.
enumHandle' :: MonadIO m => Handle -> Onum ByteString m aSource
A variant of enumHandle
type restricted to input in the Lazy
ByteString
format.
enumNonBinHandle :: (MonadIO m, ChunkData t, ListLikeIO t e) => Handle -> Onum t m aSource
Feeds an Iter
with data from a file handle, using any input
type in the ListLikeIO
class. Note that enumNonBinHandle
uses the handle as is, unlike enumHandle
, and so can be used if
you want to read the data in non-binary form.
enumFile :: (MonadIO m, ChunkData t, ListLikeIO t e) => FilePath -> Onum t m aSource
Enumerate the contents of a file for an Iter
taking input in
any ListLikeIO
type. Note that the file is opened with
openBinaryFile
to ensure binary mode.
enumFile' :: MonadIO m => FilePath -> Onum ByteString m aSource
Enumerate the contents of a file as a series of lazy
ByteString
s. (This is a type-restricted version of
enumFile
.)
Inums
inumMax :: (ChunkData t, ListLike t e, Monad m) => Int -> Inum t t m aSource
Feed up to some number of list elements (bytes in the case of
ByteString
s) to an Iter
, or feed fewer if the Iter
returns
or an EOF is encountered. The formulation inumMax n
can be used to prevent .|
iteriter
from consuming unbounded amounts of
input.
inumTakeExact :: (ChunkData t, ListLike t e, Monad m) => Int -> Inum t t m aSource
Feed exactly some number of bytes to an Iter
. Throws an error
if that many bytes are not available.
inumhLog :: (MonadIO m, ChunkData t, ListLikeIO t e) => Handle -> Inum t t m aSource
Like inumLog
, but takes a writeable file handle rather than a
file name. Does not close the handle when done.
inumStderr :: (MonadIO m, ChunkData t, ListLikeIO t e) => Inum t t m aSource
inumLtoS :: Monad m => Inum ByteString ByteString m aSource
An Inum
that converts input in the lazy ByteString
format
to strict ByteString
s.
inumStoL :: Monad m => Inum ByteString ByteString m aSource
The dual of inumLtoS
--converts input from strict
ByteString
s to lazy ByteString
s.
Functions for Iter-Inum pairs
iterHandle :: (ListLikeIO t e, ChunkData t, MonadIO m) => Handle -> IO (Iter t m (), Onum t m a)Source
"Iterizes" a file Handle
by turning into an Onum
(for
reading) and an Iter
(for writing). Uses pairFinalizer
to
hClose
the Handle
when both the Iter
and Onum
are finished.
Puts the handle into binary mode, but does not change the
buffering. As mentioned for handleI
, Haskell's default buffering
can cause problems for many network protocols. Hence, you may wish
to call
before hSetBuffering
h NoBuffering
iterHandle h
.