Skip to content

Commit

Permalink
v3.0.0
Browse files Browse the repository at this point in the history
  • Loading branch information
timhall committed Mar 16, 2014
1 parent 8176134 commit 6e21607
Show file tree
Hide file tree
Showing 11 changed files with 55 additions and 22 deletions.
Binary file modified Excel-REST - Blank.xlsm
Binary file not shown.
5 changes: 5 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -101,6 +101,11 @@ For more details, check out the [Wiki](https://github.com/timhall/Excel-REST/wik

### Release Notes

#### 3.0.0

- Add `Client.GetJSON` and `Client.PostJSON` helpers to GET and POST JSON without setting up request
- Add `AfterExecute` to `IAuthenticator`

#### 2.3.0

- Add `form-urlencoded` format and helpers
Expand Down
58 changes: 43 additions & 15 deletions authenticators/FacebookAuthenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
Implements IAuthenticator
''
' Facebook Authenticator v1.0.0
' Facebook Authenticator v2.0.0
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Custom IAuthenticator for Facebook OAuth
Expand Down Expand Up @@ -100,25 +100,15 @@ End Property
' Public Methods
' ============================================= '

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

Public Sub Setup(ApplicationId As String, ApplicationSecret As String)
Me.ApplicationId = ApplicationId
Me.ApplicationSecret = ApplicationSecret
End Sub

Private Sub IAuthenticator_BeforeExecute(Request As RestRequest)
Request.AddQuerystringParam "access_token", Me.Token
End Sub

Private Sub IAuthenticator_HttpOpen( _
http As MSXML2.IXMLHTTPRequest, _
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

Public Sub Login()
On Error GoTo CleanUp

Expand Down Expand Up @@ -179,6 +169,44 @@ End Sub
' 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)
Request.AddQuerystringParam "access_token", Me.Token
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)

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 TokenRequest() As RestRequest
Set TokenRequest = New RestRequest
TokenRequest.Resource = "oauth/access_token"
Expand Down
Binary file modified examples/Excel-REST - Example.xlsm
Binary file not shown.
Binary file modified specs/Excel-REST - Specs.xlsm
Binary file not shown.
2 changes: 1 addition & 1 deletion src/IAuthenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' IAuthenticator v2.3.0
' IAuthenticator v3.0.0
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Interface for creating authenticators for rest client
Expand Down
2 changes: 1 addition & 1 deletion src/RestClient.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' RestClient v2.3.0
' RestClient v3.0.0
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Interact with REST web services from Excel
Expand Down
2 changes: 1 addition & 1 deletion src/RestClientBase.bas
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Attribute VB_Name = "RestClientBase"
''
' RestClientBase v2.3.0
' RestClientBase v3.0.0
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Extendable RestClientBase for developing custom client classes
Expand Down
4 changes: 2 additions & 2 deletions src/RestHelpers.bas
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Attribute VB_Name = "RestHelpers"
''
' RestHelpers v2.3.0
' RestHelpers v3.0.0
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Common helpers RestClient
Expand Down Expand Up @@ -38,7 +38,7 @@ Attribute VB_Name = "RestHelpers"

#End If

Private Const UserAgent As String = "Excel Client v2.3.0 (https://github.com/timhall/Excel-REST)"
Private Const UserAgent As String = "Excel Client v3.0.0 (https://github.com/timhall/Excel-REST)"

' Moved to top from JSONLib
Private Const INVALID_JSON As Long = 1
Expand Down
2 changes: 1 addition & 1 deletion src/RestRequest.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' RestRequest v2.3.0
' RestRequest v3.0.0
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Create a request for use with a rest client
Expand Down
2 changes: 1 addition & 1 deletion src/RestResponse.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' RestResponse v2.3.0
' RestResponse v3.0.0
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Wrapper for http responses
Expand Down

0 comments on commit 6e21607

Please sign in to comment.