Analog Clock displayed over worksheet made purely with APIs !

Jaafar Tribak

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

I've been experimenting with some GDI APIs to create an analog clock and this is what i've come up with so far. - Not exactly a very useful thing but was interesting to code and it is an alternative to the known clock made of an XY chart.

Tested on one PC only running WIN XP Excel 2003 SP3. I hope it works on different machines too.

See here a WorkBook Demo.

In a Standard Module :

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 LOGFONT
    lfHeight As Long
    lfWidth As Long
    lfEscapement As Long
    lfOrientation As Long
    lfWeight As Long
    lfItalic As String * 1
    lfUnderline As String * 1
    lfStrikeOut As String * 1
    lfCharSet As String * 1
    lfOutPrecision As String * 1
    lfClipPrecision As String * 1
    lfQuality As String * 1
    lfPitchAndFamily As String * 1
    lfFaceName As String * 32
End Type
 
 
Private Declare Function GetDC Lib "user32.dll" _
(ByVal hwnd As Long) As Long
 
Private Declare Function GetDeviceCaps Lib "gdi32.dll" _
(ByVal hdc As Long, _
ByVal nIndex As Long) As Long
  
Private Declare Function ReleaseDC Lib "user32" _
(ByVal hwnd As Long, _
ByVal hdc As Long) As Long
 
Private Declare Function SetPixel Lib "gdi32" _
(ByVal hdc As Long, _
ByVal x As Long, _
ByVal Y As Long, _
ByVal crColor As Long) As Long
 
Private Declare Function InvalidateRect _
Lib "user32" (ByVal hwnd As Long, _
lpRect As Long, _
ByVal bErase As Long) As Long
 
Private Declare Function DrawText Lib "user32" _
Alias "DrawTextA" _
(ByVal hdc As Long, _
ByVal lpStr As String, _
ByVal nCount As Long, _
lpRect As RECT, _
ByVal wFormat As Long) As Long
 
Private Declare Function SetRect Lib "user32" _
(lpRect As RECT, _
ByVal X1 As Long, _
ByVal Y1 As Long, _
ByVal X2 As Long, _
ByVal Y2 As Long) As Long
 
Private Declare Function CreateFontIndirect Lib "gdi32" _
Alias "CreateFontIndirectA" _
(lpLogFont As LOGFONT) As Long
 
Private Declare Function SetBkMode Lib "gdi32" _
(ByVal hdc As Long, _
ByVal nBkMode As Long) As Long
 
Private Declare Function LineTo Lib "gdi32" _
(ByVal hdc As Long, _
ByVal x As Long, _
ByVal Y As Long) As Long
 
Private Declare Function MoveToEx Lib "gdi32" _
(ByVal hdc As Long, _
ByVal x As Long, _
ByVal Y As Long, _
lpPoint As POINTAPI) As Long
 
Private Declare Function SelectObject Lib "gdi32" _
(ByVal hdc As Long, _
ByVal hObject As Long) As Long
 
Private Declare Function CreatePen Lib "gdi32" _
(ByVal nPenStyle As Long, _
ByVal nWidth As Long, _
ByVal crColor As Long) As Long
 
Private Declare Function DeleteObject Lib "gdi32" _
(ByVal hObject As Long) As Long
 
Private Declare Function CreateEllipticRgn Lib "gdi32" _
(ByVal X1 As Long, _
ByVal Y1 As Long, _
ByVal X2 As Long, _
ByVal Y2 As Long) As Long
 
Private Declare Function RedrawWindow Lib "user32" _
(ByVal hwnd As Long, _
ByVal lprcUpdate As Long, _
ByVal hrgnUpdate As Long, _
ByVal fuRedraw As Long) As Long
 
Private Declare Function GetForegroundWindow Lib "user32" () As Long
 
Private Declare Function FindWindow Lib "user32.dll" _
Alias "FindWindowA" _
(ByVal lpClassName As String, _
ByVal lpWindowName As String) As Long
 
Private Declare Function SetTimer Lib "user32.dll" _
(ByVal hwnd As Long, _
ByVal nIDEvent As Long, _
ByVal uElapse As Long, _
ByVal lpTimerFunc As Long) As Long
 
Private Declare Function KillTimer Lib "user32.dll" _
(ByVal hwnd As Long, _
ByVal nIDEvent As Long) As Long

Private Const LOGPIXELSX        As Long = 88
Private Const LOGPIXELSY        As Long = 90
Private Const PointsPerInch     As Long = 72
Private Const PI                As Single = 3.14159265358979
Private Const Rads              As Single = PI / 180
 
Private Const RDW_INVALIDATE = &H1
Private Const RDW_ALLCHILDREN = &H80
 
Private Const PS_SOLID = 0
Private Const DT_CENTER = &H1
 
Private tp As POINTAPI
Private tR As RECT
Private oUpperLeftCell As Range
Private lTimerID As Long
Private X1 As Long, Y1 As Long
Private lDC  As Long
Private lRadius1 As Long, lRadius2 As Long
Private lRadius3 As Long, lRadius4 As Long
 
Sub Test()
    
    [COLOR=seagreen]'display the analog clock @ the
    'current screen location of cell 'D10' .
[/COLOR]    
    ShowClock TargetCell:=Range("D10")
 
End Sub

Sub StopClock()
 
    KillTimer 0, lTimerID
    lTimerID = 0
 
End Sub
 
Sub HideClock()
 
    InvalidateRect 0, 0, 0
    KillTimer 0, lTimerID
    lTimerID = 0
 
End Sub
 

[COLOR=seagreen]'=======================
'Main code              '
'=======================[/COLOR]
Private Sub ShowClock(TargetCell As Range)
 
    If lTimerID = 0 Then
        Set oUpperLeftCell = ActiveWindow.VisibleRange.Cells(1, 1)
        If Union(TargetCell, ActiveWindow.VisibleRange).Address _
        <> ActiveWindow.VisibleRange.Address Then
            GoTo errHandler:
        End If
        tp = GetRangeCenterPointInPixels(TargetCell)
        lTimerID = SetTimer(0, 0, 1000, AddressOf RunClock)
    End If
    Exit Sub
errHandler:
    MsgBox "Target Cell not visible.", vbCritical
 
End Sub
 
Private Sub RunClock()
                         
    On Error Resume Next
    
    If GetForegroundWindow = _
    FindWindow("XLMAIN", Application.Caption) Then
        If ActiveWindow.VisibleRange.Cells(1, 1).Address _
        <> oUpperLeftCell.Address Then
            InvalidateRect 0, 0, 0
            DoEvents
        End If
        Call CreateClock
        Call UpdateClock
    End If
 
End Sub
 
Private Sub CreateClock()
    
    Dim i As Long
    Dim lAngle As Long
    Dim X2 As Long, Y2 As Long
    Dim A2 As Long, B2 As Long
    
    X1 = tp.x
    Y1 = tp.Y
    
    lRadius1 = 60
    lRadius2 = lRadius1 * 80 / 100
    lDC = GetDC(0)
    SetBkMode lDC, 1
    Call CreateFont(lDC, True)
    For lAngle = 0 To 359
    
        For i = 7 To 10
        
            X2 = (lRadius1 + i) * (Sin(lAngle * Rads))
            Y2 = (lRadius1 + i) * (Cos(lAngle * Rads))
            SetPixel lDC, X2 + X1, Y2 + Y1, vbRed
        
        Next i
        
        X2 = (lRadius1) * (Sin(lAngle * Rads))
        Y2 = (lRadius1) * (Cos(lAngle * Rads))
        SetPixel lDC, X2 + X1, Y2 + Y1, vbRed
        A2 = lRadius2 * (Sin(lAngle * Rads))
        B2 = lRadius2 * (Cos(lAngle * Rads))
        SetRect tR, (A2 + X1) - 5, B2 + Y1 - 5, _
        A2 + X1 + 5, B2 + Y1 + 5
        Select Case lAngle
    
            Case Is = 0
                DrawText lDC, "6", 1, tR, DT_CENTER
            Case Is = 30
                DrawText lDC, "5", 1, tR, DT_CENTER
            Case Is = 60
                DrawText lDC, "4", 1, tR, DT_CENTER
            Case Is = 90
                DrawText lDC, "3", 1, tR, DT_CENTER
            Case Is = 120
                DrawText lDC, "2", 1, tR, DT_CENTER
            Case Is = 150
                DrawText lDC, "1", 1, tR, DT_CENTER
            Case Is = 180
                DrawText lDC, "12", 2, tR, DT_CENTER
            Case Is = 210
                DrawText lDC, "11", 2, tR, DT_CENTER
            Case Is = 240
                DrawText lDC, "10", 2, tR, DT_CENTER
            Case Is = 270
                DrawText lDC, "9", 1, tR, DT_CENTER
            Case Is = 300
                DrawText lDC, "8", 1, tR, DT_CENTER
            Case Is = 330
                DrawText lDC, "7", 1, tR, DT_CENTER
        
        End Select
    
    Next lAngle

End Sub

Private Sub UpdateClock()
 
    Dim tPt As POINTAPI
    Dim lhRng As Long
    Dim lhRPen As Long
    Dim lSecond As Single
    Dim lMinute As Single
    Dim lHour As Single
    
    lRadius3 = lRadius1 * 70 / 100
    lRadius4 = lRadius1 * 80 / 100
    
    
    lhRng = CreateEllipticRgn _
    (X1 - lRadius3, Y1 - lRadius3, X1 + lRadius3, Y1 + lRadius3)
    
    RedrawWindow 0, 0, lhRng, RDW_INVALIDATE + RDW_ALLCHILDREN
    
    DoEvents
    
    [COLOR=seagreen]'Seconds.
