servant-0.14.1: A family of combinators for defining webservices APIs

Safe HaskellSafe
LanguageHaskell2010

Servant.API.Stream

Synopsis

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.

Instances
HasLink (Stream m status fr ct a :: *) Source # 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (Stream m status fr ct a) a :: * Source #

Methods

toLink :: (Link -> a0) -> Proxy (Stream m status fr ct a) -> Link -> MkLink (Stream m status fr ct a) a0 Source #

Generic (Stream method status framing contentType a) Source # 
Instance details

Defined in Servant.API.Stream

Associated Types

type Rep (Stream method status framing contentType a) :: * -> * #

Methods

from :: Stream method status framing contentType a -> Rep (Stream method status framing contentType a) x #

to :: Rep (Stream method status framing contentType a) x -> Stream method status framing contentType a #

type MkLink (Stream m status fr ct a :: *) r Source # 
Instance details

Defined in Servant.Links

type MkLink (Stream m status fr ct a :: *) r = r
type Rep (Stream method status framing contentType a) Source # 
Instance details

Defined in Servant.API.Stream

type Rep (Stream method status framing contentType a) = D1 (MetaData "Stream" "Servant.API.Stream" "servant-0.14.1-EgbVaicHQEdCgqTzWc4SOj" False) (V1 :: * -> *)

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).

Constructors

StreamGenerator 

Fields

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.

Minimal complete definition

toStreamGenerator

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.

Constructors

ResultStream (forall b. (IO (Maybe (Either String a)) -> IO b) -> IO b) 
Instances
BuildFromStream a (ResultStream a) Source # 
Instance details

Defined in Servant.API.Stream

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.

Minimal complete definition

buildFromStream

Instances
BuildFromStream a (ResultStream a) Source # 
Instance details

Defined in Servant.API.Stream

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.

Minimal complete definition

header, boundary, trailer

Methods

header :: Proxy strategy -> Proxy a -> ByteString Source #

boundary :: Proxy strategy -> Proxy a -> BoundaryStrategy Source #

trailer :: Proxy strategy -> 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.

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.

Minimal complete definition

unrenderFrames

data NoFraming Source #

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

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).