Jaafar Tribak

Well-known Member
Joined
Dec 5, 2002
Messages
9,621
Office Version
  1. 2016
Platform
  1. Windows
Hi dear forum,

Got bored and decided to add some animation to the standard vba MsgBox. It is not going to be of much use to most excel\vba users, but it was fun to code and will add to the MsgBox, some lively aspect that can be used in capturing the user's attention.

Basically, the code simply hijacks the MsgBox and replaces its default icon with the gif of your choice.

Workbook example:
AnimatedMsgBox.xlsm





I am not versed with HTML DOM coding ... In the tests I carried out with various gifs, I could successfully set the backgroundcolor only in some of them. This is in order to match the gif background color with the MsgBox theme for blending.

Unless the gif is a transparent gif, much of the image quality may be affected if the gif has a background color that cannot be set.



1- API code in a Standard Module:
VBA Code:
Option Explicit

Private Type POINTAPI
    x As Long
    y As Long
End Type

Private Type RECT
    Left As Long
    Top As Long
    Right As Long
    Bottom As Long
End Type

Private Type RGB
    R As Long
    G As Long
    B As Long
End Type


#If VBA7 Then
    Private Declare PtrSafe Function SetWindowsHookEx Lib "user32" Alias "SetWindowsHookExA" (ByVal idHook As Long, ByVal lpfn As LongPtr, ByVal hmod As LongPtr, ByVal dwThreadId As Long) As LongPtr
    Private Declare PtrSafe Function CallNextHookEx Lib "user32" (ByVal hHook As LongPtr, ByVal ncode As Long, ByVal wParam As LongPtr, lParam As Any) As LongPtr
    Private Declare PtrSafe Function UnhookWindowsHookEx Lib "user32" (ByVal hHook As LongPtr) As Long
    Private Declare PtrSafe Function GetCurrentThreadId Lib "kernel32" () As Long
    Private Declare PtrSafe Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As LongPtr
    Private Declare PtrSafe Function GetClassName Lib "user32" Alias "GetClassNameA" (ByVal hwnd As LongPtr, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long
    Private Declare PtrSafe Function AtlAxWinInit Lib "Atl.dll" () As Long
    Private Declare PtrSafe Function AtlAxGetControl Lib "atl" (ByVal hwnd As LongPtr, Unk As stdole.IUnknown) As Long
    Private Declare PtrSafe Function CreateWindowEx Lib "user32" Alias "CreateWindowExA" (ByVal dwExStyle As Long, ByVal lpClassName As String, ByVal lpWindowName As String, ByVal dwStyle As Long, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hWndParent As LongPtr, ByVal hMenu As LongPtr, ByVal hInstance As LongPtr, lpParam As Any) As LongPtr
    Private Declare PtrSafe Function GetDlgItem Lib "user32" (ByVal hDlg As LongPtr, ByVal nIDDlgItem As Long) As LongPtr
    Private Declare PtrSafe Function GetWindowRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As RECT) As Long
    Private Declare PtrSafe Function ScreenToClient Lib "user32" (ByVal hwnd As LongPtr, lpPoint As POINTAPI) As Long
    Private Declare PtrSafe Function DestroyWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
    Private Declare PtrSafe Function TranslateColor Lib "oleAut32.dll" Alias "OleTranslateColor" (ByVal clr As OLE_COLOR, ByVal palet As LongPtr, col As Long) As Long
    Private Declare PtrSafe Function GetSysColor Lib "user32" (ByVal nIndex As Long) As Long
    Private Declare PtrSafe Function ColorHLSToRGB Lib "shlwapi.dll" (ByVal wHue As Integer, ByVal wLuminance As Integer, ByVal wSaturation As Integer) As Long
    Private Declare PtrSafe Function ColorRGBToHLS Lib "shlwapi" (ByVal clrRGB As Long, ByRef wHue As Integer, ByRef wLuminance As Integer, ByRef wSaturation As Integer) As Long
    Private Declare PtrSafe Function SetLayeredWindowAttributes Lib "user32" (ByVal hwnd As LongPtr, ByVal crey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As LongPtr
    Private Declare PtrSafe Function ShowWindow Lib "user32" (ByVal hwnd As LongPtr, ByVal nCmdShow As Long) As Long
   
    Private hHook As LongPtr
#Else
    Private Declare Function SetWindowsHookEx Lib "user32" Alias "SetWindowsHookExA" (ByVal idHook As Long, ByVal lpfn As Long, ByVal hmod As Long, ByVal dwThreadId As Long) As Long
    Private Declare Function CallNextHookEx Lib "user32" (ByVal hHook As Long, ByVal ncode As Long, ByVal wParam As Long, lParam As Any) As Long
    Private Declare Function UnhookWindowsHookEx Lib "user32" (ByVal hHook As Long) As Long
    Private Declare Function GetCurrentThreadId Lib "kernel32" () As Long
    Private Declare Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As Long
    Private Declare Function GetClassName Lib "user32" Alias "GetClassNameA" (ByVal hwnd As Long, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long
    Private Declare Function AtlAxWinInit Lib "Atl.dll" () As Long
    Private Declare Function AtlAxGetControl Lib "atl" (ByVal hwnd As Long, Unk As stdole.IUnknown) As Long
    Private Declare Function CreateWindowEx Lib "user32" Alias "CreateWindowExA" (ByVal dwExStyle As Long, ByVal lpClassName As String, ByVal lpWindowName As String, ByVal dwStyle As Long, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hWndParent As Long, ByVal hMenu As Long, ByVal hInstance As Long, lpParam As Any) As Long
    Private Declare Function GetDlgItem Lib "user32" (ByVal hDlg As Long, ByVal nIDDlgItem As Long) As Long
    Private Declare Function GetWindowRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) As Long
    Private Declare Function ScreenToClient Lib "user32" (ByVal hwnd As Long, lpPoint As POINTAPI) As Long
    Private Declare Function DestroyWindow Lib "user32" (ByVal hwnd As Long) As Long
    Private Declare Function TranslateColor Lib "oleAut32.dll" Alias "OleTranslateColor" (ByVal clr As OLE_COLOR, ByVal palet As Long, col As Long) As Long
    Private Declare Function GetSysColor Lib "user32" (ByVal nIndex As Long) As Long
    Private Declare Function ColorHLSToRGB Lib "shlwapi.dll" (ByVal wHue As Integer, ByVal wLuminance As Integer, ByVal wSaturation As Integer) As Long
    Private Declare Function ColorRGBToHLS Lib "shlwapi" (ByVal clrRGB As Long, ByRef wHue As Integer, ByRef wLuminance As Integer, ByRef wSaturation As Integer) As Long
    Private Declare Function SetLayeredWindowAttributes Lib "user32" (ByVal hwnd As Long, ByVal crey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As Long
    Private Declare Function ShowWindow Lib "user32" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long
   
    Private hHook As Long
#End If

Private sURL As String



Public Function AnimatedMsgBox( _
    ByVal PROMPT As String, _
    Optional ByVal BUTTONS As VbMsgBoxStyle, _
    Optional ByVal TITLE As String, _
    Optional GIF_URL As String _
) As VbMsgBoxResult
   
    Const WH_CBT = 5
   
    If hHook = 0 Then
        hHook = SetWindowsHookEx(WH_CBT, AddressOf HookProc, GetModuleHandle(StrPtr(vbNullString)), GetCurrentThreadId)
        sURL = GIF_URL
        BUTTONS = BUTTONS And Not (vbInformation Or vbExclamation Or vbCritical)
        AnimatedMsgBox = MsgBox(PROMPT, BUTTONS + vbInformation, TITLE)
    End If
      
End Function


#If Win64 Then
    Private Function HookProc( _
        ByVal lCode As Long, _
        ByVal wParam As LongLong, _
        ByVal lParam As LongLong _
    ) As LongLong
   
       Dim hIcon As LongLong, hWebCtrl As LongLong
#Else
    Private Function HookProc( _
        ByVal lCode As Long, _
        ByVal wParam As Long, _
        ByVal lParam As Long _
    ) As Long
   
        Dim hIcon As Long, hWebCtrl As Long
#End If

    Const HC_ACTION = 0
    Const HCBT_ACTIVATE = 5
    Const HCBT_DESTROYWND = 4
    Const WS_CHILD = &H40000000
    Const WS_VISIBLE = &H10000000
    Const WS_EX_LAYERED = &H80000
    Const LWA_COLORKEY = &H1
    Const COLOR_WINDOW = 5
   
    Dim tWinRect As RECT, tPt As POINTAPI
    Dim Unk As IUnknown, oWbrowser As Object
    Dim sClassName As String * 256, lRet As Long
    Dim lWindColor As Long
   
 
    On Error Resume Next

    If lCode < HC_ACTION Then
        HookProc = CallNextHookEx(hHook, lCode, wParam, lParam)
        Exit Function
    End If
   
    If lCode = HCBT_ACTIVATE And hWebCtrl = 0 Then
        lRet = GetClassName(wParam, sClassName, 256)
        If Left$(sClassName, lRet) = "#32770" Then
            hIcon = GetDlgItem(wParam, &H14)
            Call GetWindowRect(hIcon, tWinRect)
            tPt.x = tWinRect.Left: tPt.y = tWinRect.Top
            Call ShowWindow(hIcon, 0)
            Call ScreenToClient(wParam, tPt)
            Call AtlAxWinInit
            hWebCtrl = CreateWindowEx(WS_EX_LAYERED, "AtlAxWin", "about:blank", WS_VISIBLE + WS_CHILD, tPt.x, tPt.y, 32, 32, wParam, 0, 0, ByVal 0)
            Call TranslateColor(GetSysColor(COLOR_WINDOW), 0, lWindColor)
            Call SetLayeredWindowAttributes(hWebCtrl, vbWhite, 0, LWA_COLORKEY)
            If hWebCtrl Then
                Call AtlAxGetControl(hWebCtrl, Unk)
                Set oWbrowser = Unk
                With oWbrowser
                    Do: DoEvents: Loop While .ReadyState <> 4 Or .Busy
                    .Silent = True
                    .Document.body.innerHTML = "<img style=""position:absolute;top:0px;left:0px;width:" & 32 & _
                    "px;height:" & Fix(.Height) & "px"" src=""" & sURL & "?" & """/>"
                    .Document.body.Style.backgroundColor = GetHLS(lWindColor)
                End With
            End If
        End If
    End If
 
    If lCode = HCBT_DESTROYWND Then
        lRet = GetClassName(wParam, sClassName, 256)
        If Left$(sClassName, lRet) = "#32770" Then
            Call DestroyWindow(hWebCtrl)
            hWebCtrl = 0
            Call UnhookWindowsHookEx(hHook): hHook = 0
        End If
    End If
 
    Call CallNextHookEx(hHook, lCode, wParam, lParam)

End Function


Private Function GetHLS(ByVal col As Long) As String

    Dim sHLS As String, tARGB As RGB, tWinRect As RECT
    Dim R As Byte, G As Byte, B As Byte
    Dim iHu As Integer, iLu As Integer, iSa As Integer
   
    Call ColorRGBToHLS(col, iHu, iLu, iSa)
    tARGB = ColorToRGB(ColorHLSToRGB(iHu, iLu, iSa))
    sHLS = "#" & Right("0" & Hex(tARGB.R), 2) & Right("0" & Hex(tARGB.G), 2) & Right("0" & Hex(tARGB.B), 2)
    GetHLS = sHLS

End Function

Private Function ColorToRGB(ByVal col As Long) As RGB
    ColorToRGB.R = &HFF& And col
    ColorToRGB.G = (&HFF00& And col) \ 256
    ColorToRGB.B = (&HFF0000 And col) \ 65536
End Function


2- Test (as per the workbook demo)
VBA Code:
Option Explicit

Sub Test()

    AnimatedMsgBox "Hello!", vbInformation, "Animated Gif Demo.", "https://media.giphy.com/media/3o6fJg5J8ZkVxxXERO/giphy.gif"
    AnimatedMsgBox "Hypnosis may help you.", , "Animated Gif Demo.", "https://media.giphy.com/media/WZrOaNjFPKT5e/giphy.gif"
    AnimatedMsgBox "Never mind.", vbAbortRetryIgnore + vbInformation, "Animated Gif Demo.", "https://media.giphy.com/media/LCf1GPRCsDMagg2kMq/giphy.gif"
    AnimatedMsgBox "Use your imagination.", , "Animated Gif Demo.", "https://media.giphy.com/media/3o7TKFxkCyNzy4WiKA/giphy.gif"
    AnimatedMsgBox "Use your imagination.", , "Animated Gif Demo.", "https://media.giphy.com/media/5xaOcLO449BOl4POJVu/giphy.gif"
    AnimatedMsgBox "Use your imagination.", , "Animated Gif Demo.", "https://media.giphy.com/media/BfWLUK9MyFVRK/giphy.gif"
    AnimatedMsgBox "Use your imagination.", , "Animated Gif Demo.", "https://media.giphy.com/media/3o6gbeVN2ZPbG2COKA/giphy.gif"
    AnimatedMsgBox "Use your imagination.", , "Animated Gif Demo.", "https://media.giphy.com/media/rDb9zTgdfiPwQ/giphy.gif"
    AnimatedMsgBox "Use your imagination.", , "Animated Gif Demo.", "https://media.giphy.com/media/NU4il2utBo5Lq/giphy.gif"
    AnimatedMsgBox "Use your imagination.", , "Animated Gif Demo.", "https://media.giphy.com/media/9V73lQx5Sa7r14IDqT/giphy.gif"
    AnimatedMsgBox "Ok. That's enough." & vbNewLine & "Point made.", , "Animated Gif Demo.", "https://media.giphy.com/media/KlokXJQBqt25G/giphy.gif"
    AnimatedMsgBox "Bye!", vbExclamation, "Animated Gif Demo.", "https://media.giphy.com/media/hYD129K5IHWVMJgRvG/giphy.gif"

End Sub

Gifs can be added from disk files or from urls.
 

Excel Facts

Formula for Yesterday
Name Manager, New Name. Yesterday =TODAY()-1. OK. Then, use =YESTERDAY in any cell. Tomorrow could be =TODAY()+1.
Thank you kindly for the feedback.

As regards the transparency, I had hoped to be able to use the WIA COM Object to extract out the frames and to use either the stdPicture render method (middle image below) or the ImageList's draw method (right image) to animate the frames, but unfortunately, something happens to the transparency layer throughout the course the GIF, and what should be clear is now black. It's disappointing, but oh well. Worth a try.

View attachment 81469

Hi Dan_W

Did you find a solution to this ?

I got bored and decided to give this a shot. I have come up with the following result using a combination of GDI, GDI+, WIA and a Windows timer.

I followed the StdPicture logic you metioned above but *not* for using the StdPicture Render to DC Method as this would require repeated repainting (There is no AutoRedraw Poperty in vba forms).

The way I proceeded was by Alphablending each extracted gif frame with a temporary memory Bitmap that is painted with a brush whose color is the same as that of the container control... Each resulting alpha-blended memory bitmap is then translated to a StdPicture object inside the timer callback.

The above steps work for keeping the *transparent* background and seems to prevent screen flickering as well.

The code retrieves the Width, Height , Frame-Count and Frame-Delay of the animated GIF... The timer is in charge of setting\modifying the frame display delay as needed.

At the present time , the code only works with Labels (easier) , Frames and with the UserForm itself... The code would need some small tweaking in order to work with all types of controls that have a Picture Property.

Workbook Demo:
TransparentGIFRender.xlsm







1- In a Standard Module:
VBA Code:
Option Explicit

#If Win64 Then
    Private Const NULL_PTR = 0^
#Else
    Private Const NULL_PTR = 0&
#End If

#If VBA7 Then
    Private Declare PtrSafe Function IUnknown_GetWindow Lib "shlwapi" Alias "#172" (ByVal pIUnk As IUnknown, ByVal hUf As LongPtr) As Long
    Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
    Private Declare PtrSafe Function URLDownloadToFile Lib "urlmon" Alias "URLDownloadToFileA" (ByVal pCaller As Long, ByVal szURL As String, ByVal szFileName As String, ByVal dwReserved As Long, ByVal lpfnCB As Long) As Long
    Private Declare PtrSafe Function SetTimer Lib "user32.dll" (ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr, ByVal uElapse As Long, ByVal lpTimerFunc As LongPtr) As LongPtr
    Private Declare PtrSafe Function KillTimer Lib "user32.dll" (ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr) As Long
    Private Declare PtrSafe Function OleCreatePictureIndirectAut Lib "oleAut32.dll" Alias "OleCreatePictureIndirect" (PicDesc As uPicDesc, RefIID As GUID, ByVal fPictureOwnsHandle As Long, IPic As IPicture) As Long
    Private Declare PtrSafe Function CopyImage Lib "user32" (ByVal Handle As LongPtr, ByVal un1 As Long, ByVal n1 As Long, ByVal n2 As Long, ByVal un2 As Long) As LongPtr
    Private Declare PtrSafe Function GetDC Lib "user32.dll" (ByVal hwnd As LongPtr) As LongPtr
    Private Declare PtrSafe Function ReleaseDC Lib "user32" (ByVal hwnd As LongPtr, ByVal hDC As LongPtr) As LongPtr
    Private Declare PtrSafe Function CreateCompatibleDC Lib "gdi32" (ByVal hDC As LongPtr) As LongPtr
    Private Declare PtrSafe Function CreateCompatibleBitmap Lib "gdi32" (ByVal hDC As LongPtr, ByVal nWidth As Long, ByVal nHeight As Long) As LongPtr
    Private Declare PtrSafe Function SelectObject Lib "gdi32" (ByVal hDC As LongPtr, ByVal hObject As LongPtr) As LongPtr
    Private Declare PtrSafe Function DeleteObject Lib "gdi32" (ByVal hObject As LongPtr) As Long
    Private Declare PtrSafe Function DeleteDC Lib "gdi32" (ByVal hDC As LongPtr) As Long
    Private Declare PtrSafe Function FillRect Lib "user32" (ByVal hDC As LongPtr, lpRect As RECT, ByVal hBrush As LongPtr) As Long
    Private Declare PtrSafe Function CreateSolidBrush Lib "gdi32" (ByVal crColor As Long) As LongPtr
    Private Declare PtrSafe Function AlphaBlend Lib "msimg32.dll" (ByVal hDC As LongPtr, ByVal lInt As Long, ByVal lInt As Long, ByVal lInt As Long, ByVal lInt As Long, ByVal hDC As LongPtr, ByVal lInt As Long, ByVal lInt As Long, ByVal lInt As Long, ByVal lInt As Long, ByVal BLENDFUNCT As LongPtr) As Long
    Private Declare PtrSafe Function GetClientRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As RECT) As Long
    Private Declare PtrSafe Function TranslateColor Lib "oleAut32.dll" Alias "OleTranslateColor" (ByVal clr As OLE_COLOR, ByVal palet As LongPtr, Col As Long) As Long
    Private Declare PtrSafe Function SafeArrayGetDim Lib "oleAut32.dll" (ByRef saArray() As Any) As Long
    Private Declare PtrSafe Function PathFileExists Lib "shlwapi.dll" Alias "PathFileExistsW" (ByVal pszPath As LongPtr) As Long
    Private Declare PtrSafe Function CLSIDFromString Lib "ole32" (ByVal lpsz As Any, pclsid As Any) As Long
    Private Declare PtrSafe Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long
   
    'GDI+
    Private Declare PtrSafe Function GdiplusStartup Lib "gdiplus" (token As LongPtr, inputbuf As GdiplusStartupInput, Optional ByVal outputbuf As Long = 0) As Long
    Private Declare PtrSafe Function GdiplusShutdown Lib "gdiplus" (ByVal token As LongPtr) As Long
    Private Declare PtrSafe Function GdipLoadImageFromFile Lib "gdiplus" (ByVal sFileName As LongPtr, hImage As LongPtr) As Long
    Private Declare PtrSafe Function GdipDisposeImage Lib "gdiplus" (ByVal Image As LongPtr) As Long
    Private Declare PtrSafe Function GdipGetPropertyItemSize Lib "gdiplus" (ByVal hImage As LongPtr, ByVal lPropId As Long, lSize As Long) As Long
    Private Declare PtrSafe Function GdipGetPropertyItem Lib "gdiplus" (ByVal hImage As LongPtr, ByVal lPropId As Long, ByVal lPropSize As Long, uBuffer As Any) As Long
    Private Declare PtrSafe Function GdipImageGetFrameCount Lib "gdiplus.dll" (ByVal nImage As LongPtr, dimensionID As GUID, COUNT As Long) As Long
#Else
    Private Enum LongPtr
        [_]
    End Enum
    Private Declare Function IUnknown_GetWindow Lib "shlwapi" Alias "#172" (ByVal pIUnk As IUnknown, ByVal hUf As LongPtr) As Long
    Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
    Private Declare Function URLDownloadToFile Lib "urlmon" Alias "URLDownloadToFileA" (ByVal pCaller As Long, ByVal szURL As String, ByVal szFileName As String, ByVal dwReserved As Long, ByVal lpfnCB As Long) As Long
    Private Declare Function SetTimer Lib "user32.dll" (ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr, ByVal uElapse As Long, ByVal lpTimerFunc As LongPtr) As LongPtr
    Private Declare Function KillTimer Lib "user32.dll" (ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr) As Long
    Private Declare Function OleCreatePictureIndirectAut Lib "oleAut32.dll" Alias "OleCreatePictureIndirect" (PicDesc As uPicDesc, RefIID As GUID, ByVal fPictureOwnsHandle As Long, IPic As IPicture) As Long
    Private Declare Function CopyImage Lib "user32" (ByVal Handle As LongPtr, ByVal un1 As Long, ByVal n1 As Long, ByVal n2 As Long, ByVal un2 As Long) As LongPtr
    Private Declare Function GetDC Lib "user32.dll" (ByVal hwnd As LongPtr) As LongPtr
    Private Declare Function ReleaseDC Lib "user32" (ByVal hwnd As LongPtr, ByVal hDC As LongPtr) As LongPtr
    Private Declare Function CreateCompatibleDC Lib "gdi32" (ByVal hDC As LongPtr) As LongPtr
    Private Declare Function CreateCompatibleBitmap Lib "gdi32" (ByVal hDC As LongPtr, ByVal nWidth As Long, ByVal nHeight As Long) As LongPtr
    Private Declare Function SelectObject Lib "gdi32" (ByVal hDC As LongPtr, ByVal hObject As LongPtr) As LongPtr
    Private Declare Function DeleteObject Lib "gdi32" (ByVal hObject As LongPtr) As Long
    Private Declare Function DeleteDC Lib "gdi32" (ByVal hDC As LongPtr) As Long
    Private Declare Function FillRect Lib "user32" (ByVal hDC As LongPtr, lpRect As RECT, ByVal hBrush As LongPtr) As Long
    Private Declare Function CreateSolidBrush Lib "gdi32" (ByVal crColor As Long) As LongPtr
    Private Declare Function AlphaBlend Lib "msimg32.dll" (ByVal hDC As LongPtr, ByVal lInt As Long, ByVal lInt As Long, ByVal lInt As Long, ByVal lInt As Long, ByVal hDC As LongPtr, ByVal lInt As Long, ByVal lInt As Long, ByVal lInt As Long, ByVal lInt As Long, ByVal BLENDFUNCT As LongPtr) As Long
    Private Declare Function GetClientRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As RECT) As Long
    Private Declare Function TranslateColor Lib "oleAut32.dll" Alias "OleTranslateColor" (ByVal clr As OLE_COLOR, ByVal palet As LongPtr, Col As Long) As Long
    Private Declare Function SafeArrayGetDim Lib "oleAut32.dll" (ByRef saArray() As Any) As Long
    Private Declare Function PathFileExists Lib "shlwapi.dll" Alias "PathFileExistsW" (ByVal pszPath As LongPtr) As Long
    Private Declare Function CLSIDFromString Lib "ole32" (ByVal lpsz As Any, pclsid As Any) As Long
    Private Declare Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long
   
    'GDI+
    Private Declare Function GdiplusStartup Lib "gdiplus" (token As LongPtr, inputbuf As GdiplusStartupInput, Optional ByVal outputbuf As Long = 0) As Long
    Private Declare Function GdiplusShutdown Lib "gdiplus" (ByVal token As LongPtr) As Long
    Private Declare Function GdipLoadImageFromFile Lib "gdiplus" (ByVal sFileName As LongPtr, hImage As LongPtr) As Long
    Private Declare Function GdipDisposeImage Lib "gdiplus" (ByVal Image As LongPtr) As Long
    Private Declare Function GdipGetPropertyItemSize Lib "gdiplus" (ByVal hImage As LongPtr, ByVal lPropId As Long, lSize As Long) As Long
    Private Declare Function GdipGetPropertyItem Lib "gdiplus" (ByVal hImage As LongPtr, ByVal lPropId As Long, ByVal lPropSize As Long, uBuffer As Any) As Long
    Private Declare Function GdipImageGetFrameCount Lib "gdiplus.dll" (ByVal nImage As LongPtr, dimensionID As GUID, COUNT As Long) As Long
#End If


Private Type RECT
    Left   As Long
    Top    As Long
    Right  As Long
    Bottom As Long
End Type

 Private Type GUID
    Data1           As Long
    Data2           As Integer
    Data3           As Integer
    Data4(0& To 7&) As Byte
End Type

Private Type uPicDesc
    size As Long
    Type As Long
    hPic As LongPtr
    hpal As LongPtr
End Type

'GDI+
Private Type GdiplusStartupInput
    GdiplusVersion           As Long
    DebugEventCallback       As LongPtr
    SuppressBackgroundThread As LongPtr
    SuppressExternalCodecs   As Long
End Type

Private Type PropertyItem
    propId As Long
    Length As Long
    nType  As Integer
    value  As LongPtr
End Type

Private ArrFrames()    As Object
Private oParentControl As Object
Private lFrameDelay    As Long
Private bAutoSize      As Boolean
Private lWidth         As Long
Private lHeight        As Long
Private bPause         As Boolean
Private lFrameIndex    As Long




'__________________________________________ PUBLIC ROUTINES _________________________________________________

Public Function LoadGIF(ByVal FilePath As String) As Boolean
    If SafeArrayGetDim(ArrFrames) = 0& Then
        bPause = False
        ArrFrames = ExtractGifFrames(FilePath)
        If SafeArrayGetDim(ArrFrames) Then
            LoadGIF = True
        End If
    End If
End Function

Public Sub UnLoadGIF(Optional ByVal Dummy As Boolean)
    Call KillTimer(Application.hwnd, lFrameIndex)
    bPause = True
    lFrameDelay = 0&
    lWidth = 0&
    lHeight = 0&
    lFrameIndex = 0&
    bAutoSize = False
    Erase ArrFrames
End Sub

Public Sub PlayGIF( _
    ByVal ParentControl As Object, _
    Optional ByVal Frame_Delay As Long = -1, _
    Optional ByVal AutoSize As Boolean _
)

    bAutoSize = AutoSize
    Set oParentControl = ParentControl
    If Frame_Delay <> -1 Then
        lFrameDelay = Frame_Delay
    End If
    Call SetTimer(Application.hwnd, lFrameIndex, lFrameDelay, AddressOf TimerProc)
End Sub

Public Sub PauseGIF(Optional ByVal Dummy As Boolean)
    bPause = True
End Sub

Public Function GetFrameDelay() As Long
    If lFrameDelay = 0& Then
        GoTo errHandler
    End If
    GetFrameDelay = lFrameDelay
    Exit Function
errHandler:
    MsgBox "Failed to retrieve the GIF frame delay.", vbExclamation
End Function

Public Sub SetFrameDelay(ByVal Delay As Long)
    lFrameDelay = Delay
End Sub

Public Function GetFrameCount() As Long
    If SafeArrayGetDim(ArrFrames) = 0& Then
        GoTo errHandler
    End If
    GetFrameCount = UBound(ArrFrames) + 1&
    Exit Function
errHandler:
    MsgBox "Failed to retrieve Frame Count from the GIF.", vbCritical
End Function

Public Property Get GetFrameWidth() As Long
    If lWidth = 0& Then
        GoTo errHandler
    End If
    GetFrameWidth = lWidth
    Exit Property
errHandler:
    MsgBox "Failed to retrieve the frame Width.", vbExclamation
End Property

Public Property Get GetFrameHeight() As Long
    If lHeight = 0& Then
        GoTo errHandler
    End If
    GetFrameHeight = lHeight
    Exit Property
errHandler:
    MsgBox "Failed to retrieve the frame Height.", vbExclamation
End Property

Public Function FrameToStdPicture() As StdPicture
    If SafeArrayGetDim(ArrFrames) = 0& Then
        GoTo errHandler
    End If
    If ArrFrames(0&).FileData.Picture Is Nothing Then
        GoTo errHandler
    End If
    Set FrameToStdPicture = ArrFrames(0&).FileData.Picture
    Exit Function
errHandler:
    MsgBox "Failed to extract StdPicture Object from the GIF frame.", vbCritical
End Function




'__________________________________________ PRIVATE ROUTINES _________________________________________________

Private Property Let GetFrameWidth(ByVal vNewValue As Long)
    lWidth = vNewValue
End Property

Private Property Let GetFrameHeight(ByVal vNewValue As Long)
    lHeight = vNewValue
End Property

Private Sub TimerProc( _
    ByVal hwnd As LongPtr, _
    ByVal Msg As Long, _
    ByVal idEvent As Long, _
    ByVal dwTime As Long _
)

    Const SM_CYCAPTION = 4&
    Dim hParent As LongPtr, hDC As LongPtr
    Dim hMemSrcDC As LongPtr, lPrevSrcBmp As LongPtr
    Dim hMemDstDC As LongPtr, lPrevDstBmp As LongPtr
    Dim hMemBmp As LongPtr, hBrush As LongPtr
    Dim lFrameWidth As Long, lFrameHeight As Long
    Dim lParentWidth As Long, lParentHeight As Long
    Dim i As Long, lColor As Long
    Dim X As Long, Y As Long
    Dim oStdPic As Object
    Dim tRect As RECT
    Dim sTmpFilePath As String

    lFrameIndex = idEvent
    Call KillTimer(Application.hwnd, lFrameIndex)
   
    If bPause Then
       bPause = False
       Exit Sub
    End If

    If TypeOf oParentControl Is MSForms.Label Then
     Set oParentControl.Picture = ArrFrames(lFrameIndex).FileData.Picture
     GoTo NextFrame
    End If

    Call IUnknown_GetWindow(oParentControl, VarPtr(hParent))
    hDC = GetDC(hParent)
    Call GetClientRect(hParent, tRect)
    lParentWidth = tRect.Right
    lParentHeight = tRect.Bottom - GetSystemMetrics(SM_CYCAPTION)
    lFrameWidth = ArrFrames(lFrameIndex).Width
    lFrameHeight = ArrFrames(lFrameIndex).Height

    hMemSrcDC = CreateCompatibleDC(NULL_PTR)
    hMemDstDC = CreateCompatibleDC(NULL_PTR)
    hMemBmp = CreateCompatibleBitmap(hDC, lParentWidth, lParentHeight)
    lPrevDstBmp = SelectObject(hMemDstDC, hMemBmp)
    Call TranslateColor(oParentControl.BackColor, NULL_PTR, lColor)
    hBrush = CreateSolidBrush(lColor)
    Call FillRect(hMemDstDC, tRect, hBrush)
    lPrevSrcBmp = SelectObject(hMemSrcDC, ArrFrames(lFrameIndex).FileData.Picture.Handle)
 
    If bAutoSize = False Then
       X = (lParentWidth - lFrameWidth) / 2&
       Y = (lParentHeight - lFrameHeight) / 2&
       lParentWidth = lFrameWidth - 1&
       lParentHeight = lFrameHeight - 1&
    End If
   
    Call AlphaBlend( _
        hMemDstDC, _
        X, _
        Y, _
        lParentWidth, _
        lParentHeight, _
        hMemSrcDC, _
        0&, _
        0&, _
        lFrameWidth, _
        lFrameHeight, _
        &H1000000 + 255& * &H10000 _
        )

    Set oStdPic = BmpToStdPic(hMemBmp)
   
    If Not oStdPic Is Nothing Then
        oParentControl.Picture = oStdPic
    End If
    If hMemSrcDC Then
        Call SelectObject(hMemSrcDC, lPrevSrcBmp)
        Call DeleteDC(hMemSrcDC)
    End If
    If hMemDstDC Then
        Call SelectObject(hMemDstDC, lPrevDstBmp)
        Call DeleteDC(hMemDstDC)
    End If
    If hMemBmp Then
        Call DeleteObject(hMemBmp)
    End If
    If hBrush Then
        Call DeleteObject(hBrush)
    End If
    If hDC Then
        Call ReleaseDC(hParent, hDC)
    End If
   
    If oStdPic Is Nothing Then
        MsgBox "Failed to make Memory Bitmap.", vbCritical
        Call UnLoadGIF
        Exit Sub
    End If

NextFrame:

    lFrameIndex = lFrameIndex + 1&
    If lFrameIndex >= GetFrameCount Then
        lFrameIndex = 0&
    End If

    Call SetTimer(Application.hwnd, lFrameIndex, lFrameDelay, AddressOf TimerProc)

End Sub

Private Function GetGifFrameDelay(ByVal sFileName As String) As Long

    'GDI+ Routine: Adapted and modified from:
    '===========================
    'http://en.verysource.com/code/34260231_1/cGDIpMultiImage.cls.html#:~:text=Private%C2%A0Sub%C2%A0pvExtractFrameDelays,End%C2%A0Sub
    '==============================

    Const FrameDimensionTime = "{6AEDBD6D-3FB5-418A-83A6-7F45229DC872}"
    Const PropertyTagFrameDelay = &H5100
    Const PropertyTagTypeLong = 4&
    Const S_OK = 0&

    Dim pImage         As LongPtr
    Dim lFrameDelays() As Long
    Dim lCount         As Long
    Dim lPropSize      As Long
    Dim tPropItem      As PropertyItem
    Dim tGUID          As GUID
       
    If InitializesGDIPlus(True) = False Then
        GoTo Xit
    End If
    If GdipLoadImageFromFile(StrPtr(sFileName), pImage) <> S_OK Then
        GoTo Xit
    End If
    Call CLSIDFromString(StrPtr(FrameDimensionTime), tGUID)
    Call GdipImageGetFrameCount(pImage, tGUID, lCount)
    If pImage Then
        ReDim lFrameDelays(0& To lCount)
        If GdipGetPropertyItemSize(pImage, PropertyTagFrameDelay, lPropSize) <> S_OK Then
            GoTo Xit
        End If
        ReDim bPropData(0& To lPropSize - 1&)
        If GdipGetPropertyItem(pImage, PropertyTagFrameDelay, lPropSize, bPropData(0&)) <> S_OK Then
            GoTo Xit
        End If
        Call CopyMemory(tPropItem, bPropData(0&), LenB(tPropItem))
        If tPropItem.nType = PropertyTagTypeLong Then
            If tPropItem.Length = lCount * PropertyTagTypeLong Then
                Call CopyMemory(lFrameDelays(0&), ByVal tPropItem.value, tPropItem.Length)
                lFrameDelays(0&) = ((lFrameDelays(0&) And &HFFFF&) * 10&)
                If lFrameDelays(0&) Then
                    GetGifFrameDelay = lFrameDelays(0&)
                    GoTo Xit
                End If
            End If
        End If
    End If

Xit:
    Call GdipDisposeImage(pImage)
    Call InitializesGDIPlus(False)

End Function

Private Function ExtractGifFrames(ByVal FilePath As String) As Object()

    Const wiaFormatPNG = "{B96B3CAF-0728-11D3-9D7B-0000F81EF32E}"
    Const S_OK = 0&
   
    Dim oGIF         As Object 'WIA.ImageFile
    Dim oFrames()    As Object 'WIA.ImageFile
    Dim oFrame       As Object 'WIA.ImageFile
    Dim oProcessPNG  As Object 'WIA.ImageProcess
    Dim sTmpFilePath As String
    Dim i            As Long

    If PathFileExists(StrPtr(FilePath)) = 0& Then
        sTmpFilePath = Environ("tmp") & "\" & "tmp.gif"
        If URLDownloadToFile(0&, FilePath, sTmpFilePath, 0&, 0&) <> S_OK Then
            MsgBox "Invalid GIF file path.", vbCritical
            Exit Function
        End If
    Else
        sTmpFilePath = FilePath
    End If

    lFrameDelay = GetGifFrameDelay(sTmpFilePath)

    Set oProcessPNG = CreateObject("WIA.ImageProcess")
    With oProcessPNG
        .Filters.Add .FilterInfos("ARGB").FilterID
        .Filters.Add .FilterInfos("Convert").FilterID
        .Filters(2&).Properties("FormatID").value = wiaFormatPNG
    End With
    Set oGIF = CreateObject("WIA.ImageFile")
    With oGIF
        .LoadFile sTmpFilePath
        If .IsAnimated Then
            GetFrameWidth = .Width
            GetFrameHeight = .Height
            For i = 0& To .FrameCount - 1&
                oProcessPNG.Filters(1&).Properties("ARGBData").value = .ARGBData
                Set oFrame = oProcessPNG.Apply(.ARGBData.ImageFile(.Width, .Height))
                ReDim Preserve oFrames(i)
                Set oFrames(i) = oFrame
                .ActiveFrame = .ActiveFrame Mod .FrameCount + 1&
            Next i
        End If
        ExtractGifFrames = oFrames
    End With

End Function

Private Function BmpToStdPic(ByVal hBmp As LongPtr) As IPicture

    Const IMAGE_BITMAP = 0&: Const PICTYPE_BITMAP = 1&: Const LR_COPYRETURNORG = &H4
    Dim hPtr As LongPtr, IID_IDispatch As GUID, uPicinfo As uPicDesc

    hPtr = CopyImage(hBmp, IMAGE_BITMAP, 0&, 0&, LR_COPYRETURNORG)

    With IID_IDispatch
        .Data1 = &H20400
        .Data4(0) = &HC0
        .Data4(7) = &H46
    End With
    With uPicinfo
        .size = LenB(uPicinfo)
        .Type = PICTYPE_BITMAP
        .hPic = hPtr
        .hpal = NULL_PTR
    End With

   Call OleCreatePictureIndirectAut(uPicinfo, IID_IDispatch, True, BmpToStdPic)
   
End Function

Private Function InitializesGDIPlus(ByVal Init As Boolean) As Boolean
    Const S_OK = 0&
    Static lGDIP As LongPtr
    Dim tSI As GdiplusStartupInput
    Dim lRet As Long
 
    If Init Then
        tSI.GdiplusVersion = 1&
        lRet = GdiplusStartup(lGDIP, tSI)
        If lRet = S_OK Then InitializesGDIPlus = True
    Else
        If lGDIP Then
            Call GdiplusShutdown(lGDIP)
            lGDIP = NULL_PTR
        End If
    End If
End Function


2- UserForm Module:
VBA Code:
Option Explicit

Private Sub UserForm_Initialize()
    Spin_Delay.Max = 999&
    Spin_Delay.Min = 0&
    Buntton1_PlayGIF.Enabled = False
    Button1_PauseGIF.Enabled = False
    Buntton2_PlayGIF.Enabled = False
    Button2_PauseGIF.Enabled = False
    Button_UnLoadGIF.Enabled = False
End Sub

Private Sub UserForm_Terminate()
    Call UnLoadGIF
End Sub

Private Sub Button_LoadGIF_Click()
    Label_ExtractingFrames = "Wait -   Extracting GIF Frames ..."
    DoEvents
    If LoadGIF(Me.TextBox_Path.Text) Then
        TextBox_Delay = GetFrameDelay
        Set Frame1.Picture = FrameToStdPicture
        Label_FrameCountVal = GetFrameCount
        Label_WidthVal = GetFrameWidth
        Label_HeightVal = GetFrameHeight
        Buntton1_PlayGIF.Enabled = True
        Buntton2_PlayGIF.Enabled = True
        Button_UnLoadGIF.Enabled = True
    End If
    Label_ExtractingFrames = ""
End Sub

Private Sub Button_UnLoadGIF_Click()
    Call PauseGIF
    Call UnLoadGIF
    Button1_PauseGIF.Enabled = False
    Buntton1_PlayGIF.Enabled = False
    Button2_PauseGIF.Enabled = False
    Buntton2_PlayGIF.Enabled = False
    Spin_Delay.value = 0&
    TextBox_Delay.Text = ""
    Label_FrameCountVal = ""
    Label_WidthVal = ""
    Label_HeightVal = ""
    Set Frame1.Picture = Nothing
    Set Frame2.Picture = Nothing
    Set Label1.Picture = Nothing
End Sub

Private Sub Buntton1_PlayGIF_Click()
    Button1_PauseGIF.Enabled = True
    Buntton1_PlayGIF.Enabled = False
    Buntton2_PlayGIF.Enabled = False
    Button2_PauseGIF.Enabled = False
    Call PlayGIF(Me.Frame2)
End Sub

Private Sub Button1_PauseGIF_Click()
    Button1_PauseGIF.Enabled = False
    Buntton1_PlayGIF.Enabled = True
    Buntton2_PlayGIF.Enabled = True
    Button2_PauseGIF.Enabled = False
    Call PauseGIF
End Sub

Private Sub Buntton2_PlayGIF_Click()
    Buntton1_PlayGIF.Enabled = False
    Buntton2_PlayGIF.Enabled = False
    Button2_PauseGIF.Enabled = True
    Call PlayGIF(Me.Label1)  ', 10, True
End Sub

Private Sub Button2_PauseGIF_Click()
    Button2_PauseGIF.Enabled = False
    Buntton2_PlayGIF.Enabled = True
    Buntton1_PlayGIF.Enabled = True
    Call PauseGIF
End Sub

Private Sub TextBox_Delay_Change()
    Spin_Delay.value = Val(TextBox_Delay.value)
End Sub

Private Sub TextBox_Delay_KeyPress(ByVal KeyAscii As MSForms.ReturnInteger)
    If Chr(KeyAscii) Like "[!0-9]" Or TextBox_Delay.SelStart >= 3& Then
        KeyAscii = 0&: Exit Sub
    End If
End Sub

Private Sub Spin_Delay_Change()
    TextBox_Delay = Spin_Delay.value
    Call SetFrameDelay(TextBox_Delay)
End Sub
 
Upvote 1
Regretfully it does not function here. Running : Win 10 / 64 bit - Office 2007 / 32 bit
 
Upvote 0
Tested and works on my side. Will definitely use. Did experience issue where Giphy is blocked from running by company but workaround is I download the gif and save to a location in a folder on my PC. :cool: 🍻
 
Upvote 0
Ok .... managed to download an animated gif. Here is the code line I am using ... what am I doing wrong ?

Code:
Option Explicit

Sub Test()

    AnimatedMsgBox "Hello!", vbInformation, "Animated Gif Demo.", "C:\Users\jimga\Desktop\giphy.gif"

End Sub
 
Upvote 0
@Jaafar,

You're incredible!!!
Fantastic job !!! Amazing!!!

Tested on Win 10/64 Microsoft 365/32 and 365/64 Bit. Work excellent.
 
Upvote 0
Ok .... managed to download an animated gif. Here is the code line I am using ... what am I doing wrong ?

Code:
Option Explicit

Sub Test()

    AnimatedMsgBox "Hello!", vbInformation, "Animated Gif Demo.", "C:\Users\jimga\Desktop\giphy.gif"

End Sub
Not sure... Maybe Jafaar can assist you...
 
Upvote 0
Ok .... managed to download an animated gif. Here is the code line I am using ... what am I doing wrong ?
@Logit

I could reproduce the issue in xl2007 Win7 x32bit. I suspect the culprit is the gif window beigng a child window (WS_CHILD style) of the MsgBox host.

I will revise the code and let you know... Thanks for testing and letting us know about the problem.
 
Upvote 0

Forum statistics

Threads
1,215,352
Messages
6,124,449
Members
449,160
Latest member
nikijon

We've detected that you are using an adblocker.

We have a great community of people providing Excel help here, but the hosting costs are enormous. You can help keep this site running by allowing ads on MrExcel.com.
Allow Ads at MrExcel

Which adblocker are you using?

Disable AdBlock

Follow these easy steps to disable AdBlock

1)Click on the icon in the browser’s toolbar.
2)Click on the icon in the browser’s toolbar.
2)Click on the "Pause on this site" option.
Go back

Disable AdBlock Plus

Follow these easy steps to disable AdBlock Plus

1)Click on the icon in the browser’s toolbar.
2)Click on the toggle to disable it for "mrexcel.com".
Go back

Disable uBlock Origin

Follow these easy steps to disable uBlock Origin

1)Click on the icon in the browser’s toolbar.
2)Click on the "Power" button.
3)Click on the "Refresh" button.
Go back

Disable uBlock

Follow these easy steps to disable uBlock

1)Click on the icon in the browser’s toolbar.
2)Click on the "Power" button.
3)Click on the "Refresh" button.
Go back
Back
Top