Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module is a top-level convenience module which re-exports most of the
io-streams
library.
It is recommended to import this module qualified, as follows:
import System.IO.Streams (Generator
,InputStream
,OutputStream
) import qualified System.IO.Streams as Streams
For an in-depth tutorial on how to use io-streams
, please see the
System.IO.Streams.Tutorial module.
Is there a function missing from this library? Interested in contributing? Send a pull request to http://github.com/snapframework/io-streams.
Synopsis
- data InputStream a
- data OutputStream a
- makeInputStream :: IO (Maybe a) -> IO (InputStream a)
- makeOutputStream :: (Maybe a -> IO ()) -> IO (OutputStream a)
- read :: InputStream a -> IO (Maybe a)
- unRead :: a -> InputStream a -> IO ()
- peek :: InputStream a -> IO (Maybe a)
- write :: Maybe a -> OutputStream a -> IO ()
- writeTo :: OutputStream a -> Maybe a -> IO ()
- atEOF :: InputStream a -> IO Bool
- connect :: InputStream a -> OutputStream a -> IO ()
- connectTo :: OutputStream a -> InputStream a -> IO ()
- supply :: InputStream a -> OutputStream a -> IO ()
- supplyTo :: OutputStream a -> InputStream a -> IO ()
- appendInputStream :: InputStream a -> InputStream a -> IO (InputStream a)
- concatInputStreams :: [InputStream a] -> IO (InputStream a)
- lockingInputStream :: InputStream a -> IO (InputStream a)
- lockingOutputStream :: OutputStream a -> IO (OutputStream a)
- nullInput :: IO (InputStream a)
- nullOutput :: IO (OutputStream a)
- data Generator r a
- fromGenerator :: Generator r a -> IO (InputStream r)
- yield :: r -> Generator r ()
- module System.IO.Streams.Builder
- module System.IO.Streams.ByteString
- module System.IO.Streams.Combinators
- module System.IO.Streams.Handle
- module System.IO.Streams.File
- module System.IO.Streams.List
- module System.IO.Streams.Network
- module System.IO.Streams.Process
- module System.IO.Streams.Text
- module System.IO.Streams.Vector
- module System.IO.Streams.Zlib
Stream types
data InputStream a Source #
An InputStream
generates values of type c
in the IO
monad.
Two primitive operations are defined on InputStream
:
reads a value from the stream, where "end of stream" is signaled byread
::InputStream
c ->IO
(Maybe
c)read
returningNothing
.
"pushes back" a value to the stream.unRead
:: c ->InputStream
c ->IO
()
It is intended that InputStream
s obey the following law:
unRead
c stream >>read
stream ===return
(Just
c)
Instances
data OutputStream a Source #
An OutputStream
consumes values of type c
in the IO
monad.
The only primitive operation defined on OutputStream
is:
write
::Maybe
c ->OutputStream
c ->IO
()
Values of type c
are written in an OutputStream
by wrapping them in
Just
, and the end of the stream is indicated by supplying Nothing
.
If you supply a value after a Nothing
, the behavior is defined by the
implementer of the given OutputStream
. (All OutputStream
definitions in
this library will simply discard the extra input.)
Instances
A note about resource acquisition/release semantics
In general, the convention within this library is that input and output
streams do not deal with resource acquisition/release semantics, with rare
exceptions like withFileAsInput
. For example, sending
"end-of-stream" to an OutputStream
wrapped around a Handle
doesn't cause the handle to be closed. You can think of streams as little
state machines that are attached to the underlying resources, and the
finalization/release of these resources is up to you.
This means that you can use standard Haskell idioms like
bracket
to handle resource acquisition and cleanup in an
exception-safe way.
Creating streams
makeInputStream :: IO (Maybe a) -> IO (InputStream a) Source #
Creates an InputStream
from a value-producing action.
(makeInputStream m
) calls the action m
each time you request a value
from the InputStream
. The given action is extended with the default
pushback mechanism (see System.IO.Streams.Internal).
makeOutputStream :: (Maybe a -> IO ()) -> IO (OutputStream a) Source #
Creates an OutputStream
from a value-consuming action.
(makeOutputStream f
) runs the computation f
on each value fed to it.
Since version 1.2.0.0, makeOutputStream
also ensures that output streams
no longer receive data once EOF is received (i.e. you can now assume that
makeOutputStream will feed your function Nothing
at most once.)
Primitive stream operations
read :: InputStream a -> IO (Maybe a) Source #
Reads one value from an InputStream
.
Returns either a value wrapped in a Just
, or Nothing
if the end of the
stream is reached.
unRead :: a -> InputStream a -> IO () Source #
Pushes a value back onto an input stream. read
and unRead
should
satisfy the following law, with the possible exception of side effects:
Streams.unRead
c stream >> Streams.read
stream ===return
(Just
c)
Note that this could be used to add values back to the stream that were not originally drawn from the stream.
peek :: InputStream a -> IO (Maybe a) Source #
Observes the first value from an InputStream
without consuming it.
Returns Nothing
if the InputStream
is empty. peek
satisfies the
following law:
Streams.peek
stream >> Streams.read
stream === Streams.read
stream
write :: Maybe a -> OutputStream a -> IO () Source #
Feeds a value to an OutputStream
. Values of type c
are written in an
OutputStream
by wrapping them in Just
, and the end of the stream is
indicated by supplying Nothing
.
atEOF :: InputStream a -> IO Bool Source #
Checks if an InputStream
is at end-of-stream.
Connecting streams together
connect :: InputStream a -> OutputStream a -> IO () Source #
Connects an InputStream
and OutputStream
, supplying values from the
InputStream
to the OutputStream
, and propagating the end-of-stream
message from the InputStream
through to the OutputStream
.
The connection ends when the InputStream
yields a Nothing
.
connectTo :: OutputStream a -> InputStream a -> IO () Source #
supply :: InputStream a -> OutputStream a -> IO () Source #
Connects an InputStream
to an OutputStream
without passing the
end-of-stream notification through to the OutputStream
.
Use this to supply an OutputStream
with multiple InputStream
s and use
connect
for the final InputStream
to finalize the OutputStream
, like
so:
do Streams.supply
input1 output Streams.supply
input2 output Streams.connect
input3 output
supplyTo :: OutputStream a -> InputStream a -> IO () Source #
supply
with the arguments flipped.
appendInputStream :: InputStream a -> InputStream a -> IO (InputStream a) Source #
appendInputStream
concatenates two InputStream
s, analogous to (++
)
for lists.
The second InputStream
continues where the first InputStream
ends.
Note: values pushed back to appendInputStream
are not propagated to either
wrapped InputStream
.
concatInputStreams :: [InputStream a] -> IO (InputStream a) Source #
concatInputStreams
concatenates a list of InputStream
s, analogous to
(++
) for lists.
Subsequent InputStream
s continue where the previous one InputStream
ends.
Note: values pushed back to the InputStream
returned by
concatInputStreams
are not propagated to any of the source
InputStream
s.
Thread safety / concurrency
lockingInputStream :: InputStream a -> IO (InputStream a) Source #
Converts an InputStream
into a thread-safe InputStream
, at a slight
performance penalty.
For performance reasons, this library provides non-thread-safe streams by
default. Use the locking
functions to convert these streams into slightly
slower, but thread-safe, equivalents.
lockingOutputStream :: OutputStream a -> IO (OutputStream a) Source #
Converts an OutputStream
into a thread-safe OutputStream
, at a slight
performance penalty.
For performance reasons, this library provides non-thread-safe streams by
default. Use the locking
functions to convert these streams into slightly
slower, but thread-safe, equivalents.
Utility streams
nullInput :: IO (InputStream a) Source #
An empty InputStream
that yields Nothing
immediately.
nullOutput :: IO (OutputStream a) Source #
An empty OutputStream
that discards any input fed to it.
Generator monad
The Generator
monad makes it easier for you to define more complicated
InputStream
s. Generators have a couple of basic features:
Generator
is a MonadIO
, so you can run IO actions from within it using
liftIO
:
foo ::Generator
r a foo =liftIO
fireTheMissiles
Generator
has a yield
function:
yield
:: r ->Generator
r ()
A call to "yield
x
" causes "Just
x
" to appear when reading the
InputStream
. Finally, Generator
comes with a function to turn a
Generator
into an InputStream
:
fromGenerator
::Generator
r a ->IO
(InputStream
r)
Once the Generator
action finishes, fromGenerator
will cause an
end-of-stream Nothing
marker to appear at the output. Example:
ghci> (Streams.fromGenerator
$sequence
$map
Streams.yield
[1..5::Int]) >>= Streams.toList
[1,2,3,4,5]
A Generator
is a coroutine monad that can be used to define complex
InputStream
s. You can cause a value of type Just r
to appear when the
InputStream
is read by calling yield
:
g ::Generator
Int () g = do Streams.yield
1 Streams.yield
2 Streams.yield
3
A Generator
can be turned into an InputStream
by calling
fromGenerator
:
m ::IO
[Int
] m = Streams.fromGenerator
g >>= Streams.toList
-- value returned is [1,2,3]
You can perform IO by calling liftIO
, and turn a Generator
into an
InputStream
with fromGenerator
.
As a general rule, you should not acquire resources that need to be freed
from a Generator
, because there is no guarantee the coroutine continuation
will ever be called, nor can you catch an exception from within a
Generator
.
fromGenerator :: Generator r a -> IO (InputStream r) Source #
Turns a Generator
into an InputStream
.
yield :: r -> Generator r () Source #
Calling
causes the value yield
x
to appear on the input
when this generator is converted to an Just
xInputStream
. The rest of the
computation after the call to yield
is resumed later when the
InputStream
is read
again.
Batteries included
module System.IO.Streams.Builder
module System.IO.Streams.ByteString
module System.IO.Streams.Handle
module System.IO.Streams.File
module System.IO.Streams.List
module System.IO.Streams.Network
module System.IO.Streams.Process
module System.IO.Streams.Text
module System.IO.Streams.Vector
module System.IO.Streams.Zlib