Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Stream (method :: k1) (status :: Nat) (framing :: *) (contentType :: *) (a :: *)
- type StreamGet = Stream GET 200
- type StreamPost = Stream POST 200
- type StreamBody = StreamBody' '[]
- data StreamBody' (mods :: [*]) (framing :: *) (contentType :: *) (a :: *)
- type SourceIO = SourceT IO
- class ToSourceIO chunk a | a -> chunk where
- toSourceIO :: a -> SourceIO chunk
- class FromSourceIO chunk a | a -> chunk where
- fromSourceIO :: SourceIO chunk -> a
- class SourceToSourceIO m where
- sourceToSourceIO :: SourceT m a -> SourceT IO a
- class FramingRender strategy where
- framingRender :: Monad m => Proxy strategy -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString
- class FramingUnrender strategy where
- framingUnrender :: Monad m => Proxy strategy -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a
- 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.
Type synonyms are provided for standard methods.
type StreamPost = Stream POST 200 Source #
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 # | |
Defined in Servant.Links | |
Generic (StreamBody' mods framing contentType a) Source # | |
Defined in Servant.API.Stream type Rep (StreamBody' mods framing contentType a) :: Type -> Type # 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 # | |
Defined in Servant.Links | |
type Rep (StreamBody' mods framing contentType a) Source # | |
Defined in Servant.API.Stream |
Source
SourceIO
are equivalent to some *source* in streaming libraries.
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.
toSourceIO :: a -> SourceIO chunk Source #
Instances
ToSourceIO a [a] Source # | |
Defined in Servant.API.Stream toSourceIO :: [a] -> SourceIO a Source # | |
ToSourceIO a (NonEmpty a) Source # | |
Defined in Servant.API.Stream toSourceIO :: NonEmpty a -> SourceIO a Source # | |
SourceToSourceIO m => ToSourceIO chunk (SourceT m chunk) Source # | Relax to use auxiliary class, have m |
Defined in Servant.API.Stream 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.
fromSourceIO :: SourceIO chunk -> a Source #
Instances
MonadIO m => FromSourceIO a (SourceT m a) Source # | |
Defined in Servant.API.Stream fromSourceIO :: SourceIO a -> SourceT m a Source # |
Auxiliary classes
class SourceToSourceIO m where Source #
Auxiliary class for
instance.ToSourceIO
x (SourceT
m x)
Instances
SourceToSourceIO IO Source # | |
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
into SourceT
m a
,
therefore it can prepend, append and intercalate framing structure
around chunks.SourceT
m ByteString
Note: as the
is generic, this is pure transformation.Monad
m
framingRender :: Monad m => Proxy strategy -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source #
Instances
FramingRender NetstringFraming Source # | |
Defined in Servant.API.Stream framingRender :: Monad m => Proxy NetstringFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source # | |
FramingRender NewlineFraming Source # | |
Defined in Servant.API.Stream framingRender :: Monad m => Proxy NewlineFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source # | |
FramingRender NoFraming Source # | |
Defined in Servant.API.Stream framingRender :: Monad m => Proxy NoFraming -> (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.
framingUnrender :: Monad m => Proxy strategy -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source #
Instances
FramingUnrender NetstringFraming Source # | |
Defined in Servant.API.Stream framingUnrender :: Monad m => Proxy NetstringFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source # | |
FramingUnrender NewlineFraming Source # | |
Defined in Servant.API.Stream framingUnrender :: Monad m => Proxy NewlineFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source # | |
FramingUnrender NoFraming Source # | As That works well when |
Defined in Servant.API.Stream framingUnrender :: Monad m => Proxy NoFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source # |
Strategies
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 That works well when |
Defined in Servant.API.Stream framingUnrender :: Monad m => Proxy NoFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source # | |
FramingRender NoFraming Source # | |
Defined in Servant.API.Stream framingRender :: Monad m => Proxy NoFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source # |
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).
Instances
FramingUnrender NewlineFraming Source # | |
Defined in Servant.API.Stream framingUnrender :: Monad m => Proxy NewlineFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source # | |
FramingRender NewlineFraming Source # | |
Defined in Servant.API.Stream framingRender :: Monad m => Proxy NewlineFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source # |
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:,"
.
Instances
FramingUnrender NetstringFraming Source # | |
Defined in Servant.API.Stream framingUnrender :: Monad m => Proxy NetstringFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source # | |
FramingRender NetstringFraming Source # | |
Defined in Servant.API.Stream framingRender :: Monad m => Proxy NetstringFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source # |