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.
 
When I ddissable thì line, it's work properly:
"Call AccessibleObjectFromPoint(tCurPos.x, tCurPos.y, oIA, 0&)"
 

Attachments

  • It's work.jpg
    It's work.jpg
    195.9 KB · Views: 9
Upvote 0

Excel Facts

What did Pito Salas invent?
Pito Salas, working for Lotus, popularized what would become to be pivot tables. It was released as Lotus Improv in 1989.
Stupid me !!

I forgot to write the correct declarations for the AccessibleObjectFromPoint API so that it works in Excel x32bit.

This should be the correct declaration :
VBA Code:
#If VBA7 Then
    #If Win64 Then
        Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal arg1 As LongLong, ppacc As Any, pvarChild As Variant) As Long
    #Else
        Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal lX As Long, ByVal lY As Long, ppacc As IAccessible, pvarChild As Variant) As Long
    #End If
#Else
    Private Declare Function AccessibleObjectFromPoint Lib "oleacc" (ByVal lX As Long, ByVal lY As Long, ppacc As IAccessible, pvarChild As Variant) As Long
#End If

I can't edit the code I posted in (Post#19) because the forum 10 mins editing time is up but I have now updated the code in the workbook demo .

Please, try downloading the workbook again from the file sharing site in order to obtain the correct code.

Thanks cuongeva for bringing that to my attention and I hope this achieves what you wanted.
 
Last edited:
Upvote 0
Stupid me !!

I forgot to write the correct declarations for the AccessibleObjectFromPoint API so that it works in Excel x32bit.

This should be the correct declaration :
VBA Code:
#If VBA7 Then
    #If Win64 Then
        Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal arg1 As LongLong, ppacc As Any, pvarChild As Variant) As Long
    #Else
        Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal lX As Long, ByVal lY As Long, ppacc As IAccessible, pvarChild As Variant) As Long
    #End If
#Else
    Private Declare Function AccessibleObjectFromPoint Lib "oleacc" (ByVal lX As Long, ByVal lY As Long, ppacc As IAccessible, pvarChild As Variant) As Long
#End If

I can't edit the code I posted in (Post#19) because the forum 10 mins editing time is up but I have now updated the code in the workbook demo .

Please, try downloading the workbook again from the file sharing site in order to obtain the correct code.

Thanks cuongeva for bringing that to my attention and I hope this achieves what you wanted.

Thank you very much sir.
It has been run very good at this time.
I will check it more and put it to my project then will be respond to you in next time...
 
Upvote 0
Jaafar T,

Please look at the clock in UserForm1 (Form Clock) the 10 and 11 hours are slightly covered - you can't see the numbers completely. Please fix.

Otherwise, you are a wizard :)

Tom
 
Upvote 0
Jaafar T,

Please look at the clock in UserForm1 (Form Clock) the 10 and 11 hours are slightly covered - you can't see the numbers completely. Please fix.

Otherwise, you are a wizard :)

Tom
Hi Tom.

Thanks for testing.

Yes, I noticed that. This is due to the InvalidateRgn api call on the SecondsHand inner region which is the longest of the clock arrows.

The fix is really easy:

It is the user responsabilty to set the correct font size which can be easily done via the 4th argument of the CreateClock routine... I meant to design the code following this logic on purpose to give the user full flexibility for setting the required parameters according to the overall size of the clock.

So instead of having Font size 30, start decreasing the font size bit by bit until you reach the optimal value.

For example, if you reduce the Font size from 30 to 26 as follows, it should fix the issue and the 10 and 11 hours will no longer get slightly covered.
.
Call CreateClock(Me, 250, "Arial", 26, ......

Regards.
 
Last edited:
Upvote 0
It is the user responsabilty to set the correct font size which can be easily done via the 4th argument of the CreateClock routine.

So instead of having Font size 30, start decreasing the font size bit by bit until you reach the optimal value.

For example, if you set the font size to 26 as follows, it should fix the issue and the 10 and 11 hours will no longer get slightly covered.
.
Call CreateClock(Me, 250, "Arial", 26, ......
Thank you. Now is PERFECT !!!
 
Upvote 0
Thank you. Now is PERFECT !!!
Thanks for the feedback.

BTW, each one of the 14 arguments in the CreateClock routine follows the same logic. Their respective values are all adjustable.

Tom, one last thing: Does the clock ticktock sound work for you as expected ? I am just curious as I have only teted the sound on my pc.
 
Upvote 0
Hi

I checked it on my current laptop - Microsoft 365 MSO (Version 2212 Build 16.0.15928.20196) 32-bit. I can confirm that (1) it works on 32bit (it's great!), and (2) I clock's ticktock sound works (and is nicely in sync with the second-hand movement!). I've also tried the various settings, and haven't encountered any problems.

I looked at the original version to see what you changed, and to learn what I can from it. Doubtless, a lot of it is a reflection of what you've learnt over the decade+ since the original version. I've been trying to come to grips with GDI/GDI+ APIs, and have trying to make my own PictureBox class (that mirrors the VB6 control), so my questions/observations below are asked/posed in the (admittedly, very selfish) context of - "how can improve my own project?" :) Your thoughts on any of the following is (as always) greatly appreciated:
  • GetWindowDC (original) v GetDC - I had no idea GetWindowDC existed - is there a difference between the two? I assumed not, but I was just wondering and just wanted to check.
  • GDI+ - One big difference is that the new version now uses GDI+. Your graphics code is always useful guide for me on how to use GDI/GDI+ APIs without causing memory leaks (which I struggled wrapping my head around last year) and invariably crashing Excel! I'm wondering what prompted you to use GDI+ now, and - on a related point - why use CreateEllipticRgn and not the GDI or GDI+ equivalent? I wonder whether it might have something to do with it being a region / hittest?'
  • Dummy Parameters - You've used dummy parameters in the procedure declaration signatures - I've seen this before a few times by others, and I've always been curious as to why it's been written this way.
  • ReleaseDC - In the original, I noticed that you GetWindowDC/ReleaseDC on each run of the clock, but not in the new version, where it is released when the window is closed down. The latter approach is what I've used for the PictureBox class. I've only just realised that initialize/terminate the GDI+, though, at the start and end of every drawing procedure - lines, rectangles, etc - and I'm wondering now if I don't need to, and like here, I can termiante the GDI+ at the termination of the class along with the ReleaseDC, etc.
  • Sound - I had come across The Trick's method of tricking the PlaySound API to play MP3 files as WAV files on the VBForum's site, and it works nicely (especially to dramatically reduce the overall file size!), but it has a problem with really small MP3 files - like 1 second sound effects. Doubtless, your code above will solve that issue for me - thank you!
  • AutoRedraw - Obviously, I saw your comment in the new code, and this has been the principal challenge I've had to overcome for the Picturebox Class - I think I've managed to solve it thanks to your code solutions and a project on VbAccelarator, but I'll find out soon enough once I upload it onto github!
Thank you (again!).
 
Upvote 0

Forum statistics

Threads
1,215,349
Messages
6,124,427
Members
449,158
Latest member
burk0007

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