Introduction

Installation

  • Download the latest release (v4.1.6)
  • 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

WebRequest

WebRequest is used to create detailed requests (including formatting, querystrings, headers, cookies, and much more).

Usage:

Dim Request As New WebRequest
Request.Resource = "users/{Id}"

Request.Method = WebMethod.HttpPut
Request.RequestFormat = WebFormat.UrlEncoded
Request.ResponseFormat = WebFormat.Json

Dim Body As New Dictionary
Body.Add "name", "Tim"
Body.Add "project", "VBA-Web"
Set Request.Body = Body

Request.AddUrlSegment "Id", 123
Request.AddQuerystringParam "api_key", "abcd"
Request.AddHeader "Authorization", "Token ..."

' -> PUT (Client.BaseUrl)users/123?api_key=abcd
'    Authorization: Token ...
'
'    name=Tim&project=VBA-Web

Properties

Resource Get|Let {String}

Set the request’s portion of the url to be appended to the client’s BaseUrl. Can include Url Segments for dynamic values and Querystring parameters are smart enough to be appended to existing querystring (or added to resource if there isn’t an existing querystring).

Dim Client As New WebClient
Client.BaseUrl = "https://api.example.com/"

Dim Request As New WebRequest
Request.Resource = "messages"

' -> Url: https://api.example.com/messages

Request.Resource = "messages/{id}?a=1"
Request.AddUrlSegment "id", 123
Request.AddQuerystringParam "b", 2

' -> Url: https://api.example.com/messages/123?a=1&b=2

Method Get|Let {WebMethod}

Set the HTTP method to be used for the request: GET, POST, PUT, PATCH, DELETE

Dim Request As New WebRequest
Request.Method = WebMethod.HttpGet
Request.Method = WebMethod.HttpPost
' or HttpPut / HttpPatch / HttpDelete

Body Get|Let|Set {Variant}

Get

Body value converted to string using RequestFormat or CustomRequestFormat

Let

Use String or Array for Body

Set

Use Collection, Dictionary, or Object for Body

Dim Request As New WebRequest
Request.RequestFormat = WebFormat.Json

' Let: String|Array
Request.Body = "text"
Request.Body ' = "text"

Request.Body = Array("A", "B", "C")
Request.Body ' = "["A","B","C"]"

' Set: Collection|Dictionary|Object
Dim Body As Object
Set Body = New Collection
Body.Add "Howdy!"
Set Request.Body = Body
Request.Body ' = "["Howdy!"]"

Set Body = New Dictionary
Body.Add "a", 123
Body.Add "b", 456
Set Request.Body = Body
Request.Body ' = "{"a":123,"b":456}"

Format Get|Let {WebFormat}

Set RequestFormat, ResponseFormat, and Content-Type and Accept headers for the WebRequest

Dim Request As New WebRequest
Request.Format = WebFormat.Json
' -> Request.RequestFormat = WebFormat.Json
'    Request.ResponseFormat = WebFormat.Json
'    Content-Type: application/json
'    Accept: application/json

RequestFormat Get|Let {WebFormat}

Set the format to use for converting the response Body to string and for the Content-Type header

Note If WebFormat.Custom is used, the CustomRequestFormat must be set.

Dim Request As New WebRequest
Request.Body = Array("A", "B", "C")

Request.RequestFormat = WebFormat.Json

' -> Content-Type: application/json
' -> Convert Body to JSON string
Request.Body ' = "["A","B","C"]"

ResponseFormat Get|Let {WebFormat}

Set the format to use for converting the response Content to Data and for the Accept header

Note If WebFormat.Custom is used, the CustomResponseFormat must be set.

Dim Request As New WebRequest
Request.ResponseFormat = WebFormat.Json

' -> Accept: application/json

Dim Response As WebResponse
' ... from Execute
Response.Content ' = {"message":"Howdy!"}

' -> Parse Content to JSON Dictionary
Response.Data("message") ' = "Howdy!"

CustomRequestFormat Get|Let {String}

Use converter registered with WebHelpers.RegisterConverter to convert Body to string and set Content-Type header.

(Automatically sets RequestFormat to WebFormat.Custom)

WebHelpers.RegisterConverter "csv", "text/csv", "Module.ConvertToCSV", "Module.ParseCSV"

Dim Request As New WebRequest
Request.CustomRequestFormat = "csv"

' -> Content-Type: "text/csv"
' -> Body converted to string with Module.ConvertToCSV

