Skip to content

Commit 1adbcec

Browse files
authored
Chunked responses (#107)
* Chunked responses * Remove Chunked newtype wrapper around Streams * Use child process instead of ffi stream for chunked example * Rename additionalHeaders to defaultHeaders * Add History.md entry * General cleanup
1 parent 1bde8b4 commit 1adbcec

15 files changed

+207
-98
lines changed

History.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@ unreleased
22
==========
33
- Re-export `HTTPure.Query` and `HTTPure.Status` (thanks **@akheron**)
44
- Support binary response body (thanks **@akheron**)
5+
- Add support for chunked responses
56

67
0.7.0 / 2018-07-08
78
==================

bower.json

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -17,17 +17,18 @@
1717
"*.md"
1818
],
1919
"dependencies": {
20-
"purescript-prelude": "^4.0.1",
2120
"purescript-aff": "^5.0.0",
21+
"purescript-foldable-traversable": "^4.0.0",
2222
"purescript-node-fs": "^5.0.0",
2323
"purescript-node-http": "^5.0.0",
24-
"purescript-strings": "^4.0.0",
25-
"purescript-foldable-traversable": "^4.0.0"
24+
"purescript-prelude": "^4.0.1",
25+
"purescript-strings": "^4.0.0"
2626
},
2727
"devDependencies": {
28+
"purescript-node-child-process": "^5.0.0",
29+
"purescript-node-fs-aff": "^6.0.0",
2830
"purescript-psci-support": "^4.0.0",
2931
"purescript-spec": "^3.0.0",
30-
"purescript-unsafe-coerce": "^4.0.0",
31-
"purescript-node-fs-aff": "^6.0.0"
32+
"purescript-unsafe-coerce": "^4.0.0"
3233
}
3334
}

docs/Examples/Image/Main.purs renamed to docs/Examples/Binary/Main.purs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
module Examples.Image.Main where
1+
module Examples.Binary.Main where
22

33
import Prelude
44

@@ -16,7 +16,7 @@ portS = show port
1616

1717
-- | The path to the file containing the response to send
1818
filePath :: String
19-
filePath = "./docs/Examples/Image/circle.png"
19+
filePath = "./docs/Examples/Binary/circle.png"
2020

2121
-- | Respond with image data when run
2222
image :: HTTPure.Request -> HTTPure.ResponseM

docs/Examples/Binary/Readme.md

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
# Binary Example
2+
3+
This is a basic example of sending binary data. It serves an image file as
4+
binary data on any URL.
5+
6+
To run the server, run:
7+
8+
```bash
9+
make example EXAMPLE=Binary
10+
```
File renamed without changes.

docs/Examples/Chunked/Main.purs

Lines changed: 44 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,44 @@
1+
module Examples.Chunked.Main where
2+
3+
import Prelude
4+
5+
import Effect.Aff as Aff
6+
import Effect.Class as EffectClass
7+
import Effect.Console as Console
8+
import HTTPure as HTTPure
9+
import Node.ChildProcess as ChildProcess
10+
import Node.Stream as Stream
11+
12+
-- | Serve the example server on this port
13+
port :: Int
14+
port = 8091
15+
16+
-- | Shortcut for `show port`
17+
portS :: String
18+
portS = show port
19+
20+
-- | Run a script and return it's stdout stream
21+
runScript :: String -> Aff.Aff (Stream.Readable ())
22+
runScript script = EffectClass.liftEffect $ ChildProcess.stdout <$>
23+
ChildProcess.spawn "sh" [ "-c", script ] ChildProcess.defaultSpawnOptions
24+
25+
-- | Say 'hello world!' in chunks when run
26+
sayHello :: HTTPure.Request -> HTTPure.ResponseM
27+
sayHello _ =
28+
runScript "echo -n 'hello '; sleep 1; echo -n 'world!'" >>= HTTPure.ok
29+
30+
-- | Boot up the server
31+
main :: HTTPure.ServerM
32+
main = HTTPure.serve port sayHello do
33+
Console.log $ " ┌────────────────────────────────────────────┐"
34+
Console.log $ " │ Server now up on port " <> portS <> ""
35+
Console.log $ " │ │"
36+
Console.log $ " │ To test, run: │"
37+
Console.log $ " │ > curl -Nv localhost:" <> portS <> ""
38+
Console.log $ " │ # => ... │"
39+
Console.log $ " │ # => < Transfer-Encoding: chunked │"
40+
Console.log $ " │ # => ... │"
41+
Console.log $ " │ # => hello │"
42+
Console.log $ " │ (1 second pause) │"
43+
Console.log $ " │ # => world! │"
44+
Console.log $ " └────────────────────────────────────────────┘"

