Skip to content

Commit f836331

Browse files
committed
Add cURL - Tests pass on Mac!
1 parent 2a2faca commit f836331

File tree

8 files changed

+190
-23
lines changed

8 files changed

+190
-23
lines changed
-55.4 KB
Binary file not shown.

specs/Excel-REST - Specs.xlsm

44.4 KB
Binary file not shown.

specs/GoogleAuthenticatorSpecs.bas

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ Public Function Specs() As SpecSuite
2929

3030
With Specs.It("should login")
3131
Auth.Login
32-
.Expect(Auth.Token).ToBeDefined
32+
.Expect(Auth.Token).ToNotBeUndefined
3333
End With
3434

3535
With Specs.It("should skip login if API key is used")

specs/OAuth1AuthenticatorSpecs.bas

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -149,7 +149,7 @@ Sub LinkedInSpecs()
149149
Set Response = Client.Execute(Request)
150150

151151
.Expect(Response.StatusCode).ToEqual 200
152-
.Expect(Response.Data("firstName")).ToBeDefined
152+
.Expect(Response.Data("firstName")).ToNotBeUndefined
153153
End With
154154

155155
With Specs.It("should search with space")
@@ -160,7 +160,7 @@ Sub LinkedInSpecs()
160160
Set Response = Client.Execute(Request)
161161

162162
.Expect(Response.StatusCode).ToEqual 200
163-
.Expect(Response.Data("companies")).ToBeDefined
163+
.Expect(Response.Data("companies")).ToNotBeUndefined
164164

165165
If (Response.StatusCode <> 200) Then
166166
Debug.Print "Error :" & Response.StatusCode & " - " & Response.Content

specs/RestClientSpecs.bas

Lines changed: 44 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -246,7 +246,7 @@ Public Function Specs() As SpecSuite
246246
Set Response = Client.Execute(Request)
247247
.Expect(Response.Cookies.Count).ToEqual 4
248248
.Expect(Response.Cookies("unsigned-cookie")).ToEqual "simple-cookie"
249-
.Expect(Response.Cookies("signed-cookie")).ToContain "special-cookie"
249+
.Expect(Response.Cookies("signed-cookie")).ToMatch "special-cookie"
250250
.Expect(Response.Cookies("tricky;cookie")).ToEqual "includes; semi-colon and space at end "
251251
.Expect(Response.Cookies("duplicate-cookie")).ToEqual "B"
252252
End With
@@ -327,7 +327,9 @@ Public Function Specs() As SpecSuite
327327
.Expect(Response.Data("b")).ToEqual "2"
328328
.Expect(Response.Data("c")).ToEqual "3.14"
329329
End With
330-
330+
331+
#If Mac Then
332+
#Else
331333
With Specs.It("should convert and parse XML")
332334
Set Request = New RestRequest
333335
Request.Resource = "xml"
@@ -347,6 +349,7 @@ Public Function Specs() As SpecSuite
347349
.Expect(Response.Data.FirstChild.SelectSingleNode("X").Text).ToEqual "1.23"
348350
.Expect(Response.Data.FirstChild.SelectSingleNode("Y").Text).ToEqual "4.56"
349351
End With
352+
#End If
350353

351354
With Specs.It("should convert and parse plaintext")
352355
Set Request = New RestRequest
@@ -382,7 +385,45 @@ Public Function Specs() As SpecSuite
382385
.Expect(Response.Data("b")).ToEqual 2
383386
.Expect(Response.Data("c")).ToEqual 3.14
384387
End With
385-
388+
389+
#If Mac Then
390+
With Specs.It("should prepare cURL request")
391+
Set Client = New RestClient
392+
Client.BaseUrl = "http://localhost:3000/"
393+
Client.Username = "user"
394+
Client.Password = "password"
395+
Client.ProxyServer = "proxyserver"
396+
Client.ProxyBypassList = "proxyserver:80, *.github.com"
397+
Client.ProxyUsername = "proxyuser"
398+
Client.ProxyPassword = "proxypassword"
399+
400+
Set Request = New RestRequest
401+
Request.Resource = "text"
402+
Request.AddQuerystringParam "type", "message"
403+
Request.Method = httpPOST
404+
Request.RequestFormat = AvailableFormats.plaintext
405+
Request.ResponseFormat = AvailableFormats.json
406+
Request.AddBodyString "Howdy!"
407+
Request.AddHeader "custom", "Howdy!"
408+
Request.AddCookie "test-cookie", "howdy"
409+
410+
Dim cURL As String
411+
412+
cURL = Client.PrepareCURL(Request)
413+
.Expect(cURL).ToMatch "http://localhost:3000/text?type=message"
414+
.Expect(cURL).ToMatch "-X POST"
415+
.Expect(cURL).ToMatch "--user user:password"
416+
.Expect(cURL).ToMatch "--proxy proxyserver"
417+
.Expect(cURL).ToMatch "--noproxy proxyserver:80, *.github.com"
418+
.Expect(cURL).ToMatch "--proxy-user proxyuser:proxypassword"
419+
.Expect(cURL).ToMatch "-H 'Content-Type: text/plain'"
420+
.Expect(cURL).ToMatch "-H 'Accept: application/json'"
421+
.Expect(cURL).ToMatch "-H 'custom: Howdy!'"
422+
.Expect(cURL).ToMatch "--cookie 'test-cookie=howdy;'"
423+
.Expect(cURL).ToMatch "-d 'Howdy!'"
424+
End With
425+
#End If
426+
386427
Set Client = Nothing
387428

