Skip to content

Commit 9f8cfc1

Browse files
committed
Merge pull request #38 from timhall/linkedin-fixes
OAuth1 Fixes and Logging
2 parents ce54b47 + 5f6e92c commit 9f8cfc1

13 files changed

+185
-3
lines changed

authenticators/DigestAuthenticator.cls

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -95,6 +95,7 @@ End Sub
9595

9696
Private Sub IAuthenticator_AfterExecute(ByVal Client As RestClient, ByVal Request As RestRequest, ByRef Response As RestResponse)
9797
If Response.StatusCode = 401 And Not Me.IsAuthenticated Then
98+
RestHelpers.LogDebug "Extract Authenticate and retry 401 request " & Request.FullUrl(Client.BaseUrl), "Digest.AfterExecute"
9899
ExtractAuthenticateInformation Response
99100

100101
Request.AddHeader "Authorization", CreateHeader(Client, Request)
@@ -115,6 +116,7 @@ End Sub
115116
Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestClient, ByRef Request As RestRequest, BaseUrl As String, Optional UseAsync As Boolean = False)
116117
' Perform standard http open
117118
Call Http.Open(Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync)
119+
RestHelpers.LogDebug Request.MethodName() & Request.FullUrl(BaseUrl), "DigestAuthenticator.HttpOpen"
118120
End Sub
119121

