Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- data Stream (method :: k1) (status :: Nat) (framing :: *) (contentType :: *) (a :: *)
- type StreamGet = Stream GET 200
- type StreamPost = Stream POST 200
- newtype StreamGenerator a = StreamGenerator {
- getStreamGenerator :: (a -> IO ()) -> (a -> IO ()) -> IO ()
- class ToStreamGenerator a b | a -> b where
- newtype ResultStream a = ResultStream (forall b. (IO (Maybe (Either String a)) -> IO b) -> IO b)
- class BuildFromStream a b where
- class FramingRender strategy a where
- data BoundaryStrategy
- data ByteStringParser a = ByteStringParser {
- parseIncremental :: ByteString -> Maybe (a, ByteString)
- parseEOF :: ByteString -> (a, ByteString)
- class FramingUnrender strategy a where
- data NoFraming
- data NewlineFraming
- data NetstringFraming
Documentation
data Stream (method :: k1) (status :: Nat) (framing :: *) (contentType :: *) (a :: *) Source #
A Stream endpoint for a given method emits a stream of encoded values at a given Content-Type, delimited by a framing strategy. Stream endpoints always return response code 200 on success. Type synonyms are provided for standard methods.
type StreamPost = Stream POST 200 Source #
newtype StreamGenerator a Source #
Stream endpoints may be implemented as producing a StreamGenerator
-- a function that itself takes two emit functions -- the first to be used on the first value the stream emits, and the second to be used on all subsequent values (to allow interspersed framing strategies such as comma separation).
StreamGenerator | |
|
Instances
ToStreamGenerator (StreamGenerator a) a Source # | |
Defined in Servant.API.Stream toStreamGenerator :: StreamGenerator a -> StreamGenerator a Source # |
class ToStreamGenerator a b | a -> b where Source #
ToStreamGenerator is intended to be implemented for types such as Conduit, Pipe, etc. By implementing this class, all such streaming abstractions can be used directly as endpoints.
toStreamGenerator :: a -> StreamGenerator b Source #
Instances
ToStreamGenerator (StreamGenerator a) a Source # | |
Defined in Servant.API.Stream toStreamGenerator :: StreamGenerator a -> StreamGenerator a Source # |
newtype ResultStream a Source #
Clients reading from streaming endpoints can be implemented as producing a ResultStream
that captures the setup, takedown, and incremental logic for a read, being an IO continuation that takes a producer of Just either values or errors that terminates with a Nothing.
Instances
BuildFromStream a (ResultStream a) Source # | |
Defined in Servant.API.Stream buildFromStream :: ResultStream a -> ResultStream a Source # |
class BuildFromStream a b where Source #
BuildFromStream is intended to be implemented for types such as Conduit, Pipe, etc. By implementing this class, all such streaming abstractions can be used directly on the client side for talking to streaming endpoints.
buildFromStream :: ResultStream a -> b Source #
Instances
BuildFromStream a (ResultStream a) Source # | |
Defined in Servant.API.Stream buildFromStream :: ResultStream a -> ResultStream a Source # |
class FramingRender strategy a where Source #
The FramingRender class provides the logic for emitting a framing strategy. The strategy emits a header, followed by boundary-delimited data, and finally a termination character. For many strategies, some of these will just be empty bytestrings.
header :: Proxy strategy -> Proxy a -> ByteString Source #
boundary :: Proxy strategy -> Proxy a -> BoundaryStrategy Source #
Instances
FramingRender NoFraming (a :: k) Source # | |
FramingRender NewlineFraming (a :: k) Source # | |
Defined in Servant.API.Stream header :: Proxy NewlineFraming -> Proxy a -> ByteString Source # boundary :: Proxy NewlineFraming -> Proxy a -> BoundaryStrategy Source # trailer :: Proxy NewlineFraming -> Proxy a -> ByteString Source # | |
FramingRender NetstringFraming (a :: k) Source # | |
Defined in Servant.API.Stream header :: Proxy NetstringFraming -> Proxy a -> ByteString Source # boundary :: Proxy NetstringFraming -> Proxy a -> BoundaryStrategy Source # trailer :: Proxy NetstringFraming -> Proxy a -> ByteString Source # |
data BoundaryStrategy Source #
The bracketing strategy generates things to precede and follow the content, as with netstrings. The intersperse strategy inserts seperators between things, as with newline framing. Finally, the general strategy performs an arbitrary rewrite on the content, to allow escaping rules and such.
data ByteStringParser a Source #
A type of parser that can never fail, and has different parsing strategies (incremental, or EOF) depending if more input can be sent. The incremental parser should return Nothing
if it would like to be sent a longer ByteString. If it returns a value, it also returns the remainder following that value.
ByteStringParser | |
|
class FramingUnrender strategy a where Source #
The FramingUnrender class provides the logic for parsing a framing strategy. The outer ByteStringParser
strips the header from a stream of bytes, and yields a parser that can handle the remainder, stepwise. Each frame may be a ByteString, or a String indicating the error state for that frame. Such states are per-frame, so that protocols that can resume after errors are able to do so. Eventually this returns an empty ByteString to indicate termination.
unrenderFrames :: Proxy strategy -> Proxy a -> ByteStringParser (ByteStringParser (Either String ByteString)) Source #
Instances
FramingUnrender NoFraming (a :: k) Source # | |
Defined in Servant.API.Stream unrenderFrames :: Proxy NoFraming -> Proxy a -> ByteStringParser (ByteStringParser (Either String ByteString)) Source # | |
FramingUnrender NewlineFraming (a :: k) Source # | |
Defined in Servant.API.Stream unrenderFrames :: Proxy NewlineFraming -> Proxy a -> ByteStringParser (ByteStringParser (Either String ByteString)) Source # | |
FramingUnrender NetstringFraming (a :: k) Source # | |
Defined in Servant.API.Stream |
A framing strategy that does not do any framing at all, it just passes the input data This will be used most of the time with binary data, such as files
Instances
FramingUnrender NoFraming (a :: k) Source # | |
Defined in Servant.API.Stream unrenderFrames :: Proxy NoFraming -> Proxy a -> ByteStringParser (ByteStringParser (Either String ByteString)) Source # | |
FramingRender NoFraming (a :: k) Source # | |
data NewlineFraming Source #
A simple framing strategy that has no header or termination, and inserts a newline character between each frame. This assumes that it is used with a Content-Type that encodes without newlines (e.g. JSON).
Instances
FramingUnrender NewlineFraming (a :: k) Source # | |
Defined in Servant.API.Stream unrenderFrames :: Proxy NewlineFraming -> Proxy a -> ByteStringParser (ByteStringParser (Either String ByteString)) Source # | |
FramingRender NewlineFraming (a :: k) Source # | |
Defined in Servant.API.Stream header :: Proxy NewlineFraming -> Proxy a -> ByteString Source # boundary :: Proxy NewlineFraming -> Proxy a -> BoundaryStrategy Source # trailer :: Proxy NewlineFraming -> Proxy a -> ByteString Source # |
data NetstringFraming Source #
The netstring framing strategy as defined by djb: http://cr.yp.to/proto/netstrings.txt
Instances
FramingUnrender NetstringFraming (a :: k) Source # | |
Defined in Servant.API.Stream | |
FramingRender NetstringFraming (a :: k) Source # | |
Defined in Servant.API.Stream header :: Proxy NetstringFraming -> Proxy a -> ByteString Source # boundary :: Proxy NetstringFraming -> Proxy a -> BoundaryStrategy Source # trailer :: Proxy NetstringFraming -> Proxy a -> ByteString Source # |