Saturday 31 October 2020

Internationalise Dates in VBA

VBA does Date Internationalisation! Here find VBA code to generate and interpret dates in foreign languages. In this post I give new code to interpret dates in foreign languages as well as signpost existing code to format dates in foreign languages written by Stack Overflow user GSerg.

A while back I blogged about how VBA can interpret foreign currencies by calling into the COM runtime like other Windows API calls. Dates are another internationalisation problem and the same trick works, we call into oleaut32.dll the COM runtime.

First, let's introduce GSerg's VBA code to write dates in foreign languages. We need this first to generate test data for my code which interprets foreign language dates.

I won't replicate the code to respect intellectual property rights but I give here some test code that calls in to GSerg's FormatForLocale function...

Public Function TestFormatForLocale() As String
    
    '*
    '* for list of locale ids (LCID) see this
    '* https://docs.microsoft.com/en-us/openspecs/office_standards/ms-oe376/6c085406-a698-4e12-9d4d-c3b0ee3dbc4a
    '*
    Const EN_US As Long = 1033
    Const DE_DE As Long = 1031
    
    '*
    '* FormatForLocale written by GSerg
    '* https://stackoverflow.com/users/11683/gserg
    '*
    '* Find source code at https://stackoverflow.com/questions/8523017/excel-format-value-mask/8523219#8523219
    '*
    Debug.Print FormatForLocale(CDate("12/May/2020"), "dd/mmm/yyyy", , , EN_US, DE_DE)
    Debug.Print FormatForLocale(CDate("12/Oct/2020"), "dd/mmm/yyyy", , , EN_US, DE_DE)
    Debug.Print FormatForLocale(CDate("12/Mar/2020"), "dd/mmm/yyyy", , , EN_US, DE_DE)
    
End Function

The code aboves prints out three dates in German...

12.Mai.2020
12.Okt.2020
12.Mrz.2020

GSerg's code cleverly calls into VarFormatFromTokens and VarTokenizeFormatString to format a date in a foreign language. You can read GSerg's explanation at his StackOverflow answer. For the moment I am content he has generated some good test input for my foreign language date interpretation code.

Next is code to interpret foreign dates, it's far fewer lines because I don't have to build a string buffer instead I supply a string and get a date back. There is some test code at the bottom demonstrating the German dates are being interpreted correctly (I have thrown in a French date as well).

Option Explicit

'* https://docs.microsoft.com/en-us/previous-versions/windows/embedded/aa519031(v=msdn.10)
Private Declare Function VarDateFromStr Lib "oleaut32" (ByVal strIn As Long, ByVal lcid As Long, _
            ByVal dwFlags As Long, ByRef pdateOut As Date) As Long

Public Function VarDateFromStr2(ByVal sInDate As String, ByVal lLCID As Long) As Date
    Dim hres As Long
    Dim pdateOut As Date
    hres = VarDateFromStr(StrPtr(sInDate), lLCID, 0, pdateOut)
    
    If hres = 0 Then
        VarDateFromStr2 = pdateOut
    Else
        Debug.Print "warning error: " & hres
    End If
End Function

Sub TestVarDateFromStr2()
    '*
    '* for list of locale ids (LCID) see this
    '* https://docs.microsoft.com/en-us/openspecs/office_standards/ms-oe376/6c085406-a698-4e12-9d4d-c3b0ee3dbc4a
    '*
    Const EN_US As Long = 1033
    Const DE_DE As Long = 1031
    Const FR_FR As Long = 1036

    Debug.Print VarDateFromStr2("12.Mai.2020", DE_DE) = CDate("12-May-2020")
    Debug.Print VarDateFromStr2("12.Okt.2020", DE_DE) = CDate("12-Oct-2020")
    Debug.Print VarDateFromStr2("12.Mrz.2020", DE_DE) = CDate("12-Mar-2020")
    Debug.Print VarDateFromStr2("12/mars/2020", FR_FR) = CDate("12-Mar-2020")
    
End Sub

I was inspired to write this post because of a StackOverflow question which uses the MonthName function which will be tied to the VBA installation language. With the couple of programs demonstrated it is possible to break away from VBA's installation language and truly go international.

Wednesday 30 September 2020

ConnectToConnectionPoint offers low-level alternative wiring for VBA events

I really like when I chance across some low-level technical wizardy to help out when VBA hits its limits ( it is what this blog does best!) Today, on StackOverflow a reward bounty of 500 is being awarded to a cracking answer which uses the ConnectToConnectionPoint Win32 API function call to sink events without using the WithEvents keyword.

So, I came across this StackOverflow Q & A where the questioner is asking how to reduce WithEvent declarations and subs with VBA and ActiveX and the responder provides a solution which uses ConnectToConnectionPoint to acquire events without using WithEvents.

