Skip to content

Commit a495dc0

Browse files
committed
Merge pull request #92 from VBA-tools/curl-url-header-bugfixes
Bugfixes (cURL escaping, url-encode UrlSegments, add SetHeader)
2 parents a25373f + 4e0dc28 commit a495dc0

11 files changed

+95
-42
lines changed

authenticators/DigestAuthenticator.cls

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -81,7 +81,7 @@ End Sub
8181
Private Sub IWebAuthenticator_BeforeExecute(ByVal Client As WebClient, ByRef Request As WebRequest)
8282
If Me.IsAuthenticated Then
8383
Me.RequestCount = Me.RequestCount + 1
84-
Request.AddHeader "Authorization", CreateHeader(Client, Request)
84+
Request.SetHeader "Authorization", CreateHeader(Client, Request)
8585
End If
8686
End Sub
8787

@@ -97,7 +97,7 @@ Private Sub IWebAuthenticator_AfterExecute(ByVal Client As WebClient, ByVal Requ
9797
WebHelpers.LogDebug "Extract Authenticate and retry 401 request " & Client.GetFullUrl(Request), "Digest.AfterExecute"
9898
ExtractAuthenticateInformation Response
9999

100-
Request.AddHeader "Authorization", CreateHeader(Client, Request)
100+
Request.SetHeader "Authorization", CreateHeader(Client, Request)
101101
Response.Update Client.Execute(Request)
102102
End If
103103
End Sub
@@ -122,7 +122,7 @@ End Sub
122122
''
123123
Private Sub IWebAuthenticator_PrepareCurl(ByVal Client As WebClient, ByVal Request As WebRequest, ByRef Curl As String)
124124
' http://curl.haxx.se/docs/manpage.html#--digest
125-
Curl = Curl & " --digest --user " & Me.Username & ":" & Me.Password
125+
Curl = Curl & " --digest --user " & WebHelpers.PrepareTextForShell(Me.Username) & ":" & WebHelpers.PrepareTextForShell(Me.Password)
126126
End Sub
127127

128128
''

authenticators/GoogleAuthenticator.cls

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -242,7 +242,7 @@ Private Sub IWebAuthenticator_BeforeExecute(ByVal Client As WebClient, ByRef Req
242242
Me.Token = Me.GetToken(Client)
243243
End If
244244

245-
Request.AddHeader "Authorization", "Bearer " & Me.Token
245+
Request.SetHeader "Authorization", "Bearer " & Me.Token
246246
End If
247247
End Sub
248248

authenticators/HttpBasicAuthenticator.cls

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -57,7 +57,7 @@ End Sub
5757
' @param in|out {WebRequest} Request The request about to be executed
5858
''
5959
Private Sub IWebAuthenticator_BeforeExecute(ByVal Client As WebClient, ByRef Request As WebRequest)
60-
Request.AddHeader "Authorization", "Basic " & WebHelpers.Base64Encode(Me.Username & ":" & Me.Password)
60+
Request.SetHeader "Authorization", "Basic " & WebHelpers.Base64Encode(Me.Username & ":" & Me.Password)
6161
End Sub
6262

6363
''
@@ -91,6 +91,6 @@ End Sub
9191
''
9292
Private Sub IWebAuthenticator_PrepareCurl(ByVal Client As WebClient, ByVal Request As WebRequest, ByRef Curl As String)
9393
' e.g. Add flags to cURL
94-
Curl = Curl & " --basic --user " & Me.Username & ":" & Me.Password
94+
Curl = Curl & " --basic --user " & WebHelpers.PrepareTextForShell(Me.Username) & ":" & WebHelpers.PrepareTextForShell(Me.Password)
9595
End Sub
9696

authenticators/OAuth1Authenticator.cls

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -70,7 +70,7 @@ End Sub
7070
''
7171
Private Sub IWebAuthenticator_BeforeExecute(ByVal Client As WebClient, ByRef Request As WebRequest)
7272
' Add authorization header to request
73-
Request.AddHeader "Authorization", CreateHeader(Client, Request)
73+
Request.SetHeader "Authorization", CreateHeader(Client, Request)
7474
End Sub
7575

7676
''

authenticators/OAuth2Authenticator.cls

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -65,7 +65,7 @@ Private Sub IWebAuthenticator_BeforeExecute(ByVal Client As WebClient, ByRef Req
6565
Me.Token = Me.GetToken(Client)
6666
End If
6767

68-
Request.AddHeader "Authorization", "Bearer " & Me.Token
68+
Request.SetHeader "Authorization", "Bearer " & Me.Token
6969
End Sub
7070

7171
''

authenticators/TwitterAuthenticator.cls

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -68,7 +68,7 @@ Private Sub IWebAuthenticator_BeforeExecute(ByVal Client As WebClient, ByRef Req
6868
Me.Token = Me.GetToken(Client)
6969
End If
7070

71-
Request.AddHeader "Authorization", "Bearer " & Me.Token
71+
Request.SetHeader "Authorization", "Bearer " & Me.Token
7272
End Sub
7373

7474
''
@@ -129,7 +129,7 @@ Public Function GetToken(auth_Client As WebClient) As String
129129
auth_Request.RequestFormat = WebFormat.FormUrlEncoded
130130
auth_Request.ResponseFormat = WebFormat.Json
131131

132-
auth_Request.AddHeader "Authorization", _
132+
auth_Request.SetHeader "Authorization", _
133133
"Basic " & WebHelpers.Base64Encode(Me.ConsumerKey & ":" & Me.ConsumerSecret)
134134
auth_Request.AddBodyParameter "grant_type", "client_credentials"
135135

specs/Specs_HttpBasicAuthenticator.bas

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@ Public Function Specs() As SpecSuite
2525
Request.AddUrlSegment "user", "Tim"
2626
Request.AddUrlSegment "password", "Secret123"
2727

28+
Set Client.Authenticator = Nothing
2829
Set Response = Client.Execute(Request)
2930
.Expect(Response.StatusCode).ToEqual WebStatusCode.Unauthorized
3031

@@ -36,6 +37,24 @@ Public Function Specs() As SpecSuite
3637
.Expect(Response.Data("authenticated")).ToEqual True
3738
End With
3839

40+
With Specs.It("should properly escape username and password")
41+
Set Request = New WebRequest
42+
Request.Resource = "basic-auth/{user}/{password}"
43+
Request.AddUrlSegment "user", "Tim\`$""!"
44+
Request.AddUrlSegment "password", "Secret123\`$""!"
45+
46+
Set Client.Authenticator = Nothing
47+
Set Response = Client.Execute(Request)
48+
.Expect(Response.StatusCode).ToEqual WebStatusCode.Unauthorized
49+
50+
Auth.Setup "Tim\`$""!", "Secret123\`$""!"
51+
Set Client.Authenticator = Auth
52+
53+
Set Response = Client.Execute(Request)
54+
.Expect(Response.StatusCode).ToEqual 200
55+
.Expect(Response.Data("authenticated")).ToEqual True
56+
End With
57+
3958
InlineRunner.RunSuite Specs
4059
End Function
4160

specs/Specs_WebHelpers.bas

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -399,8 +399,7 @@ Public Function Specs() As SpecSuite
399399
' ============================================= '
400400
' 7. Mac
401401
' ============================================= '
402-
403-
#If Mac Then
402+
404403
' ExecuteInShell
405404

406405
' PrepareTextForShell
@@ -410,7 +409,6 @@ Public Function Specs() As SpecSuite
410409
.Expect(WebHelpers.PrepareTextForShell("!abc!123!")).ToEqual "'!'""abc""'!'""123""'!'"
411410
.Expect(WebHelpers.PrepareTextForShell("`!$\""%")).ToEqual """\`""'!'""\$\\\""\%"""
412411
End With
413-
#End If
414412

415413
' ============================================= '
416414
' 8. Cryptography

specs/Specs_WebRequest.bas

Lines changed: 24 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -224,6 +224,15 @@ Public Function Specs() As SpecSuite
224224
.Expect(Request.FormattedResource).ToEqual "A/B/C/D"
225225
End With
226226

227+
With Specs.It("FormattedResource should url-encode Url Segments")
228+
Set Request = New WebRequest
229+
230+
Request.Resource = "{segment}"
231+
Request.AddUrlSegment "segment", "$&+,/:;=?@"
232+
233+
.Expect(Request.FormattedResource).ToEqual "%24%26%2B%2C%2F%3A%3B%3D%3F%40"
234+
End With
235+
227236
With Specs.It("FormattedResource should include querystring parameters")
228237
Set Request = New WebRequest
229238

@@ -302,24 +311,6 @@ Public Function Specs() As SpecSuite
302311
.Expect(Request.Body).ToEqual "{""A"":123,""B"":456}"
303312
End With
304313

305-
' TODO
306-
'With Specs.It("AddBodyParameter should throw TODO if adding to existing Body this is not Dictionary")
307-
' On Error Resume Next
308-
' Set Request = New WebRequest
309-
'
310-
' Request.Body = Array("A", "B", "C")
311-
' Request.AddBodyParameter "D", 123
312-
'
313-
' ' TODO Check actual error number
314-
' .Expect(Err.Number).ToNotEqual 0
315-
' Debug.Print Err.Number & ": " & Err.Description
316-
' .Expect(Err.Description).ToEqual _
317-
' "The existing body is not a Dictionary. Adding body parameters can only be used with Dictionaries"
318-
'
319-
' Err.Clear
320-
' On Error GoTo 0
321-
'End With
322-
323314
' AddCookie
324315
' --------------------------------------------- '
325316
With Specs.It("should AddCookie")
@@ -346,6 +337,21 @@ Public Function Specs() As SpecSuite
346337
.Expect(Request.Headers(2)("Value")).ToEqual "header 2"
347338
End With
348339

340+
' SetHeader
341+
' --------------------------------------------- '
342+
With Specs.It("should SetHeader")
343+
Set Request = New WebRequest
344+
345+
Request.AddHeader "A", "add"
346+
347+
Request.SetHeader "A", "set"
348+
Request.SetHeader "B", "header"
349+
350+
.Expect(Request.Headers.Count).ToEqual 2
351+
.Expect(Request.Headers(1)("Value")).ToEqual "set"
352+
.Expect(Request.Headers(2)("Key")).ToEqual "B"
353+
End With
354+
349355
' AddQuerystringParam
350356
' --------------------------------------------- '
351357
With Specs.It("should AddQuerystringParam")

src/WebHelpers.bas

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1244,7 +1244,9 @@ Public Sub AddOrReplaceInKeyValues(KeyValues As Collection, Key As Variant, Valu
12441244
' Replace existing
12451245
KeyValues.Remove web_Index
12461246

1247-
If web_Index > KeyValues.Count Then
1247+
If KeyValues.Count = 0 Then
1248+
KeyValues.Add web_NewKeyValue
1249+
ElseIf web_Index > KeyValues.Count Then
12481250
KeyValues.Add web_NewKeyValue, After:=web_Index - 1
12491251
Else
12501252
KeyValues.Add web_NewKeyValue, Before:=web_Index
@@ -1414,7 +1416,6 @@ End Sub
14141416
' ============================================= '
14151417
' 7. Mac
14161418
' ============================================= '
1417-
#If Mac Then
14181419

14191420
''
14201421
' Execute the given command
@@ -1425,6 +1426,7 @@ End Sub
14251426
' @return {ShellResult}
14261427
''
14271428
Public Function ExecuteInShell(web_Command As String) As ShellResult
1429+
#If Mac Then
14281430
Dim web_File As Long
14291431
Dim web_Chunk As String
14301432
Dim web_Read As Long
@@ -1450,6 +1452,7 @@ Public Function ExecuteInShell(web_Command As String) As ShellResult
14501452
web_Cleanup:
14511453

14521454
ExecuteInShell.ExitCode = web_pclose(web_File)
1455+
#End If
14531456
End Function
14541457

14551458
''
@@ -1488,8 +1491,6 @@ Public Function PrepareTextForShell(ByVal web_Text As String) As String
14881491
PrepareTextForShell = web_Text
14891492
End Function
14901493

1491-
#End If
1492-
14931494
' ============================================= '
14941495
' 8. Cryptography
14951496
' ============================================= '

0 commit comments

Comments
 (0)