Sylver
Sylver

Reputation: 8967

Export Excel chart to SVG creates an empty file

I am trying to export an Excel chart in SVG format using VBA.

    Set objChrt = ActiveChart.Parent
    objChrt.Activate
    Set curChart = objChrt.Chart
    
    curChart.Export fileName:=fileName, FilterName:="SVG"

If I replace "SVG" by "PNG", the export works exactly as intended and produces a valid PNG file. However, "SVG" results in an empty file. (Manually, there is an option to save as SVG inside Excel 365, so the export filter exists).

According to the documentation, Filtername is "The language-independent name of the graphic filter as it appears in the registry.", but I couldn't find anything like that in the registry, and either way, it's hard to imagine the SVG filtername being named anything other than "SVG".

Is there a way to export a Chart in SVG format using VBA?


Note: There is another question about Chart.export producing an empty file, and the fix was to use ChartObject.Activate before the export. This question is different because the code works correctly with "PNG" but fails with "SVG" (so it's not an issue related to activation or visibility). Also the recommended fix does not work.

Upvotes: 6

Views: 2831

Answers (3)

GWD
GWD

Reputation: 4008

2023 Update

This issue seems to be fixed in Excel Version 2302 Build 16.0.16130.20186) 64-bit, it was fixed in one of the versions released since 2021. Unfortunately, I can not find a mention of this fix in the release notes / archive.

This now works as specified in the documentation:

With ThisWorkbook.Worksheets("Sheet1")
    .ChartObjects("Chart 1").Chart.Export FileName:="path\name.svg", _
                                          FilterName:="SVG"
End With

For future reference, I will leave the original workaround for the bug below. However, even if you are working with one of the bugged versions of Excel, I recommend using this more elegant workaround by Jeremy Lakeman instead.


Old Workaround

Exporting to .SVG Without Any External Applications Using Only Excel and VBA

This is a hacky mess, but it works. At least for now...

First I will explain how it works, what problems exist that had to be overcome, and how they were solved. If you are not interested in the technicalities, you can skip to the section Simple Usage Guide.

What's the idea?

The code attempts to just use the manual export method. There are several problems with this, the first being yet another bug in the Chart.Export method. Chart.Export Interactive:=True is supposed to open the desired dialog box, but this just doesn't work. By leveraging some shortcuts, the export window can be opened very reliably using SendKeys "+{F10}" followed by SendKeys "g". The first hurdle is taken, but the trouble has only just begun!

It turns out, that opening a modal Dialog stops all code execution in the entire Application. Even if code in another application instance is called before we open the dialog, how can we keep it running there and also return to finish opening the dialog? It sounds impossible because VBA is strictly single-threaded...

It turns out, the single threading is not quite so strict. The solution is called Application.OnTime, which starts a procedure at a predetermined time in the future. That procedure has to run in a different instance of Excel.Application because Application.OnTime will only start a procedure if the application is in certain modes (Ready, Copy, Cut, or Find), and having VBA code running or having a modal dialog open are not among those. Therefore, before the dialog is opened, a background instance of the Excel app needs to be created, VBA code inserted into it and scheduled to start running in the background instance once the dialog is open. Note: Because the code is inserted automatically into the background instance, Trust access to the VBA project object model needs to be enabled.

How can we now work with the Windows dialog box using only VBA code? I managed to get all the window and control handles of the dialog via EnumChildWindows and used the information to insert text into the "FileName" ComboBox. Since this input box also accepts the path, the only problems left were selecting ".svg" in the FileFormat ComboBox and clicking the "Save" Button. Unfortunately I didn't manage to avoid using SendKeys here.

Changing the selection in the Combobox is relatively easy using Windows API functions but the problem is to actually get it to register the change. It appears to change in the dialog but when clicking "Save" it still saves as .png. I spent hours in Spy++ monitoring the messages that are sent during a manual change but I wasn't able to reproduce them with VBA. Because of this, it had to be SendKeys again for changing the file format and pressing 'Save'.

SendKeys is used very carefully in this solution, including various safety checks, and pulling the target window to the front before every usage, but it is never 100% safe if the pc is being interacted with while the macro is running.

Because the method requires a background instance of an app similar to here and here, I implemented a class for a ShapeExporter object. Creating the object opens the background app, destroying the object closes it.

Simple Usage Guide

The following procedure will export all ChartObjects in the specified worksheet to the folder the workbook is saved in.

