From 12960585ba5a9fbc03be721690b4754dd0511073 Mon Sep 17 00:00:00 2001 From: bissonex Date: Fri, 22 Dec 2017 14:32:07 -0500 Subject: [PATCH 1/2] Add charset parameter Add optional parameter to select charset to use for encoding/decoding --- src/WebHelpers.bas | 38 +++++++++++++++++++++++++++++++++----- 1 file changed, 33 insertions(+), 5 deletions(-) diff --git a/src/WebHelpers.bas b/src/WebHelpers.bas index e8e45db4..528515d7 100644 --- a/src/WebHelpers.bas +++ b/src/WebHelpers.bas @@ -1,6 +1,6 @@ Attribute VB_Name = "WebHelpers" '' -' WebHelpers v4.1.3 +' WebHelpers v4.1.4 ' (c) Tim Hall - https://github.com/VBA-tools/VBA-Web ' ' Contains general-purpose helpers that are used throughout VBA-Web. Includes: @@ -1075,9 +1075,10 @@ End Function ' Base64-encode text. ' ' @param {Variant} Text Text to encode +' @param {String} [Charset=Windows-1250] - Charset for encoding (UTF-8, UTF-16, Windows-1250) ' @return {String} Encoded string '' -Public Function Base64Encode(Text As String) As String +Public Function Base64Encode(Text As String, Optional Charset As String = "Windows-1250") As String #If Mac Then Dim web_Command As String web_Command = "printf " & PrepareTextForPrintf(Text) & " | openssl base64" @@ -1085,10 +1086,22 @@ Public Function Base64Encode(Text As String) As String #Else Dim web_Bytes() As Byte - web_Bytes = VBA.StrConv(Text, vbFromUnicode) + With CreateObject("ADODB.Stream") + .Type = 2 ' adTypeText + .Open + ' For a list of the character set names that are known by a system, + ' see the subkeys of HKEY_CLASSES_ROOT\MIME\Database\Charset in the Windows Registry. + .Charset = Charset + .WriteText Text + .Position = 0 + .Type = 1 ' adTypeBinary + web_Bytes = .Read + .Close + End With + Base64Encode = web_AnsiBytesToBase64(web_Bytes) #End If - + Base64Encode = VBA.Replace$(Base64Encode, vbLf, "") End Function @@ -1096,9 +1109,10 @@ End Function ' Decode Base64-encoded text ' ' @param {Variant} Encoded Text to decode +' @param {String} [Charset=Windows-1250] - Charset for decoding (UTF-8, UTF-16, Windows-1250) ' @return {String} Decoded string '' -Public Function Base64Decode(Encoded As Variant) As String +Public Function Base64Decode(Encoded As Variant, Optional Charset As String = "Windows-1250") As String ' Add trailing padding, if necessary If (VBA.Len(Encoded) Mod 4 > 0) Then Encoded = Encoded & VBA.Left("====", 4 - (VBA.Len(Encoded) Mod 4)) @@ -1119,11 +1133,25 @@ Public Function Base64Decode(Encoded As Variant) As String web_Node.Text = Encoded Base64Decode = VBA.StrConv(web_Node.nodeTypedValue, vbUnicode) + With CreateObject("ADODB.Stream") + .Type = 1 ' adTypeBinary + .Open + .Write web_Node.nodeTypedValue + .Position = 0 + .Type = 2 ' adTypeText + ' For a list of the character set names that are known by a system, + ' see the subkeys of HKEY_CLASSES_ROOT\MIME\Database\Charset in the Windows Registry. + .Charset = Charset + Base64Decode = .ReadText + .Close + End With + Set web_Node = Nothing Set web_XmlObj = Nothing #End If End Function + '' ' Register custom converter for converting request `Body` and response `Content`. ' If the `ConvertCallback` or `ParseCallback` are object methods, From b1bd5c778e7e1e59174fb93cb3480fac14fe037a Mon Sep 17 00:00:00 2001 From: bissonex Date: Fri, 22 Dec 2017 14:38:32 -0500 Subject: [PATCH 2/2] Adding tests to decode/encode specs --- specs/Specs_WebHelpers.bas | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/specs/Specs_WebHelpers.bas b/specs/Specs_WebHelpers.bas index 11747189..e60695ae 100644 --- a/specs/Specs_WebHelpers.bas +++ b/specs/Specs_WebHelpers.bas @@ -415,6 +415,11 @@ Public Function Specs() As SpecSuite ' --------------------------------------------- ' With Specs.It("should Base64 encode string") .Expect(WebHelpers.Base64Encode("Howdy!")).ToEqual "SG93ZHkh" + + .Expect(WebHelpers.Base64Encode("üöäÄÜÖß", "Windows-1250")).ToEqual "/PbkxNzW3w==" + .Expect(WebHelpers.Base64Encode("üöäÄÜÖß", "UTF-8")).ToEqual "77u/w7zDtsOkw4TDnMOWw58=" + .Expect(WebHelpers.Base64Encode("üöäÄÜÖß", "UTF-16")).ToEqual "//78APYA5ADEANwA1gDfAA==" + End With ' Base64Decode @@ -424,6 +429,11 @@ Public Function Specs() As SpecSuite ' The following implicitly has padding of "=" and "==" at end, base-64 decoding should handle this .Expect(WebHelpers.Base64Decode("SG93ZHk")).ToEqual "Howdy" + + .Expect(WebHelpers.Base64Decode("/PbkxNzW3w==", "Windows-1250")).ToEqual "üöäÄÜÖß" + .Expect(WebHelpers.Base64Decode("77u/w7zDtsOkw4TDnMOWw58=", "UTF-8")).ToEqual "üöäÄÜÖß" + .Expect(WebHelpers.Base64Decode("//78APYA5ADEANwA1gDfAA==", "UTF-16")).ToEqual "üöäÄÜÖß" + .Expect(WebHelpers.Base64Decode("eyJzdWIiOjEyMzQ1Njc4OTAsIm5hbWUiOiJKb2huIERvZSIsImFkbWluIjp0cnVlfQ")).ToEqual _ "{""sub"":1234567890,""name"":""John Doe"",""admin"":true}" End With