CustomResponseFormat Get|Let {String}

Use converter registered with WebHelpers.RegisterConverter to convert the response Content to Data and set Accept header.

(Automatically sets ResponseFormat to WebFormat.Custom)

WebHelpers.RegisterConverter "csv", "text/csv", "Module.ConvertToCSV", "Module.ParseCSV"

Dim Request As New WebRequest
Request.CustomResponseFormat = "csv"

' -> Accept: text/csv
' -> WebResponse Content converted Data with Module.ParseCSV

ContentType Get|Let {String}

Set automatically from RequestFormat or CustomRequestFormat, but can be overriden to set Content-Type header for request.

Dim Request As New WebRequest
Request.ContentType = "text/csv"

' -> Content-Type: text/csv

Accept Get|Let {String}

Set automatically from ResponseFormat or CustomResponseFormat, but can be overriden to set Accept header for request.

Dim Request As New WebRequest
Request.Accept = "text/csv"

' -> Accept: text/csv

ContentLength Get|Let {Long}

Set automatically by length of Body, but can be overriden to set Content-Length header for request.

Dim Request As New WebRequest
Request.ContentLength = 200

' -> Content-Length: 200

FormattedResource Get {String}

Get Resource with Url Segments replaced and Querystring added.

Dim Request As New WebRequest
Request.Resource = "examples/{Id}"
Request.AddUrlSegment "Id", 123
Request.AddQuerystringParam "message", "Hello"

Request.FormattedResource ' = "examples/123?message=Hello"

Cookies Get|Set Collection

Note To add cookies, use AddCookie.

Collection of Cookies to include with request, stored as KeyValue (Dictionary: {Key: "...", Value: "..."}).

Headers Get|Set Collection

Note To add headers, use AddHeader.

Collection of Headers to include with request, stored as KeyValue (Dictionary: {Key: "...", Value: "..."}).

QuerystringParams Get|Set Collection

Note To add Querystring parameters, use AddQuerystringParam.

Collection of Querystring parameters to include with request, stored as KeyValue (Dictionary: {Key: "...", Value: "..."}).

UrlSegments Get|Set Dictionary

Note To add Url Segments, use AddUrlSegment

Url Segments are used to easily add dynamic values to Resource. Create a Url Segement in Resource with curly brackets and then replace with dynamic value with AddUrlSegment.

Dim Request As New WebRequest

Dim User As String
Dim Id As Long
User = "Tim"
Id = 123

' OK: Use string concatenation for dynamic values
Request.Resource = User & "/messages/" & Id

' BETTER: Use Url Segments for dynamic values
Request.Resource = "{User}/messages/{Id}"
Request.AddUrlSegment "User", User
Request.AddUrlSegment "Id", Id

Request.FormattedResource ' = "Tim/messages/123"

Methods

AddHeader AddHeader(Key, Value)

Key

{String}

Value

{Variant}

Add header to be sent with request

Dim Request As New WebRequest
Request.AddHeader "Authorization", "Bearer ..."

' -> Header: Authorization: Bearer ...

SetHeader SetHeader(Key, Value)

Key

{String}

Value

{Variant}

Add/replace header to be sent with request. SetHeader should be used for headers that can only be included once with a request (e.g. Authorization, Content-Type, etc.).

Dim Request As New WebRequest
Request.AddHeader "Authorization", "A..."
Request.AddHeader "Authorization", "B..."

' -> Headers:
'    Authorization: A...
'    Authorization: B...

Request.SetHeader "Authorization", "C..."

' -> Headers:
'    Authorization: C...

AddUrlSegment AddUrlSegment(Key, Value)

Key

{String}

Value

{Variant}

Url Segments are used to easily add dynamic values to Resource. Create a Url Segement in Resource with curly brackets and then replace with dynamic value with AddUrlSegment.

Dim Request As New WebRequest

Dim User As String
Dim Id As Long
User = "Tim"
Id = 123

' OK: Use string concatenation for dynamic values
Request.Resource = User & "/messages/" & Id

' BETTER: Use Url Segments for dynamic values
Request.Resource = "{User}/messages/{Id}"
Request.AddUrlSegment "User", User
Request.AddUrlSegment "Id", Id

Request.FormattedResource ' = "Tim/messages/123"

AddQuerystringParam AddQuerystringParam(Key, Value)

Key

{String}

Value

{Variant}

