Add support for non string requests (#184)

* First version of supporting non-string requests

* Clean up

* Minor cleanup

* Simplify to directly export the stream

* Add nl

* Clean up & add more testing

Co-authored-by: sigma-andex <sigma.andex@pm.me>
This commit is contained in:
Connor Prussin 2021-11-15 20:02:36 -08:00 committed by GitHub
parent beb4621f4b
commit 6e886b91ac
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
15 changed files with 179 additions and 62 deletions

View File

@ -1,10 +0,0 @@
# Binary Example
This is a basic example of sending binary data. It serves an image file as
binary data on any URL.
To run the server, run:
```bash
make example EXAMPLE=Binary
```

View File

@ -0,0 +1,7 @@
'use strict';
const crypto = require('crypto');
exports.sha256sum = function(buffer) {
return crypto.createHash('sha256').update(buffer).digest('hex');
}

View File

@ -0,0 +1,24 @@
module Examples.BinaryRequest.Main where
import Prelude
import Effect.Console as Console
import Node.Buffer (Buffer)
import HTTPure as HTTPure
foreign import sha256sum :: Buffer -> String
-- | Respond with file's sha256sum
router :: HTTPure.Request -> HTTPure.ResponseM
router { body } = HTTPure.toBuffer body >>= sha256sum >>> HTTPure.ok
-- | Boot up the server
main :: HTTPure.ServerM
main =
HTTPure.serve 8080 router do
Console.log $ " ┌─────────────────────────────────────────────────────────┐"
Console.log $ " │ Server now up on port 8080 │"
Console.log $ " │ │"
Console.log $ " │ To test, run: │"
Console.log $ " │ > curl -XPOST --data-binary @circle.png localhost:8080 │"
Console.log $ " │ # => d5e776724dd5... │"
Console.log $ " └─────────────────────────────────────────────────────────┘"

View File

@ -0,0 +1,10 @@
# Binary Request Example
This is a basic example of sending binary request data. It will read in the
binary file and send back the file's sha256 checksum.
To run the server, run:
```bash
make example EXAMPLE=BinaryRequest
```

View File

@ -1,4 +1,4 @@
module Examples.Binary.Main where module Examples.BinaryResponse.Main where
import Prelude import Prelude
import Effect.Console as Console import Effect.Console as Console
@ -7,7 +7,7 @@ import HTTPure as HTTPure
-- | The path to the file containing the response to send -- | The path to the file containing the response to send
filePath :: String filePath :: String
filePath = "./docs/Examples/Binary/circle.png" filePath = "./docs/Examples/BinaryResponse/circle.png"
responseHeaders :: HTTPure.Headers responseHeaders :: HTTPure.Headers
responseHeaders = HTTPure.header "Content-Type" "image/png" responseHeaders = HTTPure.header "Content-Type" "image/png"

View File

@ -0,0 +1,10 @@
# Binary Response Example
This is a basic example of sending binary response data. It serves an image
file as binary data on any URL.
To run the server, run:
```bash
make example EXAMPLE=BinaryResponse
```

View File

Before

Width:  |  Height:  |  Size: 453 B

After

Width:  |  Height:  |  Size: 453 B

View File

@ -6,7 +6,7 @@ import HTTPure as HTTPure
-- | Route to the correct handler -- | Route to the correct handler
router :: HTTPure.Request -> HTTPure.ResponseM router :: HTTPure.Request -> HTTPure.ResponseM
router { body, method: HTTPure.Post } = HTTPure.ok body router { body, method: HTTPure.Post } = HTTPure.toString body >>= HTTPure.ok
router _ = HTTPure.notFound router _ = HTTPure.notFound
-- | Boot up the server -- | Boot up the server

View File

@ -1,5 +1,6 @@
module HTTPure module HTTPure
( module HTTPure.Headers ( module HTTPure.Body
, module HTTPure.Headers
, module HTTPure.Lookup , module HTTPure.Lookup
, module HTTPure.Method , module HTTPure.Method
, module HTTPure.Path , module HTTPure.Path
@ -10,6 +11,7 @@ module HTTPure
, module HTTPure.Status , module HTTPure.Status
) where ) where
import HTTPure.Body (toString, toBuffer)
import HTTPure.Headers (Headers, empty, header, headers) import HTTPure.Headers (Headers, empty, header, headers)
import HTTPure.Lookup (at, (!@), has, (!?), lookup, (!!)) import HTTPure.Lookup (at, (!@), has, (!?), lookup, (!!))
import HTTPure.Method (Method(..)) import HTTPure.Method (Method(..))

View File

@ -1,13 +1,16 @@
module HTTPure.Body module HTTPure.Body
( class Body ( class Body
, defaultHeaders , defaultHeaders
, read
, write , write
, read
, toString
, toBuffer
) where ) where
import Prelude import Prelude
import Data.Either as Either import Data.Either as Either
import Effect as Effect import Effect as Effect
import Effect.Class (liftEffect)
import Effect.Aff as Aff import Effect.Aff as Aff
import Effect.Ref as Ref import Effect.Ref as Ref
import HTTPure.Headers as Headers import HTTPure.Headers as Headers
@ -17,6 +20,26 @@ import Node.HTTP as HTTP
import Node.Stream as Stream import Node.Stream as Stream
import Type.Equality as TypeEquals import Type.Equality as TypeEquals
-- | Read the body `Readable` stream out of the incoming request
read :: HTTP.Request -> Stream.Readable ()
read = HTTP.requestAsStream
-- | Slurp the entire `Readable` stream into a `String`
toString :: Stream.Readable () -> Aff.Aff String
toString = toBuffer >=> Buffer.toString Encoding.UTF8 >>> liftEffect
-- | Slurp the entire `Readable` stream into a `Buffer`
toBuffer :: Stream.Readable () -> Aff.Aff Buffer.Buffer
toBuffer stream =
Aff.makeAff \done -> do
bufs <- Ref.new []
Stream.onData stream \buf ->
void $ Ref.modify (_ <> [ buf ]) bufs
Stream.onEnd stream do
body <- Ref.read bufs >>= Buffer.concat
done $ Either.Right body
pure Aff.nonCanceler
-- | Types that implement the `Body` class can be used as a body to an HTTPure -- | Types that implement the `Body` class can be used as a body to an HTTPure
-- | response, and can be used with all the response helpers. -- | response, and can be used with all the response helpers.
class Body b where class Body b where
@ -77,17 +100,3 @@ instance bodyChunked ::
void $ Stream.pipe stream $ HTTP.responseAsStream response void $ Stream.pipe stream $ HTTP.responseAsStream response
Stream.onEnd stream $ done $ Either.Right unit Stream.onEnd stream $ done $ Either.Right unit
pure Aff.nonCanceler pure Aff.nonCanceler
-- | Extract the contents of the body of the HTTP `Request`.
read :: HTTP.Request -> Aff.Aff String
read request =
Aff.makeAff \done -> do
let
stream = HTTP.requestAsStream request
bufs <- Ref.new []
Stream.onData stream \buf ->
void $ Ref.modify (_ <> [ buf ]) bufs
Stream.onEnd stream do
body <- Ref.read bufs >>= Buffer.concat >>= Buffer.toString Encoding.UTF8
done $ Either.Right body
pure Aff.nonCanceler

View File

@ -9,6 +9,7 @@ import Effect.Aff as Aff
import Data.String as String import Data.String as String
import Foreign.Object as Object import Foreign.Object as Object
import Node.HTTP as HTTP import Node.HTTP as HTTP
import Node.Stream as Stream
import HTTPure.Body as Body import HTTPure.Body as Body
import HTTPure.Headers as Headers import HTTPure.Headers as Headers
import HTTPure.Method as Method import HTTPure.Method as Method
@ -24,7 +25,7 @@ type Request =
, path :: Path.Path , path :: Path.Path
, query :: Query.Query , query :: Query.Query
, headers :: Headers.Headers , headers :: Headers.Headers
, body :: String , body :: Stream.Readable ()
, httpVersion :: Version.Version , httpVersion :: Version.Version
, url :: String , url :: String
} }
@ -48,14 +49,12 @@ fullPath request = "/" <> path <> questionMark <> queryParams
-- | Given an HTTP `Request` object, this method will convert it to an HTTPure -- | Given an HTTP `Request` object, this method will convert it to an HTTPure
-- | `Request` object. -- | `Request` object.
fromHTTPRequest :: HTTP.Request -> Aff.Aff Request fromHTTPRequest :: HTTP.Request -> Aff.Aff Request
fromHTTPRequest request = do fromHTTPRequest request = pure
body <- Body.read request
pure $
{ method: Method.read request { method: Method.read request
, path: Path.read request , path: Path.read request
, query: Query.read request , query: Query.read request
, headers: Headers.read request , headers: Headers.read request
, body , body: Body.read request
, httpVersion: Version.read request , httpVersion: Version.read request
, url: HTTP.requestURL request , url: HTTP.requestURL request
} }

