Cache Body toBuffer/toString Results (#189)

* cache `body` processing results (Buffer, String) with `Ref`

* add `readBodyAs(Buffer|Stream|String)` for accessing `body`

* fix tests

* add tests for `readBodyAsBuffer` and `readBodyAsString`

* move Body to HTTPure.Body and rename it to RequestBody

* add HTTPure.Body.toStream

* consolidate `readBodyAs(Buffer|String)` into `to(Buffer|String)`

and move `Ref` from top level `body` down to `buffer` and `string` fields

* fix tests

* import constructors explicitly

* revert changes

This reverts commit e53188c3e6d74ca00d3d891829ca91f0803b870b.

* update `Body.read` to return `RequestBody`
This commit is contained in:
Wenbo Gao 2021-12-06 23:59:53 -05:00 committed by GitHub
parent 3f20f1cff8
commit 4319cffed6
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
4 changed files with 132 additions and 46 deletions

View File

@ -11,7 +11,7 @@ module HTTPure
, module HTTPure.Status , module HTTPure.Status
) where ) where
import HTTPure.Body (toString, toBuffer) import HTTPure.Body (toBuffer, toStream, toString)
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,46 +1,98 @@
module HTTPure.Body module HTTPure.Body
( class Body ( class Body
, RequestBody
, defaultHeaders , defaultHeaders
, write , write
, read , read
, toString
, toBuffer , toBuffer
, toStream
, toString
) where ) where
import Prelude import Prelude
import Data.Either (Either(Right)) import Data.Either (Either(Right))
import Data.Maybe (Maybe(Just, Nothing))
import Effect (Effect) import Effect (Effect)
import Effect.Class (liftEffect)
import Effect.Aff (Aff, makeAff, nonCanceler) import Effect.Aff (Aff, makeAff, nonCanceler)
import Effect.Ref (read) as Ref import Effect.Class (liftEffect)
import Effect.Ref (new, modify) import Effect.Ref (Ref)
import Effect.Ref (read, modify, new, write) as Ref
import HTTPure.Headers (Headers, header) import HTTPure.Headers (Headers, header)
import Node.Buffer (toString) as Buffer
import Node.Buffer (Buffer, concat, fromString, size) import Node.Buffer (Buffer, concat, fromString, size)
import Node.Buffer (toString) as Buffer
import Node.Encoding (Encoding(UTF8)) import Node.Encoding (Encoding(UTF8))
import Node.HTTP (Request, Response, requestAsStream, responseAsStream) import Node.HTTP (Request, Response, requestAsStream, responseAsStream)
import Node.Stream (write) as Stream
import Node.Stream (Stream, Readable, onData, onEnd, writeString, pipe, end) import Node.Stream (Stream, Readable, onData, onEnd, writeString, pipe, end)
import Node.Stream (write) as Stream
import Type.Equality (class TypeEquals, to) import Type.Equality (class TypeEquals, to)
type RequestBody =
{ buffer :: Ref (Maybe Buffer)
, stream :: Readable ()
, string :: Ref (Maybe String)
}
-- | Read the body `Readable` stream out of the incoming request -- | Read the body `Readable` stream out of the incoming request
read :: Request -> Readable () read :: Request -> Effect RequestBody
read = requestAsStream read request = do
buffer <- Ref.new Nothing
string <- Ref.new Nothing
pure
{ buffer
, stream: requestAsStream request
, string
}
-- | Slurp the entire `Readable` stream into a `String` -- | Turn `RequestBody` into a `String`
toString :: Readable () -> Aff String -- |
toString = toBuffer >=> Buffer.toString UTF8 >>> liftEffect -- | This drains the `Readable` stream in `RequestBody` for the first time
-- | and returns cached result from then on.
toString :: RequestBody -> Aff String
toString requestBody = do
maybeString <-
liftEffect
$ Ref.read requestBody.string
case maybeString of
Nothing -> do
buffer <- toBuffer requestBody
string <- liftEffect
$ Buffer.toString UTF8 buffer
liftEffect
$ Ref.write (Just string) requestBody.string
pure string
Just string -> pure string
-- | Slurp the entire `Readable` stream into a `Buffer` -- | Turn `RequestBody` into a `Buffer`
toBuffer :: Readable () -> Aff Buffer -- |
toBuffer stream = -- | This drains the `Readable` stream in `RequestBody` for the first time
makeAff \done -> do -- | and returns cached result from then on.
bufs <- new [] toBuffer :: RequestBody -> Aff Buffer
onData stream \buf -> void $ modify (_ <> [ buf ]) bufs toBuffer requestBody = do
onEnd stream do maybeBuffer <-
body <- Ref.read bufs >>= concat liftEffect
done $ Right body $ Ref.read requestBody.buffer
pure nonCanceler case maybeBuffer of
Nothing -> do
buffer <- streamToBuffer requestBody.stream
liftEffect
$ Ref.write (Just buffer) requestBody.buffer
pure buffer
Just buffer -> pure buffer
where
-- | Slurp the entire `Readable` stream into a `Buffer`
streamToBuffer :: Readable () -> Aff Buffer
streamToBuffer stream =
makeAff \done -> do
bufs <- Ref.new []
onData stream \buf -> void $ Ref.modify (_ <> [ buf ]) bufs
onEnd stream do
body <- Ref.read bufs >>= concat
done $ Right body
pure nonCanceler
-- | Return the `Readable` stream directly from `RequestBody`
toStream :: RequestBody -> Readable ()
toStream = _.stream
-- | 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.

View File

