Skip to content

Commit 1af026f

Browse files
mauriciojxstimhall
authored andcommitted
Add TodoistAuthenticator and example
Signed-off-by: Tim Hall <tim.hall.engr@gmail.com>
1 parent f5b5f74 commit 1af026f

File tree

2 files changed

+351
-0
lines changed

2 files changed

+351
-0
lines changed
Lines changed: 282 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,282 @@
1+
VERSION 1.0 CLASS
2+
BEGIN
3+
MultiUse = -1 'True
4+
END
5+
Attribute VB_Name = "TodoistAuthenticator"
6+
Attribute VB_GlobalNameSpace = False
7+
Attribute VB_Creatable = False
8+
Attribute VB_PredeclaredId = False
9+
Attribute VB_Exposed = False
10+
''
11+
' Todoist Authenticator
12+
' (c) Tim Hall - https://github.com/VBA-tools/VBA-Web
13+
'
14+
' Custom IWebAuthenticator for TODOist API
15+
' https://developer.todoist.com/#oauth
16+
' ```
17+
'
18+
' @class TodoistAuthenticator
19+
' @implements IWebAuthenticator v4.*
20+
' @author tim.hall.engr@gmail.com
21+
' @license MIT (http://www.opensource.org/licenses/mit-license.php)
22+
'' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
23+
Implements IWebAuthenticator
24+
Option Explicit
25+
26+
' --------------------------------------------- '
27+
' Constants and Private Variables
28+
' --------------------------------------------- '
29+
30+
Private Const AuthorizationUrl As String = "https://todoist.com/oauth/authorize"
31+
Private Const TokenResource As String = "access_token"
32+
Private Const BaseUrl As String = "https://todoist.com/oauth"
33+
34+
Private WithEvents IE As InternetExplorer
35+
Attribute IE.VB_VarHelpID = -1
36+
Private LoginComplete As Boolean
37+
38+
' --------------------------------------------- '
39+
' Properties
40+
' --------------------------------------------- '
41+
42+
Public ClientId As String
43+
Public ClientSecret As String
44+
Public Scope As String
45+
Public RedirectURL As String
46+
Public State As String
47+
Public AuthorizationCode As String
48+
Public Token As String
49+
Public SessionCookie As New Collection
50+
51+
' ============================================= '
52+
' Public Methods
53+
' ============================================= '
54+
55+
''
56+
' Setup
57+
'
58+
' @param {String} ClientId
59+
' @param {String} ClientSecret
60+
' @param {String} RedirectURL
61+
''
62+
Public Sub Setup(ClientId As String, ClientSecret As String, RedirectURL As String)
63+
Me.ClientId = ClientId
64+
Me.ClientSecret = ClientSecret
65+
Me.RedirectURL = RedirectURL
66+
End Sub
67+
68+
''
69+
' Login
70+
''
71+
Public Sub Login()
72+
Dim lastURL As String
73+
Dim newURL As String
74+
75+
' Don't need to login if we already have authorization code or token
76+
If Me.AuthorizationCode <> "" Or Me.Token <> "" Then
77+
Exit Sub
78+
End If
79+
80+
' Redirect users to the authorization URL
81+
Set IE = New InternetExplorer
82+
IE.Silent = True
83+
IE.AddressBar = False
84+
IE.Navigate GetLoginUrl
85+
IE.Visible = True
86+
87+
' The rest is handled in BeforeNavigate, but need to wait here
88+
Do While Not LoginComplete
89+
DoEvents
90+
newURL = IE.LocationURL
91+
If newURL <> lastURL Then Call Me.ParseURL(newURL)
92+
lastURL = newURL
93+
Loop
94+
95+
IE.Quit
96+
Set IE = Nothing
97+
98+
End Sub
99+
100+
''
101+
' Logout
102+
''
103+
Public Sub Logout()
104+
Me.AuthorizationCode = ""
105+
Me.Token = ""
106+
End Sub
107+
108+
''
109+
' Get login url for current scopes
110+
'
111+
' @internal
112+
' @return {String}
113+
''
114+
Public Function GetLoginUrl() As String
115+
' Use Request for Url helpers
116+
Dim Request As New WebRequest
117+
Request.Resource = AuthorizationUrl
118+
119+
Request.AddQuerystringParam "client_id", Me.ClientId
120+
Request.AddQuerystringParam "scope", Me.Scope
121+
Request.AddQuerystringParam "state", Me.State
122+
123+
GetLoginUrl = Request.FormattedResource
124+
Set Request = Nothing
125+
End Function
126+
127+
''
128+
' Hook for taking action before a request is executed
129+
'
130+
' @param {WebClient} Client The client that is about to execute the request
131+
' @param in|out {WebRequest} Request The request about to be executed
132+
''
133+
Private Sub IWebAuthenticator_BeforeExecute(ByVal Client As WebClient, ByRef Request As WebRequest)
134+
Dim ck As Dictionary
135+
136+
If Me.Token = "" Then
137+
If Me.AuthorizationCode = "" Then
138+
Me.Login
139+
End If
140+
141+
Me.Token = Me.GetToken(Client)
142+
End If
143+
144+
'add token in the beggining of the Querystring
145+
Request.Resource = Request.Resource & "?token=" & Me.Token
146+
147+
End Sub
148+
149+
''
150+
' Hook for taking action after request has been executed
151+
'
152+
' @param {WebClient} Client The client that executed request
153+
' @param {WebRequest} Request The request that was just executed
154+
' @param in|out {WebResponse} Response to request
155+
''
156+
Private Sub IWebAuthenticator_AfterExecute(ByVal Client As WebClient, ByVal Request As WebRequest, ByRef Response As WebResponse)
157+
' e.g. Handle 401 Unauthorized or other issues
158+
End Sub
159+
160+
''
161+
' Hook for updating http before send
162+
'
163+
' @param {WebClient} Client
164+
' @param {WebRequest} Request
165+
' @param in|out {WinHttpRequest} Http
166+
''
167+
Private Sub IWebAuthenticator_PrepareHttp(ByVal Client As WebClient, ByVal Request As WebRequest, ByRef Http As Object)
168+
' e.g. Update option, headers, etc.
169+
170+
End Sub
171+
172+
''
173+
' Hook for updating cURL before send
174+
'
175+
' @param {WebClient} Client
176+
' @param {WebRequest} Request
177+
' @param in|out {String} Curl
178+
''
179+
Private Sub IWebAuthenticator_PrepareCurl(ByVal Client As WebClient, ByVal Request As WebRequest, ByRef Curl As String)
180+
' e.g. Add flags to cURL
181+
End Sub
182+
183+
''
184+
' Compares the current URL of the InternetExplorer window to the one expected
185+
' as a return. If matches the expected one, extract the AuthorizationCode from
186+
' it for a later exchange by a token. On sucess, sets a global boolean LoginComplete
187+
' to True
188+
'
189+
' @param {String} URL
190+
''
191+
Public Sub ParseURL(ByVal URL As String)
192+
Dim UrlParts() As String
193+
194+
UrlParts = Split(URL, "?")
195+
196+
If Left(UrlParts(0), Len(Me.RedirectURL)) = Me.RedirectURL Then
197+
' Parse querystring
198+
Dim QuerystringParams As Dictionary
199+
Set QuerystringParams = WebHelpers.ParseUrlEncoded(UrlParts(1))
200+
201+
If QuerystringParams.Exists("error") Then
202+
' TODO Handle error
203+
ElseIf QuerystringParams.Exists("code") Then
204+
If QuerystringParams("state") = Me.State Then
205+
Me.AuthorizationCode = QuerystringParams("code")
206+
Else
207+
' TODO Handle mismatched state (unlikely but possible)
208+
End If
209+
Else
210+
' TODO Handle unexpected response
211+
End If
212+
213+
LoginComplete = True
214+
End If
215+
216+
End Sub
217+
218+
219+
''
220+
' Get token (for current AuthorizationCode)
221+
'
222+
' @internal
223+
' @param {WebClient} Client
224+
' @return {String}
225+
''
226+
Public Function GetToken(Client As WebClient) As String
227+
On Error GoTo Cleanup
228+
229+
Dim TokenClient As WebClient
230+
Dim Request As New WebRequest
231+
Dim Body As New Dictionary
232+
Dim Response As WebResponse
233+
Dim Var As Variant
234+
235+
236+
' Clone client (to avoid accidental interactions)
237+
Set TokenClient = Client.Clone
238+
Set TokenClient.Authenticator = Nothing
239+
TokenClient.BaseUrl = BaseUrl
240+
241+
' Prepare token request
242+
Request.Resource = TokenResource
243+
Request.Method = WebMethod.HttpPost
244+
Request.RequestFormat = WebFormat.FormUrlEncoded
245+
Request.ResponseFormat = WebFormat.Json
246+
247+
Body.Add "code", Me.AuthorizationCode
248+
Body.Add "client_id", Me.ClientId
249+
Body.Add "client_secret", Me.ClientSecret
250+
Set Request.Body = Body
251+
252+
Set Response = TokenClient.Execute(Request)
253+
254+
If Response.StatusCode = WebStatusCode.Ok Then
255+
GetToken = Response.Data("access_token")
256+
For Each Var In Response.Cookies
257+
Call Me.SessionCookie.Add(Var)
258+
Next
259+
Else
260+
' TODO Handle error
261+
End If
262+
263+
Cleanup:
264+
265+
Set TokenClient = Nothing
266+
Set Request = Nothing
267+
Set Response = Nothing
268+
269+
' Rethrow error
270+
If Err.Number <> 0 Then
271+
' TODO
272+
End If
273+
End Function
274+
275+
''
276+
' Creates a unique state for the token login transaction
277+
'
278+
' @internal
279+
''
280+
Private Sub Class_Initialize()
281+
Me.State = WebHelpers.CreateNonce
282+
End Sub