View File

@ -1,22 +1,39 @@
module Test.HTTPure.BodySpec where module Test.HTTPure.BodySpec where
import Prelude import Prelude
import Data.Maybe (Maybe(Nothing), fromMaybe)
import Effect.Class as EffectClass import Effect.Class as EffectClass
import Node.Buffer as Buffer import Node.Buffer as Buffer
import Node.Encoding as Encoding import Node.Encoding as Encoding
import Node.Stream as Stream
import Test.Spec as Spec import Test.Spec as Spec
import HTTPure.Body as Body import HTTPure.Body as Body
import HTTPure.Headers as Headers import HTTPure.Headers as Headers
import Test.HTTPure.TestHelpers as TestHelpers import Test.HTTPure.TestHelpers as TestHelpers
import Test.HTTPure.TestHelpers ((?=)) import Test.HTTPure.TestHelpers ((?=), stringToStream)
readSpec :: TestHelpers.Test readSpec :: TestHelpers.Test
readSpec = readSpec =
Spec.describe "read" do Spec.describe "read" do
Spec.it "is the body of the Request" do Spec.it "is the body of the Request" do
request <- TestHelpers.mockRequest "" "GET" "" "test" [] body <- Body.read <$> TestHelpers.mockRequest "" "GET" "" "test" []
body <- Body.read request string <- EffectClass.liftEffect $ fromMaybe "" <$> Stream.readString body Nothing Encoding.UTF8
body ?= "test" string ?= "test"
toStringSpec :: TestHelpers.Test
toStringSpec =
Spec.describe "toString" do
Spec.it "slurps Streams into Strings" do
string <- Body.toString $ stringToStream "foobar"
string ?= "foobar"
toBufferSpec :: TestHelpers.Test
toBufferSpec =
Spec.describe "toBuffer" do
Spec.it "slurps Streams into Buffers" do
buf <- Body.toBuffer $ stringToStream "foobar"
string <- EffectClass.liftEffect $ Buffer.toString Encoding.UTF8 buf
string ?= "foobar"
defaultHeadersSpec :: TestHelpers.Test defaultHeadersSpec :: TestHelpers.Test
defaultHeadersSpec = defaultHeadersSpec =
@ -73,4 +90,6 @@ bodySpec =
Spec.describe "Body" do Spec.describe "Body" do
defaultHeadersSpec defaultHeadersSpec
readSpec readSpec
toStringSpec
toBufferSpec
writeSpec writeSpec

