Safe Haskell | None |
---|---|
Language | Haskell2010 |
Streamline exports a monad that, given an uniform IO target, emulates character stream IO using high performance block IO.
- data Streamline m a
- withClient :: MonadIO m => BoundedPort -> (IP -> Int -> Streamline m a) -> m a
- withServer :: MonadIO m => IP -> Int -> Streamline m a -> m a
- withTarget :: (Monad m, UniformIO a) => a -> Streamline m b -> m b
- inStreamlineCtx :: UniformIO io => io -> a -> RSt Streamline a
- peelStreamlineCtx :: RSt Streamline a -> (a, SomeIO)
- closeTarget :: MonadIO m => Streamline m ()
- send :: MonadIO m => ByteString -> Streamline m ()
- send' :: MonadIO m => ByteString -> Streamline m ()
- recieveLine :: MonadIO m => Streamline m ByteString
- recieveLine' :: MonadIO m => Streamline m ByteString
- recieveN :: MonadIO m => Int -> Streamline m ByteString
- recieveN' :: MonadIO m => Int -> Streamline m ByteString
- runAttoparsec :: MonadIO m => Parser a -> Streamline m (Either String a)
- runAttoparsecAndReturn :: MonadIO m => Parser a -> Streamline m (ByteString, Either String a)
- runScanner :: MonadIO m => s -> IOScanner s -> Streamline m (ByteString, s)
- runScanner' :: MonadIO m => s -> IOScanner s -> Streamline m (ByteString, s)
- scan :: MonadIO m => s -> IOScanner s -> Streamline m ByteString
- scan' :: MonadIO m => s -> IOScanner s -> Streamline m ByteString
- recieveTill :: MonadIO m => ByteString -> Streamline m ByteString
- recieveTill' :: MonadIO m => ByteString -> Streamline m ByteString
- startTls :: MonadIO m => TlsSettings -> Streamline m ()
- isSecure :: Monad m => Streamline m Bool
- setTimeout :: Monad m => Int -> Streamline m ()
- echoTo :: Monad m => Maybe Handle -> Streamline m ()
- setEcho :: Monad m => Bool -> Streamline m ()
Basic Type
data Streamline m a Source
Monad that emulates character stream IO over block IO.
Interruptible Streamline Source | |
MonadTrans Streamline Source | |
MonadTransControl Streamline Source | |
MonadBase b m => MonadBase b (Streamline m) Source | |
MonadBaseControl b m => MonadBaseControl b (Streamline m) Source | |
Monad m => Monad (Streamline m) Source | |
Monad m => Functor (Streamline m) Source | |
(Functor m, Monad m) => Applicative (Streamline m) Source | |
MonadIO m => MonadIO (Streamline m) Source | |
type RSt Streamline a Source | |
type StT Streamline a Source | |
type StM (Streamline m) a = ComposeSt Streamline m a Source |
Running streamline targets
Single pass runners
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 :: (Monad m, UniformIO a) => a -> Streamline m b -> m b Source
withTarget f someIO
Runs f wrapped on a Streamline monad that does IO on someIO.
Interruptible support
inStreamlineCtx :: UniformIO io => io -> a -> RSt Streamline a Source
Creates a Streamline interrutible context
peelStreamlineCtx :: RSt Streamline a -> (a, SomeIO) Source
Removes a Streamline interruptible context
closeTarget :: MonadIO m => Streamline m () Source
Closes the target of a streamline state, releasing any resource.
Sending and recieving data
send :: MonadIO m => ByteString -> Streamline m () Source
Sends data over the 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
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
Running a parser
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.
Scanning the input
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.
runScanner' :: MonadIO m => s -> IOScanner s -> Streamline m (ByteString, s) Source
Equivalent to runScanner, but returns a strict, completely evaluated ByteString.
scan :: MonadIO m => s -> IOScanner s -> Streamline m ByteString Source
Equivalent to runScanner, but discards the final state
scan' :: MonadIO m => s -> IOScanner s -> Streamline m ByteString Source
Equivalent to runScanner', but discards the final state
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
Behavior settings
startTls :: MonadIO m => TlsSettings -> Streamline m () Source
Wraps the streamlined IO target on TLS, streamlining the new wrapper afterwads.
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.
echoTo :: Monad m => Maybe Handle -> Streamline m () Source
Sets echo of the streamlined IO target.
If echo is set, all the data read an written to the target will be echoed to the handle, with ">" and "<" markers indicating what is read and written.
Setting to Nothing will disable echo.
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.