Sub ExportEmbeddedChartToSVG()
    Dim MyWorksheet As Worksheet
    Set MyWorksheet = Application.Worksheets("MyWorksheet")
    
    'Creating the ShapeExporter object
    Dim oShapeExporter As cShapeExporter
    Set oShapeExporter = New cShapeExporter
    
    'Export as many shapes as you want here, before destroying oShapeExporter
    Dim oChart As ChartObject
    For Each oChart In MyWorksheet.ChartObjects
        'the .ExportShapeAsSVG method of the object takes three arguments:
        '1. The Chart or Shape to be exported
        '2. The target filename
        '3. The target path
        oShapeExporter.ExportShapeAsSVG oChart, oChart.Name, ThisWorkbook.Path
    Next oChart
    
    'When the object goes out of scope, its terminate procedure is automatically called
    'and the background app is closed
    Set oShapeExporter = Nothing
End Sub

For the code to work, you must first:

  1. Trust access to the VBA project object model (for reason see detailed description of the macro)
  2. Create a class module, rename it to "cShapeExporter", and paste the following code into it:
'Class for automatic exporting in SVG-Format
'Initial author: Guido Witt-Dörring, 09.12.2020
'https://stackoverflow.com/a/65212838/12287457

'Note:
'When objects created from this class are not properly destroyed, an invisible 
'background instance of Excel will keep running on your computer. In this 
'case, you can just close it via the Task Manager.
'For example, this will happen when your code hits an 'End' statement, which 
'immediately stops all code execution, or when an unhandled error forces 
'you to stop code execution manually while an instance of this class exists.

Option Explicit

#If VBA7 Then
    Private Declare PtrSafe Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
    Private Declare PtrSafe Function SetForegroundWindow Lib "user32" (ByVal hWnd As LongPtr) As Boolean
    Private Declare PtrSafe Function IsWindowVisible Lib "user32" (ByVal hWnd As LongPtr) As Boolean
    Private Declare PtrSafe Function IsIconic Lib "user32" (ByVal hWnd As LongPtr) As Boolean
    Private Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
#Else
    Private Declare Sub Sleep Lib "kernel32" (ByVal lngMilliSeconds As Long)
    Private Declare Function SetForegroundWindow Lib "user32" (ByVal hwnd As Long) As Boolean
    Private Declare Function IsWindowVisible Lib "User32" (ByVal hWnd As Long) As Boolean
    Private Declare Function IsIconic Lib "User32" Alias "IsIconic" (ByVal hWnd As long) As boolean
    Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
#End If

Private NewXlAppInstance As Excel.Application
Private xlWbInOtherInstance As Workbook
    
Private Sub Class_Initialize()
    Set NewXlAppInstance = New Excel.Application
    Set xlWbInOtherInstance = NewXlAppInstance.Workbooks.Add
    
    NewXlAppInstance.Visible = False
    
    On Error Resume Next
    xlWbInOtherInstance.VBProject.References.AddFromFile "scrrun.dll"
    xlWbInOtherInstance.VBProject.References.AddFromFile "FM20.dll"
    On Error GoTo 0
    
    Dim VbaModuleForOtherInstance As VBComponent
    Set VbaModuleForOtherInstance = xlWbInOtherInstance.VBProject.VBComponents.Add(vbext_ct_StdModule)
    
    VbaModuleForOtherInstance.CodeModule.AddFromString CreateCodeForOtherXlInstance
End Sub

Private Sub Class_Terminate()
    NewXlAppInstance.DisplayAlerts = False
    NewXlAppInstance.Quit
    Set xlWbInOtherInstance = Nothing
    Set NewXlAppInstance = Nothing
End Sub

Public Sub ExportShapeAsSVG(xlShp As Object, FileName As String, FilePath As String)
    'Check if path exists:
    If Not ExistsPath(FilePath) Then
        If vbYes = MsgBox("Warning, you are trying to export a file to a path that doesn't exist! Continue exporting to default path? " & vbNewLine & "Klick no to resume macro without exporting or cancel to debug.", vbYesNoCancel, "Warning") Then
            FilePath = ""
        ElseIf vbNo Then
            Exit Sub
        ElseIf vbCancel Then
            Error 76
        End If
    End If
    If TypeName(xlShp) = "ChartObject" Or TypeName(xlShp) = "Shape" Or TypeName(xlShp) = "Chart" Or TypeName(xlShp) = "ChartArea" Then
        'fine
    Else
        MsgBox "Exporting Objects of type " & TypeName(xlShp) & " not supported, sorry."
        Exit Sub
    End If
    
    If TypeName(xlShp) = "ChartArea" Then Set xlShp = xlShp.Parent
    