docs/Examples/Chunked/Readme.md

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
# Chunked Example
2+
3+
This is a basic example of sending chunked data. It will return 'hello world'
4+
in two separate chunks spaced a second apart on any URL.
5+
6+
To run the example server, run:
7+
8+
```bash
9+
make example EXAMPLE=Chunked
10+
```

src/HTTPure/Body.purs

Lines changed: 37 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1,61 +1,84 @@
11
module HTTPure.Body
22
( class Body
3+
, defaultHeaders
34
, read
4-
, size
55
, write
66
) where
77

88
import Prelude
99

1010
import Data.Either as Either
11-
import Data.Maybe as Maybe
1211
import Effect as Effect
1312
import Effect.Aff as Aff
1413
import Effect.Ref as Ref
1514
import Node.Buffer as Buffer
1615
import Node.Encoding as Encoding
1716
import Node.HTTP as HTTP
1817
import Node.Stream as Stream
18+
import Type.Equality as TypeEquals
19+
20+
import HTTPure.Headers as Headers
1921

2022
-- | Types that implement the `Body` class can be used as a body to an HTTPure
2123
-- | response, and can be used with all the response helpers.
2224
class Body b where
2325

24-
-- | Given a body value, return an effect that maybe calculates a size.
25-
-- | TODO: This is a `Maybe` to support chunked transfer encoding. We still
26-
-- | need to add code to send the body using chunking if the effect resolves a
27-
-- | `Maybe.Nothing`.
28-
size :: b -> Effect.Effect (Maybe.Maybe Int)
26+
-- | Return any default headers that need to be sent with this body type,
27+
-- | things like `Content-Type`, `Content-Length`, and `Transfer-Encoding`.
28+
-- | Note that any headers passed in a response helper such as `ok'` will take
29+
-- | precedence over these.
30+
defaultHeaders :: b -> Effect.Effect Headers.Headers
2931

3032
-- | Given a body value and a Node HTTP `Response` value, write the body value
3133
-- | to the Node response.
3234
write :: b -> HTTP.Response -> Aff.Aff Unit
3335

3436
-- | The instance for `String` will convert the string to a buffer first in
35-
-- | order to determine it's size. This is to properly handle UTF-8 characters
36-
-- | in the string. Writing is simply implemented by writing the string to the
37+
-- | order to determine it's additional headers. This is to ensure that the
38+
-- | `Content-Length` header properly accounts for UTF-8 characters in the
39+
-- | string. Writing is simply implemented by writing the string to the
3740
-- | response stream and closing the response stream.
3841
instance bodyString :: Body String where
39-
size body = Buffer.fromString body Encoding.UTF8 >>= size
42+
43+
defaultHeaders body = Buffer.fromString body Encoding.UTF8 >>= defaultHeaders
44+
4045
write body response = Aff.makeAff \done -> do
4146
let stream = HTTP.responseAsStream response
4247
_ <- Stream.writeString stream Encoding.UTF8 body $ pure unit
4348
_ <- Stream.end stream $ pure unit
4449
done $ Either.Right unit
4550
pure Aff.nonCanceler
4651

47-
-- | The instance for `Buffer` is trivial--to calculate size, we use
48-
-- | `Buffer.size`, and to send the response, we just write the buffer to the
49-
-- | stream and end the stream.
52+
-- | The instance for `Buffer` is trivial--we add a `Content-Length` header
53+
-- | using `Buffer.size`, and to send the response, we just write the buffer to
54+
-- | the stream and end the stream.
5055
instance bodyBuffer :: Body Buffer.Buffer where
51-
size = Buffer.size >>> map Maybe.Just
56+
57+
defaultHeaders buf =
58+
Headers.header "Content-Length" <$> show <$> Buffer.size buf
59+
5260
write body response = Aff.makeAff \done -> do
5361
let stream = HTTP.responseAsStream response
5462
_ <- Stream.write stream body $ pure unit
5563
_ <- Stream.end stream $ pure unit
5664
done $ Either.Right unit
5765
pure Aff.nonCanceler
5866