388429
InlineRunner.RunSuite Specs

specs/RestHelpersSpecs.bas

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -223,22 +223,22 @@ Public Function Specs() As SpecSuite
223223
End With
224224

225225
With Specs.It("should extract parts from url")
226-
Set Parts = RestHelpers.UrlParts("https://www.google.com/dir/1/2/search.html?arg=0-a&arg1=1-b&arg3-c#hash")
226+
Set Parts = RestHelpers.UrlParts("https://www.google.com/dir/1/2/search.html?message=Howdy World!&other=123#hash")
227227

228228
.Expect(Parts("Protocol")).ToEqual "https"
229229
.Expect(Parts("Host")).ToEqual "www.google.com"
230230
.Expect(Parts("Port")).ToEqual "443"
231231
.Expect(Parts("Path")).ToEqual "/dir/1/2/search.html"
232-
.Expect(Parts("Querystring")).ToEqual "arg=0-a&arg1=1-b&arg3-c"
232+
.Expect(Parts("Querystring")).ToEqual "message=Howdy World!&other=123"
233233
.Expect(Parts("Hash")).ToEqual "hash"
234234

235-
Set Parts = RestHelpers.UrlParts("localhost:3000/dir/1/2/search.html?arg=0-a&arg1=1-b&arg3-c#hash")
235+
Set Parts = RestHelpers.UrlParts("localhost:3000/dir/1/2/page%202.html?message=Howdy%20World%21&other=123#hash")
236236

237237
.Expect(Parts("Protocol")).ToEqual ""
238238
.Expect(Parts("Host")).ToEqual "localhost"
239239
.Expect(Parts("Port")).ToEqual "3000"
240-
.Expect(Parts("Path")).ToEqual "/dir/1/2/search.html"
241-
.Expect(Parts("Querystring")).ToEqual "arg=0-a&arg1=1-b&arg3-c"
240+
.Expect(Parts("Path")).ToEqual "/dir/1/2/page%202.html"
241+
.Expect(Parts("Querystring")).ToEqual "message=Howdy%20World%21&other=123"
242242
.Expect(Parts("Hash")).ToEqual "hash"
243243
End With
244244

src/RestClient.cls

Lines changed: 42 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ Public Password As String
3434
Public ProxyServer As String
3535
Public ProxyUsername As String
3636
Public ProxyPassword As String
37-
Public ProxyBypassList As Variant
37+
Public ProxyBypassList As String
3838

3939
' ============================================= '
4040
' Public Methods
@@ -62,9 +62,10 @@ Public Function Execute(Request As RestRequest) As RestResponse
6262
cURL = Me.PrepareCURL(Request)
6363
Result = RestHelpers.ExecuteInShell(cURL)
6464

65-
' TODO Check Result.ExitCode
66-
Set Response = RestHelpers.CreateResponseFromCURL(Result.Output, Request.ResponseFormat)
65+
Set Response = RestHelpers.CreateResponseFromCURL(Result, Request.ResponseFormat)
6766
RestHelpers.LogResponse Response, Request
67+
Set Execute = Response
68+
Exit Function
6869

6970
ErrorHandling:
7071

@@ -166,7 +167,7 @@ End Function
166167
' --------------------------------------------- '
167168

168169
Public Sub SetProxy(ProxyServer As String, _
169-
Optional Username As String = "", Optional Password As String = "", Optional BypassList As Variant)
170+
Optional Username As String = "", Optional Password As String = "", Optional BypassList As String = "")
170171

171172
Me.ProxyServer = ProxyServer
172173
Me.ProxyUsername = Username
@@ -256,18 +257,53 @@ End Function
256257

257258
Public Function PrepareCURL(Request As RestRequest) As String
258259
Dim cURL As String
260+
cURL = "curl -i"
259261

260262
' Prepare request
261263
Set Request = PrepareRequest(Request)
262264

