Skip to content

Commit

Permalink
Add AfterExecute hook for IAuthenticator
Browse files Browse the repository at this point in the history
  • Loading branch information
timhall committed Mar 16, 2014
1 parent 1073924 commit d3913ee
Show file tree
Hide file tree
Showing 11 changed files with 312 additions and 65 deletions.
64 changes: 54 additions & 10 deletions authenticators/EmptyAuthenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -7,25 +7,69 @@ Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
''
' Base for setting up authenticator
'
' @author:
' @license:
' @implements: IAuthenticator
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
Implements IAuthenticator
Option Explicit

' ============================================= '
' Public Methods
' ============================================= '

''
' Setup authenticator
' --------------------------------------------- '

Public Sub Setup()
' Define any user-specific variables needed for authentication
End Sub

Private Sub IAuthenticator_BeforeExecute(Request As RestRequest)
' (Used to add any required fields to the `Request` before it is executed)
' ============================================= '
' Private Methods
' ============================================= '

''
' Hook for taking action before a request is executed
'
' @param {RestClient} Client The client that is about to execute the request
' @param {RestRequest} Request The request about to be executed
' --------------------------------------------- '

Private Sub IAuthenticator_BeforeExecute(ByVal Client As RestClient, ByRef Request As RestRequest)
' Add headers, cookies, etc to `Request` before it is executed
' (Leave blank to pass Request through unmodified)
End Sub

''
' Hook for taking action after request has been executed
'
' @param {RestClient} Client The client that executed request
' @param {RestRequest} Request The request that was just executed
' @param {RestResponse} Response to request
' --------------------------------------------- '

Private Sub IAuthenticator_AfterExecute(ByVal Client As RestClient, ByVal Request As RestRequest, ByRef Response As RestResponse)

' Leave blank to pass Request through unmodified
End Sub

Private Sub IAuthenticator_HttpOpen( _
Http As Object, _
Request As RestRequest, _
BaseUrl As String, _
Optional UseAsync As Boolean = False)
' (Used to open the given http request, making any necessary modifications)
''
' Hook for overriding standard http open (used for HTTP Basic)
'
' @param {MSXML2.IXMLHTTPRequest} http
' @parma {RestClient} Client The client that is about to open request
' @param {RestRequest} Request The request about to be opened
' @param {String} BaseUrl
' @param {Boolean} [useAsync=False]
' --------------------------------------------- '

Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestClient, ByRef Request As RestRequest, BaseUrl As String, Optional UseAsync As Boolean = False)
' Use modified http open (if necessary)

' Perform standard http open
' Call http.Open(Request.MethodName(), Request.FullUrl(BaseUrl), useAsync)
Call Http.Open(Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync)
End Sub
50 changes: 40 additions & 10 deletions authenticators/GoogleAuthenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -7,21 +7,22 @@ Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
Implements IAuthenticator
''
' Google Authenticator v1.0.0
' Google Authenticator v2.0.0
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Custom IAuthenticator for "installed application" authentication for Google APIs
'
' - https://developers.google.com/accounts/docs/OAuth2#installed
' - https://developers.google.com/accounts/docs/OAuth2InstalledApp
'
' @dependencies
' @implements IAuthenticator
' @author: tim.hall.engr@gmail.com
' @license: MIT (http://www.opensource.org/licenses/mit-license.php)
'
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
Implements IAuthenticator
Option Explicit

Private Const AuthorizationUrl As String = "https://accounts.google.com/o/oauth2/auth"
Private Const RedirectUri As String = "urn:ietf:wg:oauth:2.0:oob"
Expand Down Expand Up @@ -111,6 +112,10 @@ End Property
' Public Methods
' ============================================= '

''
' Setup authenticator
' --------------------------------------------- '

Public Sub Setup(ClientId As String, ClientSecret As String)
Me.ClientId = ClientId
Me.ClientSecret = ClientSecret
Expand Down Expand Up @@ -148,21 +153,46 @@ Public Sub Logout()
Me.Token = ""
End Sub

Private Sub IAuthenticator_BeforeExecute(Request As RestRequest)
''
' Hook for taking action before a request is executed
'
' @param {RestClient} Client The client that is about to execute the request
' @param {RestRequest} Request The request about to be executed
' --------------------------------------------- '