67+
-- | This instance can be used to send chunked data. Here, we add a
68+
-- | `Transfer-Encoding` header to indicate chunked data. To write the data, we
69+
-- | simply pipe the newtype-wrapped `Stream` to the response.
70+
instance bodyChunked ::
71+
TypeEquals.TypeEquals (Stream.Stream r) (Stream.Readable ()) =>
72+
Body (Stream.Stream r) where
73+
74+
defaultHeaders _ = pure $ Headers.header "Transfer-Encoding" "chunked"
75+
76+
write body response = Aff.makeAff \done -> do
77+
let stream = TypeEquals.to body
78+
_ <- Stream.pipe stream $ HTTP.responseAsStream response
79+
Stream.onEnd stream $ done $ Either.Right unit
80+
pure Aff.nonCanceler
81+
5982
-- | Extract the contents of the body of the HTTP `Request`.
6083
read :: HTTP.Request -> Aff.Aff String
6184
read request = Aff.makeAff \done -> do

src/HTTPure/Response.purs

Lines changed: 9 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -78,7 +78,6 @@ module HTTPure.Response
7878

7979
import Prelude
8080

81-
import Data.Maybe as Maybe
8281
import Effect.Aff as Aff
8382
import Effect.Class as EffectClass
8483
import Node.HTTP as HTTP
@@ -97,21 +96,16 @@ type Response =
9796
{ status :: Status.Status
9897
, headers :: Headers.Headers
9998
, writeBody :: HTTP.Response -> Aff.Aff Unit
100-
, size :: Maybe.Maybe Int
10199
}
102100

103101
-- | Given an HTTP `Response` and a HTTPure `Response`, this method will return
104102
-- | a monad encapsulating writing the HTTPure `Response` to the HTTP `Response`
105103
-- | and closing the HTTP `Response`.
106104
send :: HTTP.Response -> Response -> Aff.Aff Unit
107-
send httpresponse { status, headers, writeBody, size } = do
105+
send httpresponse { status, headers, writeBody } = do
108106
EffectClass.liftEffect $ Status.write httpresponse status
109-
EffectClass.liftEffect $ Headers.write httpresponse finalHeaders
107+
EffectClass.liftEffect $ Headers.write httpresponse headers
110108
writeBody httpresponse
111-
where
112-
finalHeaders = headers <> contentLength size
113-
contentLength (Maybe.Just s) = Headers.header "Content-Length" $ show s
114-
contentLength Maybe.Nothing = Headers.empty
115109

116110
-- | For custom response statuses or providing a body for response codes that
117111
-- | don't typically send one.
@@ -124,9 +118,13 @@ response' :: forall b. Body.Body b =>
124118
Headers.Headers ->
125119
b ->
126120
ResponseM
127-
response' status headers body = do
128-
size <- EffectClass.liftEffect $ Body.size body
129-
pure $ { status, headers, size, writeBody: Body.write body }
121+
response' status headers body = EffectClass.liftEffect do
122+
defaultHeaders <- Body.defaultHeaders body
123+
pure
124+
{ status
125+
, headers: defaultHeaders <> headers
126+
, writeBody: Body.write body
127+
}
130128

131129
-- | The same as `response` but without a body.
132130
emptyResponse :: Status.Status -> ResponseM

src/HTTPure/Server.purs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -33,10 +33,9 @@ handleRequest :: (Request.Request -> Response.ResponseM) ->
3333
HTTP.Request ->
3434
HTTP.Response ->
3535
ServerM
36-
handleRequest router request response =
37-
void $ Aff.runAff (\_ -> pure unit) do
38-
req <- Request.fromHTTPRequest request
39-
router req >>= Response.send response
36+
handleRequest router request httpresponse =
37+
void $ Aff.runAff (\_ -> pure unit) $
38+
Request.fromHTTPRequest request >>= router >>= Response.send httpresponse
4039

