Skip to content

Commit a66aa8a

Browse files
authored
Merge pull request #959 from jvanbruegge/fix-stream
Change definition of StreamGenerator
2 parents 64cb1f3 + a0b6d7a commit a66aa8a

File tree

5 files changed

+33
-19
lines changed

5 files changed

+33
-19
lines changed

doc/tutorial/ApiType.lhs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -137,7 +137,7 @@ type StreamGet = Stream 'GET
137137
type StreamPost = Stream 'POST
138138
```
139139
140-
These describe endpoints that return a stream of values rather than just a single value. They not only take a single content type as a parameter, but also a framing strategy -- this specifies how the individual results are delineated from one another in the stream. The two standard strategies given with Servant are `NewlineFraming` and `NetstringFraming`, but others can be written to match other protocols.
140+
These describe endpoints that return a stream of values rather than just a single value. They not only take a single content type as a parameter, but also a framing strategy -- this specifies how the individual results are delineated from one another in the stream. The three standard strategies given with Servant are `NewlineFraming`, `NetstringFraming` and `NoFraming`, but others can be written to match other protocols.
141141
142142
143143
### `Capture`

servant-client/test/Servant/StreamSpec.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,8 @@ import Test.QuickCheck
4040
import Servant.API ((:<|>) ((:<|>)), (:>), JSON,
4141
NetstringFraming, NewlineFraming,
4242
OctetStream, ResultStream (..),
43-
StreamGenerator (..), StreamGet)
43+
StreamGenerator (..), StreamGet,
44+
NoFraming)
4445
import Servant.Client
4546
import Servant.ClientSpec (Person (..))
4647
import qualified Servant.ClientSpec as CS
@@ -59,7 +60,7 @@ spec = describe "Servant.Stream" $ do
5960
type StreamApi f =
6061
"streamGetNewline" :> StreamGet NewlineFraming JSON (f Person)
6162
:<|> "streamGetNetstring" :> StreamGet NetstringFraming JSON (f Person)
62-
:<|> "streamALot" :> StreamGet NewlineFraming OctetStream (f BS.ByteString)
63+
:<|> "streamALot" :> StreamGet NoFraming OctetStream (f BS.ByteString)
6364

6465

6566
capi :: Proxy (StreamApi ResultStream)

servant-server/src/Servant/Server/Internal.hs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -284,34 +284,34 @@ instance OVERLAPPING_
284284

285285
instance OVERLAPPABLE_
286286
( MimeRender ctype a, ReflectMethod method,
287-
FramingRender framing ctype, ToStreamGenerator f a
288-
) => HasServer (Stream method framing ctype (f a)) context where
287+
FramingRender framing ctype, ToStreamGenerator b a
288+
) => HasServer (Stream method framing ctype b) context where
289289

290-
type ServerT (Stream method framing ctype (f a)) m = m (f a)
290+
type ServerT (Stream method framing ctype b) m = m b
291291
hoistServerWithContext _ _ nt s = nt s
292292

293293
route Proxy _ = streamRouter ([],) method (Proxy :: Proxy framing) (Proxy :: Proxy ctype)
294294
where method = reflectMethod (Proxy :: Proxy method)
295295

296296
instance OVERLAPPING_
297297
( MimeRender ctype a, ReflectMethod method,
298-
FramingRender framing ctype, ToStreamGenerator f a,
299-
GetHeaders (Headers h (f a))
300-
) => HasServer (Stream method framing ctype (Headers h (f a))) context where
298+
FramingRender framing ctype, ToStreamGenerator b a,
299+
GetHeaders (Headers h b)
300+
) => HasServer (Stream method framing ctype (Headers h b)) context where
301301

302-
type ServerT (Stream method framing ctype (Headers h (f a))) m = m (Headers h (f a))
302+
type ServerT (Stream method framing ctype (Headers h b)) m = m (Headers h b)
303303
hoistServerWithContext _ _ nt s = nt s
304304

305305
route Proxy _ = streamRouter (\x -> (getHeaders x, getResponse x)) method (Proxy :: Proxy framing) (Proxy :: Proxy ctype)
306306
where method = reflectMethod (Proxy :: Proxy method)
307307

308308

309-
streamRouter :: (MimeRender ctype a, FramingRender framing ctype, ToStreamGenerator f a) =>
310-
(b -> ([(HeaderName, B.ByteString)], f a))
309+
streamRouter :: (MimeRender ctype a, FramingRender framing ctype, ToStreamGenerator b a) =>
310+
(c -> ([(HeaderName, B.ByteString)], b))
311311
-> Method
312312
-> Proxy framing
313313
-> Proxy ctype
314-
-> Delayed env (Handler b)
314+
-> Delayed env (Handler c)
315315
-> Router env
316316
streamRouter splitHeaders method framingproxy ctypeproxy action = leafRouter $ \env request respond ->
317317
let accH = fromMaybe ct_wildcard $ lookup hAccept $ requestHeaders request

servant/src/Servant/API.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -117,8 +117,8 @@ import Servant.API.Stream
117117
(BoundaryStrategy (..), BuildFromStream (..),
118118
ByteStringParser (..), FramingRender (..),
119119
FramingUnrender (..), NetstringFraming, NewlineFraming,
120-
ResultStream (..), Stream, StreamGenerator (..), StreamGet,
121-
StreamPost, ToStreamGenerator (..))
120+
NoFraming, ResultStream (..), Stream, StreamGenerator (..),
121+
StreamGet, StreamPost, ToStreamGenerator (..))
122122
import Servant.API.Sub
123123
((:>))
124124
import Servant.API.Vault

servant/src/Servant/API/Stream.hs

Lines changed: 17 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
{-# LANGUAGE DeriveDataTypeable #-}
33
{-# LANGUAGE DeriveGeneric #-}
44
{-# LANGUAGE FlexibleInstances #-}
5+
{-# LANGUAGE FunctionalDependencies #-}
56
{-# LANGUAGE KindSignatures #-}
67
{-# LANGUAGE MultiParamTypeClasses #-}
78
{-# LANGUAGE OverloadedStrings #-}
@@ -38,13 +39,13 @@ type StreamGet = Stream 'GET
3839
type StreamPost = Stream 'POST
3940

4041
-- | 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).
41-
newtype StreamGenerator a = StreamGenerator {getStreamGenerator :: (a -> IO ()) -> (a -> IO ()) -> IO ()}
42+
newtype StreamGenerator a = StreamGenerator {getStreamGenerator :: (a -> IO ()) -> (a -> IO ()) -> IO ()}
4243

4344
-- | 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.
44-
class ToStreamGenerator f a where
45-
toStreamGenerator :: f a -> StreamGenerator a
45+
class ToStreamGenerator a b | a -> b where
46+
toStreamGenerator :: a -> StreamGenerator b
4647

47-
instance ToStreamGenerator StreamGenerator a
48+
instance ToStreamGenerator (StreamGenerator a) a
4849
where toStreamGenerator x = x
4950

5051
-- | 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.
@@ -80,6 +81,18 @@ data ByteStringParser a = ByteStringParser {
8081
class FramingUnrender strategy a where
8182
unrenderFrames :: Proxy strategy -> Proxy a -> ByteStringParser (ByteStringParser (Either String ByteString))
8283

84+
-- | A framing strategy that does not do any framing at all, it just passes the input data
85+
-- This will be used most of the time with binary data, such as files
86+
data NoFraming
87+
88+
instance FramingRender NoFraming a where
89+
header _ _ = empty
90+
boundary _ _ = BoundaryStrategyGeneral id
91+
trailer _ _ = empty
92+
93+
instance FramingUnrender NoFraming a where
94+
unrenderFrames _ _ = ByteStringParser (Just . (go,)) (go,)
95+
where go = ByteStringParser (Just . (, empty) . Right) ((, empty) . Right)
8396

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

0 commit comments

Comments
 (0)