diff --git a/build/export-specs.vbs b/build/export-specs.vbs index f65cd877..ba5716d4 100644 --- a/build/export-specs.vbs +++ b/build/export-specs.vbs @@ -18,6 +18,9 @@ Set Args = Wscript.Arguments If Args.Length > 0 Then WBPath = Args(0) OutputPath = Args(1) +Else + WBPath = "specs\Excel-REST - Specs.xlsm" + OutputPath = "specs\" End If ' Setup modules to export diff --git a/specs/Excel-REST - Specs.xlsm b/specs/Excel-REST - Specs.xlsm index b7ac75bf..132041cb 100644 Binary files a/specs/Excel-REST - Specs.xlsm and b/specs/Excel-REST - Specs.xlsm differ diff --git a/specs/RestClientAsyncSpecs.bas b/specs/RestClientAsyncSpecs.bas index 86e29f70..56fd543d 100644 --- a/specs/RestClientAsyncSpecs.bas +++ b/specs/RestClientAsyncSpecs.bas @@ -32,6 +32,8 @@ Public Function Specs() As SpecSuite SimpleCallback = "RestClientAsyncSpecs.SimpleCallback" ComplexCallback = "RestClientAsyncSpecs.ComplexCallback" + Dim BodyToString As String + With Specs.It("should pass response to callback") Set Request = New RestRequest Request.Resource = "get" @@ -86,6 +88,68 @@ Public Function Specs() As SpecSuite .Expect(AsyncResponse.StatusDescription).ToEqual "Internal Server Error" End With + With Specs.It("should include binary body in response") + Set Request = New RestRequest + Request.Resource = "howdy" + + Client.ExecuteAsync Request, SimpleCallback + Wait WaitTime + .Expect(AsyncResponse).ToBeDefined + If Not AsyncResponse Is Nothing Then + .Expect(AsyncResponse.Body).ToBeDefined + + If Not IsEmpty(AsyncResponse.Body) Then + For i = LBound(AsyncResponse.Body) To UBound(AsyncResponse.Body) + BodyToString = BodyToString & Chr(AsyncResponse.Body(i)) + Next i + End If + + .Expect(BodyToString).ToEqual "Howdy!" + End If + End With + + With Specs.It("should include cookies in response") + Set Request = New RestRequest + Request.Resource = "cookie" + + Client.ExecuteAsync Request, SimpleCallback + Wait WaitTime + .Expect(AsyncResponse).ToBeDefined + If Not AsyncResponse Is Nothing Then + .Expect(AsyncResponse.Cookies.count).ToEqual 4 + .Expect(AsyncResponse.Cookies("unsigned-cookie")).ToEqual "simple-cookie" + .Expect(AsyncResponse.Cookies("signed-cookie")).ToContain "special-cookie" + .Expect(AsyncResponse.Cookies("tricky;cookie")).ToEqual "includes; semi-colon and space at end " + .Expect(AsyncResponse.Cookies("duplicate-cookie")).ToEqual "B" + End If + End With + + With Specs.It("should include cookies with request") + Set Request = New RestRequest + Request.Resource = "cookie" + + Set Response = Client.Execute(Request) + + Set Request = New RestRequest + Request.Resource = "get" + Request.AddCookie "test-cookie", "howdy" + Request.AddCookie "signed-cookie", Response.Cookies("signed-cookie") + + Client.ExecuteAsync Request, SimpleCallback + Wait WaitTime + .Expect(AsyncResponse).ToBeDefined + If Not AsyncResponse Is Nothing Then + .Expect(AsyncResponse.Data).ToBeDefined + If Not IsEmpty(AsyncResponse.Data) Then + .Expect(AsyncResponse.Data("cookies").count).ToEqual 1 + .Expect(AsyncResponse.Data("cookies")("test-cookie")).ToEqual "howdy" + .Expect(AsyncResponse.Data("signed_cookies").count).ToEqual 1 + .Expect(AsyncResponse.Data("signed_cookies")("signed-cookie")).ToEqual "special-cookie" + End If + End If + End With + + ' Note: Weird async issues can occur if timeout spec isn't last With Specs.It("should return 408 and close request on request timeout") Set Request = New RestRequest Request.Resource = "timeout" @@ -100,6 +164,7 @@ Public Function Specs() As SpecSuite .Expect(AsyncResponse.StatusDescription).ToEqual "Request Timeout" End If .Expect(Request.HttpRequest).ToBeUndefined + Client.TimeoutMS = 2000 End With InlineRunner.RunSuite Specs diff --git a/specs/RestClientSpecs.bas b/specs/RestClientSpecs.bas index eb378b78..19a85253 100644 --- a/specs/RestClientSpecs.bas +++ b/specs/RestClientSpecs.bas @@ -18,6 +18,8 @@ Public Function Specs() As SpecSuite Dim Request As RestRequest Dim Response As RestResponse Dim Body As Dictionary + Dim BodyToString As String + Dim i As Integer Client.BaseUrl = "localhost:3000/" @@ -125,7 +127,7 @@ Public Function Specs() As SpecSuite Set Response = Client.Execute(Request) .Expect(Response.StatusCode).ToEqual 408 .Expect(Response.StatusDescription).ToEqual "Request Timeout" - Debug.Print Response.Content + Client.TimeoutMS = 2000 End With With Specs.It("should add content-length header (if enabled)") @@ -158,6 +160,52 @@ Public Function Specs() As SpecSuite .Expect(Request.Headers.Exists("Content-Length")).ToEqual False End With + With Specs.It("should include binary body in response") + Set Request = New RestRequest + Request.Resource = "howdy" + + Set Response = Client.Execute(Request) + .Expect(Response.Body).ToBeDefined + + If Not IsEmpty(Response.Body) Then + For i = LBound(Response.Body) To UBound(Response.Body) + BodyToString = BodyToString & Chr(Response.Body(i)) + Next i + End If + + .Expect(BodyToString).ToEqual "Howdy!" + End With + + With Specs.It("should include cookies in response") + Set Request = New RestRequest + Request.Resource = "cookie" + + Set Response = Client.Execute(Request) + .Expect(Response.Cookies.count).ToEqual 4 + .Expect(Response.Cookies("unsigned-cookie")).ToEqual "simple-cookie" + .Expect(Response.Cookies("signed-cookie")).ToContain "special-cookie" + .Expect(Response.Cookies("tricky;cookie")).ToEqual "includes; semi-colon and space at end " + .Expect(Response.Cookies("duplicate-cookie")).ToEqual "B" + End With + + With Specs.It("should include cookies with request") + Set Request = New RestRequest + Request.Resource = "cookie" + + Set Response = Client.Execute(Request) + + Set Request = New RestRequest + Request.Resource = "get" + Request.AddCookie "test-cookie", "howdy" + Request.AddCookie "signed-cookie", Response.Cookies("signed-cookie") + + Set Response = Client.Execute(Request) + .Expect(Response.Data("cookies").count).ToEqual 1 + .Expect(Response.Data("cookies")("test-cookie")).ToEqual "howdy" + .Expect(Response.Data("signed_cookies").count).ToEqual 1 + .Expect(Response.Data("signed_cookies")("signed-cookie")).ToEqual "special-cookie" + End With + Set Client = Nothing InlineRunner.RunSuite Specs diff --git a/specs/RestHelpersSpecs.bas b/specs/RestHelpersSpecs.bas index fc1743d7..cc7a3d60 100644 --- a/specs/RestHelpersSpecs.bas +++ b/specs/RestHelpersSpecs.bas @@ -23,6 +23,9 @@ Public Function Specs() As SpecSuite Dim Combined As Object Dim Whitelist As Variant Dim Filtered As Object + Dim ResponseHeaders As String + Dim Headers As Collection + Dim Cookies As Dictionary With Specs.It("should parse json") json = "{""a"":1,""b"":3.14,""c"":""Howdy!"",""d"":true,""e"":[1,2]}" @@ -106,6 +109,10 @@ Public Function Specs() As SpecSuite .Expect(RestHelpers.URLEncode(" !""#$%&'")).ToEqual "%20%21%22%23%24%25%26%27" End With + With Specs.It("should decode url values") + .Expect(RestHelpers.URLDecode("+%20%21%22%23%24%25%26%27")).ToEqual " !""#$%&'" + End With + With Specs.It("should join url with /") .Expect(RestHelpers.JoinUrl("a", "b")).ToEqual "a/b" .Expect(RestHelpers.JoinUrl("a/", "b")).ToEqual "a/b" @@ -148,6 +155,30 @@ Public Function Specs() As SpecSuite .Expect(Filtered.Exists("dangerous")).ToEqual False End With + With Specs.It("should extract headers from response headers") + ResponseHeaders = "Connection: keep -alive" & vbCrLf & _ + "Date: Tue, 18 Feb 2014 15:00:26 GMT" & vbCrLf & _ + "Content-Length: 2" & vbCrLf & _ + "Content-Type: text/plain" & vbCrLf & _ + "Set-Cookie: unsigned-cookie=simple-cookie; Path=/" & vbCrLf & _ + "Set-Cookie: signed-cookie=s%3Aspecial-cookie.1Ghgw2qpDY93QdYjGFPDLAsa3%2FI0FCtO%2FvlxoHkzF%2BY; Path=/" & vbCrLf & _ + "Set-Cookie: duplicate-cookie=A; Path=/" & vbCrLf & _ + "Set-Cookie: duplicate-cookie=B" & vbCrLf & _ + "X-Powered-By: Express" + + Set Headers = RestHelpers.ExtractHeadersFromResponseHeaders(ResponseHeaders) + .Expect(Headers.count).ToEqual 9 + .Expect(Headers.Item(5)("key")).ToEqual "Set-Cookie" + .Expect(Headers.Item(5)("value")).ToEqual "unsigned-cookie=simple-cookie; Path=/" + End With + + With Specs.It("should extract cookies from response headers") + Set Cookies = RestHelpers.ExtractCookiesFromResponseHeaders(ResponseHeaders) + .Expect(Cookies.count).ToEqual 3 + .Expect(Cookies("unsigned-cookie")).ToEqual "simple-cookie" + .Expect(Cookies("duplicate-cookie")).ToEqual "B" + End With + With Specs.It("should encode string to base64") .Expect(RestHelpers.EncodeStringToBase64("Howdy!")).ToEqual "SG93ZHkh" End With diff --git a/specs/server.js b/specs/server.js index f69561af..a015ea02 100644 --- a/specs/server.js +++ b/specs/server.js @@ -9,6 +9,7 @@ app.use(function(req, res, next){ app.use(plain()); app.use(express.json()); app.use(express.urlencoded()); +app.use(express.cookieParser('cookie-secret')); // Standard app.get('/get', standardResponse); @@ -36,6 +37,21 @@ app.get('/json', function(req, res) { res.json({a: '1', b: 2, c: 3.14, d: false, e: [4, 5], f: {a: '1', b: 2}}); }); +// Cookies +app.get('/cookie', function(req, res) { + res.cookie('unsigned-cookie', 'simple-cookie'); + res.cookie('signed-cookie', 'special-cookie', {signed: true}); + res.cookie('tricky;cookie', 'includes; semi-colon and space at end '); + res.cookie('duplicate-cookie', 'A'); + res.cookie('duplicate-cookie', 'B'); + res.send(200); +}); + +// Simple text in body +app.get('/howdy', function(req, res) { + res.send(200, 'Howdy!'); +}); + function standardResponse(req, res) { res.send(200, { method: req.route.method.toUpperCase(), @@ -44,7 +60,9 @@ function standardResponse(req, res) { 'content-type': req.get('content-type'), 'custom': req.get('custom') }, - body: req.text || req.body + body: req.text || req.body, + cookies: req.cookies, + signed_cookies: req.signedCookies }); } diff --git a/src/RestHelpers.bas b/src/RestHelpers.bas index b51b4d12..0f1d4714 100644 --- a/src/RestHelpers.bas +++ b/src/RestHelpers.bas @@ -93,34 +93,34 @@ Public Function ConvertToJSON(Obj As Object) As String End Function '' -' URL Encode the given raw values +' URL Encode the given string ' ' @param {Variant} rawVal The raw string to encode ' @param {Boolean} [spaceAsPlus=False] Use plus sign for encoded spaces (otherwise %20) ' @return {String} Encoded string ' --------------------------------------------- ' -Public Function URLEncode(rawVal As Variant, Optional spaceAsPlus As Boolean = False) As String +Public Function URLEncode(rawVal As Variant, Optional SpaceAsPlus As Boolean = False) As String Dim urlVal As String - Dim stringLen As Long + Dim StringLen As Long urlVal = CStr(rawVal) - stringLen = Len(urlVal) + StringLen = Len(urlVal) - If stringLen > 0 Then - ReDim Result(stringLen) As String + If StringLen > 0 Then + ReDim Result(StringLen) As String Dim i As Long, charCode As Integer Dim char As String, space As String ' Set space value - If spaceAsPlus Then + If SpaceAsPlus Then space = "+" Else space = "%20" End If ' Loop through string characters - For i = 1 To stringLen + For i = 1 To StringLen ' Get character and ascii code char = Mid$(urlVal, i, 1) charCode = asc(char) @@ -143,6 +143,40 @@ Public Function URLEncode(rawVal As Variant, Optional spaceAsPlus As Boolean = F End If End Function +'' +' URL Decode the given encoded string +' +' @param {String} EncodedString +' @return {String} Decoded string +' --------------------------------------------- ' + +Public Function URLDecode(EncodedString As String) As String + Dim StringLen As Long + StringLen = Len(EncodedString) + + If StringLen > 0 Then + Dim i As Long + Dim Result As String + Dim Temp As String + + For i = 1 To StringLen + Temp = Mid$(EncodedString, i, 1) + + If Temp = "+" Then + Temp = " " + ElseIf Temp = "%" And StringLen >= i + 2 Then + Temp = Mid$(EncodedString, i + 1, 2) + Temp = Chr(CDec("&H" & Temp)) + + i = i + 2 + End If + + Result = Result & Temp + Next i + + URLDecode = Result + End If +End Function '' ' Join Url with / @@ -275,6 +309,11 @@ Public Sub SetHeaders(ByRef Http As Object, Request As RestRequest) For Each HeaderKey In Request.Headers.keys() Http.setRequestHeader HeaderKey, Request.Headers(HeaderKey) Next HeaderKey + + Dim CookieKey As Variant + For Each CookieKey In Request.Cookies.keys() + Http.setRequestHeader "Cookie", CookieKey & "=" & Request.Cookies(CookieKey) + Next CookieKey End Sub '' @@ -312,7 +351,7 @@ Public Function ExecuteRequest(ByRef Http As Object, ByRef Request As RestReques ' Send the request and handle response Http.Send Request.Body - Set Response = Request.CreateResponseFromHttp(Http) + Set Response = RestHelpers.CreateResponseFromHttp(Http, Request.Format) ErrorHandling: @@ -320,7 +359,7 @@ ErrorHandling: If Err.Number <> 0 Then If InStr(Err.Description, "The operation timed out") > 0 Then ' Return 408 - Set Response = Request.CreateResponse(StatusCodes.RequestTimeout, "Request Timeout") + Set Response = RestHelpers.CreateResponse(StatusCodes.RequestTimeout, "Request Timeout") Err.Clear Else ' Rethrow error @@ -359,6 +398,109 @@ ErrorHandling: Err.Raise Err.Number, Description:=Err.Description End Sub +'' +' Create response for http +' @param {Object} Http +' @param {AvailableFormats} [Format=json] +' @return {RestResponse} +' --------------------------------------------- ' + +Public Function CreateResponseFromHttp(ByRef Http As Object, Optional Format As AvailableFormats = AvailableFormats.json) As RestResponse + Set CreateResponseFromHttp = New RestResponse + + CreateResponseFromHttp.StatusCode = Http.Status + CreateResponseFromHttp.StatusDescription = Http.StatusText + CreateResponseFromHttp.Body = Http.ResponseBody + CreateResponseFromHttp.Content = Http.ResponseText + + ' Convert content to data by format + Select Case Format + Case Else + Set CreateResponseFromHttp.Data = RestHelpers.ParseJSON(Http.ResponseText) + End Select + + ' Extract cookies + Set CreateResponseFromHttp.Cookies = ExtractCookiesFromResponseHeaders(Http.getAllResponseHeaders) +End Function + +'' +' Create simple response +' @param {StatusCodes} StatusCode +' @param {String} StatusDescription +' @return {RestResponse} +' --------------------------------------------- ' + +Public Function CreateResponse(StatusCode As StatusCodes, StatusDescription As String) As RestResponse + Set CreateResponse = New RestResponse + CreateResponse.StatusCode = StatusCode + CreateResponse.StatusDescription = StatusDescription +End Function + +'' +' Extract cookies from response headers +' +' @param {String} ResponseHeaders +' @return {Dictionary} Cookies +' --------------------------------------------- ' + +Public Function ExtractCookiesFromResponseHeaders(ResponseHeaders As String) As Dictionary + Dim Cookies As New Dictionary + Dim Cookie As String + Dim Key As String + Dim Value As String + Dim Headers As Collection + Dim Header As Dictionary + + Set Headers = ExtractHeadersFromResponseHeaders(ResponseHeaders) + For Each Header In Headers + If Header("key") = "Set-Cookie" Then + Cookie = Header("value") + Key = Mid$(Cookie, 1, InStr(1, Cookie, "=") - 1) + Value = Mid$(Cookie, InStr(1, Cookie, "=") + 1, Len(Cookie)) + + If InStr(1, Value, ";") Then + Value = Mid$(Value, 1, InStr(1, Value, ";") - 1) + End If + + If Cookies.Exists(Key) Then + Cookies(Key) = URLDecode(Value) + Else + Cookies.Add Key, URLDecode(Value) + End If + End If + Next Header + + Set ExtractCookiesFromResponseHeaders = Cookies +End Function + +'' +' Extract headers from response headers +' +' @param {String} ResponseHeaders +' @return {Collection} Headers +' --------------------------------------------- ' + +Public Function ExtractHeadersFromResponseHeaders(ResponseHeaders As String) As Collection + Dim Headers As New Collection + Dim Header As Dictionary + + Dim Lines As Variant + Lines = Split(ResponseHeaders, vbCrLf) + + Dim i As Integer + For i = LBound(Lines) To UBound(Lines) + If Lines(i) <> "" And InStr(1, Lines(i), ":") > 0 Then + Set Header = New Dictionary + + Header.Add "key", Trim(Mid$(Lines(i), 1, InStr(1, Lines(i), ":") - 1)) + Header.Add "value", Trim(Mid$(Lines(i), InStr(1, Lines(i), ":") + 1, Len(Lines(i)))) + Headers.Add Header + End If + Next i + + Set ExtractHeadersFromResponseHeaders = Headers +End Function + ' ======================================================================================== ' ' ' Timeout Timing diff --git a/src/RestRequest.cls b/src/RestRequest.cls index bde87fdb..ed0af4a0 100644 --- a/src/RestRequest.cls +++ b/src/RestRequest.cls @@ -29,6 +29,7 @@ Private pHeaders As Dictionary Private pParameters As Dictionary Private pQuerystringParams As Dictionary Private pUrlSegments As Dictionary +Private pCookies As Dictionary Private pBody As Dictionary Private pBodyString As String Private pContentType As String @@ -65,38 +66,46 @@ Public CallbackArgs As Variant Public IncludeCacheBreaker As Boolean Public IncludeContentLength As Boolean -Public Property Get Headers() As Object +Public Property Get Headers() As Dictionary If pHeaders Is Nothing Then: Set pHeaders = New Dictionary Set Headers = pHeaders End Property -Public Property Let Headers(Value As Object) +Public Property Let Headers(Value As Dictionary) Set pHeaders = Value End Property -Public Property Get Parameters() As Object +Public Property Get Parameters() As Dictionary If pParameters Is Nothing Then: Set pParameters = New Dictionary Set Parameters = pParameters End Property -Public Property Let Parameters(Value As Object) +Public Property Let Parameters(Value As Dictionary) Set pParameters = Value End Property -Public Property Get QuerystringParams() As Object +Public Property Get QuerystringParams() As Dictionary If pQuerystringParams Is Nothing Then: Set pQuerystringParams = New Dictionary Set QuerystringParams = pQuerystringParams End Property -Public Property Let QuerystringParams(Value As Object) +Public Property Let QuerystringParams(Value As Dictionary) Set pQuerystringParams = Value End Property -Public Property Get UrlSegments() As Object +Public Property Get UrlSegments() As Dictionary If pUrlSegments Is Nothing Then: Set pUrlSegments = New Dictionary Set UrlSegments = pUrlSegments End Property -Public Property Let UrlSegments(Value As Object) +Public Property Let UrlSegments(Value As Dictionary) Set pUrlSegments = Value End Property +Public Property Get Cookies() As Dictionary + If pCookies Is Nothing Then: Set pCookies = New Dictionary + Set Cookies = pCookies +End Property +Public Property Let Cookies(Value As Dictionary) + Set pCookies = Value +End Property + Public Property Get FormattedResource() As String Dim segment As Variant Dim parameterKey As Variant @@ -302,6 +311,21 @@ Public Sub AddQuerystringParam(Key As String, Value As Variant) End If End Sub +'' +' Add cookie to request +' +' @param {String} key +' @param {Variant} value +' --------------------------------------------- ' + +Public Sub AddCookie(Key As String, Value As Variant) + If Not Me.Cookies.Exists(Key) Then + Me.Cookies.Add Key, Value + Else + Me.Cookies(Key) = Value + End If +End Sub + '' ' Add body to request ' @@ -322,39 +346,6 @@ Public Function AddBodyString(bodyVal As String) pBodyString = bodyVal End Function -'' -' Helper for creating response -' -' @param {StatusCodes} StatusCode -' @param {String} StatusDescription -' @param {String} [Content=""] -' @return {RestResponse} -' --------------------------------------------- ' - -Public Function CreateResponse(StatusCode As StatusCodes, StatusDescription As String, Optional Body As Variant, Optional Content As String = "") As RestResponse - Set CreateResponse = New RestResponse - CreateResponse.StatusCode = StatusCode - CreateResponse.StatusDescription = StatusDescription - CreateResponse.Content = Content - CreateResponse.Body = Body - - Select Case Me.Format - Case Else - Set CreateResponse.Data = RestHelpers.ParseJSON(Content) - End Select -End Function - -'' -' Helper for creating response -' -' @param {XMLHttpRequest} Http -' @return {RestResponse} -' --------------------------------------------- ' - -Public Function CreateResponseFromHttp(Http As Object) As RestResponse - Set CreateResponseFromHttp = Me.CreateResponse(Http.Status, Http.StatusText, Http.ResponseBody, Http.ResponseText) -End Function - '' ' Process asynchronous requests ' @@ -377,7 +368,7 @@ Attribute ReadyStateChangeHandler.VB_UserMemId = 0 Me.StopTimeoutTimer ' Callback - RunCallback Me.CreateResponseFromHttp(Me.HttpRequest) + RunCallback RestHelpers.CreateResponseFromHttp(Me.HttpRequest, Me.Format) ' Request is finished, clean up Set Me.HttpRequest = Nothing @@ -411,7 +402,7 @@ End Sub Public Sub TimedOut() ' Callback - RunCallback Me.CreateResponse(StatusCodes.RequestTimeout, "Request Timeout") + RunCallback RestHelpers.CreateResponse(StatusCodes.RequestTimeout, "Request Timeout") ' Request is finished, clean up Set Me.HttpRequest = Nothing diff --git a/src/RestResponse.cls b/src/RestResponse.cls index 0c1d3634..0db56ac6 100644 --- a/src/RestResponse.cls +++ b/src/RestResponse.cls @@ -27,3 +27,9 @@ Public StatusDescription As String Public Content As String Public Data As Variant Public Body As Variant +Public Cookies As Dictionary + +Private Sub Class_Initialize() + Body = Array() + Set Cookies = New Dictionary +End Sub