263-
' Setup proxy?
265+
' Set timeouts
266+
cURL = cURL & " --connect-timeout " & Me.TimeoutMS / 1000
267+
cURL = cURL & " --max-time " & 3 * Me.TimeoutMS / 1000
268+
269+
' Setup proxy
270+
If Me.ProxyServer <> "" Then
271+
cURL = cURL & " --proxy " & Me.ProxyServer
272+
273+
If Me.ProxyBypassList <> "" Then
274+
cURL = cURL & " --noproxy " & Me.ProxyBypassList
275+
End If
276+
If Me.ProxyUsername <> "" Then
277+
cURL = cURL & " --proxy-user " & Me.ProxyUsername & ":" & Me.ProxyPassword
278+
End If
279+
End If
264280

265281
' Setup Basic authentication
282+
If Me.Username <> "" Then
283+
cURL = cURL & " --user " & Me.Username & ":" & Me.Password
284+
Request.AddHeader "Authorization", "Basic " & RestHelpers.Base64Encode(Me.Username & ":" & Me.Password)
285+
End If
266286

267287
' Setup authenticator
268288
BeforeExecute Request
269289

270-
' Set headers
290+
' Set headers and cookies
291+
Dim HeaderKey As Variant
292+
For Each HeaderKey In Request.Headers.Keys
293+
cURL = cURL & " -H '" & HeaderKey & ": " & Request.Headers(HeaderKey) & "'"
294+
Next HeaderKey
295+
296+
Dim CookieKey As Variant
297+
Dim CookieString As String
298+
For Each CookieKey In Request.Cookies.Keys
299+
CookieString = CookieString & CookieKey & "=" & Request.Cookies(CookieKey) & ";"
300+
Next CookieKey
301+
cURL = cURL & " --cookie '" & CookieString & "'"
302+
303+
' Add method, data, and url
304+
cURL = cURL & " -X " & Request.MethodName
305+
cURL = cURL & " -d '" & Request.Body & "'"
306+
cURL = cURL & " '" & Request.FullUrl(Me.BaseUrl) & "'"
271307

272308
' Log request and return
273309
RestHelpers.LogRequest Request

src/RestHelpers.bas