View File

@ -9,7 +9,8 @@ import Test.Spec as Spec
import Test.HTTPure.TestHelpers as TestHelpers import Test.HTTPure.TestHelpers as TestHelpers
import Test.HTTPure.TestHelpers ((?=)) import Test.HTTPure.TestHelpers ((?=))
import Examples.AsyncResponse.Main as AsyncResponse import Examples.AsyncResponse.Main as AsyncResponse
import Examples.Binary.Main as Binary import Examples.BinaryRequest.Main as BinaryRequest
import Examples.BinaryResponse.Main as BinaryResponse
import Examples.Chunked.Main as Chunked import Examples.Chunked.Main as Chunked
import Examples.CustomStack.Main as CustomStack import Examples.CustomStack.Main as CustomStack
import Examples.Headers.Main as Headers import Examples.Headers.Main as Headers
@ -29,13 +30,22 @@ asyncResponseSpec =
EffectClass.liftEffect $ close $ pure unit EffectClass.liftEffect $ close $ pure unit
response ?= "hello world!" response ?= "hello world!"
binarySpec :: TestHelpers.Test binaryRequestSpec :: TestHelpers.Test
binarySpec = binaryRequestSpec =
Spec.it "runs the binary example" do Spec.it "runs the binary request example" do
close <- EffectClass.liftEffect Binary.main close <- EffectClass.liftEffect BinaryRequest.main
binaryBuf <- FS.readFile BinaryResponse.filePath
response <- TestHelpers.postBinary 8080 Object.empty "/" binaryBuf
EffectClass.liftEffect $ close $ pure unit
response ?= "d5e776724dd545d8b54123b46362a553d10257cee688ef1be62166c984b34405"
binaryResponseSpec :: TestHelpers.Test
binaryResponseSpec =
Spec.it "runs the binary response example" do
close <- EffectClass.liftEffect BinaryResponse.main
responseBuf <- TestHelpers.getBinary 8080 Object.empty "/" responseBuf <- TestHelpers.getBinary 8080 Object.empty "/"
EffectClass.liftEffect $ close $ pure unit EffectClass.liftEffect $ close $ pure unit
binaryBuf <- FS.readFile Binary.filePath binaryBuf <- FS.readFile BinaryResponse.filePath
expected <- EffectClass.liftEffect $ Buffer.toArray binaryBuf expected <- EffectClass.liftEffect $ Buffer.toArray binaryBuf
response <- EffectClass.liftEffect $ Buffer.toArray responseBuf response <- EffectClass.liftEffect $ Buffer.toArray responseBuf
response ?= expected response ?= expected
@ -144,7 +154,8 @@ integrationSpec :: TestHelpers.Test
integrationSpec = integrationSpec =
Spec.describe "Integration" do Spec.describe "Integration" do
asyncResponseSpec asyncResponseSpec
binarySpec binaryRequestSpec
binaryResponseSpec
chunkedSpec chunkedSpec
customStackSpec customStackSpec
headersSpec headersSpec