The responder says they found the original code on a Japanese website and indeed I believe they are referring to this from Keiichi Tsunoda: Implementation of the event handling by API : ConnectToConnectionPoint. ConnectToConnectionPoint is defined in shlwapi.h which is part of the Windows Shell API (so it's not part of the original COM runtime API).

Googling a little more and I found a VBFormus post, a Mr Excel post and a GitHub Gist which I have placed in the Links section below.

How significant is this for Excel VBA? I do believe it is already possible to reduce the number of WithEvent declarations by introducing a class and holding an array of instances of those classes. Each class instance would be instantiated with the reference to a ActiveX control acquired using OLEObjects() for a worksheet or Controls() for a UserForm. However, the fact that the implementation of ConnectToConnectionPoint is in the Windows Shell library which is what Windows Desktop and the Windows Explorer use suggests that its use for sinking events from other Windows processes may have a more dramatic potential.

However, Mathieu Guindon who runs the RubberDuck project thinks this is a key technology to solving a glitch that had been an obstacle in implementing MVVM for VBA, here is his blog post Making MVVM Work in VBA Part 2 - Event Propagation

Links

Soft Links assist with Hard Link Hell

If you build an Excel application of any size then you will probably use more than one workbook. To access information in another workbook the standard way is to link. However, having workbooks linked to one another often leads to problems managing the opening and closing of linked workbooks. In this post I offer a 'soft link' which aims to break the hard links which come as a default and let your code take control.

There is such a thing as dependency hell where it required to gather antecedent code or data. A specific instance on Windows is DLL Hell concerning the loading of correct executable libraries. In Excel, we have our own form which I am calling 'Hard Link Hell'.

I call Hard Link Hell the mess that VBA coders can encounter when we build a VBA application of size that spans multiple workbooks. In my opinion, a VBA coder ought to exercise as much control as possible over the opening and closing of workbooks. Have a cell in one workbook link to another raises the spectre of Excel opening linked workbooks when we were not expecting it.

Admittedly, there is some control over the behaviour. So from the Data ribbon if I select Edit Links then I get the following dialog box...

... where we can see in the bottom right corner the Startup Prompt button which if pressed raises the following dialog ...

Nevertheless, I have had Hard Link Hell in the past where I have had the break links and relink to a new workbook. I remember it being a nightmare. So, in this post I give some code called Soft Links which means VBA code can take control of when to open linked workbooks. The code ships two functions to be called from a worksheet, SoftLink(workbookName, sheetName, rangeName) which actually return an Excel.Range object but Excel is clever enough to call the Value property; but this works only for single cell references. So for multiple cells use SoftLinkValue(workbookName, sheetName, rangeName). Be aware that the source cell(s) must be named using a range name. Also in the listing are some test procedures

Note, you will have to write code to open the source workbooks or you will get a #VALUE!, but we wanted to take control and so comes the responsibility to ensure the source workbook is loaded when this function is calculated. Enjoy!

Option Explicit

'* Use this for a source comprising multiple cells
Public Function SoftLinkValue(ByVal sWorkbookName As String, ByVal sSheetName As String, ByVal sRangeName As String)
    Dim rng As Excel.Range
    Set rng = SoftLink(sWorkbookName, sSheetName, sRangeName)
    SoftLinkValue = rng.Value
End Function

'* Use this for a source comprising single cell, also useful in other VBA code
Public Function SoftLink(ByVal sWorkbookName As String, ByVal sSheetName As String, ByVal sRangeName As String) As Excel.Range
    Dim wb As Excel.Workbook
    Set wb = OernColItem(Application.Workbooks, sWorkbookName)

    If Not wb Is Nothing Then

        Dim ws As Excel.Worksheet
        Set ws = OernColItem(wb.Worksheets, sSheetName)
        
        If Not ws Is Nothing Then
            Set SoftLink = OernWorksheetRange(ws, sRangeName)
        End If
    End If
End Function

Private Function OernWorksheetRange(ByRef ws As Excel.Worksheet, ByVal sRangeName As String) As Excel.Range
    On Error Resume Next
    Set OernWorksheetRange = ws.Range(sRangeName)
End Function

Private Function OernColItem(ByRef col As Object, ByVal idx As Variant) As Object
    On Error Resume Next
    Set OernColItem = col.Item(idx)
End Function

'**** TEST ****

Sub TestVBACallingSoftLink_LocalSheet()

    Const csSHEET1 As String = "Sheet1"

    Dim rng As Excel.Range
    Set rng = SoftLink(ThisWorkbook.Name, csSHEET1, "A1")
    
    Debug.Assert Not rng Is Nothing
    If Not rng Is Nothing Then
        Debug.Assert rng.Address = "$A$1"
        Debug.Assert rng.Worksheet.Name = csSHEET1
    End If
End Sub


Sub TestVBACallingSoftLink_ExternalWorkbook()
    Const csSHEET1 As String = "Sheet1"

    '*** test setup: create new workbook, add a name
    Dim wbNew As Excel.Workbook
    Set wbNew = Application.Workbooks.Add
    
    Const csNAME_FOO As String = "Foo"
    Dim ws As Excel.Worksheet
    Set ws = wbNew.Worksheets.Item(1)
    ws.Names.Add Name:=csNAME_FOO, RefersToR1C1:="=Sheet1!R4C8"
    ws.Range(csNAME_FOO).Value2 = 42
    '*** end of test setup:

    '*** now we can call our function to get a link to an external workbook
    Dim rng As Excel.Range
    Set rng = SoftLink(wbNew.Name, csSHEET1, csNAME_FOO)
    
    Debug.Assert Not rng Is Nothing
    If Not rng Is Nothing Then
        Debug.Assert rng.Address = "$H$4"
        Debug.Assert rng.Worksheet.Name = csSHEET1
        Stop
    End If
    wbNew.Close False
    Stop
End Sub

Wednesday 26 August 2020

VBA - Use Dom.SelectNodes and double slash XPath to jump in anywhere in an Xml Document

Don't be tempted to loop through an Xml structure algorithmically when you can jump in using some double slash prefixed XPath.

A question arose on StackOverflow which sadly had been closed by the moderators, so I solved it myself and published the answer here. The questioner says

I want to have flexible code so that I can just point to the nodepath of the financial value and then simply go up or down in the XML tree to find all the other data I need.

So the questioner would prefer not to write code for every Xml document structure instead find the a key node and expect to find the supplementary data in elements not far away. They have given some test data and I have given some code to handle both.

A key feature of the code is to use the SelectNodes() method of the DomDocument object which will give a list of multiple matches. To avoid specifying fixed paths use double slash!

Enjoy!

Option Explicit

Private Sub TestListSingleFinancialValueItems()
    ListSingleFinancialValueItems TestData1
End Sub

Private Sub TestListMultipleFinancialValues()
    ListMultipleFinancialValues TestData2
End Sub

Private Sub ListMultipleFinancialValues(ByVal dom As MSXML2.DOMDocument60)

    Dim nodesFinancialValues As MSXML2.IXMLDOMNodeList
    Set nodesFinancialValues = dom.SelectNodes("//financialvalues")
    
    Dim nodeFinVal As MSXML2.IXMLDOMElement
    For Each nodeFinVal In nodesFinancialValues
        
        Dim sCurrency As String: sCurrency = ""
        
        Dim nodsChildVals As MSXML2.IXMLDOMNodeList
        Set nodsChildVals = nodeFinVal.SelectNodes("value")
        
        If nodsChildVals.Length > 0 Then
            sCurrency = ReadCurrency(nodeFinVal.PreviousSibling)
            Debug.Assert sCurrency <> ""
            
            Dim vals As MSXML2.IXMLDOMElement
            For Each vals In nodsChildVals
                Debug.Print sCurrency & " " & vals.Text
            Next
        End If
    Next

End Sub


Private Sub ListSingleFinancialValueItems(ByVal dom As MSXML2.DOMDocument60)

    Dim nodesFinancialValues As MSXML2.IXMLDOMNodeList
    Set nodesFinancialValues = dom.SelectNodes("//financialvalue")
    
    Dim nodeFinVal As MSXML2.IXMLDOMElement
    For Each nodeFinVal In nodesFinancialValues
        
        Dim sCurrency As String: sCurrency = ""
        sCurrency = ReadCurrency(nodeFinVal.NextSibling)
        Debug.Assert sCurrency <> ""
        Debug.Print sCurrency & " " & nodeFinVal.Text
    Next
End Sub

Private Function ReadCurrency(ByVal xmlElement As MSXML2.IXMLDOMElement) As String
    If Not xmlElement Is Nothing Then
        If xmlElement.BaseName = "currency" Then
            ReadCurrency = xmlElement.Text
        End If
    End If
End Function

Function TestData1() As MSXML2.DOMDocument60
    Dim s
    s = _
    "<transactions>" & _
    "    <transaction>" & _
    "        <transactionID>5</transactionID>" & _
    "        <lines>" & _
    "            <line>" & _
    "                <financialvalue>100.00</financialvalue>" & _
    "                <currency>USD</currency>" & _
    "            </line>" & _
    "            <line>" & _
    "                <financialvalue>200.00</financialvalue>" & _
    "                <currency>USD</currency>" & _
    "            </line>" & _
    "         </lines>" & _
    "    </transaction>" & _
    "</transactions>"
    Dim dom As MSXML2.DOMDocument60
    Set dom = New MSXML2.DOMDocument60
    Debug.Assert dom.LoadXML(s)
    Set TestData1 = dom
End Function

Function TestData2() As MSXML2.DOMDocument60
    Dim s
    s = _
    "<transactions>" & _
    "    <transaction>" & _
    "        <currency>USD</currency>" & _
    "        <financialvalues>" & _
    "            <value>100.00</value>" & _
    "            <value>200.00</value>" & _
    "        </financialvalues>" & _
    "    </transaction>" & _
    "    <transaction>" & _
    "        <currency>USD</currency>" & _
    "        <financialvalues>" & _
    "            <value>300.00</value>" & _
    "            <value>400.00</value>" & _
    "        </financialvalues>" & _
    "    </transaction>" & _
    "</transactions>"
    Dim dom As MSXML2.DOMDocument60
    Set dom = New MSXML2.DOMDocument60
    Debug.Assert dom.LoadXML(s)
    Set TestData2 = dom
End Function


Friday 24 July 2020

VBA - Writing code in the Immediate window

You can write mini-programs in the Immediate window but you'll need to change how you write code. If you want a VBA code challenge this morning this will challenge you.

So a Stack Overflow answer to this question is due to be awarded a bounty. The prize winning answer doesn't actually solve the question which is how to print a two dimensional array to the Immediate window; instead, the answer highlights the Locals window (it's a favorite of mine as well). Nevertheless this question and its answers caught my attention and amongst them was a mini-program meant to be run entirely from the Immediate window, the code and output is show below.

arr = [ {"A",1; "B",2; "C",3 } ]: _
For r = LBound(arr, 1) To UBound(arr, 1): _
        For c = LBound(arr, 2) To UBound(arr, 2): _
            Debug.Print arr(r, c): _
       Next c: _
Next
A
 1 
B
 2 
C
 3 

I have seen code for the Immediate window before and wondered 'Why bother?' when you can write a small function and so didn't register the pattern and syntax required but today for whatever reason I embraced this syntax.

I wasn't happy with the output of the given code and wanted to amend it and then I hit the syntactical challenges therein. A small list of bullet points is appropriate here.

  • You can't use Dim statements; so write code as if Option Explicit is commented out
  • You can't use a For statement with a Next statement so you are obliged to use multi-line statements
  • If statements cannot be multi-line version they must be single line version. I.e. Don't use End If
  • Feel free to use VBA.IIf instead of an If statement.

So I successfully amended the code to give output with which I'm happy.

    arr = [ {"A",1; "B",2; "C",3 } ]: _
    sAcc = "": _
    For r = LBound(arr, 1) To UBound(arr, 1): _
            For c = LBound(arr, 2) To UBound(arr, 2): _
                bRowEnd = (c = UBound(arr, 2)): _
                sAcc = sAcc & CStr(arr(r, c)) & VBA.IIf(bRowEnd, ";" & vbNewLine, ","): _
           Next c: _
    Next r: _
    Debug.Print sAcc
A,1;
B,2;
C,3;

Be mindful that your variables in the 'ether' of the Immediate window will hang around until either (a) you suffer a state loss or (b) you type End which deliberately causes a variables wipedown. This is why I clear down sAcc at the start of the mini-program, otherwise repeated execution makes it build up.

You can instantiate classes in the Immediate window but the Intellisense didn't work (Intellisense did work for standard modules).

This is all a long way from Python's REPL I must say. If you any comments, suggestions or tips for working with the Immediate window do please drop me a line below.

Monday 8 June 2020

Python - Wireframe graphics on the worksheet leveraging SVG 3D library

In this post I leverage a brilliant Python library by Philip Rideout which draws wireframe graphics to SVG files and then I convert the SVG drawing directives to Shapes on an Excel worksheet.

This means I can take this SVG file of an octahedron

and convert it to this on the Excel worksheet.

Background

On StackOverflow, a question arose about drawing a wireframe box. I had looked into drawing on the worksheet using GDI before but I ruled out that approach. Instead, it is required to draw shapes on the worksheet. GDI still works for drawing on a Form as this Stars and Stripes example demonstrates. Using the macro recorder helps to understand how to build a free form shape but we'd need to write some 3D maths library in VBA to calculate all the vertices etc.

Luckily a brilliant library written by Philip Rideout exists and can do all the business of defining wireframe shapes in terms of vertices and also how the camera is pointing and it will do all the hard mathematics and draw to an SVG file. Then, I give code which parses that SVG file (it is XML after all) and I convert the polygon drawing directives to Excel (Freeform) Shapes.

The Setup

In Visual Studio give yourself a new Python project. Add the svg3d.py file from Github. Also add the example.py file from Github. Set the example.py file to be the file to run on startup. As it stands the code will generate an SVG file of an octahedron, you can see a rendering at the top of this page. It is very good, the fill on the front sides is set to 75% opacity so you can still see the rear faces. The rear faces are drawn first meaning I don't have to worry about which faces are hidden etc.

What is now needed is just a little more code to open an Excel workbook so add the following to the end of the example.py file

class ScreenUpdatingRAII(object):
    def __init__(self, app, visible:bool=False):
        self.app = app
        self.saved = app.ScreenUpdating
        app.ScreenUpdating = visible

    def restore(self):
        self.app.ScreenUpdating = self.saved
        self.app = None