4140
-- | Given a `ListenOptions` object, a function mapping `Request` to
4241
-- | `ResponseM`, and a `ServerM` containing effects to run on boot, creates and

test/Test/HTTPure/BodySpec.purs

Lines changed: 28 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -2,13 +2,13 @@ module Test.HTTPure.BodySpec where
22

33
import Prelude
44

5-
import Data.Maybe as Maybe
65
import Effect.Class as EffectClass
76
import Node.Buffer as Buffer
87
import Node.Encoding as Encoding
98
import Test.Spec as Spec
109

1110
import HTTPure.Body as Body
11+
import HTTPure.Headers as Headers
1212

1313
import Test.HTTPure.TestHelpers as TestHelpers
1414
import Test.HTTPure.TestHelpers ((?=))
@@ -20,21 +20,27 @@ readSpec = Spec.describe "read" do
2020
body <- Body.read request
2121
body ?= "test"
2222

23-
sizeSpec :: TestHelpers.Test
24-
sizeSpec = Spec.describe "size" do
23+
defaultHeadersSpec :: TestHelpers.Test
24+
defaultHeadersSpec = Spec.describe "defaultHeaders" do
2525
Spec.describe "String" do
26-
Spec.it "returns the correct size for ASCII string body" do
27-
size <- EffectClass.liftEffect $ Body.size "ascii"
28-
size ?= Maybe.Just 5
29-
Spec.it "returns the correct size for UTF-8 string body" do
30-
size <- EffectClass.liftEffect $ Body.size "\x2603" -- snowman
31-
size ?= Maybe.Just 3
26+
Spec.describe "with an ASCII string" do
27+
Spec.it "has the correct Content-Length header" do
28+
headers <- EffectClass.liftEffect $ Body.defaultHeaders "ascii"
29+
headers ?= Headers.header "Content-Length" "5"
30+
Spec.describe "with a UTF-8 string" do
31+
Spec.it "has the correct Content-Length header" do
32+
headers <- EffectClass.liftEffect $ Body.defaultHeaders "\x2603"
33+
headers ?= Headers.header "Content-Length" "3"
3234
Spec.describe "Buffer" do
33-
Spec.it "returns the correct size for binary body" do
34-
size <- EffectClass.liftEffect do
35-
buf <- Buffer.fromString "foobar" Encoding.UTF8
36-
Body.size buf
37-
size ?= Maybe.Just 6
35+
Spec.it "has the correct Content-Length header" do
36+
buf <- EffectClass.liftEffect $ Buffer.fromString "foobar" Encoding.UTF8
37+
headers <- EffectClass.liftEffect $ Body.defaultHeaders buf
38+
headers ?= Headers.header "Content-Length" "6"
39+
Spec.describe "Readable" do
40+
Spec.it "specifies the Transfer-Encoding header" do
41+
let body = TestHelpers.stringToStream "test"
42+
headers <- EffectClass.liftEffect $ Body.defaultHeaders body
43+
headers ?= Headers.header "Transfer-Encoding" "chunked"
3844

3945
writeSpec :: TestHelpers.Test
4046
writeSpec = Spec.describe "write" do
@@ -53,9 +59,16 @@ writeSpec = Spec.describe "write" do
5359
Body.write buf resp
5460
pure $ TestHelpers.getResponseBody resp
5561
body ?= "test"
62+
Spec.describe "Readable" do
63+
Spec.it "pipes the input stream to the Response body" do
64+
body <- do
65+
resp <- EffectClass.liftEffect TestHelpers.mockResponse
66+
Body.write (TestHelpers.stringToStream "test") resp
67+
pure $ TestHelpers.getResponseBody resp
68+
body ?= "test"
5669

5770
bodySpec :: TestHelpers.Test
5871
bodySpec = Spec.describe "Body" do
72+
defaultHeadersSpec
5973
readSpec
60-
sizeSpec
6174
writeSpec

0 commit comments

Comments
 (0)