[/COLOR]    MoveToEx lDC, X1, Y1, tPt
    lhRPen = CreatePen(PS_SOLID, 1, vbRed)
    
    DeleteObject SelectObject(lDC, lhRPen)
    
    lSecond = Second(Time) * (2 * PI / 60)
    LineTo lDC, X1 + ((lRadius3) * 0.85 * Sin(lSecond)), _
    Y1 - ((lRadius3) * 0.85 * Cos(lSecond))
    
    [COLOR=seagreen]'Minutes.
[/COLOR]    MoveToEx lDC, X1, Y1, tPt
    
    lhRPen = CreatePen(PS_SOLID, 2, vbRed)
    
    DeleteObject SelectObject(lDC, lhRPen)
    
    lMinute = (Minute(Time) + (Second(Time) / 60)) * (2 * PI / 60)
    LineTo lDC, X1 + (lRadius3) * Sin(lMinute) * 0.8, _
    Y1 - (lRadius3) * Cos(lMinute) * 0.8
    
    [COLOR=seagreen]'Hours.[/COLOR]
    MoveToEx lDC, X1, Y1, tPt
    
    lhRPen = CreatePen(PS_SOLID, 4, vbBlack)
    
    DeleteObject SelectObject(lDC, lhRPen)
    
    lHour = (Hour(Time) + (Minute(Time) / 60)) * (2 * PI / 12)
    LineTo lDC, X1 + (lRadius4) * Sin(lHour) * 0.5, _
    Y1 - (lRadius4) * Cos(lHour) * 0.5
    
    Set oUpperLeftCell = ActiveWindow.VisibleRange.Cells(1, 1)
    
    ReleaseDC 0, lDC
 
End Sub
 
Private Function GetRangeCenterPointInPixels(rng As Range) As POINTAPI
 
    Dim CenterX, CenterY As Double
    Dim lDC As Long
 
    On Error Resume Next
    lDC = GetDC(0)
    CenterX = rng.Left + (rng.Width / 2)
    CenterY = rng.Top + (rng.Height / 2)
 
    With GetRangeCenterPointInPixels
        .x = ActiveWindow.PointsToScreenPixelsX((CenterX) * _
        (GetDeviceCaps _
        (lDC, LOGPIXELSX) / PointsPerInch * ActiveWindow.Zoom / 100))
        .Y = ActiveWindow.PointsToScreenPixelsY((CenterY) * _
        (GetDeviceCaps _
        (lDC, LOGPIXELSY) / PointsPerInch * ActiveWindow.Zoom / 100))
    End With
 
    ReleaseDC 0, lDC
 
End Function

Private Sub CreateFont(DC As Long, Optional Bold As Boolean)
 
    Dim uFont As LOGFONT
    Dim lNewFont As Long
 
    With uFont
        .lfFaceName = "Tahoma" & Chr$(0)
        .lfHeight = 12
        .lfWidth = 5
        .lfWeight = IIf(Bold, 900, 100)
        
    End With
 
    lNewFont = CreateFontIndirect(uFont)
    DeleteObject (SelectObject(DC, lNewFont))
 
End Sub

As a variation to the above, I guess placing the clock inside a modeless userform would be more practical.

Regards.
 
Thanks xanksx and OfficeUser for the feedback . I am glad it works accross different Win platforms .
 
Upvote 0

Excel Facts

Select a hidden cell
Somehide hide payroll data in column G? Press F5. Type G1. Enter. Look in formula bar while you arrow down through G.
Dear Mr.Jaafar Tribak.
Please help me to put the clock to Frame on that User Form.
Hi cuongeva

Welcome to the forum.

This is a very old code so it needs lots of updating (including code bitness compatibility for x64). Furthermore, the code is buggy and was meant to display the analog clock on the worksheet not on a userform.

I will try to update it later on so that it works on userforms. Plus I will see if I can make it more robust.

Regards.
 
Upvote 0
Hi cuongeva

Welcome to the forum.

This is a very old code so it needs lots of updating (including code bitness compatibility for x64). Furthermore, the code is buggy and was meant to display the analog clock on the worksheet not on a userform.

I will try to update it later on so that it works on userforms. Plus I will see if I can make it more robust.

Regards.
Thank so much for your reply.
I am trying it with the Widows10/ 64 bits and Microsorf Office 2016/64 bits system, and it works very well. So now I need it can work with frame or label on Userform.
 
Upvote 0
Hi cuongeva

Welcome to the forum.

This is a very old code so it needs lots of updating (including code bitness compatibility for x64). Furthermore, the code is buggy and was meant to display the analog clock on the worksheet not on a userform.

I will try to update it later on so that it works on userforms. Plus I will see if I can make it more robust.

Regards.
Thank so much for your reply.
I am trying it with the Widows10/ 64 bits and Microsorf Office 2016/64 bits system, and it works very well. So now I need it can work with frame or label on Userform.
 
Upvote 0
Every time I stumble across one of your demo workbooks using APIs, Jaafar, I think to myself - "This has to be the last one. By now, I must've come across all the demo workbooks JT's uploaded onto MrExcel.com" and then I add it to my (growing) list of things to study... only to then I learn that there is yet another workbook demonstrating some awesome technique, etc ... :)

This one is no different - it's great (your comment about needing to update it is noted). I started to look at it but it's very mathy (not my strongest area...) so my eyes start to glaze over after a while. I learnt a few things here - (1) that you can make a modal UF modeless by hiding it and showing it again (?), and (2) seeing the DC of a reshaped UF being painted on - it never really occurred to me to do that.

The one thing I tried to tinker with was to try replacing the API method used to move/drag the UserForm with the UserForm move method (because I have a theory re: the move method and GDI/GDI+ on the userform DC), but am encountering problems doing so from a class module. I think my brain is still in holiday mode, so will take another crack at it later (I feel I should know the solution to it), but in any event, will keep an eye out to see whatever updates you may end up making to this.
 
Upvote 0
Hi Dan_W

Glad you liked this little vba project .

I am almost done with the new code for displaying the analog clock on a UserForm\Frame... So far, looks good... In particular, because I am now using the GDIPlus library for drawing smoother lines.

As per cuongeva's request, I am not hiding the userform container at this stage in this new code. Maybe, I will leave that for the next update.

I will post what I have today.

Regards.
 
Upvote 0
Hi Dan_W

Glad you liked this little vba project .

I am almost done with the new code for displaying the analog clock on a UserForm\Frame... So far, looks good... In particular, because I am now using the GDIPlus library for drawing smoother lines.

As per cuongeva's request, I am not hiding the userform container at this stage in this new code. Maybe, I will leave that for the next update.

I will post what I have today.

Regards.

Dear Mr. Jaafar Tribak
Thank you very much for your enthusiasm.
That project is great.
We hope you post it as soon.
 
Upvote 0
Ok, here is what I have come up with:

VBA_Form_AnalogClock 32x64.xls

Basically, the CreateClock routine allows the vba user to display the analog clock either directly onto the userform or inside a userform frame.

A- In the case of a userform:
The user must provide the radius value of the clock circle outline (Second parameter in pixel units) . The form adjusts itself automatically to engulf the entire clock.
B- In the case of a frame:
It is the user resposability to ensure the frame is an exact square. The Radius parameter is not taken into consideration so it can be simply ignored.

The CreateClock routine has 14 parameters in total in order to offer the users the felxibly to format the clock components (such as the Hour fonts, the clock arrows colors, the clock outline ...etc) as they wish. The clock however, doesn't have its own background color. The background color is that of its form\frame container.

Also, I have included the bytes of a small wav file in the code (≈ 2.7 kb) for portability. The wav sound is built in memory on the fly so that the clock can play a tick-tock sound. This is the last boolean parameter and it is optional.







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

#If Win64 Then
    Const NULL_PTR = 0^