Private Sub IAuthenticator_BeforeExecute(ByVal Client As RestClient, ByRef Request As RestRequest)
If Me.ApiKey <> "" Then
Request.AddQuerystringParam "key", Me.ApiKey
Else
Request.AddHeader "Authorization", "Bearer " & Me.Token
End If
End Sub

Private Sub IAuthenticator_HttpOpen( _
Http As Object, _
Request As RestRequest, _
BaseUrl As String, _
Optional UseAsync As Boolean = False)
''
' Hook for taking action after request has been executed
'
' @param {RestClient} Client The client that executed request
' @param {RestRequest} Request The request that was just executed
' @param {RestResponse} Response to request
' --------------------------------------------- '

Private Sub IAuthenticator_AfterExecute(ByVal Client As RestClient, ByVal Request As RestRequest, ByRef Response As RestResponse)

End Sub

''
' Hook for overriding standard http open (used for HTTP Basic)
'
' @param {MSXML2.IXMLHTTPRequest} http
' @parma {RestClient} Client The client that is about to open request
' @param {RestRequest} Request The request about to be opened
' @param {String} BaseUrl
' @param {Boolean} [useAsync=False]
' --------------------------------------------- '

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
' Perform standard http open
Http.Open Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync
End Sub

Expand Down
37 changes: 33 additions & 4 deletions authenticators/HttpBasicAuthenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -9,12 +9,12 @@ Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
Implements IAuthenticator
''
' HttpBasicAuthenticator v1.0.0
' HttpBasicAuthenticator v2.0.0
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Utilize http basic authentication
'
' @author: tim.hall.engr@gmail.com
' @author tim.hall.engr@gmail.com
' @license: MIT (http://www.opensource.org/licenses/mit-license.php)
'
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
Expand Down Expand Up @@ -48,11 +48,40 @@ End Sub
' Private Methods
' ============================================= '

Private Sub IAuthenticator_BeforeExecute(Request As RestRequest)
''
' Hook for taking action before a request is executed
'
' @param {RestClient} Client The client that is about to execute the request
' @param {RestRequest} Request The request about to be executed
' --------------------------------------------- '

Private Sub IAuthenticator_BeforeExecute(ByVal Client As RestClient, ByRef Request As RestRequest)
Request.AddHeader "Authorization", CreateHeader()
End Sub

Private Sub IAuthenticator_HttpOpen(Http As Object, Request As RestRequest, BaseUrl As String, Optional UseAsync As Boolean = False)
''
' Hook for taking action after request has been executed
'
' @param {RestClient} Client The client that executed request
' @param {RestRequest} Request The request that was just executed
' @param {RestResponse} Response to request
' --------------------------------------------- '

Private Sub IAuthenticator_AfterExecute(ByVal Client As RestClient, ByVal Request As RestRequest, ByRef Response As RestResponse)

End Sub

''
' Hook for overriding standard http open (used for HTTP Basic)
'
' @param {MSXML2.IXMLHTTPRequest} http
' @parma {RestClient} Client The client that is about to open request
' @param {RestRequest} Request The request about to be opened
' @param {String} BaseUrl
' @param {Boolean} [useAsync=False]
' --------------------------------------------- '

Private Sub IAuthenticator_HttpOpen(ByRef Http As Object, ByVal Client As RestClient, ByRef Request As RestRequest, BaseUrl As String, Optional UseAsync As Boolean = False)
' 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
Expand Down
41 changes: 35 additions & 6 deletions authenticators/OAuth1Authenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -9,14 +9,14 @@ Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
Implements IAuthenticator
''
' OAuth1 Authenticator v1.0.0
' OAuth1 Authenticator v2.0.0
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Utilize OAuth1 authentication
'
' @dependencies
' Microsoft XML, v3+
' @author: tim.hall.engr@gmail.com
' @author tim.hall.engr@gmail.com
' @license: MIT (http://www.opensource.org/licenses/mit-license.php)
'
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
Expand Down Expand Up @@ -98,14 +98,43 @@ End Sub
' Private Methods
' ============================================= '