Lines changed: 96 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -29,12 +29,12 @@ Private Declare Function popen Lib "libc.dylib" (ByVal Command As String, ByVal
2929
Private Declare Function pclose Lib "libc.dylib" (ByVal File As Long) As Long
3030
Private Declare Function fread Lib "libc.dylib" (ByVal outStr As String, ByVal size As Long, ByVal Items As Long, ByVal stream As Long) As Long
3131
Private Declare Function feof Lib "libc.dylib" (ByVal File As Long) As Long
32+
#End If
3233

3334
Public Type ShellResult
3435
Output As String
3536
ExitCode As Long
3637
End Type
37-
#End If
3838

3939
Private pDocumentHelper As Object
4040
Private pElHelper As Object
@@ -360,7 +360,7 @@ Public Function UrlEncode(Text As Variant, Optional SpaceAsPlus As Boolean = Fal
360360
For i = 1 To StringLen
361361
' Get character and ascii code
362362
Char = Mid$(UrlVal, i, 1)
363-
charCode = asc(Char)
363+
charCode = Asc(Char)
364364
Select Case charCode
365365
Case 97 To 122, 65 To 90, 48 To 57, 45, 46, 95, 126
366366
' Use original for AZaz09-._~
@@ -526,6 +526,8 @@ Public Function UrlParts(Url As String) As Dictionary
526526
Dim Results As Variant
527527
Dim ResultPart As Variant
528528
Dim EqualsIndex As Long
529+
Dim Key As String
530+
Dim Value As String
529531
Command = "perl -e '{use URI::URL;" & vbNewLine & _
530532
"$url = new URI::URL """ & Url & """;" & vbNewLine & _
531533
"print ""Protocol="" . $url->scheme;" & vbNewLine & _
@@ -539,7 +541,10 @@ Public Function UrlParts(Url As String) As Dictionary
539541
Results = Split(ExecuteInShell(Command).Output, " | ")
540542
For Each ResultPart In Results
541543
EqualsIndex = InStr(1, ResultPart, "=")
542-
Parts.Add Trim(VBA.Mid$(ResultPart, 1, EqualsIndex - 1)), Trim(VBA.Mid$(ResultPart, EqualsIndex + 1))
544+
Key = Trim(VBA.Mid$(ResultPart, 1, EqualsIndex - 1))
545+
Value = Trim(VBA.Mid$(ResultPart, EqualsIndex + 1))
546+
547+
Parts.Add Key, Value
543548
Next ResultPart
544549

545550
If AddedProtocol And Parts.Exists("Protocol") Then
@@ -769,13 +774,98 @@ End Function
769774

770775
''
771776
' Create response for cURL
777+
' References:
778+
' http://www.w3.org/Protocols/rfc2616/rfc2616-sec6.html
779+
' http://curl.haxx.se/libcurl/c/libcurl-errors.html
772780
'
773781
' @param {String} Raw result from cURL
774782
' @return {RestResponse}
775783
' --------------------------------------------- '
776-
Public Function CreateResponseFromCURL(Raw As String, Optional Format As AvailableFormats = AvailableFormats.json) As RestResponse
784+
Public Function CreateResponseFromCURL(Result As ShellResult, Optional Format As AvailableFormats = AvailableFormats.json) As RestResponse
785+
Dim StatusCode As Long
786+
Dim StatusText As String
787+
Dim Headers As String
788+
Dim Body As Variant
789+
Dim ResponseText As String
790+
791+
If Result.ExitCode > 0 Then
792+
Dim ErrorNumber As Long
793+
794+
ErrorNumber = Result.ExitCode / 256
795+
If ErrorNumber = 28 Then
796+
Set CreateResponseFromCURL = CreateResponse(StatusCodes.RequestTimeout, "Request Timeout")
797+
Else
798+
LogError "cURL Error: " & ErrorNumber, "RestHelpers.CreateResponseFromCURL"
799+
End If
800+
801+
Exit Function
802+
End If
803+
804+
Dim Lines() As String
805+
Lines = Split(Result.Output, vbCrLf)
806+
807+
' Extract status code and text from status line
808+
Dim StatusLine As String
809+
Dim StatusLineParts() As String
810+
StatusLine = Lines(0)
811+
StatusLineParts = Split(StatusLine)
812+
StatusCode = CLng(StatusLineParts(1))
813+
StatusText = Mid$(StatusLine, InStr(1, StatusLine, StatusCode) + 4)
814+
815+
' Find blank line before body
816+
Dim Line As Variant
817+
Dim BlankLineIndex
818+
BlankLineIndex = 0
819+
For Each Line In Lines
820+
If Trim(Line) = "" Then
821+
Exit For
822+
End If
823+
BlankLineIndex = BlankLineIndex + 1
824+
Next Line
825+
826+
' Extract body and headers strings
827+
Dim HeaderLines() As String
828+
Dim BodyLines() As String
829+
Dim ReadIndex As Long
830+
Dim WriteIndex As Long
831+
832+
ReDim HeaderLines(0 To BlankLineIndex - 2)
833+
ReDim BodyLines(0 To UBound(Lines) - BlankLineIndex - 1)
834+
835+
WriteIndex = 0
836+
For ReadIndex = 1 To BlankLineIndex - 1
837+
HeaderLines(WriteIndex) = Lines(ReadIndex)
838+
WriteIndex = WriteIndex + 1
839+
Next ReadIndex
840+
841+
WriteIndex = 0
842+
For ReadIndex = BlankLineIndex + 1 To UBound(Lines)
843+
BodyLines(WriteIndex) = Lines(ReadIndex)
844+
WriteIndex = WriteIndex + 1
845+
Next ReadIndex
846+
847+
ResponseText = Join$(BodyLines, vbCrLf)
848+
Body = StringToBytes(ResponseText)
849+
850+
' Create Response
777851
Set CreateResponseFromCURL = New RestResponse
778-
Debug.Print "cURL Result: " & Raw
852+
CreateResponseFromCURL.StatusCode = StatusCode
853+
CreateResponseFromCURL.StatusDescription = StatusText
854+
CreateResponseFromCURL.Body = Body
855+
CreateResponseFromCURL.Content = ResponseText
856+
857+
' Convert content to data by format
858+
If Format <> AvailableFormats.plaintext Then
859+
On Error Resume Next
860+
Set CreateResponseFromCURL.Data = RestHelpers.ParseByFormat(CreateResponseFromCURL.Content, Format)
861+
On Error GoTo 0
862+
End If
863+
864+
' Extract headers
865+
Set CreateResponseFromCURL.Headers = ExtractHeaders(Join$(HeaderLines, vbCrLf))
866+
867+
' Extract cookies
868+
Set CreateResponseFromCURL.Cookies = ExtractCookies(CreateResponseFromCURL.Headers)
779869
End Function
780870

781871
''
@@ -1080,7 +1170,7 @@ End Function
10801170
' @param {String} Text
10811171
' @return {String}
10821172
' --------------------------------------------- '
1083-
Public Function PrepareTextForShell(Text As String) As String
1173+
Public Function PrepareTextForShell(ByVal Text As String) As String
10841174
Text = Replace("""" & Text & """", "!", """'!'""")
10851175

10861176
' Guard for ! at beginning or end ("'!'"..." or "..."'!'")

0 commit comments

Comments
 (0)