#Else
    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 Function GetDC Lib "user32.dll" (ByVal hwnd As LongPtr) As LongPtr
    Private Declare PtrSafe Function GetDeviceCaps Lib "gdi32.dll" (ByVal hDC As LongPtr, ByVal nIndex As Long) As Long
    Private Declare PtrSafe Function ReleaseDC Lib "user32" (ByVal hwnd As LongPtr, ByVal hDC As LongPtr) As LongPtr
    Private Declare PtrSafe Function SetPixel Lib "gdi32" (ByVal hDC As LongPtr, ByVal x As Long, ByVal y As Long, ByVal crColor As Long) As Long
    Private Declare PtrSafe Function DrawText Lib "user32" Alias "DrawTextA" (ByVal hDC As LongPtr, ByVal lpStr As String, ByVal nCount As Long, lpRect As RECT, ByVal wFormat As Long) As Long
    Private Declare PtrSafe Function SetRect Lib "user32" (lpRect As RECT, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
    Private Declare PtrSafe Function SetBkMode Lib "gdi32" (ByVal hDC As LongPtr, ByVal nBkMode As Long) As Long
    Private Declare PtrSafe Function MoveToEx Lib "gdi32" (ByVal hDC As LongPtr, ByVal x As Long, ByVal y As Long, lpPoint As POINTAPI) As Long
    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 CreateEllipticRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As LongPtr
    Private Declare PtrSafe Function CreateRectRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As LongPtr
    Private Declare PtrSafe Function CombineRgn Lib "gdi32" (ByVal hDestRgn As LongPtr, ByVal hSrcRgn1 As LongPtr, ByVal hSrcRgn2 As LongPtr, ByVal nCombineMode 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 CreateFont Lib "gdi32" Alias "CreateFontA" (ByVal h As Long, ByVal w As Long, ByVal E As Long, ByVal O As Long, ByVal w As Long, ByVal i As Long, ByVal u As Long, ByVal S As Long, ByVal C As Long, ByVal OP As Long, ByVal CP As Long, ByVal Q As Long, ByVal PAF As Long, ByVal f As String) As LongPtr
    Private Declare PtrSafe Function MulDiv Lib "kernel32" (ByVal nNumber As Long, ByVal nNumerator As Long, ByVal nDenominator As Long) As Long
    Private Declare PtrSafe Function GetClientRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As RECT) As Long
    Private Declare PtrSafe Function GetWindowRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As RECT) As Long
    Private Declare PtrSafe Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long
    Private Declare PtrSafe Function SetTextColor Lib "gdi32" (ByVal hDC As LongPtr, ByVal crColor As Long) As Long
    Private Declare PtrSafe Function AdjustWindowRect Lib "user32" (lpRect As RECT, ByVal dwStyle As Long, ByVal bMenu As Long) As Long
    Private Declare PtrSafe Function BeginDeferWindowPos Lib "user32" (ByVal nNumWindows As Long) As LongPtr
    Private Declare PtrSafe Function DeferWindowPos Lib "user32" (ByVal hWinPosInfo As LongPtr, ByVal hwnd As LongPtr, ByVal hWndInsertAfter As LongPtr, ByVal x As Long, ByVal y As Long, ByVal cx As Long, ByVal cy As Long, ByVal wFlags As Long) As LongPtr
    Private Declare PtrSafe Function EndDeferWindowPos Lib "user32" (ByVal hWinPosInfo As LongPtr) As Long
    Private Declare PtrSafe Function SetWindowPos Lib "user32" (ByVal hwnd As LongPtr, ByVal hWndInsertAfter As LongPtr, ByVal x As Long, ByVal y As Long, ByVal cx As Long, ByVal cy As Long, ByVal wFlags As Long) As Long
    Private Declare PtrSafe Function InvalidateRgn Lib "user32" (ByVal hwnd As LongPtr, ByVal hRgn As LongPtr, ByVal bErase As Long) As Long
    Private Declare PtrSafe Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
    Private Declare PtrSafe Function GetObjectAPI Lib "gdi32" Alias "GetObjectA" (ByVal hObject As LongPtr, ByVal nCount As Long, lpObject As Any) 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 AccessibleObjectFromPoint Lib "oleacc" (ByVal arg1 As LongPtr, ppacc As Any, pvarChild As Variant) As Long
    Private Declare PtrSafe Function GetCursorPos Lib "user32.dll" (lpPoint As POINTAPI) As Long
 
    'GDIPlus
    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 GdipCreatePen1 Lib "gdiplus" (ByVal color As Long, ByVal Width As Single, ByVal unit As Long, pen As LongPtr) As Long
    Private Declare PtrSafe Function GdipDeletePen Lib "gdiplus" (ByVal pen As LongPtr) As Long
    Private Declare PtrSafe Function GdipDrawLine Lib "gdiplus" (ByVal graphics As LongPtr, ByVal pen As LongPtr, ByVal X1 As Single, ByVal Y1 As Single, ByVal X2 As Single, ByVal Y2 As Single) As Long
    Private Declare PtrSafe Function GdipCreateFromHDC Lib "gdiplus" (ByVal hDC As LongPtr, hGraphics As LongPtr) As Long
    Private Declare PtrSafe Function GdipSetSmoothingMode Lib "gdiplus" (ByVal graphics As LongPtr, ByVal SmoothingMd As Long) As Long
    Private Declare PtrSafe Function GdipSetPenDashStyle Lib "gdiplus" (ByVal pen As LongPtr, ByVal dStyle As Long) As Long
    Private Declare PtrSafe Function GdipDeleteGraphics Lib "GdiPlus.dll" (ByVal mGraphics As LongPtr) As Long
    Private Declare PtrSafe Function GetSysColor Lib "user32.dll" (ByVal nIndex 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 Function GetDC Lib "user32.dll" (ByVal hwnd As LongPtr) As LongPtr
    Private Declare Function GetDeviceCaps Lib "gdi32.dll" (ByVal hDC As LongPtr, ByVal nIndex As Long) As Long
    Private Declare Function ReleaseDC Lib "user32" (ByVal hwnd As LongPtr, ByVal hDC As LongPtr) As LongPtr
    Private Declare Function SetPixel Lib "gdi32" (ByVal hDC As LongPtr, ByVal x As Long, ByVal y As Long, ByVal crColor As Long) As Long
    Private Declare Function DrawText Lib "user32" Alias "DrawTextA" (ByVal hDC As LongPtr, ByVal lpStr As String, ByVal nCount As Long, lpRect As RECT, ByVal wFormat As Long) As Long
    Private Declare Function SetRect Lib "user32" (lpRect As RECT, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
    Private Declare Function SetBkMode Lib "gdi32" (ByVal hDC As LongPtr, ByVal nBkMode As Long) As Long
    Private Declare Function MoveToEx Lib "gdi32" (ByVal hDC As LongPtr, ByVal x As Long, ByVal y As Long, lpPoint As POINTAPI) As Long
    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 CreateEllipticRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As LongPtr
    Private Declare Function CreateRectRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As LongPtr
    Private Declare Function CombineRgn Lib "gdi32" (ByVal hDestRgn As LongPtr, ByVal hSrcRgn1 As LongPtr, ByVal hSrcRgn2 As LongPtr, ByVal nCombineMode 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 CreateFont Lib "gdi32" Alias "CreateFontA" (ByVal h As Long, ByVal w As Long, ByVal E As Long, ByVal O As Long, ByVal w As Long, ByVal i As Long, ByVal u As Long, ByVal S As Long, ByVal C As Long, ByVal OP As Long, ByVal CP As Long, ByVal Q As Long, ByVal PAF As Long, ByVal f As String) As LongPtr
    Private Declare Function MulDiv Lib "kernel32" (ByVal nNumber As Long, ByVal nNumerator As Long, ByVal nDenominator As Long) As Long
    Private Declare Function GetClientRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As RECT) As Long
    Private Declare Function GetWindowRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As RECT) As Long
    Private Declare Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long
    Private Declare Function SetTextColor Lib "gdi32" (ByVal hDC As LongPtr, ByVal crColor As Long) As Long
    Private Declare Function AdjustWindowRect Lib "user32" (lpRect As RECT, ByVal dwStyle As Long, ByVal bMenu As Long) As Long
    Private Declare Function BeginDeferWindowPos Lib "user32" (ByVal nNumWindows As Long) As LongPtr
    Private Declare Function DeferWindowPos Lib "user32" (ByVal hWinPosInfo As LongPtr, ByVal hwnd As LongPtr, ByVal hWndInsertAfter As LongPtr, ByVal x As Long, ByVal y As Long, ByVal cx As Long, ByVal cy As Long, ByVal wFlags As Long) As LongPtr
    Private Declare Function EndDeferWindowPos Lib "user32" (ByVal hWinPosInfo As LongPtr) As Long
    Private Declare Function SetWindowPos Lib "user32" (ByVal hwnd As LongPtr, ByVal hWndInsertAfter As LongPtr, ByVal x As Long, ByVal y As Long, ByVal cx As Long, ByVal cy As Long, ByVal wFlags As Long) As Long
    Private Declare Function InvalidateRgn Lib "user32" (ByVal hwnd As LongPtr, ByVal hRgn As LongPtr, ByVal bErase As Long) As Long
    Private Declare Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
    Private Declare Function GetObjectAPI Lib "gdi32" Alias "GetObjectA" (ByVal hObject As LongPtr, ByVal nCount As Long, lpObject As Any) As Long
    Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
    Private Declare Function AccessibleObjectFromPoint Lib "oleacc" (ByVal arg1 As LongPtr, ppacc As Any, pvarChild As Variant) As Long
    Private Declare Function GetCursorPos Lib "user32.dll" (lpPoint As POINTAPI) As Long
 
    'GDIPlus
    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 GdipCreatePen1 Lib "gdiplus" (ByVal color As Long, ByVal Width As Single, ByVal unit As Long, pen As LongPtr) As Long
    Private Declare Function GdipDeletePen Lib "gdiplus" (ByVal pen As LongPtr) As Long
    Private Declare Function GdipDrawLine Lib "gdiplus" (ByVal graphics As LongPtr, ByVal pen As LongPtr, ByVal X1 As Single, ByVal Y1 As Single, ByVal X2 As Single, ByVal Y2 As Single) As Long
    Private Declare Function GdipCreateFromHDC Lib "gdiplus" (ByVal hDC As LongPtr, hGraphics As LongPtr) As Long
    Private Declare Function GdipSetSmoothingMode Lib "gdiplus" (ByVal graphics As LongPtr, ByVal SmoothingMd As Long) As Long
    Private Declare Function GdipSetPenDashStyle Lib "gdiplus" (ByVal pen As LongPtr, ByVal dStyle As Long) As Long
    Private Declare Function GdipDeleteGraphics Lib "GdiPlus.dll" (ByVal mGraphics As LongPtr) As Long
    Private Declare Function GetSysColor Lib "user32.dll" (ByVal nIndex As Long) As Long
#End If


Private Type GdiplusStartupInput
    GdiplusVersion As Long
    DebugEventCallback As LongPtr
    SuppressBackgroundThread As LongPtr
    SuppressExternalCodecs As Long
End Type

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 Const LF_FACESIZE = 32&
Private Type LOGFONT
    lfHeight As Long
    lfWidth As Long
    lfEscapement As Long
    lfOrientation As Long
    lfWeight As Long
    lfItalic As Byte
    lfUnderline As Byte
    lfStrikeOut As Byte
    lfCharSet As Byte
    lfOutPrecision As Byte
    lfClipPrecision As Byte
    lfQuality As Byte
    lfPitchAndFamily As Byte
    lfFaceName(1 To LF_FACESIZE) As Byte
End Type


Private hwnd As LongPtr, hDC As LongPtr
Private hGraphics As LongPtr
Private hPrevFont As LongPtr
Private SngRadius1 As Single
Private X1 As Single, Y1 As Single
Private oCanvas As Object
Private bInvalidate As Boolean
Private sngRad As Single
Private sNumbersFontName As String
Private lNumbersFontSize As Long
Private lNumbersFontColor As Long
Private lOutlineColor As Long
Private lMinLinesColor As Long
Private lHourHandColor As Long
Private lMinHandColor As Long
Private lSecHandColor As Long
Private sngHourHandThickness As Single
Private sngMinHandThickness As Single
Private sngSecHandThickness As Single
Private bTickTockSound As Boolean




Public Sub CreateClock( _
    ByVal Container As Object, _
    Optional ByVal Radius As Single, _
    Optional ByVal NumbersFontName As String, _
    Optional ByVal NumbersFontSize As Long, _
    Optional ByVal NumbersFontColor As Long, _
    Optional ByVal OutlineColor As Long, _
    Optional ByVal MinLinesColor As Long, _
    Optional ByVal HourHandColor As Long, _
    Optional ByVal MinHandColor As Long, _
    Optional ByVal SecHandColor As Long, _
    Optional ByVal HourHandThickness As Long, _
    Optional ByVal MinHandThickness As Long, _
    Optional ByVal SecHandThickness As Long, _
    Optional ByVal TickTockSound As Boolean _
)

    Const SWP_SHOWWINDOW = &H40
    Const SWP_NOSIZE = &H1
    Const SWP_NOZORDER = &H4
    Const SWP_NOACTIVATE = &H10
    Const SM_CYCAPTION = 4&
    Const DT_NOCLIP = &H100
    Const DT_CENTER = &H1
    Const TRANSPARENT = 1&
    Const POINTSPERINCH = 72&
    Const LOGPIXELSY = 90&
    Const SM_CXSCREEN = 0&
    Const SM_CYSCREEN = 1&
    Const PI = 3.14159265358979
    Const Rads = PI / 180&
    Const UnitPixel = 2&
    Const SmoothingModeAntiAlias = &H4
    Const DashStyleSolid = 0&
    Const S_OK = 0&
 
    Dim tInitContainerRect As RECT, tResizedContainerRect As RECT
    Dim tClockRect As RECT, tAppRect As RECT
    Dim tFont As LOGFONT
    Dim hFont As LongPtr, hPen As LongPtr, dwp As LongPtr
    Dim i As Long, lRet As Long
    Dim lPenColor As Long
    Dim lAngle As Long
    Dim SngRadius2 As Single
    Dim X2 As Single, Y2 As Single
    Dim X3 As Single, Y3 As Single
    Dim Z1 As Single, Z2 As Single
    Dim sngMinLinesLength As Single
    Dim sngYCaptionFactor As Single
    Dim l As Single, t As Single, w As Single, h As Single


    Set oCanvas = Container
    sngRad = Radius
    sNumbersFontName = NumbersFontName
    lNumbersFontSize = NumbersFontSize
    lNumbersFontColor = NumbersFontColor
    lOutlineColor = OutlineColor
    lMinLinesColor = MinLinesColor
    lHourHandColor = HourHandColor
    lMinHandColor = MinHandColor
    lSecHandColor = SecHandColor
    sngHourHandThickness = HourHandThickness
    sngMinHandThickness = MinHandThickness
    sngSecHandThickness = SecHandThickness
    bTickTockSound = TickTockSound

    If InitializesGDIPlus(True) Then

        Call IUnknown_GetWindow(Container, VarPtr(hwnd))
   
        If hwnd = NULL_PTR Then Exit Sub
   
        If TickTockSound Then Call CreateTickTockWavSound
   
        hDC = GetDC(hwnd)
        Call SetRect(tClockRect, 0&, 0&, Radius * 2&, Radius * 2&)
        Call GetWindowRect(hwnd, tInitContainerRect)
 
        If TypeName(Container) <> "Frame" Then
            sngYCaptionFactor = 2&
            Call AdjustWindowRect(tClockRect, 0&, False)
            dwp = BeginDeferWindowPos(1&)
            With tInitContainerRect
                Call DeferWindowPos(dwp, hwnd, NULL_PTR, .Left, .Top, tClockRect.Right, tClockRect.Bottom, 0&)
            End With
            Call EndDeferWindowPos(dwp)
            Call GetWindowRect(Application.hwnd, tAppRect)
            Call GetWindowRect(hwnd, tResizedContainerRect)
            With tResizedContainerRect
                If Container.startupposition = 1& Then
                    l = ((tAppRect.Right - tAppRect.Left) - (.Right - .Left)) / 2&
                    t = ((tAppRect.Bottom - tAppRect.Top) - (.Bottom - .Top)) / 2&
                ElseIf Container.startupposition = 2& Then
                    l = (GetSystemMetrics(SM_CXSCREEN) - (.Right - .Left)) / 2&
                    t = (GetSystemMetrics(SM_CYSCREEN) - (.Bottom - .Top)) / 2&
                End If
            End With
            If bInvalidate = False Then
                Call SetWindowPos(hwnd, NULL_PTR, l, t, 0&, 0&, SWP_NOACTIVATE + SWP_SHOWWINDOW + SWP_NOZORDER + SWP_NOSIZE)
            End If
        Else
            Container.Width = Container.Height
            sngYCaptionFactor = 1.3
        End If
 
        Call GetClientRect(hwnd, tClockRect)
        X1 = tClockRect.Right / 2&
        Y1 = tClockRect.Bottom / 2&
        SngRadius1 = tClockRect.Right / 2& - (sngYCaptionFactor * GetSystemMetrics(SM_CYCAPTION))
        SngRadius2 = SngRadius1 * 8& / 10&
   
        lRet = GdipCreateFromHDC(hDC, hGraphics)
   
        If lRet = S_OK Then
            Call GdipSetSmoothingMode(hGraphics, SmoothingModeAntiAlias)
            lPenColor = RGBtoARGB(MinLinesColor, 255&)
            Call GdipCreatePen1(lPenColor, 3&, UnitPixel, hPen)
            Call GdipSetPenDashStyle(hPen, DashStyleSolid)
            Container.Repaint
       
            For lAngle = 0& To 359&
       
                i = 10&
                If lAngle Mod 6& = 0& Then
                    X2 = (SngRadius1 + i) * (Sin(lAngle * Rads))
                    Y2 = (SngRadius1 + i) * (Cos(lAngle * Rads))
                    If lAngle Mod 5& = 0& Then
                        sngMinLinesLength = (SngRadius1 - SngRadius2) / 2&
                    Else
                        sngMinLinesLength = 4&
                    End If
                    Z1 = (X1 + X2) - (sngMinLinesLength * (Sin(lAngle * Rads)))
                    Z2 = (Y1 + Y2) - (sngMinLinesLength * (Cos(lAngle * Rads)))
                    Call GdipDrawLine(hGraphics, hPen, X1 + X2, Y1 + Y2, Z1, Z2)
                End If
                For i = 10& To 20&
                    X2 = (SngRadius1 + 20&) * (Sin(lAngle * Rads))
                    Y2 = (SngRadius1 + 20&) * (Cos(lAngle * Rads))
                    Call SetPixel(hDC, X2 + X1, Y2 + Y1, OutlineColor)
                    X3 = (SngRadius1 + 25&) * (Sin(lAngle * Rads))
                    Y3 = (SngRadius1 + 25&) * (Cos(lAngle * Rads))
                    Call SetPixel(hDC, X3 + X1, Y3 + Y1, OutlineColor)
                Next i
                X2 = SngRadius2 * (Sin(lAngle * Rads))
                Y2 = SngRadius2 * (Cos(lAngle * Rads))
                Call SetRect(tClockRect, X1 + X2, Y1 + Y2, X1 + X2, Y1 + Y2)
                Call SetTextColor(hDC, NumbersFontColor)
                hFont = CreateFont(-MulDiv(NumbersFontSize, GetDeviceCaps(hDC, LOGPIXELSY), POINTSPERINCH), _
                        0&, 0&, 0&, 0&, False, False, False, 0&, 0&, 0&, 0&, 0&, NumbersFontName & vbNullChar)
                hPrevFont = SelectObject(hDC, hFont)
                Call GetObjectAPI(hFont, LenB(tFont), tFont)
                Call DeleteObject(hFont)
                With tClockRect
                    .Top = .Top + tFont.lfHeight / 2&
                End With
                Call SetBkMode(hDC, TRANSPARENT)
                If lAngle Mod 30& = 0& Then
                    Select Case lAngle
                        Case Is = 0&
                            Call DrawText(hDC, "6", 1&, tClockRect, DT_CENTER + DT_NOCLIP)
                        Case Is = 30&
                            Call DrawText(hDC, "5", 1&, tClockRect, DT_CENTER + DT_NOCLIP)
                        Case Is = 60&
                            Call DrawText(hDC, "4", 1&, tClockRect, DT_CENTER + DT_NOCLIP)
                        Case Is = 90&
                            Call DrawText(hDC, "3", 1&, tClockRect, DT_CENTER + DT_NOCLIP)
                        Case Is = 120&
                            Call DrawText(hDC, "2", 1&, tClockRect, DT_CENTER + DT_NOCLIP)
                        Case Is = 150&
                            Call DrawText(hDC, "1", 1&, tClockRect, DT_CENTER + DT_NOCLIP)
                        Case Is = 180&
                            Call DrawText(hDC, "12", 2&, tClockRect, DT_CENTER + DT_NOCLIP)
                        Case Is = 210&
                            Call DrawText(hDC, "11", 2&, tClockRect, DT_CENTER + DT_NOCLIP)
                        Case Is = 240&
                            Call DrawText(hDC, "10", 2&, tClockRect, DT_CENTER + DT_NOCLIP)
                        Case Is = 270&
                            Call DrawText(hDC, "9", 1&, tClockRect, DT_CENTER + DT_NOCLIP)
                        Case Is = 300&
                            Call DrawText(hDC, "8", 1&, tClockRect, DT_CENTER + DT_NOCLIP)
                        Case Is = 330&
                            Call DrawText(hDC, "7", 1&, tClockRect, DT_CENTER + DT_NOCLIP)
                    End Select
                End If
   
            Next lAngle
   
            Call GdipDeletePen(hPen)
            Call StartUpdatingClock
            Call UpdateClock
        End If
 
    End If

End Sub

Public Sub DeleteClock(Optional ByVal bDummy As Boolean)
    Call KillTimer(Application.hwnd, NULL_PTR)
    Call KillTimer(hwnd, NULL_PTR)
    Call StopSound
    Call SelectObject(hDC, hPrevFont)
    Call ReleaseDC(hwnd, hDC)
    Call InitializesGDIPlus(False)
    sngRad = 0&
    sNumbersFontName = ""
    lNumbersFontSize = 0&
    lNumbersFontColor = 0&
    lOutlineColor = 0&
    lMinLinesColor = 0&
    lHourHandColor = 0&
    lMinHandColor = 0&
    lSecHandColor = 0&
    sngHourHandThickness = 0&
    sngMinHandThickness = 0&
    sngSecHandThickness = 0&
    bTickTockSound = False
    bInvalidate = False
End Sub

Public Sub StopClock(Optional ByVal bDummy As Boolean)
    Call KillTimer(Application.hwnd, NULL_PTR)
    Call KillTimer(hwnd, NULL_PTR)
End Sub

Public Sub ResumeClock(Optional ByVal bDummy As Boolean)
    Call StartUpdatingClock
End Sub


Private Sub StartUpdatingClock()
    Call KillTimer(Application.hwnd, NULL_PTR)
    Call SetTimer(hwnd, NULL_PTR, 0&, AddressOf MonitorClockScreenPos)
    Call SetTimer(Application.hwnd, NULL_PTR, 1000&, AddressOf UpdateClock)
End Sub


Private Sub UpdateClock()

    Const UnitPixel = 2&
    Const DashStyleSolid = 0&
    Const PI = 3.14159265358979

    Dim tPt As POINTAPI
    Dim hRgn As LongPtr, hPen As LongPtr
    Dim SngRadius3 As Single, SngRadius4 As Single
    Dim sngSecond As Single, sngMinute As Single, sngHour As Single
    Dim lPenColor As Long

    On Error Resume Next
 
    Call PlayWav
    SngRadius3 = SngRadius1 * 7& / 10&
    SngRadius4 = SngRadius1 * 8& / 10&
    hRgn = CreateEllipticRgn(X1 - SngRadius3, Y1 - SngRadius3, X1 + SngRadius3, Y1 + SngRadius3)
    Call InvalidateRgn(hwnd, hRgn, False)
    DoEvents
    Call DeleteObject(hRgn)
    If tPt.x = 0& Then tPt.x = X1
    If tPt.y = 0& Then tPt.y = Y1
    Call MoveToEx(hDC, X1, Y1, tPt)
    'Hours.
    If sngHourHandThickness = 0 Then sngHourHandThickness = 5&
    lPenColor = RGBtoARGB(lHourHandColor, 255)
    Call GdipCreatePen1(lPenColor, sngHourHandThickness, UnitPixel, hPen)
    Call GdipSetPenDashStyle(hPen, DashStyleSolid)
    sngHour = (Hour(Time) + (Minute(Time) / 60&)) * (2& * PI / 12&)
    Call GdipDrawLine(hGraphics, hPen, X1 + SngRadius4 * Sin(sngHour) * 0.5, Y1 - SngRadius4 * Cos(sngHour) * 0.5, X1, Y1)
    Call GdipDeletePen(hPen)
    'Minutes.
    If sngMinHandThickness = 0 Then sngMinHandThickness = 3&
    lPenColor = RGBtoARGB(lMinHandColor, 255&)
    Call GdipCreatePen1(lPenColor, sngMinHandThickness, UnitPixel, hPen)
    Call GdipSetPenDashStyle(hPen, DashStyleSolid)
    sngMinute = (Minute(Time) + (Second(Time) / 60&)) * (2& * PI / 60&)
    Call GdipDrawLine(hGraphics, hPen, X1 + SngRadius3 * Sin(sngMinute) * 0.72, Y1 - SngRadius3 * Cos(sngMinute) * 0.72, X1, Y1)
    Call GdipDeletePen(hPen)
    'Seconds.
    If sngSecHandThickness = 0& Then sngSecHandThickness = 2&
    lPenColor = RGBtoARGB(lSecHandColor, 255&)
    Call GdipCreatePen1(lPenColor, sngSecHandThickness, UnitPixel, hPen)
    Call GdipSetPenDashStyle(hPen, DashStyleSolid)
    sngSecond = Second(Time) * (2& * PI / 60&)
    Call GdipDrawLine(hGraphics, hPen, X1 + SngRadius3 * Sin(sngSecond) * 0.9, Y1 - SngRadius3 * Cos(sngSecond) * 0.9, X1, Y1)
    Call GdipDeletePen(hPen)
 
End Sub


Private Sub MonitorClockScreenPos()
    'Unlike Forms in VB6, Office Userforms don't have an 'AutoRedraw' Property.
    'So, Short of subclassing the userform,we use this hack timer-callback routine
    'to refresh the screen drawing if\when the userform is move off screen.

    Const ROLE_SYSTEM_TITLEBAR = 1&
    Const RGN_OR = 2&
    Const SM_CXSCREEN = 0&
    Const SM_CYSCREEN = 1&
 
    Static bOffScreen As Boolean
    Static lKeyAsyncState As Integer
    Dim tCurPos As POINTAPI
    Dim tCanvasRect As RECT
    Dim oIA As IAccessible
    Dim w As Long, h As Long
    Dim hScrRgn As LongPtr, hCanvasRgn As LongPtr

    If GetAsyncKeyState(VBA.vbKeyLButton) = 0& And lKeyAsyncState <> 0& Then
        Call GetCursorPos(tCurPos)
        #If Win64 Then
            Dim lPt As LongLong
            Call CopyMemory(lPt, tCurPos, LenB(lPt))
            Call AccessibleObjectFromPoint(lPt, oIA, 0&)
        #Else
            Call AccessibleObjectFromPoint(tCurPos.x, tCurPos.y, oIA, 0&)
        #End If
        If bOffScreen Then
            bOffScreen = False
            If oIA.accRole(0&) = ROLE_SYSTEM_TITLEBAR Then
                bInvalidate = True
                Call CreateClock(oCanvas, sngRad, sNumbersFontName, lNumbersFontSize, lNumbersFontColor, _
                    lOutlineColor, lMinLinesColor, lHourHandColor, lMinHandColor, lSecHandColor, bTickTockSound)
            End If
        End If
    End If
    lKeyAsyncState = GetAsyncKeyState(VBA.vbKeyLButton)
    w = GetSystemMetrics(SM_CXSCREEN)
    h = GetSystemMetrics(SM_CYSCREEN)
    Call GetWindowRect(hwnd, tCanvasRect)
    hScrRgn = CreateRectRgn(0&, 0&, w, h)
    With tCanvasRect
        hCanvasRgn = CreateRectRgn(.Left, .Top, .Right, .Bottom)
    End With
    If CombineRgn(hCanvasRgn, hScrRgn, hCanvasRgn, RGN_OR) = 3& Then
        bOffScreen = True
    End If
    Call DeleteObject(hCanvasRgn)
    Call DeleteObject(hScrRgn)

End Sub


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 GdipDeleteGraphics(hGraphics)
            Call GdiplusShutdown(lGDIP)
            lGDIP = NULL_PTR
        End If
    End If
 
End Function

Private Function RGBtoARGB(ByVal RGBColor As Long, ByVal Opacity As Long) As Long
    If (RGBColor And &H80000000) Then RGBColor = GetSysColor(RGBColor And &HFF&)
    RGBtoARGB = (RGBColor And &HFF00&) Or (RGBColor And &HFF0000) \ &H10000 Or (RGBColor And &HFF) * &H10000
    If Opacity < 128 Then
        If Opacity < 0& Then Opacity = 0&
        RGBtoARGB = RGBtoARGB Or Opacity * &H1000000
    Else
        If Opacity > 255& Then Opacity = 255&
        RGBtoARGB = RGBtoARGB Or (Opacity - 128&) * &H1000000 Or &H80000000
    End If
End Function


2- WAV file Bytes code in a Standard Module:
VBA Code:
Option Explicit

#If Win64 Then
    Const VARIANT_OFFSET_FACTOR = 24&
#Else
    Const VARIANT_OFFSET_FACTOR = 16&
#End If

#If VBA7 Then
    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 Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
    Private Declare PtrSafe Function PlaySound Lib "winmm.dll" Alias "sndPlaySoundW" (lpszSoundName As Any, ByVal uFlags As Long) As Long
    Private Declare PtrSafe Function SafeArrayGetDim Lib "oleaut32.dll" (ByRef saArray() As Any) As Long
#Else
    Private Declare Function SetTimer Lib "user32.dll" (ByVal hwnd As Long, ByVal nIDEvent As Long, ByVal uElapse As Long, ByVal lpTimerFunc As Long) As Long
    Private Declare Function KillTimer Lib "user32.dll" (ByVal hwnd As Long, ByVal nIDEvent As Long) As Long
    Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
    Private Declare Function PlaySound Lib "winmm.dll" Alias "sndPlaySoundW" (lpszSoundName As Any, ByVal uFlags As Long) As Long
    Private Declare Function SafeArrayGetDim Lib "oleaut32.dll" (ByRef saArray() As Any) As Long
#End If

Private bSoundCreated As Boolean
Private vTempSoundArray() As Variant
Private SoundBytesArray() As Byte


Public Sub CreateTickTockWavSound(Optional ByVal bDummy As Boolean)
    Call BuildSound
End Sub

Public Sub PlayWav(Optional ByVal bDummy As Boolean)
    Const SND_ASYNC = &H1
    Const SND_NODEFAULT = &H2
    Const SND_MEMORY = &H4
    If SafeArrayGetDim(SoundBytesArray) Then
        Call PlaySound(SoundBytesArray(0&), SND_ASYNC Or SND_NODEFAULT Or SND_MEMORY)
    End If
End Sub

Public Sub StopSound(Optional ByVal bDummy As Boolean)
    If SafeArrayGetDim(SoundBytesArray) Then
        Call PlaySound(ByVal StrPtr(vbNullString), 0&)
        Erase SoundBytesArray
    End If
End Sub


Private Sub BuildSound()
    Dim i As Long
    Call SetTimer(Application.hwnd, 0, 0, AddressOf BuildSoundArray1)
    Do: DoEvents: Loop Until bSoundCreated
    bSoundCreated = False
 
    ReDim SoundBytesArray(LBound(vTempSoundArray) To UBound(vTempSoundArray))
    For i = LBound(vTempSoundArray) To UBound(vTempSoundArray)
        SoundBytesArray(i) = CByte((vTempSoundArray(i)))
    Next
    Erase vTempSoundArray
End Sub

Private Sub BuildSoundArray1()

    Dim ar2() As Variant, ar3() As Variant, lPos As Long
 
    Call KillTimer(Application.hwnd, 0)
 
    vTempSoundArray = Array(82, 73, 70, 70, 158, 10, 0, 0, 87, 65, 86, 69, 102, 109, 116, 32, 16, 0, 0, 0, 1, 0, 2, 0, 34, 86, 0, 0, 136, 88, 1, 0, _
    4, 0, 16, 0, 76, 73, 83, 84, 26, 0, 0, 0, 73, 78, 70, 79, 73, 83, 70, 84, 14, 0, 0, 0, 76, 97, 118, 102, 53, 56, 46, 55, _
    54, 46, 49, 48, 48, 0, 100, 97, 116, 97, 88, 10, 0, 0, 255, 255, 254, 255, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, _
    1, 0, 0, 0, 255, 255, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 255, 255, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, _
    0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 255, 255, 0, 0, 1, 0, 1, 0, 0, 0, _
    255, 255, 0, 0, 0, 0, 255, 255, 0, 0, 1, 0, 0, 0, 255, 255, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0)
 
    ar2 = Array(0, 0, 255, 255, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, _
    0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 255, 255, 0, 0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, _
    255, 255, 0, 0, 0, 0, 0, 0, 255, 255, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, _
    0, 0, 1, 0, 0, 0, 255, 255, 0, 0, 0, 0, 0, 0, 1, 0, 1, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 1, 0, 1, 0, _
    1, 0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 255, 255, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, _
    0, 0, 1, 0, 0, 0, 255, 255, 255, 255, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, _
    2, 0, 0, 0, 0, 0, 1, 0, 0, 0, 1, 0, 255, 255, 0, 0, 1, 0, 0, 0, 255, 255, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0)
 
 
    lPos = UBound(vTempSoundArray)
    ReDim Preserve vTempSoundArray(UBound(vTempSoundArray) + UBound(ar2) + 1)
    Call CopyMemory(ByVal VarPtr(vTempSoundArray(lPos + 1)), ByVal VarPtr(ar2(0)), VARIANT_OFFSET_FACTOR * (UBound(ar2) + 1))
    Erase ar2
 
    ar3 = Array(0, 0, 255, 255, 1, 0, 0, 0, 0, 0, 1, 0, 1, 0, 0, 0, 1, 0, 0, 0, 0, 0, 1, 0, 0, 0, 1, 0, 0, 0, 0, 0, _
    254, 255, 0, 0, 255, 255, 255, 255, 0, 0, 255, 255, 255, 255, 0, 0, 255, 255, 1, 0, 255, 255, 254, 255, 255, 255, 1, 0, 0, 0, 3, 0, _
    0, 0, 255, 255, 0, 0, 1, 0, 1, 0, 2, 0, 2, 0, 0, 0, 1, 0, 2, 0, 3, 0, 2, 0, 2, 0, 255, 255, 0, 0, 255, 255, _
    0, 0, 254, 255, 0, 0, 253, 255, 2, 0, 253, 255, 2, 0, 0, 0, 254, 255, 254, 255, 1, 0, 255, 255, 255, 255, 255, 255, 254, 255, 0, 0, _
    254, 255, 3, 0, 253, 255, 1, 0, 254, 255, 0, 0, 253, 255, 1, 0, 253, 255, 255, 255, 255, 255, 3, 0, 1, 0, 0, 0, 0, 0, 254, 255, _
    3, 0, 1, 0, 6, 0, 2, 0, 6, 0, 254, 255, 5, 0, 255, 255, 4, 0, 0, 0, 1, 0, 255, 255, 253, 255, 1, 0, 255, 255, 0, 0, _
    254, 255, 0, 0, 253, 255, 254, 255, 255, 255, 253, 255, 254, 255, 1, 0, 254, 255, 254, 255, 254, 255, 1, 0, 2, 0, 254, 255, 3, 0, 255, 255)
 
 
    lPos = UBound(vTempSoundArray)
    ReDim Preserve vTempSoundArray(UBound(vTempSoundArray) + UBound(ar3) + 1)
    Call CopyMemory(ByVal VarPtr(vTempSoundArray(lPos + 1)), ByVal VarPtr(ar3(0)), VARIANT_OFFSET_FACTOR * (UBound(ar3) + 1))
    Erase ar3
    Call SetTimer(Application.hwnd, 0, 0, AddressOf BuildSoundArray2)

End Sub

Private Sub BuildSoundArray2()

    Dim ar4() As Variant, lPos As Long
 
    Call KillTimer(Application.hwnd, 0)
 
    ar4 = Array(2, 0, 1, 0, 2, 0, 255, 255, 0, 0, 3, 0, 1, 0, 5, 0, 3, 0, 3, 0, 1, 0, 3, 0, 2, 0, 0, 0, 3, 0, 1, 0, _
    3, 0, 0, 0, 0, 0, 1, 0, 253, 255, 2, 0, 254, 255, 0, 0, 0, 0, 251, 255, 250, 255, 252, 255, 251, 255, 4, 0, 253, 255, 0, 0, _
    254, 255, 255, 255, 4, 0, 253, 255, 1, 0, 0, 0, 5, 0, 253, 255, 5, 0, 254, 255, 255, 255, 252, 255, 4, 0, 255, 255, 4, 0, 3, 0, _
    253, 255, 3, 0, 252, 255, 1, 0, 252, 255, 0, 0, 253, 255, 2, 0, 253, 255, 1, 0, 255, 255, 1, 0, 252, 255, 5, 0, 252, 255, 6, 0, _
    255, 255, 1, 0, 4, 0, 255, 255, 1, 0, 252, 255, 250, 255, 1, 0, 3, 0, 252, 255, 0, 0, 254, 255, 3, 0, 0, 0, 7, 0, 1, 0, _
    255, 255, 254, 255, 4, 0, 251, 255, 5, 0, 255, 255, 0, 0, 255, 255, 0, 0, 253, 255, 5, 0, 2, 0, 0, 0, 10, 0, 252, 255, 6, 0, _
    253, 255, 2, 0, 254, 255, 9, 0, 1, 0, 11, 0, 254, 255, 5, 0, 250, 255, 0, 0, 252, 255, 254, 255, 3, 0, 251, 255, 1, 0, 252, 255)
 
 
    lPos = UBound(vTempSoundArray)
    ReDim Preserve vTempSoundArray(UBound(vTempSoundArray) + UBound(ar4) + 1)
    Call CopyMemory(ByVal VarPtr(vTempSoundArray(lPos + 1)), ByVal VarPtr(ar4(0)), VARIANT_OFFSET_FACTOR * (UBound(ar4) + 1))
    Erase ar4
    Call SetTimer(Application.hwnd, 0, 0, AddressOf BuildSoundArray3)
 
End Sub
 
Private Sub BuildSoundArray3()

    Dim ar5() As Variant, ar6() As Variant, ar7() As Variant, lPos As Long
 
    Call KillTimer(Application.hwnd, 0)
 
    ar5 = Array(0, 0, 4, 0, 10, 0, 0, 0, 9, 0, 253, 255, 3, 0, 251, 255, 10, 0, 1, 0, 4, 0, 255, 255, 1, 0, 0, 0, 2, 0, 6, 0, _
    254, 255, 255, 255, 0, 0, 254, 255, 254, 255, 1, 0, 252, 255, 247, 255, 254, 255, 2, 0, 3, 0, 6, 0, 1, 0, 6, 0, 2, 0, 255, 255, _
    2, 0, 2, 0, 5, 0, 4, 0, 10, 0, 254, 255, 255, 255, 3, 0, 252, 255, 255, 255, 252, 255, 0, 0, 255, 255, 255, 255, 4, 0, 248, 255, _
    255, 255, 0, 0, 1, 0, 1, 0, 252, 255, 254, 255, 255, 255, 4, 0, 8, 0, 4, 0, 6, 0, 3, 0, 252, 255, 252, 255, 252, 255, 2, 0, _
    4, 0, 4, 0, 5, 0, 254, 255, 0, 0, 250, 255, 254, 255, 252, 255, 253, 255, 245, 255, 254, 255, 248, 255, 252, 255, 253, 255, 250, 255, 2, 0)
 
 
    lPos = UBound(vTempSoundArray)
    ReDim Preserve vTempSoundArray(UBound(vTempSoundArray) + UBound(ar5) + 1)
    Call CopyMemory(ByVal VarPtr(vTempSoundArray(lPos + 1)), ByVal VarPtr(ar5(0)), VARIANT_OFFSET_FACTOR * (UBound(ar5) + 1))
    Erase ar5
 
    ar6 = Array(255, 255, 254, 255, 250, 255, 1, 0, 3, 0, 1, 0, 11, 0, 3, 0, 10, 0, 12, 0, 17, 0, 5, 0, 23, 0, 253, 255, 11, 0, 252, 255, _
    246, 255, 255, 255, 252, 255, 0, 0, 4, 0, 6, 0, 251, 255, 11, 0, 246, 255, 1, 0, 9, 0, 251, 255, 10, 0, 5, 0, 250, 255, 2, 0, _
    10, 0, 0, 0, 16, 0, 4, 0, 3, 0, 248, 255, 244, 255, 243, 255, 236, 255, 236, 255, 242, 255, 238, 255, 242, 255, 249, 255, 232, 255, 251, 255, _
    246, 255, 16, 0, 13, 0, 248, 255, 6, 0, 236, 255, 7, 0, 3, 0, 10, 0, 34, 0, 26, 0, 55, 0, 51, 0, 33, 0, 36, 0, 13, 0, _
    15, 0, 249, 255, 4, 0, 241, 255, 234, 255, 251, 255, 236, 255, 223, 255, 246, 255, 222, 255, 228, 255, 237, 255, 214, 255, 241, 255, 220, 255, 238, 255)
 
 
    lPos = UBound(vTempSoundArray)
    ReDim Preserve vTempSoundArray(UBound(vTempSoundArray) + UBound(ar6) + 1)
    Call CopyMemory(ByVal VarPtr(vTempSoundArray(lPos + 1)), ByVal VarPtr(ar6(0)), VARIANT_OFFSET_FACTOR * (UBound(ar6) + 1))
    Erase ar6
 
    ar7 = Array(244, 255, 237, 255, 4, 0, 254, 255, 9, 0, 22, 0, 27, 0, 14, 0, 20, 0, 251, 255, 6, 0, 249, 255, 6, 0, 241, 255, 13, 0, 12, 0, _
    19, 0, 35, 0, 12, 0, 26, 0, 4, 0, 16, 0, 21, 0, 14, 0, 21, 0, 22, 0, 20, 0, 8, 0, 17, 0, 244, 255, 5, 0, 220, 255, _
    249, 255, 226, 255, 233, 255, 232, 255, 210, 255, 215, 255, 199, 255, 207, 255, 194, 255, 216, 255, 207, 255, 247, 255, 249, 255, 16, 0, 17, 0, 48, 0, _
    36, 0, 62, 0, 58, 0, 47, 0, 62, 0, 43, 0, 47, 0, 53, 0, 41, 0, 27, 0, 30, 0, 2, 0, 18, 0, 233, 255, 1, 0, 228, 255, _
    233, 255, 213, 255, 212, 255, 209, 255, 209, 255, 211, 255, 218, 255, 211, 255, 224, 255, 236, 255, 243, 255, 239, 255, 254, 255, 249, 255, 3, 0, 11, 0, _
    7, 0, 25, 0, 18, 0, 24, 0, 23, 0, 24, 0, 15, 0, 19, 0, 10, 0, 20, 0, 24, 0, 33, 0, 36, 0, 43, 0, 30, 0, 54, 0)
 
 
    lPos = UBound(vTempSoundArray)
    ReDim Preserve vTempSoundArray(UBound(vTempSoundArray) + UBound(ar7) + 1)
    Call CopyMemory(ByVal VarPtr(vTempSoundArray(lPos + 1)), ByVal VarPtr(ar7(0)), VARIANT_OFFSET_FACTOR * (UBound(ar7) + 1))
    Erase ar7
    Call SetTimer(Application.hwnd, 0, 0, AddressOf BuildSoundArray4)

End Sub

Private Sub BuildSoundArray4()

    Dim ar8() As Variant, ar9() As Variant, ar10() As Variant, lPos As Long
 
    Call KillTimer(Application.hwnd, 0)
 
    ar8 = Array(31, 0, 17, 0, 14, 0, 2, 0, 10, 0, 253, 255, 2, 0, 226, 255, 237, 255, 214, 255, 228, 255, 193, 255, 201, 255, 189, 255, 193, 255, 202, 255, _
    215, 255, 219, 255, 223, 255, 246, 255, 237, 255, 2, 0, 8, 0, 26, 0, 19, 0, 52, 0, 39, 0, 57, 0, 71, 0, 79, 0, 84, 0, 68, 0, _
    72, 0, 35, 0, 35, 0, 17, 0, 12, 0, 253, 255, 0, 0, 228, 255, 229, 255, 210, 255, 207, 255, 210, 255, 194, 255, 219, 255, 193, 255, 230, 255, _
    222, 255, 252, 255, 236, 255, 251, 255, 251, 255, 0, 0, 6, 0, 9, 0, 10, 0, 6, 0, 28, 0, 18, 0, 26, 0, 3, 0, 23, 0, 248, 255, _
    20, 0, 28, 0, 30, 0, 30, 0, 32, 0, 14, 0, 33, 0, 15, 0, 15, 0, 12, 0, 255, 255, 35, 0, 4, 0, 13, 0, 251, 255, 6, 0)
 
 
    lPos = UBound(vTempSoundArray)
    ReDim Preserve vTempSoundArray(UBound(vTempSoundArray) + UBound(ar8) + 1)
    Call CopyMemory(ByVal VarPtr(vTempSoundArray(lPos + 1)), ByVal VarPtr(ar8(0)), VARIANT_OFFSET_FACTOR * (UBound(ar8) + 1))
    Erase ar8
 
    ar9 = Array(246, 255, 254, 255, 230, 255, 242, 255, 234, 255, 229, 255, 223, 255, 200, 255, 220, 255, 214, 255, 232, 255, 220, 255, 225, 255, 249, 255, 255, 255, 254, 255, _
    21, 0, 13, 0, 23, 0, 30, 0, 41, 0, 27, 0, 30, 0, 22, 0, 41, 0, 33, 0, 61, 0, 36, 0, 43, 0, 15, 0, 4, 0, 249, 255, _
    0, 0, 248, 255, 245, 255, 232, 255, 220, 255, 249, 255, 217, 255, 220, 255, 200, 255, 234, 255, 249, 255, 31, 0, 56, 0, 245, 255, 255, 255, 194, 255, _
    216, 255, 10, 0, 43, 0, 71, 0, 72, 0, 20, 0, 194, 255, 208, 255, 221, 255, 60, 0, 92, 0, 222, 255, 226, 255, 156, 255, 35, 255, 62, 255, _
    97, 255, 89, 255, 97, 0, 200, 255, 41, 0, 51, 1, 144, 0, 74, 1, 99, 1, 137, 0, 89, 0, 187, 255, 39, 255, 83, 255, 157, 255, 253, 255, _
    228, 0, 8, 0, 12, 1, 40, 1, 214, 255, 140, 0, 19, 255, 17, 255, 8, 0, 93, 255, 214, 255, 185, 255, 70, 254, 39, 255, 172, 254, 15, 254)
 
 
    lPos = UBound(vTempSoundArray)
    ReDim Preserve vTempSoundArray(UBound(vTempSoundArray) + UBound(ar9) + 1)
    Call CopyMemory(ByVal VarPtr(vTempSoundArray(lPos + 1)), ByVal VarPtr(ar9(0)), VARIANT_OFFSET_FACTOR * (UBound(ar9) + 1))
    Erase ar9
 
    ar10 = Array(250, 255, 66, 255, 3, 0, 114, 0, 74, 255, 55, 0, 57, 0, 94, 1, 152, 1, 97, 1, 57, 1, 39, 1, 162, 0, 158, 1, 14, 1, 65, 0, _
    254, 0, 26, 255, 139, 255, 176, 255, 254, 254, 150, 255, 244, 255, 84, 255, 9, 0, 244, 255, 59, 255, 213, 255, 62, 255, 26, 255, 164, 255, 182, 255, _
    10, 0, 34, 0, 11, 0, 209, 255, 116, 255, 145, 255, 206, 255, 147, 255, 235, 255, 169, 255, 4, 255, 51, 0, 123, 255, 49, 0, 84, 0, 136, 0, _
    141, 0, 249, 0, 26, 1, 252, 0, 116, 1, 89, 1, 29, 1, 3, 1, 12, 1, 52, 0, 99, 0, 237, 255, 195, 255, 78, 255, 115, 255, 16, 255, _
    157, 254, 238, 254, 155, 254, 189, 254, 49, 255, 197, 254, 19, 255, 171, 255, 62, 255, 92, 0, 52, 0, 70, 0, 149, 0, 128, 0, 112, 0, 7, 1, _
    255, 0, 209, 0, 236, 0, 208, 255, 217, 255, 84, 255, 13, 255, 116, 255, 115, 255, 188, 255, 11, 0, 158, 0, 134, 0, 134, 1, 28, 1, 46, 1, _
    199, 0, 40, 1, 102, 0, 65, 0, 114, 0, 103, 255, 156, 0, 142, 254, 33, 0, 30, 255, 205, 254, 124, 255, 22, 254, 148, 254, 186, 254, 158, 254)
 
 
    lPos = UBound(vTempSoundArray)
    ReDim Preserve vTempSoundArray(UBound(vTempSoundArray) + UBound(ar10) + 1)
    Call CopyMemory(ByVal VarPtr(vTempSoundArray(lPos + 1)), ByVal VarPtr(ar10(0)), VARIANT_OFFSET_FACTOR * (UBound(ar10) + 1))
    Erase ar10
    Call SetTimer(Application.hwnd, 0, 0, AddressOf BuildSoundArray5)

End Sub

Private Sub BuildSoundArray5()

    Dim ar11() As Variant, ar12() As Variant, ar13() As Variant, lPos As Long
 
    Call KillTimer(Application.hwnd, 0)
 
    ar11 = Array(78, 255, 170, 255, 210, 254, 136, 0, 113, 255, 36, 0, 210, 0, 106, 0, 15, 1, 185, 1, 173, 0, 251, 0, 247, 0, 215, 0, 115, 1, 176, 0, _
    112, 0, 215, 255, 103, 255, 25, 0, 234, 255, 25, 0, 178, 0, 58, 255, 217, 255, 122, 255, 223, 254, 231, 255, 146, 255, 128, 255, 112, 0, 20, 0, _
    45, 0, 72, 0, 157, 255, 137, 255, 85, 255, 116, 255, 138, 255, 180, 255, 226, 255, 148, 255, 182, 255, 139, 255, 123, 255, 250, 255, 224, 255, 18, 0, _
    217, 255, 78, 0, 40, 0, 200, 0, 195, 0, 2, 1, 181, 0, 62, 1, 7, 1, 187, 0, 79, 1, 116, 0, 180, 0, 71, 0, 12, 0, 133, 255, _
    187, 255, 79, 255, 100, 255, 55, 255, 73, 255, 206, 254, 217, 254, 21, 255, 149, 254, 115, 255, 75, 255, 198, 255, 203, 255, 70, 0, 214, 255, 126, 0, _
    68, 0, 103, 0, 190, 0, 112, 0, 128, 0, 128, 0, 63, 0, 21, 0, 114, 0, 219, 255, 76, 0, 31, 0, 30, 0, 134, 0, 14, 0, 149, 0)
 
 
    lPos = UBound(vTempSoundArray)
    ReDim Preserve vTempSoundArray(UBound(vTempSoundArray) + UBound(ar11) + 1)
    Call CopyMemory(ByVal VarPtr(vTempSoundArray(lPos + 1)), ByVal VarPtr(ar11(0)), VARIANT_OFFSET_FACTOR * (UBound(ar11) + 1))
    Erase ar11
 
    ar12 = Array(116, 0, 84, 0, 177, 0, 84, 0, 54, 0, 50, 0, 185, 255, 208, 255, 174, 255, 149, 255, 190, 255, 49, 255, 82, 255, 36, 255, 53, 255, 97, 255, _
    138, 255, 110, 255, 164, 255, 96, 255, 101, 255, 208, 255, 177, 255, 157, 0, 90, 0, 212, 0, 115, 0, 134, 0, 208, 0, 165, 0, 189, 0, 108, 0, _
    35, 0, 26, 0, 198, 255, 164, 255, 254, 255, 212, 255, 135, 0, 252, 255, 245, 255, 229, 0, 112, 0, 223, 0, 196, 0, 228, 255, 228, 255, 229, 254, _
    201, 254, 44, 255, 13, 255, 183, 255, 85, 0, 213, 255, 126, 0, 185, 0, 129, 255, 123, 255, 175, 254, 65, 255, 250, 255, 189, 255, 89, 0, 71, 0, _
    112, 255, 218, 255, 178, 255, 83, 255, 252, 0, 170, 0, 31, 1, 160, 0, 175, 255, 127, 0, 253, 255, 54, 0, 149, 0, 230, 255, 218, 255, 239, 0, _
    208, 255, 178, 0, 241, 0, 71, 0, 240, 0, 69, 255, 235, 254, 32, 255, 222, 254, 103, 255, 241, 0, 172, 255, 65, 1, 67, 1, 126, 255, 2, 1)
 
 
    lPos = UBound(vTempSoundArray)
    ReDim Preserve vTempSoundArray(UBound(vTempSoundArray) + UBound(ar12) + 1)
    Call CopyMemory(ByVal VarPtr(vTempSoundArray(lPos + 1)), ByVal VarPtr(ar12(0)), VARIANT_OFFSET_FACTOR * (UBound(ar12) + 1))
    Erase ar12
 
    ar13 = Array(17, 255, 177, 255, 255, 255, 211, 254, 63, 0, 53, 255, 251, 254, 72, 255, 208, 253, 38, 254, 13, 255, 228, 254, 39, 0, 149, 0, 215, 255, 22, 1, _
    114, 0, 37, 1, 119, 1, 141, 1, 194, 1, 200, 1, 212, 1, 235, 1, 254, 1, 163, 1, 125, 1, 225, 255, 216, 255, 197, 254, 39, 254, 32, 254, _
    20, 254, 18, 254, 181, 254, 233, 254, 106, 254, 38, 255, 132, 254, 79, 255, 85, 255, 140, 255, 97, 0, 156, 0, 242, 0, 40, 1, 9, 1, 210, 0, _
    208, 0, 128, 0, 103, 0, 166, 255, 239, 255, 145, 255, 105, 255, 185, 255, 106, 255, 46, 0, 245, 255, 186, 0, 143, 0, 212, 0, 71, 1, 58, 1, _
    103, 1, 116, 1, 52, 1, 5, 1, 229, 0, 97, 0, 161, 0, 97, 255, 185, 255, 10, 254, 26, 254, 118, 253, 60, 253, 129, 253, 119, 253, 233, 253, _
    47, 254, 226, 254, 134, 254, 26, 0, 150, 255, 72, 1, 62, 1, 30, 2, 81, 2, 88, 2, 173, 2, 43, 2, 121, 2, 175, 1, 208, 1, 194, 0)
 
 
    lPos = UBound(vTempSoundArray)
    ReDim Preserve vTempSoundArray(UBound(vTempSoundArray) + UBound(ar13) + 1)
    Call CopyMemory(ByVal VarPtr(vTempSoundArray(lPos + 1)), ByVal VarPtr(ar13(0)), VARIANT_OFFSET_FACTOR * (UBound(ar13) + 1))
    Erase ar13
    Call SetTimer(Application.hwnd, 0, 0, AddressOf BuildSoundArray6)
 
End Sub

Private Sub BuildSoundArray6()

    Dim ar14() As Variant, ar15() As Variant, ar16() As Variant, lPos As Long
 
    Call KillTimer(Application.hwnd, 0)
 
    ar14 = Array(180, 0, 231, 255, 150, 255, 7, 255, 182, 254, 80, 254, 147, 254, 132, 254, 182, 254, 20, 255, 173, 254, 128, 255, 65, 255, 20, 0, 249, 255, 89, 0, _
    169, 0, 84, 0, 189, 0, 45, 0, 91, 0, 153, 255, 247, 255, 25, 255, 109, 255, 224, 254, 248, 254, 133, 255, 60, 255, 55, 0, 215, 255, 148, 0, _
    83, 0, 243, 0, 186, 0, 122, 1, 2, 1, 206, 1, 144, 1, 108, 1, 195, 1, 211, 0, 14, 1, 60, 0, 63, 0, 125, 255, 200, 255, 203, 254, _
    60, 255, 32, 254, 121, 254, 242, 253, 249, 253, 53, 254, 13, 254, 197, 254, 143, 254, 143, 255, 76, 255, 65, 0, 23, 0, 240, 0, 221, 0, 43, 1, _
    17, 1, 92, 1, 47, 1, 59, 1, 51, 1, 56, 1, 94, 1, 227, 0, 34, 1, 136, 0, 182, 0, 28, 0, 25, 0, 75, 255, 53, 255, 215, 254, _
    50, 255, 200, 254, 214, 255, 215, 255, 232, 255, 125, 0, 150, 255, 149, 0, 153, 255, 0, 0, 244, 255, 222, 254, 144, 255, 231, 254, 162, 254, 125, 254, _
    57, 254, 191, 254, 241, 254)
 
    lPos = UBound(vTempSoundArray)
    ReDim Preserve vTempSoundArray(UBound(vTempSoundArray) + UBound(ar14) + 1)
    Call CopyMemory(ByVal VarPtr(vTempSoundArray(lPos + 1)), ByVal VarPtr(ar14(0)), VARIANT_OFFSET_FACTOR * (UBound(ar14) + 1))
    Erase ar14
 
    bSoundCreated = True

End Sub



3- Code Usage Example in the UserForm Module (as per test workbook)
VBA Code:
Option Explicit

Private Sub UserForm_Activate()
    Call CreateClock(Me, 250, "Arial", 30, vbYellow, vbWhite, vbCyan, vbRed, vbGreen, vbWhite, 8, , , True)
End Sub

Private Sub UserForm_Terminate()
    Call DeleteClock
End Sub


Tested only on Win10 x64bit Excel 2016 x64... I hope the code behaves as expected under other environnements.

Regards.
 
Last edited:
Upvote 0
It's not work for me:

1674644137942.png
 
Upvote 0

Forum statistics

Threads
1,214,988
Messages
6,122,620
Members
449,092
Latest member
amyap

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