| Safe Haskell | None | 
|---|
System.IO.Streams.Internal
Contents
Description
Internal implementation of the io-streams library, intended for library
 writers
Library users should use the interface provided by System.IO.Streams
- data SP a b = SP !a !b
 - type StreamPair a = SP (InputStream a) (OutputStream a)
 - data InputStream a = InputStream {}
 - data OutputStream a = OutputStream {}
 - read :: InputStream a -> IO (Maybe a)
 - unRead :: a -> InputStream a -> IO ()
 - peek :: InputStream a -> IO (Maybe a)
 - write :: Maybe a -> OutputStream a -> IO ()
 - atEOF :: InputStream a -> IO Bool
 - makeInputStream :: IO (Maybe a) -> IO (InputStream a)
 - makeOutputStream :: (Maybe a -> IO ()) -> IO (OutputStream a)
 - appendInputStream :: InputStream a -> InputStream a -> IO (InputStream a)
 - concatInputStreams :: [InputStream a] -> IO (InputStream a)
 - connect :: InputStream a -> OutputStream a -> IO ()
 - connectTo :: OutputStream a -> InputStream a -> IO ()
 - supply :: InputStream a -> OutputStream a -> IO ()
 - supplyTo :: OutputStream a -> InputStream a -> IO ()
 - 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 ()
 - data Consumer c a
 - fromConsumer :: Consumer r a -> IO (OutputStream r)
 - await :: Consumer r (Maybe r)
 
Types
type StreamPair a = SP (InputStream a) (OutputStream a)Source
Internal convenience synonym for a pair of input/output streams.
About pushback
Users can push a value back into an input stream using the unRead
 function. Usually this will use the default pushback mechanism which
 provides a buffer for the stream. Some stream transformers, like
 takeBytes, produce streams that send pushed-back values back to the
 streams that they wrap. A function like map
 cannot do this because the types don't match up:
map:: (a -> b) ->InputStreama ->IO(InputStreamb)
A function will usually document if its pushback behaviour differs from the default. No matter what the case, input streams should obey the following law:
Streams.unReadc stream >> Streams.readstream ===return(Justc)
Input and output streams
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::InputStreamc ->IO(Maybec)readreturningNothing. -  
"pushes back" a value to the stream.unRead:: c ->InputStreamc ->IO() 
It is intended that InputStreams obey the following law:
unReadc stream >>readstream ===return(Justc)
data OutputStream a Source
An OutputStream consumes values of type c in the IO monad.
 The only primitive operation defined on OutputStream is:
write::Maybec ->OutputStreamc ->IO()
Values of type c are written in an OutputStream by wrapping them in
 Just, and the end of the stream is indicated by 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.)
Constructors
| OutputStream | |
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.unReadc stream >> Streams.readstream ===return(Justc)
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.peekstream >> Streams.readstream === Streams.readstream
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 by supplying Nothing.
atEOF :: InputStream a -> IO BoolSource
Checks if an InputStream is at end-of-stream.
Building 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.
appendInputStream :: InputStream a -> InputStream a -> IO (InputStream a)Source
appendInputStream concatenates two InputStreams, 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 InputStreams, analogous to
 (++) for lists.
Subsequent InputStreams 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
 InputStreams.
Connecting streams
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 InputStreams and use
 connect for the final InputStream to finalize the OutputStream, like
 so:
do Streams.supplyinput1 output Streams.supplyinput2 output Streams.connectinput3 output
supplyTo :: OutputStream a -> InputStream a -> IO ()Source
supply with the arguments flipped.
Thread safety
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
A Generator is a coroutine monad that can be used to define complex
 InputStreams. You can cause a value of type Just r to appear when the
 InputStream is read by calling yield:
g ::GeneratorInt () g = do Streams.yield1 Streams.yield2 Streams.yield3
A Generator can be turned into an InputStream by calling
 fromGenerator:
m ::IO[Int] m = Streams.fromGeneratorg >>= 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.
Consumer monad
fromConsumer :: Consumer r a -> IO (OutputStream r)Source