@ -5,12 +5,11 @@ module HTTPure.Request
) where ) where
import Prelude import Prelude
import Effect.Aff (Aff)
import Data.String (joinWith) import Data.String (joinWith)
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Foreign.Object (isEmpty, toArrayWithKey) import Foreign.Object (isEmpty, toArrayWithKey)
import Node.HTTP (requestURL) import HTTPure.Body (RequestBody)
import Node.HTTP (Request) as HTTP
import Node.Stream (Readable)
import HTTPure.Body (read) as Body import HTTPure.Body (read) as Body
import HTTPure.Headers (Headers) import HTTPure.Headers (Headers)
import HTTPure.Headers (read) as Headers import HTTPure.Headers (read) as Headers
@ -23,6 +22,8 @@ import HTTPure.Query (read) as Query
import HTTPure.Utils (encodeURIComponent) import HTTPure.Utils (encodeURIComponent)
import HTTPure.Version (Version) import HTTPure.Version (Version)
import HTTPure.Version (read) as Version import HTTPure.Version (read) as Version
import Node.HTTP (Request) as HTTP
import Node.HTTP (requestURL)
-- | The `Request` type is a `Record` type that includes fields for accessing -- | The `Request` type is a `Record` type that includes fields for accessing
-- | the different parts of the HTTP request. -- | the different parts of the HTTP request.
@ -31,7 +32,7 @@ type Request =
, path :: Path , path :: Path
, query :: Query , query :: Query
, headers :: Headers , headers :: Headers
, body :: Readable () , body :: RequestBody
, httpVersion :: Version , httpVersion :: Version
, url :: String , url :: String
} }
@ -51,12 +52,15 @@ 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 Request fromHTTPRequest :: HTTP.Request -> Aff Request
fromHTTPRequest request = pure fromHTTPRequest request = do
{ method: Method.read request body <- liftEffect $ Body.read request
, path: Path.read request pure
, query: Query.read request { method: Method.read request
, headers: Headers.read request , path: Path.read request
, body: Body.read request , query: Query.read request
, httpVersion: Version.read request , headers: Headers.read request
, url: requestURL request , body
} , httpVersion: Version.read request
, url: requestURL request
}

View File

@ -1,39 +1,69 @@
module Test.HTTPure.BodySpec where module Test.HTTPure.BodySpec where
import Prelude import Prelude
import Data.Maybe (Maybe(Nothing), fromMaybe) import Data.Maybe (Maybe(Nothing), fromMaybe)
import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Node.Buffer (toString) as Buffer import Effect.Ref (new) as Ref
import HTTPure.Body (RequestBody, defaultHeaders, read, toBuffer, toStream, toString, write)
import HTTPure.Headers (header)
import Node.Buffer (Buffer, fromString) import Node.Buffer (Buffer, fromString)
import Node.Buffer (toString) as Buffer
import Node.Encoding (Encoding(UTF8)) import Node.Encoding (Encoding(UTF8))
import Node.Stream (readString) import Node.Stream (readString)
import Test.Spec (describe, it)
import HTTPure.Body (read, toString, toBuffer, defaultHeaders, write)
import HTTPure.Headers (header)
import Test.HTTPure.TestHelpers (Test, (?=), mockRequest, mockResponse, getResponseBody, stringToStream) import Test.HTTPure.TestHelpers (Test, (?=), mockRequest, mockResponse, getResponseBody, stringToStream)
import Test.Spec (describe, it)
mockRequestBody :: String -> Aff RequestBody
mockRequestBody body =
liftEffect do
buffer <- Ref.new Nothing
string <- Ref.new Nothing
pure
{ buffer
, stream: stringToStream body
, string
}
readSpec :: Test readSpec :: Test
readSpec = readSpec =
describe "read" do describe "read" do
it "is the body of the Request" do it "is the body of the Request" do
body <- read <$> mockRequest "" "GET" "" "test" [] body <- (liftEffect <<< read) =<< mockRequest "" "GET" "" "test" []
string <- liftEffect $ fromMaybe "" <$> readString body Nothing UTF8 string <- liftEffect $ fromMaybe "" <$> readString (toStream body) Nothing UTF8
string ?= "test" string ?= "test"
toStringSpec :: Test toStringSpec :: Test
toStringSpec = toStringSpec =
describe "toString" do describe "toString" do
it "slurps Streams into Strings" do it "turns RequestBody into a String" do
string <- toString $ stringToStream "foobar" requestBody <- mockRequestBody "foobar"
string <- toString requestBody
string ?= "foobar" string ?= "foobar"
it "is idempotent" do
requestBody <- mockRequestBody "foobar"
string1 <- toString requestBody
string2 <- toString requestBody
string1 ?= string2
toBufferSpec :: Test toBufferSpec :: Test
toBufferSpec = toBufferSpec =
describe "toBuffer" do describe "toBuffer" do
it "slurps Streams into Buffers" do it "turns RequestBody into a Buffer" do
buf <- toBuffer $ stringToStream "foobar" requestBody <- mockRequestBody "foobar"
buf <- toBuffer requestBody
string <- liftEffect $ Buffer.toString UTF8 buf string <- liftEffect $ Buffer.toString UTF8 buf
string ?= "foobar" string ?= "foobar"
it "is idempotent" do
requestBody <- mockRequestBody "foobar"
buffer1 <- toBuffer requestBody
buffer2 <- toBuffer requestBody
string1 <- bufferToString buffer1
string2 <- bufferToString buffer2
string1 ?= string2
where
bufferToString = liftEffect <<< Buffer.toString UTF8
defaultHeadersSpec :: Test defaultHeadersSpec :: Test
defaultHeadersSpec = defaultHeadersSpec =