VBA-tools / VBA-Web

VBA-Web: Connect VBA, Excel, Access, and Office for Windows and Mac to web services and the web
http://vba-tools.github.io/VBA-Web/
MIT License
2.01k stars 494 forks source link

Help creating a Microsoft Graph Authenticator #415

Open adriangith opened 5 years ago

adriangith commented 5 years ago

Can anybody help me create a Microsoft Graph Authenticator. My knowledge is currently too limited to figure it out. Currently, I'm trying to adapt the Todoist Authenticator

TK-99 commented 1 year ago

If you are still interested, I have managed to work it out using the OAuth2 authenticator with a few changes. It took a fair bit of searching to find the resources and headers to use

supsnehal commented 7 months ago

Hi @TK-99 ,

Could you share the changes you made to get the Microsoft Graph Authentication working

TK-99 commented 7 months ago
''
' Microsoft Graph Authenticator v0.0.1
' by TK - Jan 2023
'
' based on:
' OAuth2 Authenticator v3.0.5
' (c) Tim Hall - https://github.com/VBA-tools/VBA-Web
'
' Custom IWebAuthenticator for application-only authentication in Microsoft Graph API
'
' Details:
' - Where to get TenantID, ClientID, ClientSecret:
'         - get from Azure Activate Directory, App registration - Directory (Tenant ID)
'                        ClientID = ApplicationID,
'                        ClientSecret in Certificates & Secrets under relevant App name
' see Get access without a user: Application Permissions
' need to get Administator appoved permissions in Azure Activate Directory set up  - Request API permissions
' see Postman video:
'           'J Thake - how to use Postman and set up access
'            https://www.youtube.com/watch?v=3RTHY3jScmA

'   https://learn.microsoft.com/en-us/graph/auth-v2-service?context=graph%2Fapi%2F1.0&view=graph-rest-1.0
'
' - https://github.com/VBA-tools/VBA-Web/wiki/Implementing-your-own-IWebAuthenticator
'
' Errors:
' 11041 / 80042b21 / -2147210463 - Error retreiving token
'
' @example
'   Dim Auth As New GraphAuthenticator
'   Auth.Setup "Your Tenant ID", "Your Client ID", "Your Client Secret"
'
'   Set Client.Authenticator = Auth
'
' @class GraphAuthenticator
' @implements IWebAuthenticator v4.*
' @author TK
' @license
'' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
Implements IWebAuthenticator
Option Explicit

' --------------------------------------------- '
' Constants and Private Variables
' --------------------------------------------- '

Private Const auth_TokenResource As String = "access_token"
Private Const auth_BaseUrl As String = "https://login.microsoftonline.com"

' --------------------------------------------- '
' Properties
' --------------------------------------------- '

Public TenantId As String
Public ClientId As String
Public ClientSecret As String

Public Token As String
Public TokenKey As String

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

Public Sub Setup(TenantId As String, ClientId As String, ClientSecret As String)
    Me.TenantId = TenantId
    Me.ClientId = ClientId
    Me.ClientSecret = ClientSecret
End Sub

Private Function auth_AuthorizationUrl() As String
    auth_AuthorizationUrl = "https://login.microsoftonline.com/" & Me.TenantId & "/oauth2/v2.0/token"
End Function

Private Sub IWebAuthenticator_BeforeExecute(ByVal client As WebClient, ByRef Request As WebRequest)
    If Me.Token = "" Then
        Me.Token = Me.GetToken(client)
    End If

    Request.SetHeader "Authorization", "Bearer " & Me.Token
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 Sub

Public Function GetToken(Optional auth_Client As WebClient) As String
'https://docs.microsoft.com/en-us/graph/auth-v2-service

    On Error GoTo auth_Cleanup

    Dim auth_TokenClient As New WebClient
    Dim auth_Request As New WebRequest
    Dim auth_Response As WebResponse

    ' Clone client (to avoid accidental interactions)
'    Set auth_TokenClient = auth_Client.Clone
'    Set auth_TokenClient.Authenticator = Nothing
 '   auth_TokenClient.BaseURL = auth_BaseUrl

    ' Prepare token request
    auth_Request.Resource = auth_AuthorizationUrl '"https://login.microsoftonline.com/" & Me.TenantId & "/oauth2/v2.0/token"
    auth_Request.method = WebMethod.HttpPost
    auth_Request.AddHeader "Host", "login.microsoftonline.com"
    auth_Request.ContentType = "application/x-www-form-urlencoded"

    auth_Request.body = "client_id=" & Me.ClientId & _
                        "&scope=https://graph.microsoft.com/.default" & _
                        "&client_secret=" & Me.ClientSecret & _
                        "&grant_type=client_credentials"

    Set auth_Response = auth_TokenClient.Execute(auth_Request)

    If auth_Response.StatusCode = WebStatusCode.OK Then
        GetToken = auth_Response.data(auth_TokenResource)
    Else
        Err.Raise 11041 + vbObjectError, Description:=auth_Response.StatusCode & ": " & auth_Response.CONTENT
    End If