def convertSvgToExcelShapes(filename):
    import xml.etree.ElementTree as ET
    from win32com.client  import GetObject,Dispatch

    # code below is highly dependent on the child
    # structure because xpath was not working for me (my bad)
    dom = ET.parse(filename)
    rootxml = dom.getroot()
    g = rootxml[1] # second child 
    wb = Dispatch(GetObject(r"C:\Users\Simon\source\repos\WireframeExcelShapes\WireframeExcelShapes\WireframeExcelShapes.xlsx"))
    app = Dispatch(wb.Parent)
    ws = Dispatch(wb.Worksheets.Item("WireFrame"))

    shps = Dispatch(ws.Shapes)

    for x in shps:
        Dispatch(x).Delete()
    idx =0
    scale, xoffset, yoffset = 500, 300,300
    
    screenUpdates = ScreenUpdatingRAII(app)

    for polygon in g:

        # triple nested list comprehension parsing the points by splitting 
        # first by space then by comma then converting to float
        points = [[float(z[0])*scale+xoffset, float(z[1])*scale+yoffset] for z in [y.split(',') for y in [x for x in polygon.attrib['points'].split()]]]

        #print(points)
        msoEditingAuto,msoSegmentLine, msoFalse, msoTrue = 0,0,0, -1 

        freeformbuilder=shps.BuildFreeform(msoEditingAuto, points[0][0] , points[0][1])
        freeformbuilder.AddNodes(msoSegmentLine, msoEditingAuto, points[1][0] , points[1][1])
        freeformbuilder.AddNodes(msoSegmentLine, msoEditingAuto, points[2][0] , points[2][1])
        freeformbuilder.AddNodes(msoSegmentLine, msoEditingAuto, points[0][0], points[0][1])
        newShp = Dispatch(freeformbuilder.ConvertToShape())

        shpFill = Dispatch(newShp.Fill)

        shpFill.Visible = msoTrue
        shpFill.Transparency = 0.25
        shpFill.Solid
        shpFill.ForeColor.RGB = 0xFFFFFF 
        idx=+1

    screenUpdates.restore()
    pass

        

filename = "octahedron.svg" 
generate_svg(filename)
convertSvgToExcelShapes(filename)

First comes a class called ScreenUpdatingRAII() which I use to switch on screen updates whilst drawing. This speeds the code and also kills screen flicker.

Next comes the function convertSvgToExcelShapes() which loads the SVG file into Python's Element tree XML parser. Then using some COM calls will open an Excel workbook which you must have saved before hand, and then accesses a sheet called WireFrame which you must have created beforehand as well! The code deletes any Shapes from that sheet and then proceeds to draw an Excel free form shape for each Polygon element in the SVG file. I haven't really added much value here it was quite straightforward. The dramatic output is 99% to Philip's credit.

However, I am proud of a line of code I did contribute. My triple nested list comprehension parses the string of points co-ordinates, scales and translates (math) them ready for the worksheet...

points = [[float(z[0])*scale+xoffset, float(z[1])*scale+yoffset] for z in [y.split(',') for y in [x for x in polygon.attrib['points'].split()]]]

Links

Below is a link to Philip's blog and his Github repo.

Wednesday 3 June 2020

VBA - Shell a process and acquire its StdIn, StdOut, StdErr pipes

Juts a quickie. On Stackoverflow some code posted which shells a process and reads the piped output purely using Window API calls, quite impressive but seems to be tripping up on some 64-bit issue. Actually VBA developers need not wrestle Windows API on this one and can in fact use the Windows Script Host Object Model library instead.

Option Explicit

Function ShellAndGetText() As String

    '* Tools -> References
    '* Windows Script Host Object Model

    Dim oWshShell As IWshRuntimeLibrary.WshShell
    Set oWshShell = New IWshRuntimeLibrary.WshShell


    Dim oWshExec As IWshRuntimeLibrary.WshExec
    
    Dim sComSpec As String
    sComSpec = Environ$("COMSPEC")
    
    Dim sReturnText As String
    Set oWshExec = oWshShell.Exec(sComSpec & " foo.exe")
    
    While oWshExec.Status = WshRunning
        DoEvents
    Wend
    If oWshExec.Status = WshFinished Then
        '* success
        sReturnText = oWshExec.StdOut
    Else
        '* failure
        sReturnText = oWshExec.StdErr
    End If

    ShellAndGetText = sReturnText

End Function

Wednesday 27 May 2020

VBA, ADODB - Asynchronous Query Execution with ADODB.Connection Events

VBA doesn't have multiple threads but that's ok because network latent operations such as running queries are packed into libraries which do the multi-threading for you. The ADODB.Connection object that is used to connect to a database can run queries in asynchronous mode with notification of completion implemented with an event if you declare the Connection object with the WithEvents keyword and and supply adAsyncExecute to the Connection's Execute method.

What follows is a code pattern not actual code because I do not know what databases you have installed on your computer dear reader. But what must be stressed is that this is to be placed into a class module (not a standard module). I called my class AsyncQuery

Option Explicit

Private WithEvents cnAsynchronousConnection As ADODB.Connection

Public Sub RunAsyncQuery()
    
    Set cnAsynchronousConnection = New ADODB.Connection

    cnAsynchronousConnection.connectionString = "" '<---- Insert your connection string

    
    cnAsynchronousConnection.Open
    
    Debug.Print "Preparing to execute asynchronously: " & Now
    cnAsynchronousConnection.Execute "<select query>", adAsyncExecute  '<----- Insert you own query

    Debug.Print "Has begun executing asynchronously: " & Now
End Sub

Private Sub cnAsynchronousConnection_ExecuteComplete(ByVal RecordsAffected As Long, _
        ByVal pError As ADODB.Error, adStatus As ADODB.EventStatusEnum, ByVal pCommand As ADODB.Command, _
        ByVal pRecordset As ADODB.Recordset, ByVal pConnection As ADODB.Connection)
    Debug.Print "The query has completed asynchronously: " & Now
End Sub

Then in a standard module place the following code.

Option Explicit

Sub Test()
    Dim oAsyncQuery As AsyncQuery
    Set oAsyncQuery = New AsyncQuery

    oAsyncQuery.RunAsyncQuery

End Sub

So without a database we can't take this any further. There are two key points working here, firstly there is the WithEvents keyword in the variable declaration which is only valid in a class module. Secondly there is the flag adAsyncExecute which must be passed to the Connection's Execute method. I have highlighted these key points in bold red.

Monday 25 May 2020

A rather neat piece of plumbing, Chrome extension pushes byte array of jobs data to Excel via Python

Transcript

The United States is suffering from extremely high unemployment and in this post I give an application that harvests job leads from a leading jobs website. The application has numerous technical components, (i) a Chrome extension, (ii) a Python webserver housed as a COM component and (iii) a VBA deserialization component. Taken together they demonstrate transmitting binary data from the browser through to the Excel worksheet.

In the US, initial jobless claims are running at a 4-week average of 3 million and the non-farm payrolls are currently at 20 million. These figures are both depressing and staggering. Europe can expect suffering on similar terms. Hopefully the code in this post can assist some to find work.

Co-browsing vs Web-scraping

Websites depend upon ad revenue to survive and so they need humans to see the adverts placed. Every time a human sees an advert it is known as an impression. Web-scraping is the process of running code to fetch a web page and to scrape data from the HTML; this typically involves the automation of a hidden web browser and as such any adverts on a hidden web page are no longer viewable but rendering ad impression statistics false. Eventually, this means that ad revenue is debased and devalued. As such, I disapprove of web scraping.

Instead, I give a ‘co-browsing’ application where code captures job leads from a web page that a human user is browsing. So this application is only active when a human browses a web page. This means any advert impressions are genuine and website’s revenue is not threatened.

The code

There are three separate parts to this application, (i) the chrome extension, (ii) the Python web server (housed as a COM component) and (iii) the VBA deserialization component. They are all in Github, https://github.com/smeaden/ExcelDevelopmentPlatform/tree/master/PythonWebSeverCallsBackToExcel/

The Chrome Extension

https://github.com/smeaden/ExcelDevelopmentPlatform/tree/master/PythonWebSeverCallsBackToExcel/Chrome%20Extension/

The chrome extension will wait for a jobs page to load and then read the jobs data, it builds a JavaScript array of jobs and when complete it will convert the single dimensioned array of jobs into a two-dimensional grid array where each row is one job and the attributes are spread across the columns.

I convert to a grid because ultimately it will be sent to an Excel session where it is to be pasted onto a worksheet. The grid is then persisted to a byte array instead of JSON to take advantage of a data interchange format native to VB6, VBA that I have re-discovered and that allows a byte array to be deserialized to a VBA (OLE Automation) Variant (two dimensional).

Once converted to a byte array we make an XMLHttpRequest() to the Python web server (see next component). If you are experimenting then you might need to change port number in the code here.

There are two main JavaScript files, content.js and JavaScriptToVBAVariantArray.js. The former houses logic specific to this application whilst the latter is the array conversion code library file which I intend to use across a number of projects.

Python Web Server housed as a COM component

https://github.com/smeaden/ExcelDevelopmentPlatform/tree/master/PythonWebSeverCallsBackToExcel/PythonWebSeverCallsBackToExcel

I have previously written about and given code as to how to write a Python web server housed as a COM component and instantiable from VBA. I have also previously written about and given code as to how to call back into Excel VBA from a Python class.

But there is something new in this Python web server which needs detailing, in short one cannot simply call back into Excel with an interface pointer passed in a different threading apartment; instead the interface pointer has first to be ‘marshalled’. I have encapsulated the plain vanilla callback code in the Python class CallbackInfo and the special marshalling case in its derived class MarshalledCallbackInfo.

In the context of the application, the Python web server is part of the pipeline that passes the byte array from the Chrome extension into Excel VBA. It calls into Excel VBA by calling Application.Run on a (marshalled) Excel.Application pointer. The name of the procedure called by Application.Run is configurable, and passed in. Time to look into the VBA code.

Excel VBA

https://github.com/smeaden/ExcelDevelopmentPlatform/tree/master/PythonWebSeverCallsBackToExcel/ExcelVBA

I do not check into whole workbooks, I check in the individual code modules instead. Thus to build the Excel VBA workbook code base one needs to import the modules. Luckily, I wrote one module called devBuild to import the rest of them. I intend to follow this pattern when placing code in GitHub. Look at the README.md file for more detail. From here, I’ll assume you’ve built a workbook codebase.

