purescript-httpurple/test/Test/HTTPure/TestHelpers.purs

177 lines
5.9 KiB
Haskell
Raw Normal View History

2017-10-26 21:19:30 +00:00
module Test.HTTPure.TestHelpers where
2017-07-10 10:17:13 +00:00
import Prelude
2017-07-10 10:17:13 +00:00
import Effect as Effect
import Effect.Aff as Aff
import Effect.Class as EffectClass
import Effect.Ref as Ref
import Data.Array as Array
2018-02-25 02:51:07 +00:00
import Data.Either as Either
import Data.List as List
import Data.Maybe as Maybe
2017-07-23 06:13:47 +00:00
import Data.Options ((:=))
import Data.String as StringUtil
2017-09-26 06:08:07 +00:00
import Data.Tuple as Tuple
import Foreign.Object as Object
import Node.Buffer as Buffer
2017-07-10 10:17:13 +00:00
import Node.Encoding as Encoding
import Node.HTTP as HTTP
import Node.HTTP.Client as HTTPClient
import Node.Stream as Stream
import Test.Spec as Spec
import Test.Spec.Assertions as Assertions
2017-07-10 10:17:13 +00:00
import Unsafe.Coerce as Coerce
infix 1 Assertions.shouldEqual as ?=
2017-07-10 10:17:13 +00:00
-- | The type for integration tests.
type Test = Spec.Spec Unit
2017-07-10 10:17:13 +00:00
-- | The type for the entire test suite.
type TestSuite = Effect.Effect Unit
2017-07-10 10:17:13 +00:00
-- | Given a URL, a failure handler, and a success handler, create an HTTP
-- | client request.
request :: Boolean ->
2017-07-18 17:09:03 +00:00
Int ->
String ->
Object.Object String ->
2017-07-18 17:09:03 +00:00
String ->
String ->
Aff.Aff HTTPClient.Response
2018-02-25 02:51:07 +00:00
request secure port method headers path body = Aff.makeAff \done -> do
req <- HTTPClient.request options $ Either.Right >>> done
2017-07-18 17:09:03 +00:00
let stream = HTTPClient.requestAsStream req
2017-07-23 06:13:47 +00:00
_ <- Stream.writeString stream Encoding.UTF8 body $ pure unit
Stream.end stream $ pure unit
2018-02-25 02:51:07 +00:00
pure Aff.nonCanceler
2017-07-18 17:09:03 +00:00
where
options =
2017-07-23 19:17:02 +00:00
HTTPClient.protocol := (if secure then "https:" else "http:") <>
2017-07-23 06:13:47 +00:00
HTTPClient.method := method <>
HTTPClient.hostname := "localhost" <>
HTTPClient.port := port <>
HTTPClient.path := path <>
2017-07-23 19:17:02 +00:00
HTTPClient.headers := HTTPClient.RequestHeaders headers <>
HTTPClient.rejectUnauthorized := false
2017-07-10 10:17:13 +00:00
-- | Convert a request to an Aff containing the `Buffer with the response body.
toBuffer :: HTTPClient.Response -> Aff.Aff Buffer.Buffer
toBuffer response = Aff.makeAff \done -> do
let stream = HTTPClient.responseAsStream response
chunks <- Ref.new List.Nil
Stream.onData stream $ \new -> Ref.modify_ (List.Cons new) chunks
Stream.onEnd stream $
Ref.read chunks
>>= List.reverse >>> Array.fromFoldable >>> Buffer.concat
>>= Either.Right >>> done
pure Aff.nonCanceler
2017-07-10 10:17:13 +00:00
-- | Convert a request to an Aff containing the string with the response body.
toString :: HTTPClient.Response -> Aff.Aff String
toString resp = do
buf <- toBuffer resp
EffectClass.liftEffect $ Buffer.toString Encoding.UTF8 buf
2017-07-10 10:17:13 +00:00
-- | Run an HTTP GET with the given url and return an Aff that contains the
-- | string with the response body.
get :: Int ->
Object.Object String ->
2017-07-18 17:09:03 +00:00
String ->
Aff.Aff String
2017-07-23 19:17:02 +00:00
get port headers path = request false port "GET" headers path "" >>= toString
-- | Like `get` but return a response body in a `Buffer`
getBinary :: Int ->
Object.Object String ->
String ->
Aff.Aff Buffer.Buffer
getBinary port headers path =
request false port "GET" headers path "" >>= toBuffer
2017-07-23 19:17:02 +00:00
-- | Run an HTTPS GET with the given url and return an Aff that contains the
-- | string with the response body.
get' :: Int ->
Object.Object String ->
2017-07-23 19:17:02 +00:00
String ->
Aff.Aff String
2017-07-23 19:17:02 +00:00
get' port headers path = request true port "GET" headers path "" >>= toString
2017-07-18 17:09:03 +00:00
-- | Run an HTTP POST with the given url and body and return an Aff that
-- | contains the string with the response body.
post :: Int ->
Object.Object String ->
2017-07-18 17:09:03 +00:00
String ->
String ->
Aff.Aff String
2017-07-23 19:17:02 +00:00
post port headers path = request false port "POST" headers path >=> toString
-- | Convert a request to an Aff containing the string with the given header
-- | value.
extractHeader :: String -> HTTPClient.Response -> String
extractHeader header = unmaybe <<< lookup <<< HTTPClient.responseHeaders
where
unmaybe = Maybe.fromMaybe ""
lookup = Object.lookup $ StringUtil.toLower header
-- | Run an HTTP GET with the given url and return an Aff that contains the
-- | string with the header value for the given header.
getHeader :: Int ->
Object.Object String ->
String ->
String ->
Aff.Aff String
2017-07-18 17:09:03 +00:00
getHeader port headers path header =
2017-07-23 19:17:02 +00:00
extractHeader header <$> request false port "GET" headers path ""
2017-07-10 10:17:13 +00:00
getStatus :: Int ->
Object.Object String ->
String ->
Aff.Aff Int
getStatus port headers path =
HTTPClient.statusCode <$> request false port "GET" headers path ""
2017-07-10 10:17:13 +00:00
-- | Mock an HTTP Request object
2017-09-26 06:08:07 +00:00
foreign import mockRequestImpl ::
2017-07-18 05:25:14 +00:00
String ->
String ->
String ->
String ->
Object.Object String ->
Effect.Effect HTTP.Request
2017-07-10 10:17:13 +00:00
2017-09-26 06:08:07 +00:00
-- | Mock an HTTP Request object
mockRequest :: String ->
String ->
2017-09-26 06:08:07 +00:00
String ->
String ->
Array (Tuple.Tuple String String) ->
Aff.Aff HTTP.Request
mockRequest httpVersion method url body =
EffectClass.liftEffect <<< mockRequestImpl httpVersion method url body <<< Object.fromFoldable
-- | Mock an HTTP Response object
foreign import mockResponse :: Effect.Effect HTTP.Response
-- | Get the current body from an HTTP Response object (note this will only work
-- | with an object returned from mockResponse).
getResponseBody :: HTTP.Response -> String
getResponseBody = _.body <<< Coerce.unsafeCoerce
-- | Get the currently set status from an HTTP Response object.
getResponseStatus :: HTTP.Response -> Int
getResponseStatus = _.statusCode <<< Coerce.unsafeCoerce
-- | Get all current headers on the HTTP Response object.
getResponseHeaders :: HTTP.Response -> Object.Object String
getResponseHeaders = Coerce.unsafeCoerce <<< _.headers <<< Coerce.unsafeCoerce
-- | Get the current value for the header on the HTTP Response object.
getResponseHeader :: String -> HTTP.Response -> String
getResponseHeader header =
Maybe.fromMaybe "" <<< Object.lookup header <<< getResponseHeaders
-- | Create a stream out of a string.
foreign import stringToStream :: String -> Stream.Readable ()