retry:
    SetForegroundWindow FindWindow("XLMAIN", ThisWorkbook.Name & " - Excel")
    
    If Not Application.Visible Then 'Interestingly, API function "IsWindowVisible(Application.hWnd)" doesn't work here! (maybe because of multi monitor setup?)
        MsgBox "The workbook must be visible for the svg-export to proceed! It must be at least in window mode!"
        Application.WindowState = xlNormal
        Application.Visible = True
        Sleep 100
        GoTo retry
    End If
    
    If IsIconic(Application.hWnd) Then 'Interestingly "Application.WindowState = xlMinimized" doesn't work here!"
        MsgBox "The workbook can't be minimized for the svg-export to proceed! It must be at least in window mode!"
        Application.WindowState = xlNormal
        Sleep 100
        GoTo retry
    End If
    
    'check if background instance still exists and start support proc
    On Error GoTo errHand
    NewXlAppInstance.Run "ScheduleSvgExportHelperProcess", Application.hWnd, ThisWorkbook.Name, FileName, FilePath
    On Error GoTo 0
    
    Sleep 100

    xlShp.Activate
    
    SetForegroundWindow FindWindow("XLMAIN", ThisWorkbook.Name & " - Excel")
    SendKeys "+{F10}"
    DoEvents
    SendKeys "g"
    DoEvents
    Exit Sub
errHand:
    MsgBox "Error in ShapeExporter Object. No more shapes can be exported."
    Err.Raise Err.Number
End Sub