I have written about the serialization and deserialization of Variants to byte arrays and back again so I’ll refer you to that post for the details. In short we take the byte array passed from the Chrome extension via the Python web server and deserialize this to a two dimensional variant array which can then be pasted onto the worksheet.

I guess I could write some more code to build a cumulative list but the point of this project was to show binary data being passed from browser to Excel, to demonstrate (a) the plumbing and (b) the binary data interface format (i.e. no JSON).

Monday 18 May 2020

Returning to GitHub - this time at the command line

So my blog posts have become large and full of code, best to start using GitHub to store the code. Last time I used to use the Win32 desktop application but this time around I'm going to learn to use the command line. This post is about my efforts to configure and check in code from the command line. I hope to abstract a cheat sheet at some point.

So I started with the Hello World and execute Step 1. Create a Repository (this is still web-page based) but after that I was presented with a new web page of steps reproduced below and so I started from the command line to follow these instructions...

echo "# ExcelDevelopmentPlatform" >> README.md
git init
git add README.md
git commit -m "first commit"
git remote add origin https://github.com/smeaden/ExcelDevelopmentPlatform.git
git push -u origin master

So I executed the first three lines and whilst there is not much feedback at the command line, the first command git init creates a .get subfolder in the current selected folder, this is the local git repository.

C:\Users\Simon>git init
Initialized empty Git repository in C:/Users/Simon/.git/

C:\Users\Simon>echo "# ExcelDevelopmentPlatform" >> README.md

C:\Users\Simon>git add README.md

After I executed the first three lines I got slowed up on the fourth. Initially, I got the error below but it turned out that I had put a space between the dash and the em.

C:\Users\Simon>git commit - m "first commit"
error: pathspec '-' did not match any file(s) known to git
error: pathspec 'm' did not match any file(s) known to git
error: pathspec 'first commit' did not match any file(s) known to git

So trying again with corrected line I then got

C:\Users\Simon>git commit -m "first commit"

*** Please tell me who you are.

Run

  git config --global user.email "you@example.com"
  git config --global user.name "Your Name"

to set your account's default identity.
Omit --global to set the identity only in this repository.

fatal: unable to auto-detect email address (got 'Simon@xxxx.(none)')

So it seems I have to configure credentials; so I do but not globally ...

C:\Users\Simon>git config user.email "xxxx@xxxx.com"

C:\Users\Simon>git config user.name "S Meaden"

then I try (yet) again with the commit which gives...

C:\Users\Simon>git commit -m "first commit"
[master (root-commit) adca8f5] first commit
 1 file changed, 1 insertion(+)
 create mode 100644 README.md

So now over that hurdle I can continue with the instructions, the next line below is what ties the local repository to the one on GitHub...

C:\Users\Simon>git remote add origin https://github.com/smeaden/ExcelDevelopmentPlatform.git

C:\Users\Simon>git push -u origin master

Upon executing the second line from above there was a delay and then the following dialog box appeared which I then completed and clicked login.

which then progressed that line command's execution thus ...

C:\Users\Simon>git push -u origin master
Enumerating objects: 3, done.
Counting objects: 100% (3/3), done.
Writing objects: 100% (3/3), 245 bytes | 245.00 KiB/s, done.
Total 3 (delta 0), reused 0 (delta 0)
To https://github.com/smeaden/ExcelDevelopmentPlatform.git
 * [new branch]      master -> master
Branch 'master' set up to track remote branch 'master' from 'origin'.

And now checking the web page I have a ReadMe.Md file checked in.

Moving the Git Repository

Next I ran a command git status which listed all the files not yet tracked and there were too many and also made me realise I could locate the git repository better such as in the directory where Microsoft Visual Studio creates projects. After a quick StackOverflow surf it looked like I could just move the directory and I tried at the command line with no success but then used Windows Explorer with drag and drop to take it to it new location. The command git status then failed which meant I needed to change the current working directory to where I relocated the .git folder. Once there I could run git status and git log again so it looks like this move succeeded.

C:\Users\Simon>git status
warning: could not open directory 'Application Data/': Permission denied
...
On branch master
Your branch is up to date with 'origin/master'.

Untracked files:
  (use "git add <file>..." to include in what will be committed)
        .Neo4jDesktop/
        .cargo/
        .conda/
    ...
nothing added to commit but untracked files present (use "git add" to track)

C:\Users\Simon>git log
commit adca8f54ee85ed4395b1df6b35eae5ecb70d7c5e (HEAD -> master, origin/master)
Author: S Meaden <simonmeaden@xxxx.com>
Date:   Fri May 15 12:31:29 2020 +0100

    first commit


C:\Users\Simon>move README.md C:\Users\Simon\source\repos
        1 file(s) moved.

C:\Users\Simon>move \.git C:\Users\Simon\source\repos
The system cannot find the file specified.

C:\Users\Simon>explorer .

At this point I used Windows explorer to drag the .git folder down to .\source\repos

C:\Users\Simon>git log
fatal: not a git repository (or any of the parent directories): .git

C:\Users\Simon>cd source

C:\Users\Simon\source>cd repos

C:\Users\Simon\source\repos>git log
commit adca8f54ee85ed4395b1df6b35eae5ecb70d7c5e (HEAD -> master, origin/master)
Author: S Meaden <simonmeaden@xxxx.com>
Date:   Fri May 15 12:31:29 2020 +0100

    first commit

C:\Users\Simon\source\repos>git status
On branch master
Your branch is up to date with 'origin/master'.

Untracked files:
  (use "git add ..." to include in what will be committed)
        ATLProject1/
        ATLProject2/
        ...
nothing added to commit but untracked files present (use "git add" to track)

C:\Users\Simon\source\repos>

I found the following video and discovered that the first 12-15 minutes more or less cover the same territory as my notes. So for more information, I recommend this video.

Finally, it would appear GitHub is now free both public and private repositories with unlimited collaborators