View File

@ -4,6 +4,7 @@ import Prelude
import Data.Tuple as Tuple import Data.Tuple as Tuple
import Foreign.Object as Object import Foreign.Object as Object
import Test.Spec as Spec import Test.Spec as Spec
import HTTPure.Body as Body
import HTTPure.Headers as Headers import HTTPure.Headers as Headers
import HTTPure.Method as Method import HTTPure.Method as Method
import HTTPure.Request as Request import HTTPure.Request as Request
@ -27,8 +28,8 @@ fromHTTPRequestSpec =
mock <- mockRequest mock <- mockRequest
mock.headers ?= Headers.headers mockHeaders mock.headers ?= Headers.headers mockHeaders
Spec.it "contains the correct body" do Spec.it "contains the correct body" do
mock <- mockRequest mockBody <- mockRequest >>= _.body >>> Body.toString
mock.body ?= "body" mockBody ?= "body"
Spec.it "contains the correct httpVersion" do Spec.it "contains the correct httpVersion" do
mock <- mockRequest mock <- mockRequest
mock.httpVersion ?= Version.HTTP1_1 mock.httpVersion ?= Version.HTTP1_1

View File

@ -40,7 +40,7 @@ request ::
String -> String ->
Object.Object String -> Object.Object String ->
String -> String ->
String -> Buffer.Buffer ->
Aff.Aff HTTPClient.Response Aff.Aff HTTPClient.Response
request secure port method headers path body = request secure port method headers path body =
Aff.makeAff \done -> do Aff.makeAff \done -> do
@ -48,7 +48,7 @@ request secure port method headers path body =
let let
stream = HTTPClient.requestAsStream req stream = HTTPClient.requestAsStream req
void void
$ Stream.writeString stream Encoding.UTF8 body $ Stream.write stream body
$ Stream.end stream $ Stream.end stream
$ pure unit $ pure unit
pure Aff.nonCanceler pure Aff.nonCanceler
@ -62,6 +62,31 @@ request secure port method headers path body =
<> HTTPClient.headers := HTTPClient.RequestHeaders headers <> HTTPClient.headers := HTTPClient.RequestHeaders headers
<> HTTPClient.rejectUnauthorized := false <> HTTPClient.rejectUnauthorized := false
-- | Same as `request` but without.
request' ::
Boolean ->
Int ->
String ->
Object.Object String ->
String ->
Aff.Aff HTTPClient.Response
request' secure port method headers path =
EffectClass.liftEffect (Buffer.create 0)
>>= request secure port method headers path
-- | Same as `request` but with a `String` body.
requestString ::
Boolean ->
Int ->
String ->
Object.Object String ->
String ->
String ->
Aff.Aff HTTPClient.Response
requestString secure port method headers path body = do
EffectClass.liftEffect (Buffer.fromString body Encoding.UTF8)
>>= request secure port method headers path
-- | Convert a request to an Aff containing the `Buffer with the response body. -- | Convert a request to an Aff containing the `Buffer with the response body.
toBuffer :: HTTPClient.Response -> Aff.Aff Buffer.Buffer toBuffer :: HTTPClient.Response -> Aff.Aff Buffer.Buffer
toBuffer response = toBuffer response =
@ -91,7 +116,7 @@ get ::
Object.Object String -> Object.Object String ->
String -> String ->
Aff.Aff String Aff.Aff String
get port headers path = request false port "GET" headers path "" >>= toString get port headers path = request' false port "GET" headers path >>= toString
-- | Like `get` but return a response body in a `Buffer` -- | Like `get` but return a response body in a `Buffer`
getBinary :: getBinary ::
@ -99,7 +124,7 @@ getBinary ::
Object.Object String -> Object.Object String ->
String -> String ->
Aff.Aff Buffer.Buffer Aff.Aff Buffer.Buffer
getBinary port headers path = request false port "GET" headers path "" >>= toBuffer getBinary port headers path = request' false port "GET" headers path >>= toBuffer
-- | Run an HTTPS GET with the given url and return an Aff that contains the -- | Run an HTTPS GET with the given url and return an Aff that contains the
-- | string with the response body. -- | string with the response body.
@ -108,7 +133,7 @@ get' ::
Object.Object String -> Object.Object String ->
String -> String ->
Aff.Aff String Aff.Aff String
get' port headers path = request true port "GET" headers path "" >>= toString get' port headers path = request' true port "GET" headers path >>= toString
-- | Run an HTTP POST with the given url and body and return an Aff that -- | Run an HTTP POST with the given url and body and return an Aff that
-- | contains the string with the response body. -- | contains the string with the response body.
@ -118,7 +143,17 @@ post ::
String -> String ->
String -> String ->
Aff.Aff String Aff.Aff String
post port headers path = request false port "POST" headers path >=> toString post port headers path = requestString false port "POST" headers path >=> toString
-- | Run an HTTP POST with the given url and binary buffer body and return an
-- | Aff that contains the string with the response body.
postBinary ::
Int ->
Object.Object String ->
String ->
Buffer.Buffer ->
Aff.Aff String
postBinary port headers path = request false port "POST" headers path >=> toString
-- | Convert a request to an Aff containing the string with the given header -- | Convert a request to an Aff containing the string with the given header
-- | value. -- | value.
@ -137,14 +172,14 @@ getHeader ::
String -> String ->
String -> String ->
Aff.Aff String Aff.Aff String
getHeader port headers path header = extractHeader header <$> request false port "GET" headers path "" getHeader port headers path header = extractHeader header <$> request' false port "GET" headers path
getStatus :: getStatus ::
Int -> Int ->
Object.Object String -> Object.Object String ->
String -> String ->
Aff.Aff Int Aff.Aff Int
getStatus port headers path = HTTPClient.statusCode <$> request false port "GET" headers path "" getStatus port headers path = HTTPClient.statusCode <$> request' false port "GET" headers path
-- | Mock an HTTP Request object -- | Mock an HTTP Request object
foreign import mockRequestImpl :: foreign import mockRequestImpl ::