Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
9 changes: 9 additions & 0 deletions authenticators/DigestAuthenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -95,6 +95,7 @@ End Sub

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

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

Public Function CreateHeader(Client As RestClient, Request As RestRequest) As String
Expand All @@ -131,6 +133,8 @@ Public Function CreateHeader(Client As RestClient, Request As RestRequest) As St
", cnonce=""" & Me.ClientNonce & """" & _
", response=""" & CalculateResponse(Client, Request) & """" & _
", opaque=""" & Me.Opaque & """"

RestHelpers.LogDebug CreateHeader, "DigestAuthenticator.CreateHeader"
End Function

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

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

' Extract authentication information from 401 response headers
Expand Down Expand Up @@ -172,6 +177,8 @@ Public Sub ExtractAuthenticateInformation(Response As RestResponse)
If Key = "nonce" Then Me.ServerNonce = Value
If Key = "opaque" Then Me.Opaque = Value
Next i

RestHelpers.LogDebug "realm=" & Me.Realm & ", nonce=" & Me.ServerNonce & ", opaque=" & Me.Opaque, "DigestAuthenticator.ExtractAuthenticateInformation"
End If

Exit Sub
Expand All @@ -181,10 +188,12 @@ End Sub

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

Public Function CalculateHA2(Method As String, Uri As String) As String
CalculateHA2 = MD5(Method & ":" & Uri)
RestHelpers.LogDebug CalculateHA2 & " for " & Method & ":" & Uri, "DigestAuthenticator.CalculateHA2"
End Function

' Pad request count to 8 places
Expand Down
1 change: 1 addition & 0 deletions authenticators/EmptyAuthenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -73,4 +73,5 @@ Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestCl

' Perform standard http open
Call Http.Open(Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync)
RestHelpers.LogDebug Request.MethodName() & Request.FullUrl(BaseUrl), "Authenticator.HttpOpen"
End Sub
10 changes: 10 additions & 0 deletions authenticators/FacebookAuthenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,9 @@ Public Property Get Token() As String
EndIndex = InStr(StartIndex, Response.Content, "&expires=")

pToken = Mid$(Response.Content, StartIndex, EndIndex - StartIndex)
RestHelpers.LogDebug "Received token: " & RestHelpers.Obfuscate(pToken), "FacebookAuthenticator.Token"
Else
RestHelpers.LogError "Failed to load token: " & Response.StatusCode & " - " & Response.Content, "FacebookAuthenticator.Token"
Err.Raise vbObjectError + Response.StatusCode, _
Description:="Failed to load Bearer Token: " & Response.StatusCode & " - " & Response.Content
End If
Expand Down Expand Up @@ -95,6 +97,7 @@ Public Property Get LoginUrl()
ScopeString = Me.Scope
End If
LoginUrl = LoginUrl & "&scope=" & ScopeString
RestHelpers.LogDebug LoginUrl, "FacebookAuthenticator.LoginUrl"
End Property

' ============================================= '
Expand Down Expand Up @@ -140,6 +143,7 @@ Public Sub Login()
Code = OAuthExtractCode(IE)
Else
' Login failed
RestHelpers.LogError "Facebook login failed or was denied", "FacebookAuthenticator.Login"
Err.Raise vbObjectError + 1, "OAuthDialog", "Login failed or was denied"
End If
End With
Expand All @@ -150,13 +154,16 @@ CleanUp:
Set IE = Nothing

If Not Completed Then
RestHelpers.LogError "Facebook login did not complete", "FacebookAuthenticator.Login"
Err.Raise vbObjectError + 1, "OAuthDialog", "Login did not complete"
ElseIf Err.Number <> 0 Then
' Rethrow error
Err.Raise Err.Number, Err.Source, Err.Description
ElseIf Left(Code, 5) = "Error" Then
RestHelpers.LogError "Facebook login returned error: " & Code, "FacebookAuthenticator.Login"
Err.Raise vbObjectError + 1, "OAuthDialog", Code
Else
RestHelpers.LogDebug "Successfully logged in: " & Code, "FacebookAuthenticator.Login"
' Success!
Me.Code = Code

Expand Down Expand Up @@ -187,6 +194,7 @@ End Sub

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

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

Private Function TokenRequest() As RestRequest
Expand Down Expand Up @@ -267,6 +276,7 @@ Private Function OAuthExtractCode(IE As Object) As String
If StartIndex >= 0 And EndIndex > StartIndex Then
OAuthExtractCode = Mid$(Url, StartIndex, EndIndex - StartIndex)
Else
RestHelpers.LogError "Unrecognized token format: " & Url, "FacebookAuthenticator.OAuthExtractCode"
OAuthExtractCode = "Error: Unrecognized token formatting"
End If
End Function
Expand Down
10 changes: 10 additions & 0 deletions authenticators/GoogleAuthenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -110,6 +110,7 @@ Public Property Get LoginUrl() As String
Request.AddQuerystringParam "scope", ScopeString

LoginUrl = Request.FormattedResource
RestHelpers.LogDebug LoginUrl, "GoogleAuthenticator.LoginUrl"
Set Request = Nothing
End Property

Expand All @@ -129,7 +130,9 @@ Public Property Get Token() As String
Dim Data As Object
Set Data = RestHelpers.ParseJSON(Response.Content)
pToken = Data("access_token")
RestHelpers.LogDebug "Received Token: " & RestHelpers.Obfuscate(pToken), "GoogleAuthenticator.Token"
Else
RestHelpers.LogError "Failed to load token: " & Response.StatusCode & " - " & Response.Content, "GoogleAuthenticator.Token"
Err.Raise vbObjectError + Response.StatusCode, _
Description:="Failed to load Bearer Token: " & Response.StatusCode & " - " & Response.Content
End If
Expand Down Expand Up @@ -197,14 +200,17 @@ Public Sub Login(Optional APIKey As String = "")
Completed = True
If OAuthIsDenied(IE) Then
' Login failed
RestHelpers.LogError "Login failed or was denied", "GoogleAuthenticator.Login"
Err.Raise vbObjectError + 1, "OAuthDialog", "Login failed or was denied"
Else
Code = OAuthExtractCode(IE)
If Left(Code, 5) = "Error" Then
RestHelpers.LogError "Login error: " & Code, "GoogleAuthenticator.Login"
Err.Raise vbObjectError + 1, "OAuthDialog", Code
Else
' Success!
Me.AuthorizationCode = Code
RestHelpers.LogDebug "Login success: " & Code, "GoogleAuthenticator.Login"

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

If Not Completed Then
RestHelpers.LogError "Login did not complete", "GoogleAuthenticator.Login"
Err.Raise vbObjectError + 1, "OAuthDialog", "Login did not complete"
ElseIf Err.Number <> 0 Then
' Rethrow error
Expand Down Expand Up @@ -305,8 +312,10 @@ End Sub
Private Sub IAuthenticator_BeforeExecute(ByVal Client As RestClient, ByRef Request As RestRequest)
If Me.APIKey <> "" Then
Request.AddQuerystringParam "key", Me.APIKey
RestHelpers.LogDebug "Login with key: " & RestHelpers.Obfuscate(Me.APIKey), "GoogleAuthenticator.BeforeExecute"
Else
Request.AddHeader "Authorization", "Bearer " & Me.Token
RestHelpers.LogDebug "Login with token: " & RestHelpers.Obfuscate(Me.Token), "GoogleAuthenticator.BeforeExecute"
End If
End Sub

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

Private Function TokenRequest() As RestRequest
Expand Down
1 change: 1 addition & 0 deletions authenticators/HttpBasicAuthenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,7 @@ Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestCl
' Use http open with username and password values set
' (This is used in addition to setting request header, as some services required this)
Http.Open Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync, Me.Username, Me.Password
RestHelpers.LogDebug Request.MethodName() & Request.FullUrl(BaseUrl), "FacebookAuthenticator.HttpOpen"
End Sub

Private Function CreateHeader() As String
Expand Down
11 changes: 10 additions & 1 deletion authenticators/OAuth1Authenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -136,6 +136,7 @@ End Sub
Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestClient, ByRef Request As RestRequest, BaseUrl As String, Optional UseAsync As Boolean = False)
' Perform standard http open
Call Http.Open(Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync)
RestHelpers.LogDebug Request.MethodName() & Request.FullUrl(BaseUrl), "FacebookAuthenticator.HttpOpen"
End Sub

Public Function CreateHeader(Client As RestClient, Request As RestRequest) As String
Expand Down Expand Up @@ -180,6 +181,8 @@ Public Function CreateHeader(Client As RestClient, Request As RestRequest) As St
Header = Header & "oauth_token=" & Chr(34) & Me.Token & Chr(34) & ", "
Header = Header & "oauth_version=" & Chr(34) & "1.0" & Chr(34)
CreateHeader = Header

RestHelpers.LogDebug CreateHeader, "OAuth1Authenticator.CreateHeader"
End Function

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

CreateBaseString = Request.MethodName() & "&" & RestHelpers.UrlEncode(RequestUrl(Client, Request)) & "&" & RestHelpers.UrlEncode(base)
RestHelpers.LogDebug CreateBaseString, "OAuth1Authenticator.CreateBaseString"
End Function

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

RequestParameters = RestHelpers.UrlDecode(Replace(Parts("Querystring"), "?", ""))
' Remove leading ?
RequestParameters = Replace(Parts("Querystring"), "?", "")

' Replace + for spaces with %20
RequestParameters = Replace(RequestParameters, "+", "%20")
End Function

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

Public Function CreateSignature(base As String, signingKey As String) As String
CreateSignature = RestHelpers.Base64_HMACSHA1(base, signingKey)
RestHelpers.LogDebug CreateSignature, "OAuth1Authenticator.CreateSignature"
End Function

Public Function CreateTimestamp() As String
Expand Down
5 changes: 5 additions & 0 deletions authenticators/OAuth2Authenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -90,6 +90,7 @@ Private Sub IAuthenticator_BeforeExecute(ByVal Client As RestClient, ByRef Reque

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

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

Private Function CreateHeader() As String
Expand All @@ -165,4 +169,5 @@ Private Function CreateTokenRequest() As String
CreateTokenRequest = CreateTokenRequest & "&client_secret=" & Me.ClientSecret
CreateTokenRequest = CreateTokenRequest & "&username=" & Me.Username
CreateTokenRequest = CreateTokenRequest & "&password=" & Me.Password
RestHelpers.LogDebug CreateTokenRequest, "OAuth2Authenticator.CreateTokenRequest"
End Function
3 changes: 3 additions & 0 deletions authenticators/TwitterAuthenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,9 @@ Public Property Get Token() As String
' Store token if successful, otherwise throw error
If Response.StatusCode = Ok Then
pToken = Response.Data("access_token")
RestHelpers.LogDebug "Successfully received token: " & RestHelpers.Obfuscate(pToken), "TwitterAuthenticator.Token"
Else
RestHelpers.LogError "Failed to load token: " & Response.StatusCode & " - " & Response.Content, "TwitterAuthenticator.Token"
Err.Raise vbObjectError + Response.StatusCode, _
Description:="Failed to load Bearer Token: " & Response.StatusCode & " - " & Response.Content
End If
Expand Down Expand Up @@ -121,6 +123,7 @@ Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestCl

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

Private Function TokenRequest() As RestRequest
Expand Down
Binary file modified specs/Excel-REST - Specs.xlsm
Binary file not shown.
76 changes: 75 additions & 1 deletion specs/OAuth1AuthenticatorSpecs.bas
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,17 @@ Public Function Specs() As SpecSuite
Request.AddParameter "c", "Howdy!"
Request.AddQuerystringParam "d", 789

.Expect(Auth.RequestParameters(Client, Request)).ToEqual "a=123&b=456&c=Howdy!&d=789"
.Expect(Auth.RequestParameters(Client, Request)).ToEqual "a=123&b=456&c=Howdy%21&d=789"
End With

With Specs.It("should handle spaces in parameters correctly")
Client.BaseUrl = "http://localhost:3000/"
Set Request = New RestRequest
Request.Resource = "testing"
Request.AddQuerystringParam "a", "a b"

.Expect(Auth.RequestParameters(Client, Request)).ToEqual "a=a%20b"
.Expect(Request.FullUrl(Client.BaseUrl)).ToEqual "http://localhost:3000/testing?a=a+b"
End With

Set Client = New RestClient
Expand Down Expand Up @@ -95,3 +105,67 @@ Public Function Specs() As SpecSuite

InlineRunner.RunSuite Specs
End Function

' LinkedIn Specific
' ----------------- '
Sub LinkedInSpecs()
Dim Specs As New SpecSuite

Dim Client As New RestClient
Client.BaseUrl = "http://api.linkedin.com/v1/"

Dim Auth As New OAuth1Authenticator
Dim ConsumerKey As String
Dim ConsumerSecret As String
Dim Token As String
Dim TokenSecret As String

If Credentials.Loaded Then
ConsumerKey = Credentials.Values("LinkedIn")("api_key")
ConsumerSecret = Credentials.Values("LinkedIn")("api_secret")
Token = Credentials.Values("LinkedIn")("user_token")
TokenSecret = Credentials.Values("LinkedIn")("user_secret")
Else
ConsumerKey = InputBox("Enter Consumer Key")
ConsumerSecret = InputBox("Enter Consumer Secret")
Token = InputBox("Enter Token")
TokenSecret = InputBox("Enter Token Secret")
End If
Auth.Setup _
ConsumerKey:=ConsumerKey, _
ConsumerSecret:=ConsumerSecret, _
Token:=Token, _
TokenSecret:=TokenSecret

Set Client.Authenticator = Auth

Dim Request As RestRequest
Dim Response As RestResponse

With Specs.It("should get profile")
Set Request = New RestRequest
Request.Resource = "people/~?format={format}"

Set Response = Client.Execute(Request)

.Expect(Response.StatusCode).ToEqual 200
.Expect(Response.Data("firstName")).ToBeDefined
End With

With Specs.It("should search with space")
Set Request = New RestRequest
Request.Resource = "company-search?format={format}"
Request.AddQuerystringParam "keywords", "microsoft corp"

Set Response = Client.Execute(Request)

.Expect(Response.StatusCode).ToEqual 200
.Expect(Response.Data("companies")).ToBeDefined

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

InlineRunner.RunSuite Specs
End Sub
Loading