Add querysting parameter to be used in FormattedResource for request.

Dim Request As New WebRequest
Request.Resource = "messages"
Request.AddQuerystringParam "from", "Tim"

Request.FormattedResource ' = "messages?from=Tim"

AddCookie AddCookie(Key, Value)

Key

{String}

Value

{Variant}

Add cookie to be sent with request.

Dim Request As New WebRequest
Request.AddCookie "a", "abc"
Request.AddCookie "b", 123

' -> Header: Cookie: a=abc; b=123;

AddBodyParameter AddBodyParameter(Key, Value)

Key

{Variant}

Value

{Variant}

Add Key-Value to Body. Body must be a Dictionary (if it’s an Array or Collection an error is thrown).

Dim Request As New WebRequest
Request.Format = WebFormat.Json

Request.AddBodyParameter "a", 123
Request.Body ' = "{"a":123}"

' Can add parameters to existing Dictionary
Dim Body As New Dictionary
Body.Add "a", 123

Set Request.Body = Body
Request.AddBodyParameter "b", 456

Request.Body ' = "{"a":123,"b":456}"

CreateFromOptions CreateFromOptions(Options)

Options

{Dictionary}

Options("Headers")

{Collection} Optional Collection of KeyValue

Options("Cookies")

{Collection} Optional Collection of KeyValue

Options("QuerystringParams")

{Collection} Optional Collection of KeyValue

Options("UrlSegments")

{Dictionary} Optional

WebClient

WebClient executes requests and handles response and is responsible for functionality shared between requests, such as authentication, proxy configuration, and security.

Usage:

Dim Client As New WebClient
Client.BaseUrl = "https://www.example.com/api/"

Dim Auth As New HttpBasicAuthenticator
Auth.Setup Username, Password
Set Client.Authenticator = Auth

Dim Request As New WebRequest
Dim Response As WebResponse
' Setup WebRequest...

Set Response = Client.Execute(Request)
' -> Uses Http Basic authentication and appends Request.Resource to BaseUrl

Properties

BaseUrl Get|Let {String}

Set the base url that is shared by all requests and that the request Resource is appended to.

' Desired URLs
' https://api.example.com/v1/messages
' https://api.example.com/v1/users/id
'                BaseUrl <- ^ -> Resource

Dim Client As New WebClient
Client.BaseUrl = "https://api.example.com/v1/"

Dim Request As New WebRequest
Request.Resource = "messages"
Request.Resource = "users/{id}"

Authenticator Get|Set {IWebAuthenticator}

Attach an authenticator to the client for authentication requests.

Dim Client As New WebClient
Dim Auth As New OAuth1Authenticator
Auth.Setup ...

Set Client.Authenticator = Auth
' -> All requests use Auth to add "Authorization" header

TimeoutMs Get|Let {Long}

Timeout (in milliseconds) to wait for timeout in each request phase (Resolve, Connect, Send, Receive).

ProxyServer Get|Let {String}

Proxy server to pass requests through (except for those that match ProxyBypassList).

ProxyBypassList Get|Let {String}

Comma separated list of domains to bypass the proxy.

ProxyUsername Get|Let {String}

Username for proxy.

ProxyPassword Get|Let {String}

Password for proxy.

EnableAutoProxy Get|Let {Boolean}

Load proxy server and bypass list automatically (False by default).

Insecure Get|Let {Boolean}

Turn off SSL validation (False by default). Useful for self-signed certificates and should only be used with trusted servers.

FollowRedirects Get|Let {Boolean}

Follow redirects (301, 302, 307) using Location header (True by default).

Methods

Execute Execute(Request) {WebResponse}

Request

{WebRequest}

Execute the given request (append the request’s FormattedResource to the BaseUrl) and return the response.

Dim Client As New WebClient
Client.BaseUrl = "https://api.example.com/v1/"

Dim Request As New WebRequest
Request.Resource = "messages/{id}"
Request.AddUrlSegment "id", 123

' Add querystring, body, headers, cookies, etc. for request

Dim Response As WebResponse
Set Response = Client.Execute(Request)

' -> GET https://api.example/com/v1/messages/123
'    headers, cookies, and body...

GetJson GetJson(Url, [Options]) {WebResponse}

Url

{String}

Options

{Dictionary} Optional Headers, Cookies, QuerystringParams, and UrlSegments

  • Headers, Cookies, QuerystringParams: Collection of KeyValue (Create with WebHelpers.CreateKeyValue)
  • UrlSegments: Dictionary