auth_Cleanup:

    Set auth_TokenClient = Nothing
    Set auth_Request = Nothing
    Set auth_Response = Nothing

    ' Rethrow error
    If Err.Number <> 0 Then
        Dim auth_ErrorDescription As String

        auth_ErrorDescription = "An error occurred while retrieving token" & vbNewLine
        If Err.Number - vbObjectError <> 11041 Then
            auth_ErrorDescription = auth_ErrorDescription & _
                Err.Number & VBA.IIf(Err.Number < 0, " (" & VBA.LCase$(VBA.Hex$(Err.Number)) & ")", "") & ": "
        End If
        auth_ErrorDescription = auth_ErrorDescription & Err.Description

        WebHelpers.LogError auth_ErrorDescription, "GraphAuthenticator.GetToken", 11041 + vbObjectError
        Err.Raise 11041 + vbObjectError, "GraphAuthenticator.GetToken", auth_ErrorDescription
    End If
End Function

' ============================================= '
' Private Methods
' ============================================= '

Private Sub Class_Initialize()

End Sub
TK-99 commented 7 months ago

This is my poor but working code based on Tim Hall's original Authenticator class.

The important part is in the GetToken function:

Public Function GetToken(Optional auth_Client As WebClient) As String
'https://docs.microsoft.com/en-us/graph/auth-v2-service

    On Error GoTo auth_Cleanup

    Dim auth_TokenClient As New WebClient
    Dim auth_Request As New WebRequest
    Dim auth_Response As WebResponse

    ' Clone client (to avoid accidental interactions)
  '// the next bit is commented out because I couldn't get it to work
'    Set auth_TokenClient = auth_Client.Clone
'    Set auth_TokenClient.Authenticator = Nothing
 '   auth_TokenClient.BaseURL = auth_BaseUrl

    ' Prepare token request - THIS BIT BELOW IS THE CRITICAL PART
    auth_Request.Resource = "https://login.microsoftonline.com/" & Me.TenantId & "/oauth2/v2.0/token"
    auth_Request.method = WebMethod.HttpPost
    auth_Request.AddHeader "Host", "login.microsoftonline.com"
    auth_Request.ContentType = "application/x-www-form-urlencoded"

    auth_Request.body = "client_id=" & Me.ClientId & _
                        "&scope=https://graph.microsoft.com/.default" & _
                        "&client_secret=" & Me.ClientSecret & _
                        "&grant_type=client_credentials"

    Set auth_Response = auth_TokenClient.Execute(auth_Request)

    If auth_Response.StatusCode = WebStatusCode.OK Then
        GetToken = auth_Response.data(auth_TokenResource)
    Else
        Err.Raise 11041 + vbObjectError, Description:=auth_Response.StatusCode & ": " & auth_Response.CONTENT
    End If

auth_Cleanup:
    '// code as per original

End Function
TK-99 commented 7 months ago

My code works with app permissions using the TenantID, ClientID and ClientSecret.

I got it working with my own Microsoft Business account - so I had access to everything.

When I started using it at work, I needed to get the SharePoint admin to activate Sites.Selected for my site. It needs to be done via PowerShell

zgrose commented 7 months ago

Be careful placing secrets in "public clients" like VBA. A bad actor can grab them without too much effort.

TK-99 commented 7 months ago

@zgrose - yes, it's a problem I have been struggling with: where to store the secrets when using VBA. Have you got any tips?

zgrose commented 7 months ago

Using the Device Code flow was the most secure option I found for a pure VBA solution. You basically treat Excel like a SmartTV and pop a URL for the user to navigate to and then grab the access token when they have completed the login process. It's not the most seemless process (you're in Excel, then you're in a browser, then you have to go back to Excel manually), but it's probably the most secure/flexible without invoking C/C++/C# libraries.

It looks like MS Graph supports the flow https://learn.microsoft.com/en-us/graph/sdks/choose-authentication-providers?tabs=csharp#device-code-provider

but whether or not the user experience meets your needs is up to you.

TK-99 commented 6 months ago

Thanks @zgrose, I'll look into Device Code flow. My current solution is to put the secrets into a SharePoint Online list which connects to a querytable in an Excel worksheet. The querytable is empty on opening of the file so users need to authenticate with their Microsoft 365 credentials to allow the querytable to refresh.