120122
Public Function CreateHeader(Client As RestClient, Request As RestRequest) As String
@@ -131,6 +133,8 @@ Public Function CreateHeader(Client As RestClient, Request As RestRequest) As St
131133
", cnonce=""" & Me.ClientNonce & """" & _
132134
", response=""" & CalculateResponse(Client, Request) & """" & _
133135
", opaque=""" & Me.Opaque & """"
136+
137+
RestHelpers.LogDebug CreateHeader, "DigestAuthenticator.CreateHeader"
134138
End Function
135139

136140
Public Function CalculateResponse(Client As RestClient, Request As RestRequest) As String
@@ -143,6 +147,7 @@ Public Function CalculateResponse(Client As RestClient, Request As RestRequest)
143147
HA2 = CalculateHA2(Request.MethodName, Uri)
144148

145149
CalculateResponse = RestHelpers.MD5(HA1 & ":" & Me.ServerNonce & ":" & FormattedRequestCount & ":" & Me.ClientNonce & ":" & qop & ":" & HA2)
150+
RestHelpers.LogDebug CalculateResponse, "DigestAuthenticator.CalculateResponse"
146151
End Function
147152

148153
' Extract authentication information from 401 response headers
@@ -172,6 +177,8 @@ Public Sub ExtractAuthenticateInformation(Response As RestResponse)
172177
If Key = "nonce" Then Me.ServerNonce = Value
173178
If Key = "opaque" Then Me.Opaque = Value
174179
Next i
180+
181+
RestHelpers.LogDebug "realm=" & Me.Realm & ", nonce=" & Me.ServerNonce & ", opaque=" & Me.Opaque, "DigestAuthenticator.ExtractAuthenticateInformation"
175182
End If
176183

177184
Exit Sub
@@ -181,10 +188,12 @@ End Sub
181188

182189
Public Function CalculateHA1() As String
183190
CalculateHA1 = MD5(Me.Username & ":" & Me.Realm & ":" & Me.Password)
191+
RestHelpers.LogDebug CalculateHA1 & " for " & Me.Username & ":" & Me.Realm & ":" & RestHelpers.Obfuscate(Me.Password), "DigestAuthenticator.CalculateHA1"
184192
End Function
185193

186194
Public Function CalculateHA2(Method As String, Uri As String) As String
187195
CalculateHA2 = MD5(Method & ":" & Uri)
196+
RestHelpers.LogDebug CalculateHA2 & " for " & Method & ":" & Uri, "DigestAuthenticator.CalculateHA2"
188197
End Function
189198

190199
' Pad request count to 8 places

authenticators/EmptyAuthenticator.cls

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -73,4 +73,5 @@ Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestCl
7373

7474
' Perform standard http open
7575
Call Http.Open(Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync)
76+
RestHelpers.LogDebug Request.MethodName() & Request.FullUrl(BaseUrl), "Authenticator.HttpOpen"
7677
End Sub

authenticators/FacebookAuthenticator.cls

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,9 @@ Public Property Get Token() As String
5555
EndIndex = InStr(StartIndex, Response.Content, "&expires=")
5656

5757
pToken = Mid$(Response.Content, StartIndex, EndIndex - StartIndex)
58+
RestHelpers.LogDebug "Received token: " & RestHelpers.Obfuscate(pToken), "FacebookAuthenticator.Token"
5859
Else
60+
RestHelpers.LogError "Failed to load token: " & Response.StatusCode & " - " & Response.Content, "FacebookAuthenticator.Token"
5961
Err.Raise vbObjectError + Response.StatusCode, _
6062
Description:="Failed to load Bearer Token: " & Response.StatusCode & " - " & Response.Content
6163
End If
@@ -95,6 +97,7 @@ Public Property Get LoginUrl()
9597
ScopeString = Me.Scope
9698
End If
9799
LoginUrl = LoginUrl & "&scope=" & ScopeString
100+
RestHelpers.LogDebug LoginUrl, "FacebookAuthenticator.LoginUrl"
98101
End Property
99102

100103
' ============================================= '
@@ -140,6 +143,7 @@ Public Sub Login()
140143
Code = OAuthExtractCode(IE)
141144
Else
142145
' Login failed
146+
RestHelpers.LogError "Facebook login failed or was denied", "FacebookAuthenticator.Login"
143147
Err.Raise vbObjectError + 1, "OAuthDialog", "Login failed or was denied"
144148
End If
145149
End With
@@ -150,13 +154,16 @@ CleanUp:
150154
Set IE = Nothing
151155

152156
If Not Completed Then
157+
RestHelpers.LogError "Facebook login did not complete", "FacebookAuthenticator.Login"
153158
Err.Raise vbObjectError + 1, "OAuthDialog", "Login did not complete"
154159
ElseIf Err.Number <> 0 Then
155160
' Rethrow error
156161
Err.Raise Err.Number, Err.Source, Err.Description
157162
ElseIf Left(Code, 5) = "Error" Then
163+
RestHelpers.LogError "Facebook login returned error: " & Code, "FacebookAuthenticator.Login"
158164
Err.Raise vbObjectError + 1, "OAuthDialog", Code
159165
Else
166+
RestHelpers.LogDebug "Successfully logged in: " & Code, "FacebookAuthenticator.Login"
160167
' Success!
161168
Me.Code = Code
162169

@@ -187,6 +194,7 @@ End Sub
187194

188195
Private Sub IAuthenticator_BeforeExecute(ByVal Client As RestClient, ByRef Request As RestRequest)
189196
Request.AddQuerystringParam "access_token", Me.Token
197+
RestHelpers.LogDebug "Add access_token=" & Me.Token, "FacebookAuthenticator.BeforeExecute"
190198
End Sub
191199

192200
''
@@ -214,6 +222,7 @@ End Sub
214222
Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestClient, ByRef Request As RestRequest, BaseUrl As String, Optional UseAsync As Boolean = False)
215223
' Perform standard http open
216224
Call Http.Open(Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync)
225+
RestHelpers.LogDebug Request.MethodName() & Request.FullUrl(BaseUrl), "FacebookAuthenticator.HttpOpen"
217226
End Sub
218227

219228
Private Function TokenRequest() As RestRequest
@@ -267,6 +276,7 @@ Private Function OAuthExtractCode(IE As Object) As String
267276
If StartIndex >= 0 And EndIndex > StartIndex Then
268277
OAuthExtractCode = Mid$(Url, StartIndex, EndIndex - StartIndex)
269278
Else
279+
RestHelpers.LogError "Unrecognized token format: " & Url, "FacebookAuthenticator.OAuthExtractCode"
270280
OAuthExtractCode = "Error: Unrecognized token formatting"
271281
End If
272282
End Function

authenticators/GoogleAuthenticator.cls

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -110,6 +110,7 @@ Public Property Get LoginUrl() As String
110110
Request.AddQuerystringParam "scope", ScopeString
111111

112112
LoginUrl = Request.FormattedResource
113+
RestHelpers.LogDebug LoginUrl, "GoogleAuthenticator.LoginUrl"
113114
Set Request = Nothing
114115
End Property
115116

@@ -129,7 +130,9 @@ Public Property Get Token() As String
129130
Dim Data As Object
130131
Set Data = RestHelpers.ParseJSON(Response.Content)
131132
pToken = Data("access_token")
133+
RestHelpers.LogDebug "Received Token: " & RestHelpers.Obfuscate(pToken), "GoogleAuthenticator.Token"
132134
Else
135+
RestHelpers.LogError "Failed to load token: " & Response.StatusCode & " - " & Response.Content, "GoogleAuthenticator.Token"
133136
Err.Raise vbObjectError + Response.StatusCode, _
134137
Description:="Failed to load Bearer Token: " & Response.StatusCode & " - " & Response.Content
135138
End If
@@ -197,14 +200,17 @@ Public Sub Login(Optional APIKey As String = "")
197200
Completed = True
198201
If OAuthIsDenied(IE) Then
199202
' Login failed
203+
RestHelpers.LogError "Login failed or was denied", "GoogleAuthenticator.Login"
200204
Err.Raise vbObjectError + 1, "OAuthDialog", "Login failed or was denied"
201205
Else
202206
Code = OAuthExtractCode(IE)
203207
If Left(Code, 5) = "Error" Then
208+
RestHelpers.LogError "Login error: " & Code, "GoogleAuthenticator.Login"
204209
Err.Raise vbObjectError + 1, "OAuthDialog", Code
205210
Else
206211
' Success!
207212
Me.AuthorizationCode = Code
213+
RestHelpers.LogDebug "Login success: " & Code, "GoogleAuthenticator.Login"
208214

209215
' Temporarily assign token to force request
210216
Dim Token As String
@@ -220,6 +226,7 @@ CleanUp:
220226
Set IE = Nothing
221227

222228
If Not Completed Then
229+
RestHelpers.LogError "Login did not complete", "GoogleAuthenticator.Login"
223230
Err.Raise vbObjectError + 1, "OAuthDialog", "Login did not complete"
224231
ElseIf Err.Number <> 0 Then
225232
' Rethrow error
@@ -305,8 +312,10 @@ End Sub
305312
Private Sub IAuthenticator_BeforeExecute(ByVal Client As RestClient, ByRef Request As RestRequest)
306313
If Me.APIKey <> "" Then
307314
Request.AddQuerystringParam "key", Me.APIKey
315+
RestHelpers.LogDebug "Login with key: " & RestHelpers.Obfuscate(Me.APIKey), "GoogleAuthenticator.BeforeExecute"
308316
Else
309317
Request.AddHeader "Authorization", "Bearer " & Me.Token
318+
RestHelpers.LogDebug "Login with token: " & RestHelpers.Obfuscate(Me.Token), "GoogleAuthenticator.BeforeExecute"
310319
End If
311320
End Sub
312321

@@ -335,6 +344,7 @@ End Sub
335344
Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestClient, ByRef Request As RestRequest, BaseUrl As String, Optional UseAsync As Boolean = False)
336345
' Perform standard http open
337346
Http.Open Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync
347+
RestHelpers.LogDebug Request.MethodName() & Request.FullUrl(BaseUrl), "FacebookAuthenticator.HttpOpen"
338348
End Sub
339349

340350
Private Function TokenRequest() As RestRequest

authenticators/HttpBasicAuthenticator.cls

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -86,6 +86,7 @@ Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestCl
8686
' Use http open with username and password values set
8787
' (This is used in addition to setting request header, as some services required this)
8888
Http.Open Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync, Me.Username, Me.Password
89+
RestHelpers.LogDebug Request.MethodName() & Request.FullUrl(BaseUrl), "FacebookAuthenticator.HttpOpen"
8990
End Sub
9091

9192
Private Function CreateHeader() As String

authenticators/OAuth1Authenticator.cls

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -136,6 +136,7 @@ End Sub
136136
Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestClient, ByRef Request As RestRequest, BaseUrl As String, Optional UseAsync As Boolean = False)
137137
' Perform standard http open
138138
Call Http.Open(Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync)
139+
RestHelpers.LogDebug Request.MethodName() & Request.FullUrl(BaseUrl), "FacebookAuthenticator.HttpOpen"
139140
End Sub
140141

141142
Public Function CreateHeader(Client As RestClient, Request As RestRequest) As String
@@ -180,6 +181,8 @@ Public Function CreateHeader(Client As RestClient, Request As RestRequest) As St
180181
Header = Header & "oauth_token=" & Chr(34) & Me.Token & Chr(34) & ", "
181182
Header = Header & "oauth_version=" & Chr(34) & "1.0" & Chr(34)
182183
CreateHeader = Header
184+
185+
RestHelpers.LogDebug CreateHeader, "OAuth1Authenticator.CreateHeader"
183186
End Function
184187

185188
Public Function CreateBaseString(Nonce As String, Timestamp As String, Client As RestClient, Request As RestRequest) As String
@@ -200,6 +203,7 @@ Public Function CreateBaseString(Nonce As String, Timestamp As String, Client As
200203
base = base & "&" & "oauth_version=1.0"
201204

202205
CreateBaseString = Request.MethodName() & "&" & RestHelpers.UrlEncode(RequestUrl(Client, Request)) & "&" & RestHelpers.UrlEncode(base)
206+
RestHelpers.LogDebug CreateBaseString, "OAuth1Authenticator.CreateBaseString"
203207
End Function
204208

205209
Public Function RequestUrl(Client As RestClient, Request As RestRequest) As String
@@ -239,7 +243,11 @@ Public Function RequestParameters(Client As RestClient, Request As RestRequest)
239243
Dim Parts As Dictionary
240244
Set Parts = RestHelpers.UrlParts(Request.FullUrl(Client.BaseUrl))
241245

242-
RequestParameters = RestHelpers.UrlDecode(Replace(Parts("Querystring"), "?", ""))
246+
' Remove leading ?
247+
RequestParameters = Replace(Parts("Querystring"), "?", "")
248+
249+
' Replace + for spaces with %20
250+
RequestParameters = Replace(RequestParameters, "+", "%20")
243251
End Function
244252

245253
Public Function CreateSigningKey() As String
@@ -248,6 +256,7 @@ End Function
248256

249257
Public Function CreateSignature(base As String, signingKey As String) As String
250258
CreateSignature = RestHelpers.Base64_HMACSHA1(base, signingKey)
259+
RestHelpers.LogDebug CreateSignature, "OAuth1Authenticator.CreateSignature"
251260
End Function
252261

253262
Public Function CreateTimestamp() As String

authenticators/OAuth2Authenticator.cls

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -90,6 +90,7 @@ Private Sub IAuthenticator_BeforeExecute(ByVal Client As RestClient, ByRef Reque
9090

9191
If Http.Status <> 200 Then
9292
' Error getting OAuth2 token
93+
RestHelpers.LogError "Token request failed: " & Http.Status & " - " & Http.ResponseText, "OAuth2Authenticator.BeforeExecute"
9394
Err.Raise vbObjectError + Http.Status, _
9495
Description:="Failed to retrieve OAuth2 Token - " & Http.Status & ": " & Http.ResponseText
9596
End If
@@ -99,13 +100,15 @@ Private Sub IAuthenticator_BeforeExecute(ByVal Client As RestClient, ByRef Reque
99100
If Not Response Is Nothing Then
100101
If Response.Exists(Me.TokenKey) Then
101102
Me.Token = Response(Me.TokenKey)
103+
RestHelpers.LogDebug "Received token: " & RestHelpers.Obfuscate(Me.Token), "OAuth2Authenticator.BeforeExecute"
102104
End If
103105

104106
' (Salesforce specific, but shouldn't affect any other OAuth2 clients)
105107
If Response.Exists("instance_url") Then
106108
Request.BaseUrl = Response("instance_url")
107109
End If
108110
Else
111+
RestHelpers.LogError "Failed to read OAuth2 Token: " & Http.ResponseText, "OAuth2Authenticator.BeforeExecute"
109112
Err.Raise vbObjectError + 2, _
110113
Description:="Failed to read OAuth2 Token"
111114
End If
@@ -148,6 +151,7 @@ End Sub
148151
Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestClient, ByRef Request As RestRequest, BaseUrl As String, Optional UseAsync As Boolean = False)
149152
' Perform standard http open
150153
Call Http.Open(Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync)
154+
RestHelpers.LogDebug Request.MethodName() & Request.FullUrl(BaseUrl), "FacebookAuthenticator.HttpOpen"
151155
End Sub
152156

153157
Private Function CreateHeader() As String
@@ -165,4 +169,5 @@ Private Function CreateTokenRequest() As String
165169
CreateTokenRequest = CreateTokenRequest & "&client_secret=" & Me.ClientSecret
166170
CreateTokenRequest = CreateTokenRequest & "&username=" & Me.Username
167171
CreateTokenRequest = CreateTokenRequest & "&password=" & Me.Password
172+
RestHelpers.LogDebug CreateTokenRequest, "OAuth2Authenticator.CreateTokenRequest"
168173
End Function

authenticators/TwitterAuthenticator.cls

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,9 @@ Public Property Get Token() As String
4848
' Store token if successful, otherwise throw error
4949
If Response.StatusCode = Ok Then
5050
pToken = Response.Data("access_token")
51+
RestHelpers.LogDebug "Successfully received token: " & RestHelpers.Obfuscate(pToken), "TwitterAuthenticator.Token"
5152
Else
53+
RestHelpers.LogError "Failed to load token: " & Response.StatusCode & " - " & Response.Content, "TwitterAuthenticator.Token"
5254
Err.Raise vbObjectError + Response.StatusCode, _
5355
Description:="Failed to load Bearer Token: " & Response.StatusCode & " - " & Response.Content
5456
End If
@@ -121,6 +123,7 @@ Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestCl
121123

122124
' Perform standard http open
123125
Call Http.Open(Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync)
126+
RestHelpers.LogDebug "Http.Open " & Request.MethodName() & Request.FullUrl(BaseUrl), "FacebookAuthenticator.HttpOpen"
124127
End Sub
125128

126129
Private Function TokenRequest() As RestRequest

specs/Excel-REST - Specs.xlsm

80.9 KB
Binary file not shown.

specs/OAuth1AuthenticatorSpecs.bas

Lines changed: 75 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -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
97107
End 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

Comments
 (0)