Get JSON from the given URL (with options for Headers, Cookies, QuerystringParams, and UrlSegments).

Dim Client As New WebClient
Dim Url As String
Url = "https://api.example.com/v1/messages/1"

Dim Response As WebResponse
Set Response = Client.GetJson(Url)

Dim Headers As New Collection
Headers.Add WebHelpers.CreateKeyValue("Authorization", "Bearer ...")

Dim Options As New Dictionary
Options.Add "Headers", Headers

Set Response = Client.GetJson(Url, Options)

PostJson PostJson(Url, Body, [Options]) {WebResponse}

Url

{String}

Body

{Variant} Array, Collection, or Dictionary to post

Options

{Dictionary} Optional Headers, Cookies, QuerystringParams, and UrlSegments

  • Headers, Cookies, QuerystringParams: Collection of KeyValue (Create with WebHelpers.CreateKeyValue)
  • UrlSegments: Dictionary

Post JSON Body (Array, Collection, Dictionary) to the given URL (with options for Headers, Cookies, QuerystringParams, and UrlSegments).

Dim Client As New WebClient
Dim Url As String
Url = "https://api.example.com/v1/messages/1"

' Body
' Array, Collection, or Dictionary
Dim Body As New Dictionary
Body.Add "message", "Howdy!"

Dim Response As WebResponse
Set Response = Client.PostJson(Url, Body)

Dim Headers As New Collection
Headers.Add WebHelpers.CreateKeyValue("Authorization", "Bearer ...")

Dim Options As New Dictionary
Options.Add "Headers", Headers

Set Response = Client.PostJson(Url, Body, Options)

SetProxy SetProxy(Server, [Username], [Password], [BypassList])

Server

{String} Proxy server to pass requests through

Username

{String} Optional Username for proxy

Password

{String} Optional Password for proxy

BypassList

{String} Optional Comma-separated list of servers that should bypass proxy

Helper for setting proxy values.

Dim Client As New WebClient

' Just Server
Client.SetProxy "proxy_server:80"

' Server + Username and Password
Client.SetProxy "proxy_server:80", "Tim", "Password"

' Server + Username and Password + BypassList
Client.SetProxy "proxy_server:80", "Tim", "Password", "<local>,*.bypass.com"

GetFullUrl GetFullUrl(Request) {String}

Request

{WebRequest}

Get full url by joining given WebRequest.FormattedResource and BaseUrl.

WebResponse

Wrapper for http/cURL responses that includes parsed Data based on WebRequest.ResponseFormat.

Usage:

Dim Response As WebResponse
Set Response = Client.Execute(Request)

If Response.StatusCode = WebStatusCode.Ok Then
  ' Response.Headers, Response.Cookies
  ' Response.Data -> Parsed Response.Content based on Request.ResponseFormat
  ' Response.Body -> Raw response bytes
Else
  Debug.Print "Error: " & Response.StatusCode & " - " & Response.Content
End If

Properties

StatusCode Get|Let {WebStatusCode}

Status code that the server returned (e.g. 200).

StatusDescription Get|Let {String}

Status string that the server returned (e.g. 404 -> "Not Found").

Content Get|Let {String}

Content string that the server returned.

Data Get|Set {Object}

Parsed Content or Body based on the WebRequest.ResponseFormat.

Body Get|Let {Variant}

Raw bytes for the response.

Headers Get|Set {Collection}

Headers that were included with the response (Collection of KeyValue).

Cookies Get|Set {Collection}

Cookies that were included with the response (Collection of KeyValue).

Methods

Update Update(Updated)

Updated

{WebResponse}

Helper for updating the response with the given updated response values. Useful for ByRef cases to update response in place.

WebHelpers

Contains general-purpose helpers that are used throughout VBA-Web. Includes:

  • Logging
  • Converters and encoding
  • Url handling
  • Object/Dictionary/Collection/Array helpers
  • Request preparation / handling
  • Timing
  • Mac
  • Cryptography
  • Converters (JSON, XML, Url-Encoded)

Properties

WebStatusCode {WebStatusCode}

Ok

200

Created

201

NoContent

204

BadRequest

400

Unauthorized

401

Forbidden

403

NotFound

404

RequestTimeout

408

UnsupportedMediaType

415

InternalServerError

500

BadGateway

502

ServiceUnavailable

503

