uniform-io-1.1.1.0: Uniform IO over files, network, anything.

Safe HaskellNone
LanguageHaskell2010

System.IO.Uniform.Streamline

Description

Streamline exports a monad that, given an uniform IO target, emulates character tream IO using high performance block IO.

Synopsis

Documentation

data Streamline m a Source

Monad that emulates character stream IO over block IO.

data IOScannerState a Source

State of an IO scanner. Differently from a parser scanner, an IO scanner must deal with blocking behavior.

Constructors

Finished

A scanner returns Finished when the current input is not part of the result, and the scanning must stop before this input.

LastPass a

A scanner returns LastPass when the current input is the last one of the result, and the scanning must stop before after this input, without consuming more data.

Running a

A scanner returns Running when the current input is part of the result, and the scanning must continue.

withClient :: MonadIO m => BoundedPort -> (IP -> Int -> Streamline m a) -> m a Source

withClient f boundPort

Accepts a connection at the bound port, runs f and closes the connection.

withServer :: MonadIO m => IP -> Int -> Streamline m a -> m a Source

withServer f serverIP port

Connects to the given server port, runs f, and closes the connection.

withTarget :: (MonadIO m, UniformIO a) => a -> Streamline m b -> m b Source

withTarget f someIO

Runs f wrapped on a Streamline monad that does IO on nomeIO.

send :: MonadIO m => ByteString -> Streamline m () Source

Sends data over the streamlines an IO target.

send' :: MonadIO m => ByteString -> Streamline m () Source

Sends data from a lazy byte string

recieveLine :: MonadIO m => Streamline m ByteString Source

Recieves data untill the next end of line (n or rn)

recieveLine' :: MonadIO m => Streamline m ByteString Source

Lazy version of recieveLine

lazyRecieveLine :: MonadIO m => Streamline m [ByteString] Source

Use recieveLine'.

recieveN :: MonadIO m => Int -> Streamline m ByteString Source

Recieves the given number of bytes.

recieveN' :: MonadIO m => Int -> Streamline m ByteString Source

Lazy version of recieveN

lazyRecieveN :: (Functor m, MonadIO m) => Int -> Streamline m [ByteString] Source

Use recieveN'.

recieveTill :: MonadIO m => ByteString -> Streamline m ByteString Source

Recieves data until it matches the argument. Returns all of it, including the matching data.

recieveTill' :: MonadIO m => ByteString -> Streamline m ByteString Source

Lazy version of recieveTill

startTls :: MonadIO m => TlsSettings -> Streamline m () Source

Wraps the streamlined IO target on TLS, streamlining the new wrapper afterwads.

runAttoparsec :: MonadIO m => Parser a -> Streamline m (Either String a) Source

Runs an Attoparsec parser over the data read from the streamlined IO target. Returning the parser result.

runAttoparsecAndReturn :: MonadIO m => Parser a -> Streamline m (ByteString, Either String a) Source

Runs an Attoparsec parser over the data read from the streamlined IO target. Returns both the parser result and the string consumed by it.

isSecure :: Monad m => Streamline m Bool Source

Indicates whether transport layer security is being used.

setTimeout :: Monad m => Int -> Streamline m () Source

Sets the timeout for the streamlined IO target.

setEcho :: Monad m => Bool -> Streamline m () Source

Sets echo of the streamlines IO target. If echo is set, all the data read an written to the target will be echoed in stdout, with ">" and "<" markers indicating what is read and written.

runScanner :: MonadIO m => s -> IOScanner s -> Streamline m (ByteString, s) Source

Equivalent to runScanner', but returns a strict, completely evaluated ByteString.

runScanner' :: MonadIO m => s -> IOScanner s -> Streamline m (ByteString, s) Source

Very much like Attoparsec's runScanner:

runScanner' scanner initial_state

Recieves data, running the scanner on each byte, using the scanner result as initial state for the next byte, and stopping when the scanner returns Nothing.

Returns the scanned ByteString.

scan :: MonadIO m => s -> IOScanner s -> Streamline m ByteString Source

Equivalent to runScanner, but dischards the final state

scan' :: MonadIO m => s -> IOScanner s -> Streamline m ByteString Source

Equivalent to runScanner', but dischards the final state