- 
          
 - 
                Notifications
    
You must be signed in to change notification settings  - Fork 507
 
Implementing your own IWebAuthenticator
If the built-in authenticators don't meet your needs, you can create your own. Here's an example of how I set up a new authenticator for Twitter's Application-only authentication in their new V1.1 REST API.
Import the EmptyAuthenticator class to your project and rename it to your desired class name.
Implements IWebAuthenticator
Public Sub Setup()
    ' Define any user-specific variables needed for authentication
End Sub
Private Sub IWebAuthenticator_BeforeExecute(ByVal Client As WebClient, ByRef Request As WebRequest)
    ' e.g Add headers, cookies, etc.
End Sub
Private Sub IWebAuthenticator_AfterExecute(ByVal Client As WebClient, ByVal Request As WebRequest, ByRef Response As WebResponse)
    ' e.g. Handle 401 Unauthorized or other issues
End Sub
Private Sub IWebAuthenticator_PrepareHttp(ByVal Client As WebClient, ByVal Request As WebRequest, ByRef Http As Object)
    ' e.g. Update option, headers, etc.
End Sub
Private Sub IWebAuthenticator_PrepareCurl(ByVal Client As WebClient, ByVal Request As WebRequest, ByRef Curl As String)
    ' e.g. Add flags to cURL
End SubTwitter's Application-only authentication uses a variant of OAuth 2.0 Client Credentials flow where an application is granted access with a unique token that will be included with each request. The following flow is used to get a token and then authenticate requests:
- Request token: POST Consumer Key and Consumer Secret using Basic authentication and Twitter's specified request info to 
https://api.twitter.com/oauth2/tokento receive token - Include the token in the header of each API request 
Authorization: Bearer {token} 
The Setup function is a convention used to define any user-specific variables needed for authentication. The Consumer Key and Consumer Secret are needed to get a bearer token so these will be passed in and stored during setup.
Public ConsumerKey As String
Public ConsumerSecret As String
Public Sub Setup(ConsumerKey As String, ConsumerSecret As String)
    Me.ConsumerKey = ConsumerKey
    Me.ConsumerSecret = ConsumerSecret
End SubThe BeforeExecute function is used to add fields to the Request before it is executed. Examples include adding parameters to the querystring, adding headers to the request, or updating the resource to point to a secure route. Request is passed in ByRef so fields can be added directly. Leave the BeforeExecute function empty to pass through the Request unmodified)
In this example, we are going to request a bearer token and then attach it as an Authorization header to the request. A few notes:
- Use the 
WebClientpassed toBeforeExecuteto get the token so that any proxy values are used for the token request - Clone the 
WebClientso that there are no unforeseen interactions with the original passed toBeforeExecute 
Public Function GetToken(Client As WebClient) As String
    On Error GoTo Cleanup
    
    Dim TokenClient As WebClient
    Dim Request As New WebRequest
    Dim Response As WebResponse
    
    ' Clone client (to avoid accidental interactions)
    Set TokenClient = auth_Client.Clone
    Set TokenClient.Authenticator = Nothing
    TokenClient.BaseUrl = "https://api.twitter.com/"
    
    ' Prepare token request
    Request.Resource = "oauth2/token"
    Request.Method = WebMethod.HttpPost
    Request.RequestFormat = WebFormat.FormUrlEncoded
    Request.ResponseFormat = WebFormat.Json
    
    ' Request a token using Basic authentication
    Request.AddHeader "Authorization", _
        "Basic " & WebHelpers.Base64Encode(Me.ConsumerKey & ":" & Me.ConsumerSecret)
    Request.AddBodyParameter "grant_type", "client_credentials"
    
    Set Response = TokenClient.Execute(auth_Request)
    
    If Response.StatusCode = WebStatusCode.Ok Then
        GetToken = Response.Data("access_token")
    Else
        Err.Raise 11041 + vbObjectError, Description:=Response.StatusCode & ": " & Response.Content
    End If
    
Cleanup:
    
    Set TokenClient = Nothing
    Set Request = Nothing
    Set Response = Nothing
    
    ' Rethrow error
    If Err.Number <> 0 Then
        ' Error handling...
    End If
End FunctionPrivate Sub IWebAuthenticator_BeforeExecute(ByVal Client As RestClient, ByRef Request As RestRequest)
    If Me.Token = "" Then
        Me.Token = Me.GetToken(Client)
    End If
    Request.AddHeader "Authorization", "Bearer " & Me.Token
End SubThat's it! Now you can use whatever authentication scheme you please, although the main ones (Basic and OAuth 1.0) have already been created and can be found in the authenticators/ directory. The TwitterAuthenticator created here is located there and includes small changes to cache the token between requests.
The AfterExecute function is used to handle Unauthorized or Forbidden responses and retry with added credentials or other behavior.
In this example, no after execute behavior is needed and the method is left blank, but for an example of how this is used, see the DigestAuthenticator.
PrepareHttp and PrepareCurl can be used to update the underlying WinHttpRequest or cURL command that will be used to execute the request. For an example of how this is used, see the HttpBasicAuthenticator.
Dim TwitterClient As New WebClient
Dim Auth As New TwitterAuthenticator
Auth.Setup _
    ConsumerKey:="Your consumer key", _
    ConsumerSecret:="Your consumer secret"
Set TwitterClient.Authenticator = Auth