@@ -6,9 +6,9 @@ Attribute VB_Name = "TodoistAuthenticator"
66Attribute VB_GlobalNameSpace = False
77Attribute VB_Creatable = False
88Attribute VB_PredeclaredId = False
9- Attribute VB_Exposed = False
9+ Attribute VB_Exposed = True
1010''
11- ' Todoist Authenticator
11+ ' Todoist Authenticator v3.0.8
1212' (c) Tim Hall - https://github.com/VBA-tools/VBA-Web
1313' Mauricio Souza (mauriciojxs@yahoo.com.br)
1414'
@@ -100,7 +100,7 @@ Public Sub Login()
100100 If Me.AuthorizationCode <> "" Or Me.Token <> "" Then
101101 Exit Sub
102102 End If
103-
103+
104104 Dim auth_Completed As Boolean
105105 If Me.State = "" Then
106106 Me.State = WebHelpers.CreateNonce
@@ -110,15 +110,15 @@ Public Sub Login()
110110 ' User retrieves and pastes token for Mac login
111111 Dim auth_Response As String
112112 auth_Completed = True
113-
113+
114114 auth_Response = VBA.InputBox("To login to Todoist, insert your API token from" & vbNewLine & _
115115 "todoist.com > Settings > Todoist Settings > Account > API token" , _
116116 Title:="Insert Todoist API Token" )
117-
117+
118118 If auth_Response = "" Then
119119 Err.Raise 11040 + vbObjectError, "OAuthDialog" , "Login was cancelled"
120120 End If
121-
121+
122122 ' Success!
123123 Me.Token = auth_Response
124124#Else
@@ -133,7 +133,7 @@ Public Sub Login()
133133 auth_IE.AddressBar = False
134134 auth_IE.Navigate Me.GetLoginUrl
135135 auth_IE.Visible = True
136-
136+
137137 Do While Not auth_LoginIsComplete(auth_IE)
138138 DoEvents
139139 Loop
@@ -163,7 +163,7 @@ auth_Cleanup:
163163auth_ErrorHandling:
164164
165165 Dim auth_ErrorDescription As String
166-
166+
167167 auth_ErrorDescription = "An error occurred while logging in." & vbNewLine
168168 If Err.Number <> 0 Then
169169 If Err.Number - vbObjectError <> 11040 Then
@@ -197,11 +197,11 @@ Public Function GetLoginUrl() As String
197197 ' Use Request for Url helpers
198198 Dim auth_Request As New WebRequest
199199 auth_Request.Resource = auth_AuthorizationUrl
200-
200+
201201 auth_Request.AddQuerystringParam "client_id" , Me.ClientId
202202 auth_Request.AddQuerystringParam "scope" , Me.Scope
203203 auth_Request.AddQuerystringParam "state" , Me.State
204-
204+
205205 GetLoginUrl = auth_Request.FormattedResource
206206 Set auth_Request = Nothing
207207End Function
@@ -217,10 +217,10 @@ Private Sub IWebAuthenticator_BeforeExecute(ByVal Client As WebClient, ByRef Req
217217 If Me.AuthorizationCode = "" Then
218218 Me.Login
219219 End If
220-
220+
221221 Me.Token = Me.GetToken(Client)
222222 End If
223-
223+
224224 ' Add token as querystring param
225225 Request.AddQuerystringParam "token" , Me.Token
226226End Sub
@@ -267,55 +267,55 @@ End Sub
267267''
268268Public Function GetToken (Client As WebClient ) As String
269269 On Error GoTo auth_Cleanup
270-
270+
271271 Dim auth_TokenClient As WebClient
272272 Dim auth_Request As New WebRequest
273273 Dim auth_Body As New Dictionary
274274 Dim auth_Response As WebResponse
275275 Dim auth_Cookie As Variant
276-
276+
277277 ' Clone client (to avoid accidental interactions)
278278 Set auth_TokenClient = Client.Clone
279279 Set auth_TokenClient.Authenticator = Nothing
280280 auth_TokenClient.BaseUrl = auth_BaseUrl
281-
281+
282282 ' Prepare token request
283283 auth_Request.Resource = auth_TokenResource
284284 auth_Request.Method = WebMethod.HttpPost
285285 auth_Request.RequestFormat = WebFormat.FormUrlEncoded
286286 auth_Request.ResponseFormat = WebFormat.Json
287-
287+
288288 auth_Body.Add "code" , Me.AuthorizationCode
289289 auth_Body.Add "client_id" , Me.ClientId
290290 auth_Body.Add "client_secret" , Me.ClientSecret
291291 Set auth_Request.Body = auth_Body
292-
292+
293293 Set auth_Response = auth_TokenClient.Execute(auth_Request)
294-
294+
295295 If auth_Response.StatusCode = WebStatusCode.Ok Then
296296 GetToken = auth_Response.Data(auth_TokenResource)
297297 Else
298298 Err.Raise 11041 + vbObjectError, "TodoistAuthenticator.GetToken" , _
299299 auth_Response.StatusCode & ": " & auth_Response.Content
300300 End If
301-
301+
302302auth_Cleanup:
303-
303+
304304 Set auth_TokenClient = Nothing
305305 Set auth_Request = Nothing
306306 Set auth_Response = Nothing
307-
307+
308308 ' Rethrow error
309309 If Err.Number <> 0 Then
310310 Dim auth_ErrorDescription As String
311-
311+
312312 auth_ErrorDescription = "An error occurred while retrieving token." & vbNewLine
313313 If Err.Number - vbObjectError <> 11041 Then
314314 auth_ErrorDescription = auth_ErrorDescription & _
315315 Err.Number & VBA.IIf (Err.Number < 0 , " (" & VBA.LCase$(VBA.Hex$(Err.Number)) & ")" , "" ) & ": "
316316 End If
317317 auth_ErrorDescription = auth_ErrorDescription & Err.Description
318-
318+
319319 WebHelpers.LogError auth_ErrorDescription, "TodoistAuthenticator.GetToken" , 11041 + vbObjectError
320320 Err.Raise 11041 + vbObjectError, "TodoistAuthenticator.GetToken" , auth_ErrorDescription
321321 End If
@@ -345,7 +345,7 @@ Private Function auth_LoginIsDenied(auth_IE As Object) As Boolean
345345 Dim auth_Querystring As Dictionary
346346 Set auth_UrlParts = WebHelpers.GetUrlParts(auth_IE.LocationURL)
347347 Set auth_Querystring = WebHelpers.ParseUrlEncoded(auth_UrlParts("Querystring" ))
348-
348+
349349 If auth_Querystring.Exists("error" ) Then
350350 If auth_Querystring("error" ) = "access_denied" Then
351351 auth_LoginIsDenied = True
0 commit comments