Skip to content

Commit

Permalink
v4.0.20
Browse files Browse the repository at this point in the history
  • Loading branch information
timhall committed Nov 6, 2015
1 parent 254fcd1 commit 4286a9f
Show file tree
Hide file tree
Showing 13 changed files with 153 additions and 152 deletions.
1 change: 1 addition & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ Major Changes:
- __4.0.17__ Add `FollowRedirects` and follow redirects by default, convert stored body to Variant, fix multiple 100 Continue bug
- __4.0.18__ Add `VBA.Randomize` to `CreateNonce` and add `TodoistAuthenticator`
- __4.0.19__ Fix installer and update VBA-JSON to v1.0.3
- __4.0.20__ Update VBA-JSON to v2.0.1 (Note: Breaking change in VBA-JSON, Solidus is no longer escaped by default)

Breaking Changes:

Expand Down
42 changes: 21 additions & 21 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ VBA-Web (formerly Excel-REST) makes working with complex webservices and APIs ea
Getting started
---------------

- Download the [latest release (v4.0.19)](https://github.com/VBA-tools/VBA-Web/releases)
- Download the [latest release (v4.0.20)](https://github.com/VBA-tools/VBA-Web/releases)
- To install/upgrade in an existing file, use `VBA-Web - Installer.xlsm`
- To start from scratch in Excel, `VBA-Web - Blank.xlsm` has everything setup and ready to go

Expand Down Expand Up @@ -39,19 +39,19 @@ Function GetDirections(Origin As String, Destination As String) As String
' and set a base url that all requests will be appended to
Dim MapsClient As New WebClient
MapsClient.BaseUrl = "https://maps.googleapis.com/maps/api/"

' Use GetJSON helper to execute simple request and work with response
Dim Resource As String
Dim Response As WebResponse

Resource = "directions/json?" & _
"origin=" & Origin & _
"&destination=" & Destination & _
"&sensor=false"
Set Response = MapsClient.GetJSON(Resource)

' => GET https://maps.../api/directions/json?origin=...&destination=...&sensor=false

ProcessDirections Response
End Function

Expand All @@ -70,13 +70,13 @@ Public Sub ProcessDirections(Response As WebResponse)
End Sub
```

There are 3 primary components in VBA-Web:
There are 3 primary components in VBA-Web:

1. `WebRequest` for defining complex requests
2. `WebClient` for executing requests
3. `WebResponse` for dealing with responses.
In the above example, the request is fairly simple, so we can skip creating a `WebRequest` and instead use the `Client.GetJSON` helper to GET json from a specific url. In processing the response, we can look at the `StatusCode` to make sure the request succeeded and then use the parsed json in the `Data` parameter to extract complex information from the response.
3. `WebResponse` for dealing with responses.

In the above example, the request is fairly simple, so we can skip creating a `WebRequest` and instead use the `Client.GetJSON` helper to GET json from a specific url. In processing the response, we can look at the `StatusCode` to make sure the request succeeded and then use the parsed json in the `Data` parameter to extract complex information from the response.

### WebRequest Example

Expand All @@ -86,30 +86,30 @@ If you wish to have more control over the request, the following example uses `W
Function GetDirections(Origin As String, Destination As String) As String
Dim MapsClient As New WebClient
MapsClient.BaseUrl = "https://maps.googleapis.com/maps/api/"

' Create a WebRequest for getting directions
Dim DirectionsRequest As New WebRequest
DirectionsRequest.Resource = "directions/{format}"
DirectionsRequest.Method = WebMethod.HttpGet
' Set the request format

' Set the request format
' -> Sets content-type and accept headers and parses the response
DirectionsRequest.Format = WebFormat.Json

' Replace {format} segment
DirectionsRequest.AddUrlSegment "format", "json"

' Add querystring to the request
DirectionsRequest.AddQuerystringParam "origin", Origin
DirectionsRequest.AddQuerystringParam "destination", Destination
DirectionsRequest.AddQuerystringParam "sensor", "false"

' => GET https://maps.../api/directions/json?origin=...&destination=...&sensor=false

' Execute the request and work with the response
Dim Response As WebResponse
Set Response = MapsClient.Execute(DirectionsRequest)

ProcessDirections Response
End Function

Expand Down Expand Up @@ -138,14 +138,14 @@ The following example demonstrates using an authenticator with VBA-Web to query
Function QueryTwitter(Query As String) As WebResponse
Dim TwitterClient As New WebClient
TwitterClient.BaseUrl = "https://api.twitter.com/1.1/"

' Setup authenticator
Dim TwitterAuth As New TwitterAuthenticator
TwitterAuth.Setup _
ConsumerKey:="Your consumer key", _
ConsumerSecret:="Your consumer secret"
Set TwitterClient.Authenticator = TwitterAuth

' Setup query request
Dim Request As New WebRequest
Request.Resource = "search/tweets.json"
Expand All @@ -154,10 +154,10 @@ Function QueryTwitter(Query As String) As WebResponse
Request.AddParameter "q", Query
Request.AddParameter "lang", "en"
Request.AddParameter "count", 20

' => GET https://api.twitter.com/1.1/search/tweets.json?q=...&lang=en&count=20
' Authorization Bearer Token... (received and added automatically via TwitterAuthenticator)

Set QueryTwitter = TwitterClient.Execute(Request)
End Function
```
Expand Down
Binary file modified VBA-Web - Blank.xlsm
Binary file not shown.
Binary file modified VBA-Web - Installer.xlsm
Binary file not shown.
Binary file modified examples/VBA-Web - Example.xlsm
Binary file not shown.
Binary file modified specs/VBA-Web - Specs - Async.xlsm
Binary file not shown.
Binary file modified specs/VBA-Web - Specs.xlsm
Binary file not shown.
2 changes: 1 addition & 1 deletion src/IWebAuthenticator.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
''
' IWebAuthenticator v4.0.19
' IWebAuthenticator v4.0.20
' (c) Tim Hall - https://github.com/VBA-tools/VBA-Web
'
' Interface for creating authenticators for rest client
Expand Down
32 changes: 16 additions & 16 deletions src/WebAsyncWrapper.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
''
' WebAsyncWrapper v4.0.19
' WebAsyncWrapper v4.0.20
' (c) Tim Hall - https://github.com/VBA-tools/VBA-Web
'
' Wrapper WebClient and WebRequest that enables callback-style async requests
Expand Down Expand Up @@ -84,7 +84,7 @@ Public Property Set Client(Value As WebClient)
Dim web_ErrorDescription As String
web_ErrorDescription = "The Client for a WebAsyncWrapper should not be changed as it may affect any currently executing Requests. " & _
"A new WebAsyncWrapper should be created for each WebClient."

WebHelpers.LogError web_ErrorDescription, "WebAsyncWrapper.Client", vbObjectError + 11050
Err.Raise vbObjectError + 11050, "WebAsyncWrapper.Client", web_ErrorDescription
End If
Expand All @@ -107,7 +107,7 @@ Public Sub ExecuteAsync(Request As WebRequest, Callback As String, Optional ByVa
' - AsyncWrapper can only watch one WinHttpRequest's events
' - Callback + CallbackArgs would need to be stored per Request
Dim web_Async As WebAsyncWrapper

Set web_Async = Me.Clone
web_Async.PrepareAndExecuteRequest Request, Callback, CallbackArgs
End Sub
Expand Down Expand Up @@ -138,19 +138,19 @@ Public Sub PrepareAndExecuteRequest(Request As WebRequest, Callback As String, O

Me.Callback = Callback
Me.CallbackArgs = CallbackArgs

Set Me.Request = Request.Clone
Set Me.Http = Me.Client.PrepareHttpRequest(Request)

web_StartTimeoutTimer
Me.Http.Send Request.Body
Exit Sub

web_ErrorHandling:

Set Me.Http = Nothing
Set Me.Request = Nothing

' Rethrow error
Err.Raise Err.Number, Err.Source, Err.Description
End Sub
Expand All @@ -163,10 +163,10 @@ End Sub
''
Public Sub TimedOut()
Dim web_Response As New WebResponse

web_StopTimeoutTimer
WebHelpers.LogDebug "Timed out", "WebAsyncWrapper.TimedOut"

' Callback
web_Response.StatusCode = WebStatusCode.RequestTimeout
web_Response.StatusDescription = "Request Timeout"
Expand All @@ -191,9 +191,9 @@ Private Sub web_RunCallback(web_Response As WebResponse)
' Debug.Print args(i) & " was passed into async execute"
' Next i
' End Function

WebHelpers.LogResponse Me.Client, Me.Request, web_Response

If Not Me.Client.Authenticator Is Nothing Then
Me.Client.Authenticator.AfterExecute Me.Client, Me.Request, web_Response
End If
Expand All @@ -205,7 +205,7 @@ Private Sub web_RunCallback(web_Response As WebResponse)
Application.Run Me.Callback, web_Response
End If
End If

Set Me.Http = Nothing
Set Me.Request = Nothing
End Sub
Expand All @@ -215,13 +215,13 @@ Private Sub web_StartTimeoutTimer()
Dim web_TimeoutS As Long

If WebHelpers.AsyncRequests Is Nothing Then: Set WebHelpers.AsyncRequests = New Dictionary

' Round ms to seconds with minimum of 1 second if ms > 0
web_TimeoutS = Round(Me.Client.TimeoutMs / 1000, 0)
If Me.Client.TimeoutMs > 0 And web_TimeoutS = 0 Then
web_TimeoutS = 1
End If

WebHelpers.AsyncRequests.Add Me.Request.Id, Me
Application.OnTime Now + TimeValue("00:00:" & web_TimeoutS), "'WebHelpers.OnTimeoutTimerExpired """ & Me.Request.Id & """'"
End Sub
Expand All @@ -238,9 +238,9 @@ End Sub
' Process asynchronous requests
Private Sub Http_OnResponseFinished()
Dim web_Response As New WebResponse

web_StopTimeoutTimer

' Callback
web_Response.CreateFromHttp Me.Client, Me.Request, Me.Http
web_RunCallback web_Response
Expand Down
Loading

0 comments on commit 4286a9f

Please sign in to comment.