Public Function ExistsPath(ByVal FilePath As String) As Boolean
    Dim oFso As Object
    Dim oFolder As Object
    
    Set oFso = CreateObject("Scripting.FileSystemObject")
    'Setting the Folder of the Filepath
    On Error GoTo PathNotFound
    Set oFolder = oFso.GetFolder(Left(Replace(FilePath & "\", "\\", "\"), Len(Replace(FilePath & "\", "\\", "\")) - 1))
    On Error GoTo 0
    
    ExistsPath = True
    Exit Function
    
PathNotFound:
    ExistsPath = False
End Function

Private Function CreateCodeForOtherXlInstance() As String
    Dim s As String
    s = s & "Option Explicit" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "#If VBA7 Then" & vbCrLf
    s = s & "    Public Declare PtrSafe Sub Sleep Lib ""kernel32"" (ByVal dwMilliseconds As Long)" & vbCrLf
    s = s & "    Private Declare PtrSafe Function GetForegroundWindow Lib ""user32"" () As LongPtr" & vbCrLf
    s = s & "    Private Declare PtrSafe Function GetWindowText Lib ""user32"" Alias ""GetWindowTextA"" (ByVal hWnd As LongPtr, ByVal lpString As String, ByVal cch As Long) As Long" & vbCrLf
    s = s & "    Private Declare PtrSafe Function FindWindow Lib ""user32"" Alias ""FindWindowA"" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr" & vbCrLf
    s = s & "    Private Declare PtrSafe Function SetForegroundWindow Lib ""user32"" (ByVal hWnd As LongPtr) As Boolean" & vbCrLf
    s = s & "    Private Declare PtrSafe Function SendMessage Lib ""user32"" Alias ""SendMessageA"" (ByVal hWnd As LongPtr, ByVal wMsg As Long, ByVal wParam As LongPtr, lParam As Any) As LongPtr" & vbCrLf
    s = s & "    Private Declare PtrSafe Function GetClassName Lib ""user32"" Alias ""GetClassNameA"" (ByVal hWnd As LongPtr, ByVal lpStr As String, ByVal nMaxCount As Long) As Long" & vbCrLf
    s = s & "    Private Declare PtrSafe Function EnumChildWindows Lib ""user32"" (ByVal hWndParent As LongPtr, ByVal lpEnumFunc As LongPtr, ByVal lParam As LongPtr) As Boolean" & vbCrLf
    s = s & "    Private Declare PtrSafe Function GetWindowTextLength Lib ""user32"" Alias ""GetWindowTextLengthA"" (ByVal hWnd As LongPtr) As Long" & vbCrLf
    s = s & "    Private Declare PtrSafe Function GetWindowLongPtr Lib ""user32"" Alias ""GetWindowLongPtrA"" (ByVal hWnd As LongPtr, ByVal nindex As Long) As LongPtr" & vbCrLf
    s = s & "#Else" & vbCrLf
    s = s & "    Public Declare Sub Sleep Lib ""kernel32"" (ByVal lngMilliSeconds As Long)" & vbCrLf
    s = s & "    Private Declare Function GetForegroundWindow Lib ""user32"" () As Long" & vbCrLf
    s = s & "    Private Declare Function GetWindowText Lib ""user32"" Alias ""GetWindowTextA"" (ByVal hwnd As Long, ByVal lpString As String, ByVal cch As Long) As Long" & vbCrLf
    s = s & "    Private Declare Function FindWindow Lib ""user32"" Alias ""FindWindowA"" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long" & vbCrLf
    s = s & "    Private Declare Function SetForegroundWindow Lib ""user32"" (ByVal hwnd As Long) As Boolean" & vbCrLf
    s = s & "    Private Declare Function SendMessage Lib ""user32"" Alias ""SendMessageA"" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long" & vbCrLf
    s = s & "    Private Declare Function GetClassName Lib ""user32"" Alias ""GetClassNameA"" (ByVal hwnd As Long, ByVal lpStr As String, ByVal nMaxCount As Long) As Long" & vbCrLf
    s = s & "    Private Declare Function EnumChildWindows Lib ""User32"" (ByVal hwndParent As Long, ByVal lpEnumFunc As Long, ByVal lParam As Long) As boolean" & vbCrLf
    s = s & "    Private Declare Function GetWindowTextLength Lib ""User32"" Alias ""GetWindowTextLengthA"" (ByVal hwnd As Long) As Long" & vbCrLf
    s = s & "    Private Declare Function GetWindowLongPtr Lib ""User32"" Alias ""GetWindowLongPtrA"" (ByVal hwnd As Long, ByVal nindex As Long) As Long" & vbCrLf
    s = s & "#End If" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "Private Const GWL_ID = -12" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "Private Const WM_SETTEXT = &HC" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "'Const for this Application:" & vbCrLf
    s = s & "Private Const dc_Hwnd = 1" & vbCrLf
    s = s & "Private Const dc_ClassName = 2" & vbCrLf
    s = s & "Private Const dc_CtlID = 3" & vbCrLf
    s = s & "Private Const dc_CtlText = 4" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "Private Const Window_Search_Timeout As Single = 5#" & vbCrLf
    s = s & "Public ChildWindowsPropDict As Object" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "#If VBA7 Then" & vbCrLf
    s = s & "    Private Function GetCtlText(ByVal hctl As LongPtr) As String" & vbCrLf
    s = s & "#Else" & vbCrLf
    s = s & "    Private Function GetCtlText(ByVal hctl As Long) As String" & vbCrLf
    s = s & "#End If" & vbCrLf
    s = s & "    Dim ControlText As String" & vbCrLf
    s = s & " On Error GoTo WindowTextTooLarge" & vbCrLf
    s = s & "    ControlText = Space(GetWindowTextLength(hctl) + 1)" & vbCrLf
    s = s & "    GetWindowText hctl, ControlText, Len(ControlText)" & vbCrLf
    s = s & "    GetCtlText = ControlText 'Controls Text" & vbCrLf
    s = s & "    Exit Function" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "WindowTextTooLarge:" & vbCrLf
    s = s & "    ControlText = Space(256)" & vbCrLf
    s = s & "    On Error GoTo -1" & vbCrLf
    s = s & "    GetWindowText hctl, ControlText, Len(ControlText)" & vbCrLf
    s = s & "    GetCtlText = ControlText  'Controls Text" & vbCrLf
    s = s & "End Function" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "#If VBA7 Then" & vbCrLf
    s = s & "    Private Function EnumChildProc(ByVal hWnd As LongPtr, ByVal lParam As LongPtr) As Long" & vbCrLf
    s = s & "#Else" & vbCrLf
    s = s & "    Private Function EnumChildProc(ByVal hWnd As Long, ByVal lParam As Long) As Long" & vbCrLf
    s = s & "#End If" & vbCrLf
    s = s & "    Dim ClassName As String" & vbCrLf
    s = s & "    Dim subCtlProp(1 To 4) As Variant" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    subCtlProp(dc_Hwnd) = hWnd 'Controls Handle" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    ClassName = Space(256)" & vbCrLf
    s = s & "    GetClassName hWnd, ClassName, Len(ClassName)" & vbCrLf
    s = s & "    subCtlProp(dc_ClassName) = Trim(CStr(ClassName)) 'Controls ClassName" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    subCtlProp(dc_CtlID) = GetWindowLongPtr(hWnd, GWL_ID) 'Controls ID" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    subCtlProp(dc_CtlText) = GetCtlText(hWnd)   'Controls Text 'Doesn't always work for some reason..." & vbCrLf
    s = s & "                                                '(sometimes returns """" when Spy++ finds a string)" & vbCrLf
    s = s & "    ChildWindowsPropDict.Add key:=CStr(hWnd), Item:=subCtlProp" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    'continue to enumerate (0 would stop it)" & vbCrLf
    s = s & "    EnumChildProc = 1" & vbCrLf
    s = s & "End Function" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "#If VBA7 Then" & vbCrLf
    s = s & "    Private Sub WriteChildWindowsPropDict(hWnd As LongPtr)" & vbCrLf
    s = s & "#Else" & vbCrLf
    s = s & "    Private Sub WriteChildWindowsPropDict(hWnd As Long)" & vbCrLf
    s = s & "#End If" & vbCrLf
    s = s & "    On Error Resume Next" & vbCrLf
    s = s & "    Set ChildWindowsPropDict = Nothing" & vbCrLf
    s = s & "    On Error GoTo 0" & vbCrLf
    s = s & "    Set ChildWindowsPropDict = CreateObject(""Scripting.Dictionary"")" & vbCrLf
    s = s & "    EnumChildWindows hWnd, AddressOf EnumChildProc, ByVal 0&" & vbCrLf
    s = s & "End Sub" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "Private Function ExistsFileInPath(ByVal FileName As String, ByVal FilePath As String, Optional warn As Boolean = False) As Boolean" & vbCrLf
    s = s & "    Dim oFso As Object" & vbCrLf
    s = s & "    Dim oFile As Object" & vbCrLf
    s = s & "    Dim oFolder As Object" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    Set oFso = CreateObject(""Scripting.FileSystemObject"")" & vbCrLf
    s = s & "    'Setting the Folder of the Filepath" & vbCrLf
    s = s & "    On Error GoTo PathNotFound" & vbCrLf
    s = s & "    Set oFolder = oFso.GetFolder(Left(Replace(FilePath & ""\"", ""\\"", ""\""), Len(Replace(FilePath & ""\"", ""\\"", ""\"")) - 1))" & vbCrLf
    s = s & "    On Error GoTo 0" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    'Writing all Filenames of the Files in the Folder to flStr" & vbCrLf
    s = s & "    For Each oFile In oFolder.Files" & vbCrLf
    s = s & "        If oFile.Name = FileName Then" & vbCrLf
    s = s & "            ExistsFileInPath = True" & vbCrLf
    s = s & "            Exit Function" & vbCrLf
    s = s & "        End If" & vbCrLf
    s = s & "    Next oFile" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    ExistsFileInPath = False" & vbCrLf
    s = s & "    Exit Function" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "PathNotFound:" & vbCrLf
    s = s & "    If warn Then MsgBox ""The path "" & Chr(10) & FilePath & Chr(10) & "" was not found by the function ExistsFileInPath."" & Chr(10) & ""Returning FALSE""" & vbCrLf
    s = s & "    ExistsFileInPath = False" & vbCrLf
    s = s & "End Function" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "#If VBA7 Then" & vbCrLf
    s = s & "    Public Sub ScheduleSvgExportHelperProcess(ByVal Wb1hwnd As LongPtr, ByVal Wb1Name As String, ByVal SvgFileName As String, ByVal SvgFilePath As String)" & vbCrLf
    s = s & "#Else" & vbCrLf
    s = s & "    Public Sub ScheduleSvgExportHelperProcess(ByVal Wb1hwnd As Long, ByVal Wb1Name As String, ByVal SvgFileName As String, ByVal SvgFilePath As String)" & vbCrLf
    s = s & "#End If" & vbCrLf
    s = s & "    If Not Wb1hwnd = FindWindow(""XLMAIN"", Wb1Name & "" - Excel"") Then" & vbCrLf
    s = s & "        MsgBox ""Error finding Wb1hwnd - something unforseen happened!""" & vbCrLf
    s = s & "        GoTo badExit" & vbCrLf
    s = s & "    End If" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    Application.OnTime Now + TimeValue(""00:00:02""), ""'SvgExportHelperProcess """""" & CStr(Wb1hwnd) & """""", """""" & Wb1Name & """""", """""" & SvgFileName _" & vbCrLf
    s = s & "                        & """""", """""" & SvgFilePath & """"""'"", Now + TimeValue(""00:00:015"")" & vbCrLf
    s = s & "    Exit Sub" & vbCrLf
    s = s & "badExit:" & vbCrLf
    s = s & "    MsgBox ""Shutting down background instance of excel.""" & vbCrLf
    s = s & "    Application.DisplayAlerts = False" & vbCrLf
    s = s & "    Application.Quit" & vbCrLf
    s = s & "End Sub" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "Public Sub SvgExportHelperProcess(ByVal Wb1hwndStr As String, ByVal Wb1Name As String, ByVal SvgFileName As String, ByVal SvgFilePath As String)" & vbCrLf
    s = s & "    #If VBA7 And Win64 Then" & vbCrLf
    s = s & "        Dim Wb1hwnd As LongPtr" & vbCrLf
    s = s & "        Wb1hwnd = CLngPtr(Wb1hwndStr)" & vbCrLf
    s = s & "        Dim dlgHwnd As LongPtr" & vbCrLf
    s = s & "        Dim tempHctrl As LongPtr" & vbCrLf
    s = s & "    #Else" & vbCrLf
    s = s & "        Dim Wb1hwnd As LongPtr" & vbCrLf
    s = s & "        Wb1hwnd = CLng(Wb1hwndStr)" & vbCrLf
    s = s & "        Dim dlgHwnd As Long" & vbCrLf
    s = s & "        Dim tempHctrl As Long" & vbCrLf
    s = s & "    #End If" & vbCrLf
    s = s & "    Dim i As Long" & vbCrLf
    s = s & "    Dim stopTime As Single" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    'Find dialog window handle" & vbCrLf
    s = s & "    stopTime = Timer() + Window_Search_Timeout" & vbCrLf
    s = s & "    Do" & vbCrLf
    s = s & "        dlgHwnd = 0" & vbCrLf
    s = s & "        Sleep 15" & vbCrLf
    s = s & "        DoEvents" & vbCrLf
    s = s & "        SetForegroundWindow Wb1hwnd  'FindWindow(""XLMAIN"", Wb1Name & "" - Excel"")" & vbCrLf
    s = s & "        Sleep 150" & vbCrLf
    s = s & "        dlgHwnd = FindWindow(""#32770"", vbNullString)" & vbCrLf
    s = s & "    Loop Until Timer() > stopTime Or dlgHwnd <> 0" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    If dlgHwnd = 0 Then" & vbCrLf
    s = s & "        MsgBox ""Couldn't find dialog window handle!""" & vbCrLf
    s = s & "        GoTo errHand" & vbCrLf
    s = s & "    End If" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    'Enumerate the child windows of the dialog and write their properties to a dictionary" & vbCrLf
    s = s & "    WriteChildWindowsPropDict dlgHwnd" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "    'the first window of class ""Edit"" inside ChildWindowsPropDict will be the filename box" & vbCrLf
    s = s & "    Dim v As Variant" & vbCrLf
    s = s & "    For Each v In ChildWindowsPropDict.items" & vbCrLf
    s = s & "        If Left(CStr(v(dc_ClassName)), Len(CStr(v(dc_ClassName))) - 1) = ""Edit"" Then" & vbCrLf
    s = s & "            tempHctrl = v(dc_Hwnd)" & vbCrLf
    s = s & "            'send message" & vbCrLf
    s = s & "            SendMessage tempHctrl, WM_SETTEXT, 0&, ByVal SvgFilePath & ""\"" & SvgFileName" & vbCrLf
    s = s & "            'we don't need this hwnd anymore" & vbCrLf
    s = s & "            ChildWindowsPropDict.Remove CStr(v(dc_Hwnd))" & vbCrLf
    s = s & "            Exit For" & vbCrLf
    s = s & "        End If" & vbCrLf
    s = s & "    Next v" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "retry:" & vbCrLf
    s = s & "    SetForegroundWindow dlgHwnd" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    SendKeys ""{TAB}""" & vbCrLf
    s = s & "    Sleep 250" & vbCrLf
    s = s & "    SetForegroundWindow dlgHwnd" & vbCrLf
    s = s & "    For i = 1 To 10" & vbCrLf
    s = s & "        SendKeys ""{DOWN}""" & vbCrLf
    s = s & "        Sleep 100" & vbCrLf
    s = s & "        SetForegroundWindow dlgHwnd" & vbCrLf
    s = s & "    Next i" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    SendKeys ""~""" & vbCrLf
    s = s & "    Sleep 100" & vbCrLf
    s = s & "    SetForegroundWindow dlgHwnd" & vbCrLf
    s = s & "    SendKeys ""~""" & vbCrLf
    s = s & "    Sleep 50" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    'give the keystrokes time to process" & vbCrLf
    s = s & "    Sleep 300" & vbCrLf
    s = s & "" & vbCrLf
    s = s & "    'Wait until the file appears in the specified path:" & vbCrLf
    s = s & "    Dim cleanFileName As String" & vbCrLf
    s = s & "    If InStr(1, Right(SvgFileName, 4), "".svg"", vbTextCompare) = 0 Then" & vbCrLf
    s = s & "        cleanFileName = SvgFileName & "".svg""" & vbCrLf
    s = s & "    Else" & vbCrLf
    s = s & "        cleanFileName = SvgFileName" & vbCrLf
    s = s & "    End If" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    Dim retryTime As Single" & vbCrLf
    s = s & "    retryTime = Timer + 5" & vbCrLf
    s = s & "    stopTime = Timer + 60  '1 minute timeout." & vbCrLf
    s = s & "                            'relatively long in case a file already exists dialog appears..." & vbCrLf
    s = s & "    Do Until ExistsFileInPath(SvgFileName, SvgFilePath, False)" & vbCrLf
    s = s & "        Sleep 700" & vbCrLf
    s = s & "        DoEvents" & vbCrLf
    s = s & "        If Timer > retryTime Then" & vbCrLf
    s = s & "            'check if graphic export dialog is top window" & vbCrLf
    s = s & "            If dlgHwnd = GetForegroundWindow Then GoTo retry" & vbCrLf
    s = s & "        End If" & vbCrLf
    s = s & "        If Timer > stopTime Then GoTo timeoutHand" & vbCrLf
    s = s & "    Loop" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "    Exit Sub" & vbCrLf
    s = s & "errHand:" & vbCrLf
    s = s & "    MsgBox ""Error in the helper process""" & vbCrLf
    s = s & "    GoTo badExit" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "timeoutHand:" & vbCrLf
    s = s & "    MsgBox ""Timeout. It seems like something went wrong creating the file. File "" & cleanFileName & "" didn't appear in folder "" & SvgFilePath & "".""" & vbCrLf
    s = s & "    GoTo badExit" & vbCrLf
    s = s & "    " & vbCrLf
    s = s & "badExit:" & vbCrLf
    s = s & "    MsgBox ""Shutting down background instance of excel.""" & vbCrLf
    s = s & "    Application.DisplayAlerts = False" & vbCrLf
    s = s & "    Application.Quit" & vbCrLf
    s = s & "End Sub" & vbCrLf
    s = s & "" & vbCrLf
    CreateCodeForOtherXlInstance = s
End Function

Upvotes: 4

Jeremy Lakeman
Jeremy Lakeman

Reputation: 11138

When you copy a chart to the clipboard, Excel adds lots of different clipboard formats. Since version 2011 (Application.Build >= 13426), this now includes "image/svg+xml".

So all we have to do is find that format on the clipboard and save it to a file. Which turns out to be fairly annoying.

Private Declare PtrSafe Function OpenClipboard Lib "user32" (ByVal hwnd As LongPtr) As Long
Private Declare PtrSafe Function GetClipboardData Lib "user32" (ByVal wFormat As Long) As LongPtr
Private Declare PtrSafe Function EnumClipboardFormats Lib "user32" (ByVal wFormat As Long) As Long
Private Declare PtrSafe Function GetClipboardFormatName Lib "user32" _
    Alias "GetClipboardFormatNameW" _
    (ByVal wFormat As Long, _
    ByVal lpString As LongPtr, _
    ByVal nMaxCount As Integer) As Integer
Private Declare PtrSafe Function CloseClipboard Lib "user32" () As Long

Private Declare PtrSafe Function GlobalUnlock Lib "Kernel32" (ByVal hMem As LongPtr) As LongPtr
Private Declare PtrSafe Function GlobalLock Lib "Kernel32" (ByVal hMem As LongPtr) As LongPtr
Private Declare PtrSafe Function GlobalSize Lib "Kernel32" (ByVal hMem As LongPtr) As LongPtr

Private Declare PtrSafe Function CreateFile Lib "Kernel32" _
    Alias "CreateFileA" (ByVal lpFileName As String, _
    ByVal dwDesiredAccess As Long, _
    ByVal dwShareMode As Long, _
    ByVal lpSecurityAttributes As LongPtr, _
    ByVal dwCreationDisposition As Long, _
    ByVal dwFlagsAndAttributes As Long, _
    ByVal hTemplateFile As LongPtr) As LongPtr

Private Declare PtrSafe Function WriteFile Lib "Kernel32" _
    (ByVal hFile As LongPtr, _
    ByVal lpBuffer As LongPtr, _
    ByVal nNumberOfBytesToWrite As Long, _
    ByRef lpNumberOfBytesWritten As Long, _
    ByVal lpOverlapped As LongPtr) As Long

Private Declare PtrSafe Function CloseHandle Lib "Kernel32" (ByVal hObject As LongPtr) As Long


Sub SaveClipboard(formatName As String, filename As String)
    Dim fmtName As String
    Dim fmt As Long
    Dim length As Long
    Dim wrote As Long
    Dim data As LongPtr
    Dim fileHandle As LongPtr
    Dim content As LongPtr
    Dim ret As Long
    
    If OpenClipboard(ActiveWindow.hwnd) = 0 Then
        Exit Sub
    End If
    
    fmt = 0
    Do
        fmt = EnumClipboardFormats(fmt)
        If fmt = 0 Then Exit Do
        
        fmtName = String$(255, vbNullChar)
        length = GetClipboardFormatName(fmt, StrPtr(fmtName), 255)
        If length <> 0 And Left(fmtName, length) = formatName Then
            data = GetClipboardData(fmt)
            
            length = CLng(GlobalSize(data))
            content = GlobalLock(data)

            ' use win32 api file handling to avoid copying buffers
            fileHandle = CreateFile(filename, &H120089 Or &H120116, 0, 0, 2, 0, 0)
            ret = WriteFile(fileHandle, content, length, wrote, 0)
            CloseHandle fileHandle
            
            GlobalUnlock data
            Exit Do
        End If
    Loop

    CloseClipboard
    
    If fmt = 0 Then
        MsgBox "Did not find clipboard format " & formatName
        Exit Sub
    End If

End Sub

Then just copy the chart and save the svg;

shape.Copy
SaveClipboard "image/svg+xml", "C:\temp\output.svg"

Upvotes: 2

Cristian Buse
Cristian Buse

Reputation: 4588

If you don't need .svg in particular then .emf is another vector format. It does not work directly from Excel but it does work using a 'helper' PowerPoint app:

Sub ExportChartToEMF(ByVal ch As Chart, ByVal filePath As String)
    Const methodName As String = "ExportChartToEMF"
    Const ppShapeFormatEMF As Long = 5
    '
    If ch Is Nothing Then Err.Raise 91, methodName, "Chart not set"
    '
    Dim pp As Object
    Dim slide As Object
    Dim errNumber As Long
    '
    Set pp = CreateObject("PowerPoint.Application")
    With pp.Presentations.Add(msoFalse) 'False so it's not Visible
        Set slide = .Slides.AddSlide(.Slides.Count + 1, .Designs(1).SlideMaster.CustomLayouts(1))
    End With
    '
    ch.Parent.Copy
    On Error Resume Next
    slide.Shapes.Paste.Export filePath, ppShapeFormatEMF
    errNumber = Err.Number
    On Error GoTo 0
    '
    pp.Quit
    If Err.Number <> 0 Then Err.Raise Err.Number, methodName, "Error while exporting to file"
End Sub

You would use it like:

ExportChartToEMF ActiveChart, "[FolderPath]\[FileName].emf"

If you really need .svg then unfortunately the functionality is not exposed to VBA although it works manually in Excel and PowerPoint via the Save as Picture dialog (right-click on chart shape).

In short, you cannot fully automate the export of chart to .svg file unless you go through an intermediate format (like .emf or .pdf) or manually saving to .svg via the Save as Picture dialog.

Upvotes: 2

Related Questions