GatewayTimeout

504

Helper for common http status codes. (Use underlying status code for any codes not listed)

Dim Response As WebResponse

If Response.StatusCode = WebStatusCode.Ok Then
  ' Ok
ElseIf Response.StatusCode = 418 Then
  ' I'm a teapot
End If

WebMethod {WebMethod}

HttpGet

0

HttpPost

1

HttpPut

2

HttpDelete

3

HttpPatch

4

WebFormat {WebFormat}

PlainText

0

Json

1

FormUrlEncoded

2

Xml

3

Custom

4

UrlEncodingMode {UrlEncodingMode}

StrictUrlEncoding

0

FormUrlEncoding

1

QueryUrlEncoding

2

CookieUrlEncoding

3

PathUrlEncoding

4

  • StrictUrlEncoding uses RFC 3986 and is the default
  • FormUrlEncoding uses HTML5 form url-encoding and is used with WebFormat.FormUrlEncoded
  • QueryUrlEncoding uses subset of Strict and Form for default querystring encoding
  • CookieUrlEncoding uses RFC 6265
  • PathUrlEncoding uses “pchar” from RFC 3986 and is the default

EnableLogging Get|Let {Boolean}

Enable logging of requests and responses and other internal messages from VBA-Web. Should be the first step in debugging VBA-Web if something isn’t working as expected. (Logs display in Immediate Window (View > Immediate Window or ctrl+g)

Dim Client As New WebClient
Client.BaseUrl = "https://api.example.com/v1/"

Dim RequestWithTypo As New WebRequest
RequestWithTypo.Resource = "peeple/{id}"
RequestWithType.AddUrlSegment "idd", 123

' Enable logging before the request is executed
WebHelpers.EnableLogging = True

Dim Response As WebResponse
Set Response = Client.Execute(Request)

' Immediate window:
' --> Request - (Time)
' GET https://api.example.com/v1/peeple/{id}
' Headers...
'
' <-- Response - (Time)
' 404 ...

Methods

LogDebug LogDebug(Message, [From])

Message

{String}

From

{String} Optional

Log message (when logging is enabled with EnableLogging) with optional location where the message is coming from. Useful when writing extensions to VBA-Web (like an IWebAuthenticator).

LogDebug "Executing request..."
' -> VBA-Web: Executing request...

LogDebug "Executing request...", "Module.Function"
' -> Module.Function: Executing request...

LogWarning LogWarning(Message, [From])

Message

{String}

From

{String} Optional

Log warning (even when logging is disabled with EnableLogging) with optional location where the message is coming from. Useful when writing extensions to VBA-Web (like an IWebAuthenticator).

WebHelpers.LogWarning "Something could go wrong"
' -> WARNING - VBA-Web: Something could go wrong

WebHelpers.LogWarning "Something could go wrong", "Module.Function"
' -> WARNING - Module.Function: Something could go wrong

LogError LogError(Message, [From], [ErrNumber])

Message

{String}

From

{String} Optional

ErrNumber

{Long} Optional

Log error (even when logging is disabled with EnableLogging) with optional location where the message is coming from and error number. Useful when writing extensions to VBA-Web (like an IWebAuthenticator).

WebHelpers.LogError "Something went wrong"
' -> ERROR - VBA-Web: Something went wrong

WebHelpers.LogError "Something went wrong", "Module.Function"
' -> ERROR - Module.Function: Something went wrong

WebHelpers.LogError "Something went wrong", "Module.Function", 100
' -> ERROR - Module.Function: 100, Something went wrong

LogRequest LogRequest(Client, Request)

Client

{WebClient}

Request

{WebRequest}

Log details of the request (Url, headers, cookies, body, etc.).

LogResponse LogResponse(Client, Request, Response)

Client

{WebClient}

Request

{WebRequest}

Response

{WebResponse}

Log details of the response (Status, headers, content, etc.).

Obfuscate Obfuscate(Secure, [Character])

Secure

{String} Message to obfuscate

Character

{String} Optional Character to obfuscate with (“*” is default)

Obfuscate any secure information before logging.

Dim Password As String
Password = "Secret"

LogDebug "Password = " & Obfuscate(Password)
' -> Password = ******

ParseJson ParseJson(Value) {Object}

Value

{String} JSON value to parse

Parse JSON value to Dictionary if it’s an object or Collection if it’s an array.

ConvertToJson ConvertToJson(Value, [Whitespace]) {String}

Value

{Variant} Dictionary, Collection, or Array to convert to string

Whitespace

{Integer|String} Pretty-print with given number of spaces or string per indentation

Convert Dictionary, Collection, or Array to JSON string.

ParseUrlEncoded ParseUrlEncoded(Value) {Dictionary}

Value

{String} Url-Encoded value to parse

Parse Url-Encoded value to Dictionary.

ConvertToUrlEncoded ConvertToUrlEncoded(Obj, [EncodingMode = FormUrlEncoding]) {String}

Obj

{Dictionary|Collection|Variant} Value to convert to Url-Encoded string

EncodingMode

{UrlEncodingMode} Optional Default is UrlEncodingMode.FormUrlEncoding

Convert Dictionary/Collection to Url-Encoded string.

ParseXml ParseXml(Value) {Dictionary}

Value

{String} Encoded XML value to parse

Parse XML value to Dictionary.

Note Currently, XML is not supported in 4.0.0 due to lack of Mac support. An updated parser is being created that supports Mac and Windows, but in order to avoid future breaking changes, ParseXml and ConvertToXml are not currently implemented.

See XML Support in 4.0 for details on how to use XML in Windows in the meantime.

ConvertToXml ConvertToXml(Value) {String}

Value

Dictionary|Variant XML

Convert Dictionary to XML string.

Note Currently, XML is not supported in 4.0.0 due to lack of Mac support. An updated parser is being created that supports Mac and Windows, but in order to avoid future breaking changes, ParseXml and ConvertToXml are not currently implemented.

See XML Support in 4.0 for details on how to use XML in Windows in the meantime.

ParseByFormat ParseByFormat(Value, Format, [CustomFormat], [Bytes]) {Object}

Value

{String} Value to parse

Format

{WebFormat}

CustomFormat

{String} Optional Name of registered custom converter

Bytes

{Variant} Optional Bytes for custom converter (if ParseType = "Binary")

Helper for parsing value to given WebFormat or custom format. Returns Dictionary or Collection based on given Value.

ConvertToFormat ConvertToFormat(Value, Format, [CustomFormat]) {String}

Value

{Dictionary|Collection|Variant} Dictionary, Collection, or Array to convert to string

Format

{WebFormat}

CustomFormat

{String} Optional Name of registered custom converter

Helper for converting value to given WebFormat or custom format.

Note Only some converters handle Collection or Array.

UrlEncode UrlEncode(Text, [SpaceAsPlus = False], [EncodeUnsafe = True], [EncodingMode = StrictUrlEncoding]) {String}

Text

{Variant} Text to encode

SpaceAsPlus

{Boolean} Optional Default is False

DEPRECATED Use EncodingMode:=FormUrlEncoding

EncodeUnsafe

{Boolean} Optional Default is True

DEPRECATED This was based on an outdated URI spec and has since been removed. EncodingMode:=CookieUrlEncoding is the closest approximation of this behavior

EncodingMode

{UrlEncodingMode} Optional Default is UrlEncodingMode.StrictUrlEncoding

Encode string for URLs (Reference).

UrlDecode UrlDecode(Encoded, [PlusAsSpace = True], [EncodingMode = StrictUrlEncoding]) {String}

Encoded

{String} Text to decode

PlusAsSpace

{Boolean} Optional Default is True

DEPRECATED Use EncodingMode:=FormUrlEncoded or QueryUrlEncoding

EncodingMode

{UrlEncodingMode} Optional Default is UrlEncodingMode.StrictUrlEncoding

Decode Url-encoded string.

Base64Encode Base64Encode(Text) {String}

Text

{String} Text to encode

Base64-encode text.

Base64Decode Base64Decode(Encoded) {String}

Encoded

{String} Text to decode

Decode Base64-encoded text

RegisterConverter RegisterConverter(Name, MediaType, ConvertCallback, ParseCallback, [Instance], [ParseType])

Name

{String} Name of converter for use with CustomRequestFormat or CustomResponseFormat

MediaType

{String} Media type to use for Content-Type and Accept headers

ConvertCallback

{String} Global or object function name for converting

ParseCallback

{String} Global or object function name for parsing

Instance

{Object} Optional Use instance methods for ConvertCallback and ParseCallback

ParseType

{String} Optional "String" (default) or "Binary" to pass raw binary response to ParseCallback

Register custom converter for converting request Body and response Content. If the ConvertCallback or ParseCallback are object methods, pass in an object instance. If the ParseCallback needs the raw binary response value (e.g. file download), set ParseType = "Binary", otherwise "String" is used.

  • ConvertCallback signature: Function ...(Value As Variant) As String
  • ParseCallback signature: Function ...(Value As String) As Object
' 1. Use global module functions for Convert and Parse
' ---
' Module: CSVConverter
Function ParseCSV(Value As String) As Object
  ' ...
End Function
Function ConvertToCSV(Value As Variant) As String
  ' ...
End Function

WebHelpers.RegisterConverter "csv", "text/csv", _
  "CSVConverter.ConvertToCSV", "CSVConverter.ParseCSV"

' 2. Use object instance functions for Convert and Parse
' ---
' Object: CSVConverterClass
' same as above...

Dim Converter As New CSVConverterClass
WebHelpers.RegisterConverter "csv", "text/csv", _
  "ConvertToCSV", "ParseCSV", Instance:=Converter

' 3. Pass raw binary value to ParseCallback
' ---
' Module: ImageConverter
Function ParseImage(Bytes As Variant) As Object
  ' ...
End Function
Function ConvertToImage(Value As Variant) As String
  ' ...
End Function

WebHelpers.RegisterConverter "image", "image/jpeg", _
  "ImageConverter.ConvertToImage", "ImageConverter.ParseImage", _
  ParseType:="Binary"

JoinUrl JoinUrl(LeftSide, RightSide) {String}

LeftSide

{String}

RightSide

{String}

Join two url parts, handling “/” in between them.

Debug.Print WebHelpers.JoinUrl("a/", "/b")
Debug.Print WebHelpers.JoinUrl("a", "b")
Debug.Print WebHelpers.JoinUrl("a/", "b")
Debug.Print WebHelpers.JoinUrl("a", "/b")

UrlParts UrlParts(Url) {Dictionary}

Url

{String}

Get relevant parts of the given url. Returns Protocol, Host, Port, Path, Querystring, and Hash.

WebHelpers.UrlParts "https://www.google.com/a/b/c.html?a=1&b=2#hash"
' -> Protocol = https
'    Host = www.google.com
'    Port = 443
'    Path = /a/b/c.html
'    Querystring = a=1&b=2
'    Hash = hash

WebHelpers.UrlParts "localhost:3000/a/b/c"
' -> Protocol = ""
'    Host = localhost
'    Port = 3000
'    Path = /a/b/c
'    Querystring = ""
'    Hash = ""

CloneDictionary CloneDictionary(Dict) {Dictionary}

Dict

{Dictionary}

Create a cloned copy of the Dictionary. This is not a deep copy, so children objects are copied by reference.

CloneCollection CloneCollection(Coll) {Collection}

Coll

{Collection}

Create a cloned copy of the Collection. This is not a deep copy, so children objects are copied by reference.

CreateKeyValue CreateKeyValue(Key, Value) {Dictionary}

Key

{String}

Value

{Variant}

Helper for creating Key-Value pair with Dictionary. Used in WebRequest/WebResponse Cookies, Headers, and QuerystringParams

WebHelpers.CreateKeyValue "abc", 123
' -> {"Key": "abc", "Value": 123}

FindInKeyValues FindInKeyValues(KeyValues, Key) {Variant}

KeyValues

{Collection} of Key-Value

Key

{Variant}

Search a Collection of Key-Value and retrieve the value for the given key.

Dim KeyValues As New Collection
KeyValues.Add WebHelpers.CreateKeyValue("abc", 123)

WebHelpers.FindInKeyValues KeyValues, "abc"
' -> 123

WebHelpers.FindInKeyValues KeyValues, "unknown"
' -> Empty

AddOrReplaceInKeyValues AddOrReplaceInKeyValues(KeyValues, Key, Value)

KeyValues

{Collection}

Key

{String}

Value

{Variant}

Helper for adding/replacing KeyValue in Collection of KeyValue

  • Add if key not found
  • Replace if key is found
Dim KeyValues As New Collection
KeyValues.Add WebHelpers.CreateKeyValue("a", 123)
KeyValues.Add WebHelpers.CreateKeyValue("b", 456)
KeyValues.Add WebHelpers.CreateKeyValue("c", 789)

WebHelpers.AddOrReplaceInKeyValues KeyValues, "b", "abc"
WebHelpers.AddOrReplaceInKeyValues KeyValues, "d", "def"

' -> [
'      {"Key":"a","Value":123},
'      {"Key":"b","Value":"abc"},
'      {"Key":"c","Value":789},
'      {"Key":"d","Value":"def"}
'    ]

FormatToMediaType FormatToMediaType(Format, [CustomFormat]) {String}

Format

{WebFormat}

CustomFormat

{String} Optional Needed if Format = WebFormat.Custom

Get the media-type for the given format / custom format.

MethodToName MethodToName(Method) {String}

Method

{WebMethod}

Get the method name for the given WebMethod

WebHelpers.MethodToName WebMethod.HttpPost
' -> "POST"

HMACSHA1 HMACSHA1(Text, Secret, [Format]) {String}

Text

{String}

Secret

{String}

Format

{String} Optional "Hex" or "Base64" encoding for result

Determine the HMAC for the given text and secret using the SHA1 hash algorithm.

WebHelpers.HMACSHA1 "Howdy!", "Secret"
' -> c8fdf74a9d62aa41ac8136a1af471cec028fb157

HMACSHA256 HMACSHA256(Text, Secret, [Format]) {String}

Text

{String}

Secret

{String}

Format

{String} Optional "Hex" or "Base64" encoding for result

Determine the HMAC for the given text and secret using the SHA256 hash algorithm.

WebHelpers.HMACSHA256 "Howdy!", "Secret"
' -> fb5d65...

MD5 MD5(Text, [Format]) {String}

Text

{String}

Format

{String} Optional "Hex" or "Base64" encoding for result

Determine the MD5 hash of the given text.

WebHelpers.MD5 "Howdy!"
' -> 7105f32280940271293ee00ac97da5a7

CreateNonce CreateNonce([NonceLength])

NonceLength

{Integer} Optional Default is 32

Create random alphanumeric nonce (0-9a-zA-Z)

IWebAuthenticator

Interface for creating authenticators for WebClients. EmptyAuthenticator has everything setup for creating your own authenticators. See Implementing your own IWebAuthenticator for a detailed guide on creating an authenticator.

Methods

BeforeExecute BeforeExecute(Client, Request)

Client

{WebClient}

Request

ByRef {WebRequest} The request about to be executed

Hook for taking action before a request is executed. Useful for adding headers (e.g. “Authorization”), cookies, etc.

AfterExecute AfterExecute(Client, Request, Response)

Client

{WebClient}

Request

{WebRequest} The request that was just executed

Response

ByRef {WebResponse}

Hook for taking action after a request has been executed. Useful for handling 401 Unauthorized or other issues.

PrepareHttp PrepareHttp(Client, Request, Http)

Client

{WebClient}

Request

{WebRequest}

Http

{WinHttpRequest}

Hook for updating http before send. Useful for setting internal http options (WinHttpRequest Docs).

PrepareCurl PrepareCurl(Client, Request, Curl)

Client

{WebClient}

Request

{WebRequest}

Curl

{String}

Hook for update cURL command before send. Useful for setting internal cURL options (cURL Docs)

WebAsyncWrapper

Wrapper WebClient and WebRequest that enables callback-style async requests

Note Windows-only and Excel-only and requires reference to "Microsoft WinHTTP Services, version 5.1"

Usage:

' Module: Handler
Public Sub Simple(Response As WebResponse)
  ' ...
End Sub
Public Sub WithArgs(Response As WebResponse, Args As Variant)
  ' ...
End Sub

Dim Client As New WebClient
Client.BaseUrl = "https://api.example.com/v1/"

' Wrapper needs Client to execute requests
Dim Wrapper As New WebAsyncWrapper
Set Wrapper.Client = Client

Dim Request As New WebRequest
Request.Resource = "messages"

Wrapper.ExecuteAsync Request, "Handler.Simple"

' -> Simple called later with response

' If you need to pass state to callback, use CallbackArgs
Dim Args As Variant
Args = Array("abc", 123)

Wrapper.ExecuteAsync Request, "Handler.WithArgs", Args

' -> WithArgs called later with response and args

Properties

Client Get|Set {WebClient}

Client to use for executing requests.

Methods

ExecuteAsync ExecuteAsync(Request, Callback, [CallbackArgs])

Request

{WebRequest}

Callback

{String}

CallbackArgs

{Variant} Optional

Execute the given WebRequest asynchronously, passing the response (and CallbackArgs if given) to the Callback.