Links

  • Markdown cheat sheet
  • Friday 8 May 2020

    Python COM Component to get windows handles hierarchy

    In this blog I give a Python COM component that returns a windows handle hierarchy as found in Spy++. It returns the details in one large table.

    So I had cause to poke around the windows hierarchy for Excel and I had previously written code to query the Windows API and get all the windows handles in a tree just like Spy++ but I chose to revisit the code with Python. Also, I chose to return the results in tabular form.

    Here is the Python listing

    import pythoncom 
    import os
    import logging
    import win32gui
    import win32con 
    
    class LocalsEnhancedErrorMessager(object):
        @staticmethod
        def Enhance(ex, localsString):
            locals2 = "n Locals:{ " + (",n".join(localsString[1:-1].split(","))) + " }"
            if hasattr(ex,"message"):
                return "Error:" + ex.message + locals2
            else:
                return "Error:" + str(ex) + locals2
    
    
    class PythonFindWindow(object):
        _reg_clsid_ = "{490784B6-5174-4794-8888-769DE4688B2C}"
        _reg_progid_ = 'PythonInVBA.PythonFindWindow'
        _public_methods_ = ['FindAllXlMainWindows','FindXlMainWindowWithCaptionFragment','FindChildWindows']
        _reg_clsctx_ = pythoncom.CLSCTX_LOCAL_SERVER ## uncomment this for a separate COM Exe server instead of in-process DLL
    
        def FindAllXlMainWindows(self):
            try:
                logging.basicConfig(filename =  (os.path.dirname(os.path.realpath(__file__))) + '\app2.log', 
                            format="%(asctime)s: %(message)s", 
                            level=logging.INFO, datefmt="%H:%M:%S")
    
                windows = []
    
                hwnd = win32gui.FindWindowEx(0,0,"XLMAIN",None)
                while hwnd != 0:
                    windows.append(hwnd)
                    hwnd = win32gui.FindWindowEx(0,hwnd,"XLMAIN",None)
    
                logging.info('PythonFindWindow.FindAllXlMainWindows completed')
                return windows
            except Exception as ex:
                msg = "PythonFindWindow.FindAllXlMainWindows error:" + LocalsEnhancedErrorMessager.Enhance(ex,str(locals()))
                logging.info(msg)
                return msg
    
        def FindXlMainWindowWithCaptionFragment(self, captionStringFragment):
            try:
                logging.basicConfig(filename =  (os.path.dirname(os.path.realpath(__file__))) + '\app2.log', 
                            format="%(asctime)s: %(message)s", 
                            level=logging.INFO, datefmt="%H:%M:%S")
    
                windows = []
    
                hwnd = win32gui.FindWindowEx(0,0,"XLMAIN",None)
                while hwnd != 0:
                    caption = win32gui.GetWindowText(hwnd)
                    if captionStringFragment in caption:
                        windows.append(hwnd)
                    hwnd = win32gui.FindWindowEx(0,hwnd,"XLMAIN",None)
    
                logging.info('PythonFindWindow.FindXlMainWindowWithCaptionFragment completed')
                return windows
            except Exception as ex:
                msg = "PythonFindWindow.FindXlMainWindowWithCaptionFragment error:" + LocalsEnhancedErrorMessager.Enhance(ex,str(locals()))
                logging.info(msg)
                return msg
    
    
        def FindChildWindows(self, parentHandle, selectStyles):
            try:
                logging.basicConfig(filename =  (os.path.dirname(os.path.realpath(__file__))) + '\app2.log', 
                            format="%(asctime)s: %(message)s", 
                            level=logging.INFO, datefmt="%H:%M:%S")
    
                windows = []
                hwnd = parentHandle
                row = [hwnd,0,"{0:#0{1}x}".format(hwnd,8), 
                                    win32gui.GetWindowText(hwnd), 
                                    win32gui.GetClassName(hwnd),
                                    win32gui.GetWindowLong(hwnd, win32con.GWL_STYLE)]
                windows.append(row)
    
                self.FindChildWindowsInner(parentHandle,windows, selectStyles,0)
                
                logging.info('PythonFindWindow.FindChildWindows completed')
                return windows
            except Exception as ex:
                msg = "PythonFindWindow.FindChildWindows error:" + LocalsEnhancedErrorMessager.Enhance(ex,str(locals()))
                logging.info(msg)
                return msg
    
        def FindChildWindowsInner(self, parentHandle, windows, selectStyles, depth):
            try:
    
                hwnd = win32gui.FindWindowEx(parentHandle,0,None,None)
                while hwnd != 0:
                    style = win32gui.GetWindowLong(hwnd, win32con.GWL_STYLE)
                    stylesSelected = True if selectStyles is None else (style & selectStyles)!=0
                    if stylesSelected:
                        row = [hwnd,parentHandle,"{0:#0{1}x}".format(hwnd,8), 
                                         win32gui.GetWindowText(hwnd), 
                                         win32gui.GetClassName(hwnd),
                                         style]
                        windows.append(row)
                        self.FindChildWindowsInner(hwnd, windows, selectStyles, depth+1)
                    hwnd = win32gui.FindWindowEx(parentHandle,hwnd,None,None)
                
                
                return windows
            except Exception as ex:
                msg = "PythonFindWindow.FindChildWindowsInner error:" + LocalsEnhancedErrorMessager.Enhance(ex,str(locals()))
                logging.info(msg)
                return msg
    
    
    
    def run():
        # this code is to be run in Microsoft Visual Studio by pressing F5
        # it is a developer's entry.  for production instantiate the COM component
        try:
    
            print("Executing run")
            print((os.path.dirname(os.path.realpath(__file__))))
    
            logging.basicConfig(filename = (os.path.dirname(os.path.realpath(__file__))) + '\app2.log', 
                            format="%(asctime)s: %(message)s", 
                            level=logging.INFO, datefmt="%H:%M:%S")
    
            fw = PythonFindWindow()
    
            xlMains = fw.FindAllXlMainWindows()
            
            windowList = fw.FindChildWindows(xlMains[0], win32con.WS_VISIBLE)
    
            logging.info('called PythonFindWindow.FindChildWindows ...n')
    
            logging.info('finishing run()n')
        except Exception as ex:
            print(ex)
    
    def RegisterCOMServers():
        print("Registering COM servers...")
        import win32com.server.register
        win32com.server.register.UseCommandLine(PythonFindWindow)
    
    if __name__ == '__main__':
        
        RegisterCOMServers()
        run()

    and here is some sample VBA client code...

    Option Explicit
    
    Const WS_VISIBLE As Long = &H10000000   'WS_VISIBLE = 0x10000000
    
    Sub Test()
        Dim obj As Object
        Set obj = VBA.CreateObject("PythonInVBA.PythonFindWindow")
        
        Dim vXlMains
        vXlMains = obj.FindXlMainWindowWithCaptionFragment("MyWorkbook")
        
        Dim vWindows
    
        vWindows = obj.FindChildWindows(vXlMains(0), Empty)  '* No styles to select with, so selects all
        vWindows = obj.FindChildWindows(vXlMains(0), WS_VISIBLE)  '* Only shows those that are visible (and whose ancestors are visible)
        
        Dim lRow As Long
        For lRow = LBound(vWindows, 1) To UBound(vWindows, 1)
            If vWindows(lRow, 4) = "EXCEL7" Then
                Stop
            End If
        Next
        Stop
    End Sub

    Once the table is returned one can dig in and find what you want, much better to take a whole snapshot recursing down through the hierarchy then to piece together separate calls to FindWindow in my humble opinion.

    Thursday 7 May 2020

    VBA, Python - Python Web Server housed as a COM component

    In this post I give code for a Python web server housed as a COM component which is startable and stoppable from VBA or any other COM-enabled client. The code demonstrates COM server code, Python web server code, multi-threading and Python logging.

    Multithreading possible but ill-advised in VBA

    Multithreading in VBA is technically possible as VBA code can access Windows API functions such as CreateThread as well as the operating system artefacts used to manage concurrency and synchronization such as semaphores, critical sections and mutexs. Unfortunately, if you create threads in VBAs and then place breakpoints in the code to debug then Excel will crash because the Excel VBA IDE is not multi-threading aware/capable. Never mind, for multi-threading problems an Excel VBA developer can co-opt either C# (or other .NET languages) or Python to build a COM component callable from VBA. In this post I use Python.

    Code commentary - the COM server code

    The code below demonstrates COM server code which keen readers of this blog will have seen many times before so I will be brief. The StarterAndStopper class (excerpt given below) is the COM server gateway class, we can tell this from the _reg_clsid and _reg_progid attributes as well as the list of methods. Also there is a key line of code which determines how to implement the COM server's housing; _reg_clsctx_ which if omitted defaults to an in-process DLL pattern but if pythoncom.CLSCTX_ instead then the COM server will be housed in a separate .Exe. This is extremely useful during development for tearing down one instance and replace with another implementing the latest changes.

    class StarterAndStopper(object):
        ...
        _reg_clsid_ = "{2D23D974-73B1-4106-9096-DA6006BD84AA}"
        _reg_progid_ = 'PythonInVBA.StarterAndStopper'
        _public_methods_ = ['StartWebServer','StopWebServer','CheckThreadStatus','StopLogging']
        ##_reg_clsctx_ = pythoncom.CLSCTX_ ## uncomment this for a separate COM Exe server instead of in-process DLL server

    the registration code is given in the following lines, these need to be run once; if not with Admin rights then an escalation is requested.

    def RegisterCOMServers():
        print("Registering COM servers...")
        import win32com.server.register
        win32com.server.register.UseCommandLine(StarterAndStopper)
    
    if __name__ == '__main__':
        #run()
        RegisterCOMServers()

    then once registered the COM server is creatable with the following CreateObject line of code...

        Set mobjPythonWebServer = VBA.CreateObject("PythonInVBA.StarterAndStopper")

    I will give further commentary of this class later when talking about multi-threading.

    Code commentary - stoppable web server code

    So we utilize the Python library's basic web server, this is not for use unless behind a firewall but is usable for facilitating HTTP communication between programs on the same computer. For robust internet-facing industrial strength production web serving one should use Apache web server with a Python plug-in. For my purposes the basic web server is fine, I am planning some code where the browser on a machine calls into Excel.exe running on the same machine, i.e. we are not internet-facing.

    The base class http.server.HTTPServer has a serve_forever method which runs in an infinite loop which only interrupts when Ctrl+C is pressed on the keyboard in the console window in which the web server is running. If running in a COM server housing then there is no visible console and so we need a mechanism to stop the web server without a keyboard interrupt. The code in an article over on activestate.com gives the pattern for a stoppable web server by amending the standard implementation thus,

    1. Adding an additional HTTP verb handler to the class derived from SimpleHTTPRequestHandler to handle a QUIT request. The code here sets a Stop flag to True.
    2. Subclassing http.server.HTTPServer and providing overriding implementation of serve_forever that will acknowledge the stop and drop out of the (otherwise infinite) loop.
    3. In the shutdown code make a HTTP QUIT request to one's own webserver
    class MyRequestHandler(SimpleHTTPRequestHandler):
        ...
        def do_QUIT (self):
                # http://code.activestate.com/recipes/336012-stoppable-http-server/ 
                """send 200 OK response, and set server.stop to True"""
                self.send_response(200)
                self.end_headers()
                self.server.stop = True
                self.wfile.write("quit called".encode('utf-8'))
    class StoppableHttpServer(HTTPServer):
        # http://code.activestate.com/recipes/336012-stoppable-http-server/ 
        """http server that reacts to self.stop flag"""
    
        def serve_forever (self):
                """Handle one request at a time until stopped."""
                self.stop = False
                while not self.stop:
                    self.handle_request()
    class StarterAndStopper(object):
        def StopWebServer(self):
    
                        ## make a quit request to our own server 
                        quitRequest  = urllib.request.Request("http://" + self.server_name + ":" + str(self.server_port) + "/quit",
                                                          method="QUIT")
                        with urllib.request.urlopen(quitRequest ) as resp:
                            logging.info("StarterAndStopper.StopWebServer      : quit response '" + resp.read().decode("utf-8") + "'")

    Whilst on the subject of no visible console window, we have to redirect stdout and stderr to somewhere, e.g. a file otherwise the code complains and throws errors. So I found adding the following is sufficient to suppress such errors.

            sys.stderr = open((os.path.dirname(os.path.realpath(__file__))) + '\\logfile.txt', 'w', buffer)
            sys.stdout = open((os.path.dirname(os.path.realpath(__file__))) + '\\logfile.txt', 'w', buffer)

    Code commentary - multithreading

    Creating and starting a new thread in Python is quite simple using the Thread constructor threading.Thread(name, target, args) where target is a function or a class's method, in this case a standalone function called thread_function which itself simply calls the web server's serve_forever method given above. Once constructed, we call the Thread's start method.

    class StarterAndStopper(object):
        def StartWebServer(self,foo, bar: str, baz: str, server_name:str, server_port: int):
                self.running = False 
                
                self.httpd = StoppableHttpServer((server_name, server_port), MyRequestHandler)
    
                self.serverthread = threading.Thread(name="webserver", target=thread_function, args=(self,))
                self.serverthread.setDaemon(True)
                
                self.serverthread.start()
                ... 
    
    def thread_function(webserver):
        try:
            webserver.httpd.serve_forever()  #code enters into the subclass's implementation, an almost infinite loop
            ...
    

    When we come to stop the web server by sending the QUIT HTTP request notifying the web server thread of close down we then call the Thread.join method on the main thread to wait for the web server thread to drop off. In the code given we set the Thread to a daemon, which means the Thread's refusal to finish does not prevent unloading the code once the main thread has finished.

    Code commentary - developing a multithreaded COM component

    The code is meant to be executed as a COM component with execution beginning with a COM client such as VBA. Unfortunately such a scenario does not facilitate hitting break points and stepping through the source code. For this reason a separate run() function is found at the bottom of the code. This is to be run in Microsoft Visual Studio and doing this we get to hit break points and step through the code. Sometimes, it's necessary to comment out the setDaemon(True) line so that the code does not unload, allowing continued debugging. This can be a bit of pain but until I can get the breakpoints to hit in the original scenario I will have to persist with this.

    Code commentary - Python logging

    In addition to the lack of breakpoints in the primary one use case (see above) the code can be difficult to debug because of the nature of multithreading. One cannot always tell the order in what events occurred! To solve this I put in the code a ton of logging so that I could see just what precisely is happening. Here is a sample of my log which expresses the sequence of events for starting the web server, using a browser to make a HTTP GET, then stopping the web server. In fact this log says so much more than any prose that I could write.

    22:37:17: StarterAndStopper.StartWebServer     : server_name: localhost, server_port:8014
    22:37:17: StarterAndStopper.StartWebServer     : about to create thread
    22:37:17: StarterAndStopper.StartWebServer     : about to start thread
    22:37:17: StarterAndStopper.StartWebServer     : after call to start thread
    22:37:17: thread_function                      : about to enter webserver.httpd.serve_forever
    22:37:17: StoppableHttpServer.serve_forever    : entered
    22:37:20: MyRequestHandler.do_GET              : entered.  path=/testurl
    22:37:20: StoppableHttpServer.serve_forever    : request successfully handled self.stop=False
    22:37:22: StarterAndStopper.StopWebServer      : entered
    22:37:22: StarterAndStopper.StopWebServer      : call quit on own web server
    22:37:24: MyRequestHandler.do_QUIT             : entered
    22:37:24: MyRequestHandler.do_QUIT             : setting self.server.stop = True
    22:37:24: StoppableHttpServer.serve_forever    : request successfully handled self.stop=True
    22:37:24: StarterAndStopper.StopWebServer      : quit response 'quit called'
    22:37:24: StoppableHttpServer.serve_forever    : dropped out of the loop
    22:37:24: StarterAndStopper.StopWebServer      : about to join thread
    22:37:24: thread_function                      : returned from webserver.httpd.serve_forever
    22:37:24: thread_function                      : finished
    22:37:24: StarterAndStopper.StopWebServer      : thread joined
    22:37:24: StarterAndStopper.StopWebServer      : about to call httpd.server_close()
    22:37:24: StarterAndStopper.StopWebServer      : completed

    Full Code Listings

    So here is the full Python code listing which has all the full logging statements in it.

    import sys
    import time #sleep
    import http.server
    import threading
    import tempfile
    import os
    
    import win32com.client
    from io import BytesIO
    import pythoncom
    
    import urllib.request
    
    from http.server import HTTPServer, BaseHTTPRequestHandler, SimpleHTTPRequestHandler
    import logging
    
    class MyRequestHandler(SimpleHTTPRequestHandler):
    
        def do_GET(self):
            try:
                logging.info("MyRequestHandler.do_GET              : entered.  path=" + self.path)
                self.send_response(200)
                self.send_header('Content-type', 'text/html')
                self.end_headers()
                if (self.path != r"/favicon.ico"):
                    self.wfile.write("GET request for {}".format(self.path).encode('utf-8'))
                    self.wfile.write((" default response").encode('utf-8'))
            except Exception as ex:
                logging.info("MyRequestHandler.do_GET   error   : " + 
                    LocalsEnhancedErrorMessager.Enhance(ex,str(locals())))
    
        def do_POST(self):
            try:
                logging.info("MyRequestHandler.do_POST             : entered ")
                content_length = int(self.headers['Content-Length']) # <--- Gets the size of data
                post_data = self.rfile.read(content_length) # <--- Gets the data itself
    
                self.send_response(200)
                self.send_header('Content-type', 'text/html')
                self.end_headers()
    
                msgBytesReceived = "POST body:" + str(len(post_data)) + " bytes received" 
    
                response = BytesIO()
                response.write(msgBytesReceived.encode('utf-8'))
    
                self.wfile.write(response.getvalue())
                self.wfile.flush()
    
                print(msgBytesReceived)
    
                logging.info("MyRequestHandler.do_POST             : " + msgBytesReceived)
    
            except Exception as ex:
                logging.info("MyRequestHandler.do_POST  error    : " + 
                    LocalsEnhancedErrorMessager.Enhance(ex,str(locals())))
    
        def do_QUIT (self):
            try:
                logging.info("MyRequestHandler.do_QUIT             : entered")
                """send 200 OK response, and set server.stop to True"""
                self.send_response(200)
                self.end_headers()
                logging.info("MyRequestHandler.do_QUIT             : setting self.server.stop = True")
                self.server.stop = True
                self.wfile.write("quit called".encode('utf-8'))
            except Exception as ex:
                logging.info("MyRequestHandler.do_QUIT  error    : " + 
                    LocalsEnhancedErrorMessager.Enhance(ex,str(locals())))
    
    class LocalsEnhancedErrorMessager(object):
        @staticmethod
        def Enhance(ex, localsString):
            locals2 = "n Locals:{ " + (",n".join(localsString[1:-1].split(","))) + " }"
            if hasattr(ex,"message"):
                return "Error:" + ex.message + locals2
            else:
                return "Error:" + str(ex) + locals2
    
    def thread_function(webserver):
        try:
            pythoncom.CoInitialize() # need this to tell the COM runtime that a new thread exists
            webserver.running = True 
    
            ## we need to pipe output to a file because whilst running as COM server there is no longer a console window to print to
            buffer = 1
            sys.stderr = open((os.path.dirname(os.path.realpath(__file__))) + '\logfile.txt', 'w', buffer)
            sys.stdout = open((os.path.dirname(os.path.realpath(__file__))) + '\logfile.txt', 'w', buffer)
    
            logging.info("thread_function                      : about to enter webserver.httpd.serve_forever")
            webserver.httpd.serve_forever()  #code enters into the subclass's implementation, an almost infinite loop
            logging.info("thread_function                      : returned from webserver.httpd.serve_forever")
            
            logging.info("thread_function                      : finished")
    
        except Exception as ex:
            logging.info("thread_function   error   : " + 
                LocalsEnhancedErrorMessager.Enhance(ex,str(locals())))
    
    class StoppableHttpServer(HTTPServer):
        # http://code.activestate.com/recipes/336012-stoppable-http-server/ 
        """http server that reacts to self.stop flag"""
    
        def serve_forever (self):
            try:
                logging.info("StoppableHttpServer.serve_forever    : entered")
                """Handle one request at a time until stopped."""
                self.stop = False
                while not self.stop:
                    self.handle_request()
                    logging.info("StoppableHttpServer.serve_forever    : request successfully handled self.stop=" + str(self.stop))
                logging.info("StoppableHttpServer.serve_forever    : dropped out of the loop")
            except Exception as ex:
                logging.info("StoppableHttpServer.serve_forever  error   : " + 
                    LocalsEnhancedErrorMessager.Enhance(ex,str(locals())))
                
    class StarterAndStopper(object):
        import logging
        import threading
        import time
        
        _reg_clsid_ = "{2D23D974-73B1-4106-9096-DA6006BD84AA}"
        _reg_progid_ = 'PythonInVBA.StarterAndStopper'
        _public_methods_ = ['StartWebServer','StopWebServer','CheckThreadStatus','StopLogging']
        ##_reg_clsctx_ = pythoncom.CLSCTX_ ## uncomment this for a separate COM Exe server instead of in-process DLL server
    
        def StopLogging(self):
            try:
                logging.shutdown()
                return "logging.shutdown() ran"
            except Exception as ex:
                msg = "StarterAndStopper.StopLogging error:" + LocalsEnhancedErrorMessager.Enhance(ex,str(locals()))
                logging.info(msg)
                return msg
    
        def StartWebServer(self,foo, bar: str, baz: str, server_name:str, server_port: int):
            try:
                self.server_name = server_name
                self.server_port = server_port
    
                logging.basicConfig(filename =  (os.path.dirname(os.path.realpath(__file__))) + '\app2.log', format="%(asctime)s: %(message)s", 
                            level=logging.INFO, datefmt="%H:%M:%S")
    
                logging.info("StarterAndStopper.StartWebServer     : server_name: " + server_name + ", server_port:" + str(server_port))
    
                self.running = False 
                
                self.httpd = StoppableHttpServer((server_name, server_port), MyRequestHandler)
    
                logging.info("StarterAndStopper.StartWebServer     : about to create thread")
    
                self.serverthread = threading.Thread(name="webserver", target=thread_function, args=(self,))
                self.serverthread.setDaemon(True)
                logging.info("StarterAndStopper.StartWebServer     : about to start thread")
    
                self.serverthread.start()
                logging.info("StarterAndStopper.StartWebServer     : after call to start thread")
                
                return "StartWebServer ran ok ( server_name: " + server_name + ", server_port:" + str(server_port) + ")"
    
            except Exception as ex:
                msg = "StarterAndStopper.StartWebServer error:" +  LocalsEnhancedErrorMessager.Enhance(ex,str(locals()))
                logging.info(msg)
                return msg
    
        def CheckThreadStatus(self):
            try:
                # Clear the stream now that we have finished
                global callbackInfo
    
                if self.running:
                    if hasattr(self,'httpd') :
                        logging.info("StarterAndStopper.CheckThreadStatus    : checking thread status")
                        return self.serverthread.is_alive()
                    else:
                        return "StopWebServer ran ok, nothing to stop"
                else:
                    return "StopWebServer ran ok, nothing to stop"
    
            except Exception as ex:
                msg = "StarterAndStopper.CheckThreadStatus error:" +  LocalsEnhancedErrorMessager.Enhance(ex,str(locals()))
                logging.info(msg)
                return msg
    
        def StopWebServer(self):
            try:
                retMsg = "StopWebServer ran (default)"
                logging.info("StarterAndStopper.StopWebServer      : entered")
    
                if self.running:
                    if hasattr(self,'httpd') :
    
                        logging.info("StarterAndStopper.StopWebServer      : call quit on own web server")
                        ## make a quit request to our own server 
                        quitRequest  = urllib.request.Request("http://" + self.server_name + ":" + str(self.server_port) + "/quit",
                                                          method="QUIT")
                        with urllib.request.urlopen(quitRequest ) as resp:
                            logging.info("StarterAndStopper.StopWebServer      : quit response '" + resp.read().decode("utf-8") + "'")
    
                        # web server should have exited loop and its thread should be ready to terminate
                        logging.info("StarterAndStopper.StopWebServer      : about to join thread")
                        self.serverthread.join()    # get the server thread to die and join this thread
                        self.running = False 
                        
                        logging.info("StarterAndStopper.StopWebServer      : thread joined")
    
                        logging.info("StarterAndStopper.StopWebServer      : about to call httpd.server_close()")
                        self.httpd.server_close()  #now we can close the server cleanly
                        
                        logging.info("StarterAndStopper.StopWebServer      : completed")
    
                        retMsg = "StopWebServer ran ok, web server stopped"
                    else:
                        retMsg = "StopWebServer ran ok, nothing to stop"
                else:
                    retMsg = "StopWebServer ran ok, nothing to stop"
                return retMsg
    
            except Exception as ex:
                msg = "StarterAndStopper.StopWebServer error:" +  LocalsEnhancedErrorMessager.Enhance(ex,str(locals()))
                print(msg)
                logging.info(msg)
                return msg
    
    def run():
        # this code is to be run in Microsoft Visual Studio by pressing F5
        # use this code to step through and debug the web server portion of code 
        try:
    
            print("Executing run")
            print((os.path.dirname(os.path.realpath(__file__))))
    
            logging.basicConfig(filename = (os.path.dirname(os.path.realpath(__file__))) + '\app2.log', format="%(asctime)s: %(message)s", 
                            level=logging.INFO, datefmt="%H:%M:%S")
    
            ws = StarterAndStopper()
            ws.StartWebServer(None,None, None,'localhost',8009)
    
            logging.info('called StarterAndStopper.StartWebServer ...n')
    
            if False:
    
                logging.info('what next? ...n')
                ws.StopWebServer()
    
                logging.info('finishing run()n')
        except Exception as ex:
            print(ex)
    
    def RegisterCOMServers():
        print("Registering COM servers...")
        import win32com.server.register
        win32com.server.register.UseCommandLine(StarterAndStopper)
    
    if __name__ == '__main__':
        run()
        #RegisterCOMServers()

    And here is the client VBA code which calls into the COM server (ensure it is registered!).

    Option Explicit
    Option Private Module
    
    Dim mobjPythonWebServer As Object
    
    Public Const PORT As Long = 8014
    
    Function TestPythonVBAWebserver_StartWebServer()
        Set mobjPythonWebServer = VBA.CreateObject("PythonInVBA.StarterAndStopper")
    
        Debug.Print mobjPythonWebServer.StartWebServer(Null, Null, Null, "localhost", PORT)
    
    End Function
    
    Sub TestPythonVBAWebserver_StopWebServer()
        If Not mobjPythonWebServer Is Nothing Then
            Debug.Print mobjPythonWebServer.StopWebServer
        End If
    End Sub
    
    Sub TestPythonVBAWebserver_StopLogging()
        '# This releases the log file so I can delete it occassionally
        If Not mobjPythonWebServer Is Nothing Then
            Debug.Print mobjPythonWebServer.StopLogging
        End If
    End Sub
    
    Sub PickupNewPythonScript()
        '# for development only to help pick up script changes we kill the python process
        Call CreateObject("WScript.Shell").Run("taskkill /f /im pythonw.exe", 0, True)
        Set mobjPythonWebServer = Nothing
    End Sub

    Tuesday 28 April 2020

    VBA, Named Pipes (& JavaScript) - binary serialization revisited

    In this post I revisit the matter of the serialization of VBA Variant arrays to bytes and back again. This can be used VBA to VBA or interoperating with other technologies that can be sequence bytes, in this post I demonstrate JavaScript to VBA. I incorporate a better serialization technique code that uses Windows OS Named Pipes as written by VBForums.com contributor Olaf Schmidt.

    Background

    This is a revisit of an earlier article where I saved and loaded a Variant array to disk using VBA’s Open File For Binary, Put and Get statements. Whilst the code did what I wanted, I had complained that my code required a disk operation which carries a performance penalty.

    I am indebted to a commenter (who gives no name) who tipped me off as to some code on VBForums written by Olaf Schmidt; Olaf’s code serializes using Windows OS Named Pipes and not a disk write. The Named Pipes are purely in memory and so this makes his code faster.

    Moreover, the Named Pipes serialization yields a leading sequence of bytes that describes the number of dimensions in the array and the size and bounds of each dimension. This was something formally missing from disk write version my code and which I had had to implement manually, something of a nuisance.

    I am thus doubly indebted to Olaf Schmidt’s code and to the commenter who tipped me off. Thank you. Do please keep the comments coming.

    VBA Class Module - cPipedVariants

    So with Olaf Schmidt's code as a starting point I have modified it to handle the use case of VBA variant arrays, i.e. a two dimensional array which is ready for pasting onto a worksheet. Olaf's original code demonstrated the serialization of user-defined types and these data structures are more prevalent in Visual Basic 6 (VB6) whereas Excel developers (I would argue) are more likely to deal with grids drawn from a worksheet or grids to be pasted onto a worksheet.

    If you want the original version that deals with the serialization of UDTs it is on this link here to vb6forums.com.

    So what follows in cPipedVariants, a modification on Olaf's original class cPipedUDTs. Much of the code is easy to follow but I will comment on the ‘secret sauce’ of the InitializePipe function.

    The two key lines of code are the call to CreateNamedPipeW and then the Open "\\.\pipe\foo" For Binary statement. If I switch the order of these two around then the code fails. Internally, in its implementation the Open For Binary Statement must have a special case where it identifies the "\\.\pipe\ " prefix and then looks up in the list of created named pipes. This is not documented in any Microsoft documentation, or indeed StackOverflow. Only the VB6Forums.com users and specifically Olaf Schmidt understand this lore, it must be a throw back to the era of VB6. Anyway, it does work and I am grateful.

    Add a class to your VBA project, call it cPipedVariants and then paste in the following code

    Option Explicit
    
    '* Pipe-based helper to serialize/deserialize VB-Variants InMemory ... [based on original code by Olaf Schmidt 2015]
    '* Based on code by Olaf Schmidt 2015, http://www.vbforums.com/showthread.php?807205-VB6-pipe-based-UDT-serializing-deserializing-InMemory
    
    
    '* https://docs.microsoft.com/en-us/windows/win32/api/winbase/nf-winbase-createnamedpipea
    Private Declare Function CreateNamedPipeW& Lib "kernel32" (ByVal lpName As Long, ByVal dwOpenMode&, ByVal dwPipeMode&, _
                ByVal nMaxInstances&, ByVal nOutBufferSize&, ByVal nInBufferSize&, _
                ByVal nDefaultTimeOut&, ByVal lpSecurityAttributes&)
    
    '* https://docs.microsoft.com/en-us/windows/win32/api/fileapi/nf-fileapi-writefile
    Private Declare Function WriteFile& Lib "kernel32" (ByVal hFile&, lpBuffer As Any, _
                ByVal nNumberOfBytesToWrite&, lpNumberOfBytesWritten&, ByVal lpOverlapped&)
    
    '* https://docs.microsoft.com/en-us/windows/win32/api/fileapi/nf-fileapi-readfile
    Private Declare Function ReadFile& Lib "kernel32" (ByVal hFile&, lpBuffer As Any, _
                ByVal nNumberOfBytesToRead&, lpNumberOfBytesRead&, ByVal lpOverlapped&)
    
    '* https://docs.microsoft.com/en-us/windows/win32/api/namedpipeapi/nf-namedpipeapi-peeknamedpipe
    Private Declare Function PeekNamedPipe& Lib "kernel32" (ByVal hNamedPipe&, lpBuffer As Any, _
                ByVal nBufferSize&, lpBytesRead&, lpTotalBytesAvail&, lpBytesLeftThisMessage&)
    
    '* https://docs.microsoft.com/en-us/windows/win32/api/namedpipeapi/nf-namedpipeapi-disconnectnamedpipe
    Private Declare Function DisconnectNamedPipe& Lib "kernel32" (ByVal hPipe&)
    
    Private Declare Function CloseHandle& Lib "kernel32" (ByVal hObject&)
    
    Private mhPipe As Long
    Private mlFileNumber As Long
    Private mabytSerialized() As Byte
    
    Private Enum eOpenMode
        PIPE_ACCESS_INBOUND = 1
        PIPE_ACCESS_OUTBOUND = 2
        PIPE_ACCESS_DUPLEX = 3
    End Enum
    
    Private Enum ePipeMode
        PIPE_TYPE_BYTE = 0
        PIPE_TYPE_MESSAGE = 4
    
        PIPE_READMODE_BYTE = 0
        PIPE_READMODE_MESSAGE = 2
       
        PIPE_WAIT = 0
        PIPE_NOWAIT = 1
    End Enum
    
    Private Enum ePipeInstances
        PIPE_UNLIMITED_INSTANCES = 255
    End Enum
    
    Public Function InitializePipe(Optional sPipeNameSuffix As String = "vbaPipedVariantArrays") As Boolean
        Const csPipeNamePrefix As String = "\\.\pipe\"
        CleanUp
       
        Dim sPipeName As String
        sPipeName = csPipeNamePrefix & sPipeNameSuffix
       
        '* Must call CreateNamedPipe first before calling Open <<pathname>> For Binary otherwise you get bad file number
        mhPipe = CreateNamedPipeW(StrPtr(sPipeName), PIPE_ACCESS_DUPLEX, PIPE_TYPE_BYTE + PIPE_READMODE_BYTE + PIPE_WAIT, _
                PIPE_UNLIMITED_INSTANCES, -1, -1, 0, 0)
               
        If mhPipe = -1 Then mhPipe = 0 'reset from InvalidHandleValue to "no Handle"
       
        If mhPipe Then
            '* only try to find a free VB-FileNumber when mhPipe is valid (i.e. pipe has been created)
            mlFileNumber = FreeFile
            If mlFileNumber Then
                Open sPipeName For Binary As mlFileNumber  'open only, when we got an mlFileNumber
            End If
        End If
       
        InitializePipe = mhPipe <> 0 And mlFileNumber <> 0
    End Function
    
    Public Function SerializeToBytes(ByRef vSrc As Variant, ByRef pabytSerialized() As Byte) As Long
    
        Dim lBytesAvail As Long
    
        Debug.Assert IsArray(vSrc)
    
        If mlFileNumber <> 0 Then
       
            '* this next line writes the Variant array to the pipe
            Put mlFileNumber, 1, vSrc
           
            '* we should now have some bytes to read out of the pipe, use PeekNamedPipe to verify there are bytes available
            PeekNamedPipe mhPipe, ByVal 0&, 0, ByVal 0&, lBytesAvail, 0
           
            If lBytesAvail > 0 Then
               
                '* so now we can dimension the byte array
                ReDim Preserve pabytSerialized(0 To lBytesAvail - 1)
               
                '* and now we can read the bytes out of the pipe and into the byte array
                ReadFile mhPipe, pabytSerialized(0), lBytesAvail, lBytesAvail, ByVal 0&
               
                '* return number of bytes as a courtesy (not actually required)
                SerializeToBytes = lBytesAvail
            End If
        End If
    End Function
    
    Public Function DeserializeFromBytes(ByRef abytSerialized() As Byte, ByRef pvDest As Variant) As Long
       
        Dim lBytesWritten As Long
       
        If mhPipe <> 0 And mlFileNumber <> 0 Then
    
            '* write the byte array to the pipe
            WriteFile mhPipe, abytSerialized(0), UBound(abytSerialized) + 1, lBytesWritten, 0
           
            If lBytesWritten = UBound(abytSerialized) + 1 Then
                '* the pipe contains a byte array serialization of a variant array
                '* we can use VBA's Get statement to read it directly into a variant array variable
                Get mlFileNumber, 1, pvDest
               
                '* report the amount of deserialized Bytes as a courtesy (not actually required)
                DeserializeFromBytes = Loc(mlFileNumber)
            End If
        End If
    End Function
    
    Private Sub CleanUp()
        If mlFileNumber Then Close mlFileNumber: mlFileNumber = 0
        If mhPipe Then DisconnectNamedPipe mhPipe
        If mhPipe Then CloseHandle mhPipe: mhPipe = 0
    End Sub
    
    Private Sub Class_Terminate()
        CleanUp
    End Sub

    VBA Standard Module - tstPipedVariants

    So now we need some client code. Add a standard module to your VBA project and paste in the following code. I called this module tstPipedVariants.

    Sub SamePipeForSerializeAndDeserialize()
        Dim oPipe As cPipedVariants
        Set oPipe = New cPipedVariants
       
        If oPipe.InitializePipe Then
            Dim vSource As Variant
            vSource = TestData
    
            Dim abytSerialized() As Byte
    
            Call oPipe.SerializeToBytes(vSource, abytSerialized)
    
            Stop '* at this point vSource is populated but vDestination is empty
    
            Dim vDestination As Variant
            oPipe.DeserializeFromBytes abytSerialized, vDestination
       
            Stop
        End If
    End Sub
    
    Function TestData() As Variant
        Dim vSource(1 To 2, 1 To 4) As Variant
        vSource(1, 1) = "Hello World"
        vSource(1, 2) = True
        vSource(1, 3) = False
        vSource(1, 4) = Null
        vSource(2, 1) = 65535
        vSource(2, 2) = 7.5
        vSource(2, 3) = CDate("12:00:00 16-Sep-1989") 'now()
        vSource(2, 4) = CVErr(xlErrNA)
        TestData = vSource
    End Function

    In the module tstPipedVariants run the test code subroutine SamePipeForSerializeAndDeserialize() by navigating and pressing F5 to reach the first Stop statement. On the first Stop statement vSource is populated but vDestination isn’t.

    However, the byte array abytSerialized() is populated and we can go inspect this. The first twenty bytes are similar to SafeArray and SafeArrayBounds structures. The first two bytes represent a vbVarType of vbArray+vbVariant in low byte, high byte order. Next, two bytes gives the count of dimensions. Then for each dimension there are 8 bytes, giving a 4 byte dimension size and a 4 byte lower bound. This abridged SafeArray descriptor is most welcome. When VBA code writes a variant array to disk it omits such a descriptor which meant I had to augment the code to manually write in the dimensions. I am very much pleased that the Named Pipes implementation does this automatically for me.

    After the first twenty bytes of abridged SafeArray descriptor the rest of the data follows. I wrote this up in the original blog post so I’ll refer you to that and skip the rest.

    Returning to the test code, press F5 again to get the second Stop statement and behold in the Locals window the vDestination variable is now populated exactly the same as the vSource variable. Note how we did not need to dimension the vDestination variable before populating it, excellent!

    This completes the VBA to VBA demo. We can move onto the JavaScript to VBA use case.

    Revisiting the Javascript to VBA use case

    JavaScript Changes

    In the original article I gave some Javascript code to serialize a Javascript array to a byte array that can then be deserialized to a VBA variant array. This JavaScript code needs modifying to interoperate with the new Named Pipes VBA code given above. The change required is to give a correctly formatted abridged safe array descriptor. This is a simple change found at the top of the JavaScriptToVBAVariantArray.prototype.persistGrid function. All other code remains the same, so no further explanation is required. The JavaScript module remains something loadable into both browser and server JavaScript environments. The Node.js project given in the original blog post can still be used.

    I have only included the function that has changed, JavaScriptToVBAVariantArray.prototype.persistGrid; for rest of the JavaScript module listing see the original blog post.

    JavaScriptToVBAVariantArray.prototype.persistGrid = function persistGrid(grid, rows, columns) {
    	try {
    		/* Opening sequence of bytes is a reduced form of SAFEARRAY and SAFEARRAYBOUND
    		 * SAFEARRAY       https://docs.microsoft.com/en-gb/windows/win32/api/oaidl/ns-oaidl-safearray
    		 * SAFEARRAYBOUND  https://docs.microsoft.com/en-gb/windows/win32/api/oaidl/ns-oaidl-safearraybound
    		 */
    
    		var payloadEncoded = new Uint8Array(20);
    
    		// vbArray + vbVariant, lo byte, hi byte
    		payloadEncoded[0] = 12; payloadEncoded[1] = 32;
    
    		// number of dimensions, lo byte, hi byte
    		payloadEncoded[2] = 2; payloadEncoded[3] = 0;
    
    		// number of columns, 4 bytes, least significant byte first
    		payloadEncoded[4] = columns % 256; payloadEncoded[5] = Math.floor(columns / 256);
    		payloadEncoded[6] = 0; payloadEncoded[7] = 0;
    
    		// columns lower bound (safearray)
    		payloadEncoded[8] = 1; payloadEncoded[9] = 0;
    		payloadEncoded[10] = 0; payloadEncoded[11] = 0;
    
    		// number of rows, 4 bytes, least significant byte first
    		payloadEncoded[12] = rows % 256; payloadEncoded[13] = Math.floor(rows / 256);
    		payloadEncoded[14] = 0; payloadEncoded[15] = 0;
    
    		// rows lower bound (safearray)
    		payloadEncoded[16] = 1; payloadEncoded[17] = 0;
    		payloadEncoded[18] = 0; payloadEncoded[19] = 0;
    
    		var elementBytes;
    		for (var colIdx = 0; colIdx < columns; colIdx++) {
    			for (var rowIdx = 0; rowIdx < rows; rowIdx++) {
    				elementBytes = this.persistVar(grid[rowIdx][colIdx]);
    				var arr = [payloadEncoded, elementBytes];
    
    				payloadEncoded = this.concatArrays(arr); // Browser
    			}
    		}
    		return payloadEncoded;
    	}
    	catch (err) {
    		console.log(err.message);
    	}
    };

    VBA web client code

    Turning to the client VBA code we can greatly simplify the code now that the dimensioning is done for us. The resulting code is now trivial, here it is below. Add the following code to the tstPipedVariants module you added earlier. This code below requires you to add a Tools->Reference to Microsoft WinHTTP Services, version 5.1...
    Sub TestByWinHTTP()
        '* this calls the Node.js project with the new JavaScript serialization
        Dim oWinHttp As WinHttp.WinHttpRequest '* Tools->References->Microsoft WinHTTP Services, version 5.1
        Set oWinHttp = New WinHttp.WinHttpRequest
        oWinHttp.Open "GET", "http://localhost:1337/", False
        oWinHttp.send
       
        If oWinHttp.Status = 200 Then
            If IsEmpty(oWinHttp.ResponseBody) Then Err.Raise vbObjectError, , "No bytes returned!"
            If UBound(oWinHttp.ResponseBody) = 0 Then Err.Raise vbObjectError, , "No bytes returned!"
           
            Dim oPipedVariants As cPipedVariants
            Set oPipedVariants = New cPipedVariants
            If oPipedVariants.InitializePipe Then
           
                Dim vGrid As Variant
                oPipedVariants.DeserializeFromBytes oWinHttp.ResponseBody, vGrid
               
                Stop '* Observe vGrid in the Locals window
               
                '* vGrid is now ready to paste on a worksheet
            End If
        End If
    End Sub

    So run this code with the Node.js project running and the vGrid should be populated. That's all folks. Enjoy!

    Thanks again

    Thanks once again to Olaf Schmidt and the anonymous tipper! Getting help to fix my code is very welcome.