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

Safe HaskellNone
LanguageHaskell2010

Servant.API.Stream

Contents

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. Type synonyms are provided for standard methods.

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

Defined in Servant.Links

Associated Types

type MkLink (Stream m status fr ct a) a :: Type 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) :: Type -> Type #

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 :: Type) r Source # 
Instance details

Defined in Servant.Links

type MkLink (Stream m status fr ct a :: Type) 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.15-2a7SBGEROHzDCNgJSw8q3s" False) (V1 :: Type -> Type)

type StreamBody = StreamBody' '[] Source #

A stream request body.

data StreamBody' (mods :: [*]) (framing :: *) (contentType :: *) (a :: *) Source #

Instances
HasLink sub => HasLink (StreamBody' mods framing ct a :> sub :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (StreamBody' mods framing ct a :> sub) a :: Type Source #

Methods

toLink :: (Link -> a0) -> Proxy (StreamBody' mods framing ct a :> sub) -> Link -> MkLink (StreamBody' mods framing ct a :> sub) a0 Source #

Generic (StreamBody' mods framing contentType a) Source # 
Instance details

Defined in Servant.API.Stream

Associated Types

type Rep (StreamBody' mods framing contentType a) :: Type -> Type #

Methods

from :: StreamBody' mods framing contentType a -> Rep (StreamBody' mods framing contentType a) x #

to :: Rep (StreamBody' mods framing contentType a) x -> StreamBody' mods framing contentType a #

type MkLink (StreamBody' mods framing ct a :> sub :: Type) r Source # 
Instance details

Defined in Servant.Links

type MkLink (StreamBody' mods framing ct a :> sub :: Type) r = MkLink sub r
type Rep (StreamBody' mods framing contentType a) Source # 
Instance details

Defined in Servant.API.Stream

type Rep (StreamBody' mods framing contentType a) = D1 (MetaData "StreamBody'" "Servant.API.Stream" "servant-0.15-2a7SBGEROHzDCNgJSw8q3s" False) (V1 :: Type -> Type)

Source

SourceIO are equivalent to some *source* in streaming libraries.

type SourceIO = SourceT IO Source #

Stream endpoints may be implemented as producing a SourceIO chunk.

Clients reading from streaming endpoints can be implemented as consuming a SourceIO chunk.

class ToSourceIO chunk a | a -> chunk where Source #

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

Methods

toSourceIO :: a -> SourceIO chunk Source #

Instances
ToSourceIO a [a] Source # 
Instance details

Defined in Servant.API.Stream

Methods

toSourceIO :: [a] -> SourceIO a Source #

ToSourceIO a (NonEmpty a) Source # 
Instance details

Defined in Servant.API.Stream

SourceToSourceIO m => ToSourceIO chunk (SourceT m chunk) Source #

Relax to use auxiliary class, have m

Instance details

Defined in Servant.API.Stream

Methods

toSourceIO :: SourceT m chunk -> SourceIO chunk Source #

class FromSourceIO chunk a | a -> chunk where Source #

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

Methods

fromSourceIO :: SourceIO chunk -> a Source #

Instances
MonadIO m => FromSourceIO a (SourceT m a) Source # 
Instance details

Defined in Servant.API.Stream

Methods

fromSourceIO :: SourceIO a -> SourceT m a Source #

Auxiliary classes

class SourceToSourceIO m where Source #

Auxiliary class for ToSourceIO x (SourceT m x) instance.

Instances
SourceToSourceIO IO Source # 
Instance details

Defined in Servant.API.Stream

Framing

class FramingRender strategy where Source #

The FramingRender class provides the logic for emitting a framing strategy. The strategy transforms a SourceT m a into SourceT m ByteString, therefore it can prepend, append and intercalate framing structure around chunks.

Note: as the Monad m is generic, this is pure transformation.

Methods

framingRender :: Monad m => Proxy strategy -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source #

class FramingUnrender strategy where Source #

The FramingUnrender class provides the logic for parsing a framing strategy.

Methods

framingUnrender :: Monad m => Proxy strategy -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source #

Instances
FramingUnrender NetstringFraming Source # 
Instance details

Defined in Servant.API.Stream

FramingUnrender NewlineFraming Source # 
Instance details

Defined in Servant.API.Stream

FramingUnrender NoFraming Source #

As NoFraming doesn't have frame separators, we take the chunks as given and try to convert them one by one.

That works well when a is a ByteString.

Instance details

Defined in Servant.API.Stream

Strategies

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

Instances
FramingUnrender NoFraming Source #

As NoFraming doesn't have frame separators, we take the chunks as given and try to convert them one by one.

That works well when a is a ByteString.

Instance details

Defined in Servant.API.Stream

FramingRender NoFraming Source # 
Instance details

Defined in Servant.API.Stream

data NewlineFraming Source #

A simple framing strategy that has no header, and inserts a newline character after each frame. This assumes that it is used with a Content-Type that encodes without newlines (e.g. JSON).

data NetstringFraming Source #

The netstring framing strategy as defined by djb: http://cr.yp.to/proto/netstrings.txt

Any string of 8-bit bytes may be encoded as [len]":"[string]",". Here [string] is the string and [len] is a nonempty sequence of ASCII digits giving the length of [string] in decimal. The ASCII digits are 30 for 0, 31 for 1, and so on up through 39 for 9. Extra zeros at the front of [len] are prohibited: [len] begins with 30 exactly when [string] is empty.

For example, the string "hello world!" is encoded as 32 3a 68 65 6c 6c 6f 20 77 6f 72 6c 64 21 2c, i.e., "12:hello world!,". The empty string is encoded as "0:,".