@@ -61,7 +61,17 @@ Public Function Specs() As SpecSuite
6161 Request.AddParameter "c" , "Howdy!"
6262 Request.AddQuerystringParam "d" , 789
6363
64- .Expect(Auth.RequestParameters(Client, Request)).ToEqual "a=123&b=456&c=Howdy!&d=789"
64+ .Expect(Auth.RequestParameters(Client, Request)).ToEqual "a=123&b=456&c=Howdy%21&d=789"
65+ End With
66+
67+ With Specs.It("should handle spaces in parameters correctly" )
68+ Client.BaseUrl = "http://localhost:3000/"
69+ Set Request = New RestRequest
70+ Request.Resource = "testing"
71+ Request.AddQuerystringParam "a" , "a b"
72+
73+ .Expect(Auth.RequestParameters(Client, Request)).ToEqual "a=a%20b"
74+ .Expect(Request.FullUrl(Client.BaseUrl)).ToEqual "http://localhost:3000/testing?a=a+b"
6575 End With
6676
6777 Set Client = New RestClient
@@ -95,3 +105,67 @@ Public Function Specs() As SpecSuite
95105
96106 InlineRunner.RunSuite Specs
97107End Function
108+
109+ ' LinkedIn Specific
110+ ' ----------------- '
111+ Sub LinkedInSpecs ()
112+ Dim Specs As New SpecSuite
113+
114+ Dim Client As New RestClient
115+ Client.BaseUrl = "http://api.linkedin.com/v1/"
116+
117+ Dim Auth As New OAuth1Authenticator
118+ Dim ConsumerKey As String
119+ Dim ConsumerSecret As String
120+ Dim Token As String
121+ Dim TokenSecret As String
122+
123+ If Credentials.Loaded Then
124+ ConsumerKey = Credentials.Values("LinkedIn" )("api_key" )
125+ ConsumerSecret = Credentials.Values("LinkedIn" )("api_secret" )
126+ Token = Credentials.Values("LinkedIn" )("user_token" )
127+ TokenSecret = Credentials.Values("LinkedIn" )("user_secret" )
128+ Else
129+ ConsumerKey = InputBox("Enter Consumer Key" )
130+ ConsumerSecret = InputBox("Enter Consumer Secret" )
131+ Token = InputBox("Enter Token" )
132+ TokenSecret = InputBox("Enter Token Secret" )
133+ End If
134+ Auth.Setup _
135+ ConsumerKey:=ConsumerKey, _
136+ ConsumerSecret:=ConsumerSecret, _
137+ Token:=Token, _
138+ TokenSecret:=TokenSecret
139+
140+ Set Client.Authenticator = Auth
141+
142+ Dim Request As RestRequest
143+ Dim Response As RestResponse
144+
145+ With Specs.It("should get profile" )
146+ Set Request = New RestRequest
147+ Request.Resource = "people/~?format={format}"
148+
149+ Set Response = Client.Execute(Request)
150+
151+ .Expect(Response.StatusCode).ToEqual 200
152+ .Expect(Response.Data("firstName" )).ToBeDefined
153+ End With
154+
155+ With Specs.It("should search with space" )
156+ Set Request = New RestRequest
157+ Request.Resource = "company-search?format={format}"
158+ Request.AddQuerystringParam "keywords" , "microsoft corp"
159+
160+ Set Response = Client.Execute(Request)
161+
162+ .Expect(Response.StatusCode).ToEqual 200
163+ .Expect(Response.Data("companies" )).ToBeDefined
164+
165+ If (Response.StatusCode <> 200 ) Then
166+ Debug.Print "Error :" & Response.StatusCode & " - " & Response.Content
167+ End If
168+ End With
169+
170+ InlineRunner.RunSuite Specs
171+ End Sub
0 commit comments