examples/todoist/todoist_Auth.bas

Lines changed: 69 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,69 @@
1+
Attribute VB_Name = "todoist_Auth"
2+
'---------------------------------------------------------------------------------------
3+
' Project : Excel_TODOist
4+
' Module : todoist_Auth
5+
' Author : Mauricio Souza (mauriciojxs@yahoo.com.br)
6+
' Date : 2015-09-21
7+
' License : MIT (http://www.opensource.org/licenses/mit-license.php
8+
' Purpose : Example of TODOist authentication to obtain a Token
9+
'---------------------------------------------------------------------------------------
10+
11+
Option Explicit
12+
13+
'---------------------------------------------------------------------------------------
14+
' Procedure : login_example
15+
' Purpose : Shows an example of a request to TODOist using an Authenticator
16+
'
17+
' Parameters : []
18+
' Return : []
19+
'---------------------------------------------------------------------------------------
20+
Sub login_example()
21+
22+
'set TRUE to enable debbuging in the immediate window
23+
WebHelpers.EnableLogging = True
24+
25+
Dim Auth As New TodoistAuthenticator
26+
Dim CLIENT_ID As String
27+
Dim CLIENT_SECRET As String
28+
Dim REDIRECT_URL As String
29+
30+
'set your ClientID, ClientSecret and RedirectURL obtained at https://developer.todoist.com/appconsole.html
31+
'you can set a ficticious URL, like https://com.yourappname.redirecturl, but use the same one in the App Console
32+
'and here in the code
33+
CLIENT_ID = "your ID here"
34+
CLIENT_SECRET = "your Secret here"
35+
REDIRECT_URL = "your redirect URL here"
36+
Call Auth.Setup(CLIENT_ID, CLIENT_SECRET, REDIRECT_URL)
37+
38+
'set the scope you want for the access, as defined in https://developer.todoist.com/index.html#oauth
39+
Auth.Scope = "data:read_write"
40+
41+
Dim Client As New WebClient
42+
43+
'API Base URL provided by TODOist
44+
Client.BaseUrl = "https://todoist.com/API/v6/"
45+
46+
'Define the authenticator to be used by the client
47+
Set Client.Authenticator = Auth
48+
49+
50+
Dim Request As New WebRequest
51+
52+
'this is commom to all requests to TODOist
53+
Request.Method = WebMethod.HttpPost
54+
Request.Format = WebFormat.FormUrlEncoded
55+
Request.Resource = "sync"
56+
Request.AddQuerystringParam "seq_no", 0 'or the last one you received
57+
Request.AddQuerystringParam "seq_no_global", 0 'or the last one you received
58+
59+
'this is the specific to the type of request you want
60+
Request.AddQuerystringParam "resource_types", "[""projects""]"
61+
62+
Dim Response As WebResponse
63+
64+
'execute
65+
Set Response = Client.Execute(Request)
66+
67+
'do whatever you want with the Response
68+
69+
End Sub

0 commit comments

Comments
 (0)