Skip to content

Saving Image Response To A PNG File In Mac #494

@1504168

Description

@1504168

I am trying to call an API get the image response and save it back to a PNG file. It is working fine in Windows, but I can't make it work on Mac.

Here is my sample code:

Option Explicit

Public Sub Test()
    
    Dim Response As WebResponse
    Dim Clinet As New WebClient
    Const URL As String = "https://kayaconnect.org/pluginfile.php/383257/course/overviewfiles/excel.png"
    Clinet.BaseURL = URL
    
    Dim Req As New WebRequest
    Req.ContentType = "image/png"
    Req.Method = HttpGet
    
    Set Response = Clinet.Execute(Req)
    SaveResponseBodyAsImage Response.Body, ThisWorkbook.Path & Application.PathSeparator & "Output.png"
    If IsMacOS() Then
        Sheet1.Range("A2:A1048576").ClearContents
        Sheet1.Range("A2").Resize(UBound(Response.Body)).Value = Application.WorksheetFunction.Transpose(Response.Body)
    Else
        Sheet1.Range("B2:B1048576").ClearContents
        Sheet1.Range("B2").Resize(UBound(Response.Body)).Value = Application.WorksheetFunction.Transpose(Response.Body)
    End If
    MsgBox "Done."
    
End Sub

Private Sub SaveResponseBodyAsImage(ByRef ResponseBody() As Byte, FilePath As String)
    
    If Dir(FilePath) <> vbNullString Then
        Kill FilePath
    End If
    
    Dim FileNo As Integer
    FileNo = FreeFile
    Open FilePath For Binary Access Write As #FileNo
    Put #FileNo, 1, ResponseBody
    Close #FileNo
    
End Sub

Public Function IsMacOS() As Boolean
        
    '@Description("This Short function will let you know if the current OS is MAC or Windows.")
    '@Dependency("No Dependency")
    '@ExampleCall : IsMacOS
    '@Date : 13 October 2021

    Const WindowsIdentifierPattern As String = "*Windows*"
    IsMacOS = Not (Application.OperatingSystem Like WindowsIdentifierPattern)

End Function

Just place this code in a new module in the VBA - Web -Blank.xlsm file and then we can test it out.

I am not using ADODB.Stream as I need it to work in both Win and Mac.

Metadata

Metadata

Assignees

No one assigned

    Labels

    No labels
    No labels

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions