| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Servant.API.Stream
Synopsis
- data Stream (method :: k1) (status :: Nat) (framing :: Type) (contentType :: Type) (a :: Type)
- type StreamGet = Stream 'GET 200
- type StreamPost = Stream 'POST 200
- type StreamBody = StreamBody' '[]
- data StreamBody' (mods :: [Type]) (framing :: Type) (contentType :: Type) (a :: Type)
- 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 -> IO 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 :: Type) (contentType :: Type) (a :: Type) 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 :: [Type]) (framing :: Type) (contentType :: Type) (a :: Type) Source #
Instances
| HasLink sub => HasLink (StreamBody' mods framing ct a :> sub :: Type) Source # | |
| Defined in Servant.Links Associated Types type MkLink (StreamBody' mods framing ct a :> sub) a Source # | |
| Generic (StreamBody' mods framing contentType a) Source # | |
| 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 # | |
| 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.
Methods
toSourceIO :: a -> SourceIO chunk Source #
Instances
| ToSourceIO a (NonEmpty a) Source # | |
| Defined in Servant.API.Stream Methods toSourceIO :: NonEmpty a -> SourceIO a Source # | |
| ToSourceIO a [a] Source # | |
| Defined in Servant.API.Stream Methods toSourceIO :: [a] -> SourceIO a Source # | |
| SourceToSourceIO m => ToSourceIO chunk (SourceT m chunk) Source # | Relax to use auxiliary class, have m | 
| 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 -> IO a Source #
Instances
| MonadIO m => FromSourceIO a (SourceT m a) Source # | |
| Defined in Servant.API.Stream | |
Auxiliary classes
class SourceToSourceIO m where Source #
Auxiliary class for 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 SourceT m aSourceT m ByteString
Note: as the Monad m
Methods
framingRender :: Monad m => Proxy strategy -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source #
Instances
| FramingRender NetstringFraming Source # | |
| Defined in Servant.API.Stream Methods framingRender :: forall (m :: Type -> Type) a. Monad m => Proxy NetstringFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source # | |
| FramingRender NewlineFraming Source # | |
| Defined in Servant.API.Stream Methods framingRender :: forall (m :: Type -> Type) a. Monad m => Proxy NewlineFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source # | |
| FramingRender NoFraming Source # | |
| Defined in Servant.API.Stream Methods framingRender :: forall (m :: Type -> Type) a. 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.
Methods
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 Methods framingUnrender :: forall (m :: Type -> Type) a. Monad m => Proxy NetstringFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source # | |
| FramingUnrender NewlineFraming Source # | |
| Defined in Servant.API.Stream Methods framingUnrender :: forall (m :: Type -> Type) a. 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 Methods framingUnrender :: forall (m :: Type -> Type) a. 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
| FramingRender NoFraming Source # | |
| Defined in Servant.API.Stream Methods framingRender :: forall (m :: Type -> Type) a. Monad m => Proxy NoFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source # | |
| FramingUnrender NoFraming Source # | As  That works well when  | 
| Defined in Servant.API.Stream Methods framingUnrender :: forall (m :: Type -> Type) a. Monad m => Proxy NoFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a 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
| FramingRender NewlineFraming Source # | |
| Defined in Servant.API.Stream Methods framingRender :: forall (m :: Type -> Type) a. Monad m => Proxy NewlineFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source # | |
| FramingUnrender NewlineFraming Source # | |
| Defined in Servant.API.Stream Methods framingUnrender :: forall (m :: Type -> Type) a. Monad m => Proxy NewlineFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a 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
| FramingRender NetstringFraming Source # | |
| Defined in Servant.API.Stream Methods framingRender :: forall (m :: Type -> Type) a. Monad m => Proxy NetstringFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source # | |
| FramingUnrender NetstringFraming Source # | |
| Defined in Servant.API.Stream Methods framingUnrender :: forall (m :: Type -> Type) a. Monad m => Proxy NetstringFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source # | |