Private Sub IAuthenticator_BeforeExecute(Request As RestRequest)
''
' Hook for taking action before a request is executed
'
' @param {RestClient} Client The client that is about to execute the request
' @param {RestRequest} Request The request about to be executed
' --------------------------------------------- '

Private Sub IAuthenticator_BeforeExecute(ByVal Client As RestClient, ByRef Request As RestRequest)
' Add authorization header to request
Request.AddHeader "Authorization", CreateHeader(Request)
End Sub

Private Sub IAuthenticator_HttpOpen(Http As Object, Request As RestRequest, BaseUrl As String, Optional UseAsync As Boolean = False)
' Standard http open
Http.Open Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync
''
' Hook for taking action after request has been executed
'
' @param {RestClient} Client The client that executed request
' @param {RestRequest} Request The request that was just executed
' @param {RestResponse} Response to request
' --------------------------------------------- '

Private Sub IAuthenticator_AfterExecute(ByVal Client As RestClient, ByVal Request As RestRequest, ByRef Response As RestResponse)

End Sub

''
' Hook for overriding standard http open (used for HTTP Basic)
'
' @param {MSXML2.IXMLHTTPRequest} http
' @parma {RestClient} Client The client that is about to open request
' @param {RestRequest} Request The request about to be opened
' @param {String} BaseUrl
' @param {Boolean} [useAsync=False]
' --------------------------------------------- '

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)
End Sub

Private Function CreateHeader(Request As RestRequest) As String
Expand Down
41 changes: 35 additions & 6 deletions authenticators/OAuth2Authenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -9,15 +9,15 @@ Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
Implements IAuthenticator
''
' OAuth2 Authenticator v1.0.0
' OAuth2 Authenticator v2.0.0
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Utilize OAuth2 authentication
' (Currently using client credentials flow only)
'
' @dependencies
' Microsoft XML, v3+
' @author: tim.hall.engr@gmail.com
' @author tim.hall.engr@gmail.com
' @license: MIT (http://www.opensource.org/licenses/mit-license.php)
'
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
Expand Down Expand Up @@ -68,15 +68,22 @@ Public Sub SetupTokenUrl(TokenUrl As String, Optional TokenKey As String = "acce
Me.TokenKey = TokenKey
End Sub

Private Sub IAuthenticator_BeforeExecute(Request As RestRequest)
''
' Hook for taking action before a request is executed
'
' @param {RestClient} Client The client that is about to execute the request
' @param {RestRequest} Request The request about to be executed
' --------------------------------------------- '

Private Sub IAuthenticator_BeforeExecute(ByVal Client As RestClient, ByRef Request As RestRequest)
On Error GoTo ErrorHandling
If (Me.Token = "" Or Not Me.CacheToken) And (Me.TokenUrl <> "" And Me.TokenKey <> "") Then
' Get new token
Dim Http As Object
Set Http = CreateObject("MSXML2.ServerXMLHTTP")

Http.Open "POST", CreateTokenRequest, False
Http.send
Http.Send

If Http.Status <> 200 Then
' Error getting OAuth2 token
Expand Down Expand Up @@ -113,9 +120,31 @@ ErrorHandling:
End If
End Sub

Private Sub IAuthenticator_HttpOpen(Http As Object, Request As RestRequest, BaseUrl As String, Optional UseAsync As Boolean = False)
''
' Hook for taking action after request has been executed
'
' @param {RestClient} Client The client that executed request
' @param {RestRequest} Request The request that was just executed
' @param {RestResponse} Response to request
' --------------------------------------------- '

Private Sub IAuthenticator_AfterExecute(ByVal Client As RestClient, ByVal Request As RestRequest, ByRef Response As RestResponse)

End Sub

''
' Hook for overriding standard http open (used for HTTP Basic)
'
' @param {MSXML2.IXMLHTTPRequest} http
' @parma {RestClient} Client The client that is about to open request
' @param {RestRequest} Request The request about to be opened
' @param {String} BaseUrl
' @param {Boolean} [useAsync=False]
' --------------------------------------------- '

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
Call Http.Open(Request.MethodName(), Request.FullUrl(BaseUrl), UseAsync)
End Sub

' ============================================= '
Expand Down
Loading

0 comments on commit d3913ee

Please sign in to comment.