Jaafar Tribak

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

I have just completed this code which as the thread title says, it adds a balloon tip to the worksheets of your choice... Having a tooltip displaying info about the sheet when placing the mouse pointer over the tab can be useful and fun.

The code is based on the sheet CodeName so that it keeps identifying the correct sheet even if the user changes the sheet name.

I have written the code in excel 2016-64bit but hopefully, it should work fine in other excel versions.

Although the code makes API calls, it should be stable and (hopefully) won't crash excel even if an unhandled error occurs while running.


Workbook Download



TabTips.gif






1- Class Code ( Class name is : clsTabTips)
VBA Code:
Option Explicit

Private WithEvents wb As Workbook
Private WithEvents cmb As CommandBars
Private WithEvents cmbTimeOut As CommandBars

Private Enum ICON_TYPE
    I_NoIcon
    I_Info
    I_Warning
    I_Error
End Enum

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 TOOLINFO
   cbSize    As Long
   uFlags    As Long
   #If VBA7 Then
        hwnd      As LongPtr
        uId       As LongPtr
        cRect     As RECT
        hinst     As LongPtr
   #Else
        hwnd      As Long
        uId       As Long
        cRect     As RECT
        hinst     As Long
   #End If
   lpszText  As String
End Type

Private Type InitCommonControlsEx
   Size As Long
   ICC As Long
End Type

Private Type ToolTip
    SheetCodeName As String * 256
    Title As String * 256
    Text As String * 256
    Icon As ICON_TYPE
    SystemLook As Boolean
    BackColor As XlRgbColor
    TextColor As XlRgbColor
    Beep As Boolean
    TimeOut As Single
End Type


#If VBA7 Then
    #If Win64 Then
        Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal arg1 As LongPtr, 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
    Private Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
    Private Declare PtrSafe Function IsWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
    Private Declare PtrSafe Function GetActiveWindow Lib "user32" () As LongPtr
    Private Declare PtrSafe Function InitCommonControlsEx Lib "comctl32.dll" (iccex As InitCommonControlsEx) 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 GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As LongPtr
    Private Declare PtrSafe Function DestroyWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
    Private Declare PtrSafe Function SendMessage Lib "user32.dll" Alias "SendMessageA" (ByVal hwnd As LongPtr, ByVal wMsg As Long, ByVal wParam As LongPtr, ByRef lParam As Any) As LongPtr
    Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
    Private Declare PtrSafe Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As LongPtr
#Else
    Private Declare Function AccessibleObjectFromPoint Lib "oleacc" (ByVal lX As Long, ByVal lY As Long, ppacc As IAccessible, pvarChild As Variant) As Long
    Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
    Private Declare Function IsWindow Lib "user32" (ByVal hwnd As Long) As Long
    Private Declare Function GetActiveWindow Lib "user32" () As Long
    Private Declare Function InitCommonControlsEx Lib "comctl32.dll" (iccex As InitCommonControlsEx) 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 GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As Long
    Private Declare Function DestroyWindow Lib "user32" (ByVal hwnd As Long) As Long
    Private Declare Function SendMessage Lib "user32.dll" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByRef lParam As Any) As Long
    Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
    Private Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long
#End If


Private tToolTipsArray() As ToolTip, sSheetCodeNamesArray() As String
Private sngTipStartTime As Single, sngTipTimeOut As Single


Private Sub Class_Initialize()
    Set wb = ThisWorkbook
End Sub

Private Sub Class_Terminate()
    Call RemoveToolTip(True)
End Sub


Public Sub Add(ByVal TipsCollection)

    #If VBA7# Then
        Dim lPtr As LongPtr
    #Else
        Dim lPtr As Long
    #End If

    Dim tTemp() As ToolTip, lNullCharPos As Long, i As Integer

    ReDim tTemp(TipsCollection.Count)
    ReDim sSheetCodeNamesArray(TipsCollection.Count)

    For i = 1 To TipsCollection.Count
        lPtr = TipsCollection(i)
        Call CopyMemory(ByVal VarPtr(tTemp(i - 1)), ByVal lPtr, LenB(tTemp(i - 1)))
        lNullCharPos = InStr(1, tTemp(i - 1).SheetCodeName, vbNullChar, vbTextCompare)
        sSheetCodeNamesArray(i - 1) = Left(tTemp(i - 1).SheetCodeName, lNullCharPos)
    Next i

    tToolTipsArray = tTemp

    Set cmb = Application.CommandBars
    Call cmb_OnUpdate

End Sub


Private Sub cmb_OnUpdate()

    Const ROLE_SYSTEM_HELPBALLOON = &H1F
    Const ROLE_SYSTEM_PAGETAB = &H25
    Const CHILDID_SELF = &H0&
    Const S_OK = &H0

    Static oPrveAcc As IAccessible

    Dim vChild As Variant, oIAcc As IAccessible, oIAParent As IAccessible
    Dim tCurPos As POINTAPI, sTextUnderMouse As String, indx As Long


    On Error Resume Next

    If Not ActiveWorkbook Is ThisWorkbook Then GoTo Xit

    Call GetCursorPos(tCurPos)

    #If Win64 Then
        Dim lPt As LongPtr
        Call CopyMemory(lPt, tCurPos, LenB(lPt))
        If AccessibleObjectFromPoint(lPt, oIAcc, vChild) = S_OK Then
    #Else
        If AccessibleObjectFromPoint(tCurPos.x, tCurPos.y, oIAcc, vChild) = S_OK Then
    #End If

            If oIAcc.accRole(CHILDID_SELF) = ROLE_SYSTEM_PAGETAB Then
                If oPrveAcc.accName(CHILDID_SELF) <> oIAcc.accName(CHILDID_SELF) Then
            
                    Set oIAParent = oIAcc.accParent
                    If oIAParent.accName(CHILDID_SELF) = "Sheet Tabs" Then
                        sTextUnderMouse = oIAcc.accName(0&)
                        sTextUnderMouse = GetSheetCodeName(sTextUnderMouse)
                        indx = Application.Match(sTextUnderMouse, sSheetCodeNamesArray, 0)
                        If indx Then
                            Call CreateToolTip(tToolTipsArray(indx - 1))
                        Else
                            Call RemoveToolTip
                        End If
                    End If
                End If
            Else
                Call RemoveToolTip
            End If
        End If

Xit:

    Set oPrveAcc = oIAcc

    If GetActiveWindow <> Application.hwnd Or _
        oIAcc.accRole(CHILDID_SELF) = ROLE_SYSTEM_HELPBALLOON Then
            Call RemoveToolTip
    End If

    Application.CommandBars.FindControl(ID:=2040).Enabled = _
    Not Application.CommandBars.FindControl(ID:=2040).Enabled

End Sub




Private Sub CreateToolTip(ToolTipStruct As ToolTip)

    Const CW_USEDEFAULT = &H80000000
    Const WS_POPUP = &H80000000
    Const WM_USER = &H400
    Const TTS_BALLOON = &H40
    Const TTS_NOPREFIX = &H2
    Const TTM_ADDTOOL = (WM_USER + 4)
    Const TTM_TRACKACTIVATE = (WM_USER + 17)
    Const TTM_TRACKPOSITION = (WM_USER + 18)
    Const TTM_SETTITLEA = (WM_USER + 32)
    Const TTM_SETTIPBKCOLOR = (WM_USER + 19)
    Const TTM_SETTIPTEXTCOLOR = WM_USER + 20
    Const TTF_TRACK = &H20
    Const ICC_WIN95_CLASSES = &HFF

    #If VBA7 Then
        Dim hToolTip As LongPtr
    #Else
            Dim hToolTip As Long
    #End If

    Dim tToolInfo As TOOLINFO, tCurPos As POINTAPI, tIccex As InitCommonControlsEx, lIcon As ICON_TYPE
    Dim sTitle As String, sText As String
    Dim lBackColor As Long, lForeColor As Long
    Dim bSysLook As Boolean, bBeep As Boolean
    Dim sngTimeOut As Single, lNullCharPos As Long

    With ToolTipStruct
        lNullCharPos = InStr(1, .Title, vbNullChar, vbTextCompare)
        sTitle = Left(.Title, lNullCharPos)
        lNullCharPos = InStr(1, .Text, vbNullChar, vbTextCompare)
        sText = Left(.Text, lNullCharPos)
        lIcon = .Icon
        bSysLook = .SystemLook
        lBackColor = .BackColor
        lForeColor = .TextColor
        bBeep = .Beep
        sngTimeOut = .TimeOut
    End With

    Call RemoveToolTip

    Call GetCursorPos(tCurPos)
            
    If IsWindow(hToolTip) = 0 Then

        With tIccex
            .Size = LenB(tIccex)
            .ICC = ICC_WIN95_CLASSES
        End With
    
        Call InitCommonControlsEx(tIccex)
    
        hToolTip = CreateWindowEx(0, "tooltips_class32", "MyToolTip", WS_POPUP Or TTS_BALLOON Or TTS_NOPREFIX, _
        CW_USEDEFAULT, CW_USEDEFAULT, CW_USEDEFAULT, CW_USEDEFAULT, 0, 0, GetModuleHandle(vbNullString), 0)
    
        If hToolTip Then
    
            With tToolInfo
                .cbSize = LenB(tToolInfo)
                .uFlags = TTF_TRACK
                .lpszText = sText
            End With
        
            Call SendMessage(hToolTip, TTM_SETTITLEA, lIcon, ByVal sTitle)
            Call SendMessage(hToolTip, TTM_ADDTOOL, 0, tToolInfo)
        
            If Not bSysLook Then
                Call SendMessage(hToolTip, TTM_SETTIPBKCOLOR, lBackColor, 0)
                Call SendMessage(hToolTip, TTM_SETTIPTEXTCOLOR, lForeColor, 0)
            End If
        
            With tCurPos
                Call SendMessage(hToolTip, TTM_TRACKACTIVATE, True, tToolInfo)
                Call SendMessage(hToolTip, TTM_TRACKPOSITION, ByVal 0&, ByVal MakeDWord(CInt(.x), CInt(.y)))
            End With
        
            If bBeep Then
                Call Beep
            End If
        
            If sngTimeOut Then
                sngTipTimeOut = sngTimeOut
                If sngTipTimeOut >= 20 Then sngTipTimeOut = 20
                If sngTipTimeOut <= 1 Then sngTipTimeOut = 1
                sngTipStartTime = Timer
                Set cmbTimeOut = Application.CommandBars
            End If
        
        End If
    
    End If


End Sub


Private Sub cmbTimeOut_OnUpdate()
    If Timer - sngTipStartTime >= sngTipTimeOut Then
           Call RemoveToolTip(True)
    End If
End Sub


Private Function GetSheetCodeName(ByVal TabName As String) As String

    Dim i As Long

    For i = 1 To ThisWorkbook.Sheets.Count
        If ThisWorkbook.Sheets(i).Name = TabName Then
            GetSheetCodeName = ThisWorkbook.Sheets(i).CodeName
            Exit Function
        End If
    Next

End Function

Private Sub RemoveToolTip(Optional ByVal StopTimeOutEvents As Boolean = False)

    If StopTimeOutEvents Then
        Set cmbTimeOut = Nothing
    End If

    If IsWindow(FindWindow("tooltips_class32", "MyToolTip")) Then
        Call DestroyWindow(FindWindow("tooltips_class32", "MyToolTip"))
    End If

End Sub

Private Function loword(DWord As Long) As Integer
    If DWord And &H8000& Then
        loword = DWord Or &HFFFF0000
    Else
        loword = DWord And &HFFFF&
    End If
End Function

Private Function hiword(ByVal DWord As Long) As Integer
    hiword = (DWord And &HFFFF0000) \ &H10000
End Function

Private Function MakeDWord(loword As Integer, hiword As Integer) As Long
    MakeDWord = (hiword * &H10000) Or (loword And &HFFFF&)
End Function

Private Sub wb_Deactivate()
        Call RemoveToolTip(True)
End Sub



2- Code Usage Example in a Standard Module:
VBA Code:
Option Explicit

Private Enum ICON_TYPE
    I_NoIcon
    I_Info
    I_Warning
    I_Error
End Enum

Private Type ToolTip
    SheetCodeName As String * 256
    Title As String * 256
    Text As String * 256
    Icon As ICON_TYPE
    SystemLook As Boolean
    BackColor As XlRgbColor
    TextColor As XlRgbColor
    Beep As Boolean
    TimeOut As Single
End Type

Private oTabTips As clsTabTips


Sub Test()

    Dim oTip1 As ToolTip
    Dim oTip2 As ToolTip
    Dim oTip3 As ToolTip
    Dim oTip4 As ToolTip
    Dim oTip5 As ToolTip

    Dim oCol As Collection


    With oTip1
        .SheetCodeName = Sheet1.CodeName & vbNullChar
        .Title = Sheet1.Name & vbNullChar
        .Text = "This is a Balloon Tooltip with no custom formatting." & vbNewLine & _
        "The Tooltip has a timer set and will vanish in 10 Secs." & vbNullChar
        .Icon = I_Info
        .SystemLook = True
        .Beep = True
        .TimeOut = 10
    End With

    With oTip2
        .SheetCodeName = Sheet2.CodeName & vbNullChar
        .Title = Sheet2.Name & vbNullChar
        .Text = "The Balloon attributes won't change even if the tab name is changed." & vbNullChar
        .Icon = I_Warning
        .BackColor = rgbAliceBlue
        .TextColor = rgbDarkSlateGray
    End With

    With oTip3
        Dim sText As String, i As Long
        sText = "Max Charcters 256." & vbNewLine & vbNewLine
        sText = sText & "Testing a long text entry."
        For i = 1 To 7
            sText = sText & vbNewLine & "Testing a long text entry."
        Next i
        .SheetCodeName = Sheet3.CodeName & vbNullChar
        .Title = Sheet3.Name & vbNullChar
        .Text = sText & vbNullChar
        .Icon = I_NoIcon
        .BackColor = rgbGreenYellow
        .TextColor = rgbDarkSlateGray
    End With

    With oTip4
        .SheetCodeName = Sheet4.CodeName & vbNullChar
        .Title = Sheet4.Name & vbNullChar
        .Text = "This is a Balloon Tooltip with no custom formatting." & vbNewLine & _
        "The Tooltip has a timer set and will vanish in 10 Secs." & vbNullChar
        .Icon = I_Info
        .BackColor = rgbLightGray
        .TextColor = rgbDarkRed
        .Beep = True
    End With

    With oTip5
        .SheetCodeName = Sheet5.CodeName & vbNullChar
        .Title = Sheet5.Name & vbNullChar
        .Text = "Just another TabTip !" & vbNullChar
        .Icon = I_Info
        .BackColor = rgbMistyRose
    End With


    Set oCol = New Collection

    oCol.Add VarPtr(oTip1)
    oCol.Add VarPtr(oTip2)
    oCol.Add VarPtr(oTip3)
    oCol.Add VarPtr(oTip4)
    oCol.Add VarPtr(oTip5)

    Set oTabTips = New clsTabTips

    oTabTips.Add oCol

End Sub


Sub StopTest()

    Set oTabTips = Nothing

End Sub
 
On the topic of manifests, if I may ask, what are they and how do we use them? I see them referenced in VB6,, but it's not clear to me how this applies to VBA.
Hi Dan,

I like to think of application manifests as the Office Ribbon XML which defines the ribbon user interface. The manifest is an xml file that informs Windows how to handle a program when it is started. Things that may be included in the manifest are info such as whether the program should need admin privileges, which visual styles should be used, DPI and theme awareness, layered child windows ... etc. By using manifests, a program chooses which version of a dll to load. This is the case with the common controls dll which is what we are using here for creating the tooltips. My understanding is that some control modern looking styles\settings require Common Controls 6.0 to be enabled via a manifest.

The manifest is embedded in an exe as as resource but it can also be located in a separate xml file... Some time ago, to my surprise, I found out that we can even apply the manifest at runtime via Activation Contexts functions such as CreateActCtx\ActivateActCtx apis. This is super ideal for non-exe programs like vba as well as for ease of portability as we can easily build the small temp xml manifest file and pass it to the CreateActCtx api. I have successfully done this in the past for adding icons with text to button controls.

I think (hopefully) the issue brought up by Tobi Shi regarding the Righ-To-Left (WS_EX_LAYOUTRTL Ex_Style) reading order tooltip popping out in the wrong location should be solved if we enable the CC6 via a manifest.
 
Last edited:
Upvote 1

Excel Facts

When they said...
When they said you are going to "Excel at life", they meant you "will be doing Excel your whole life".
Thank you! That's a very helpful explanation- by comparing it to the Ribbon, it makes a whole lot of sense.

I dont know if its in anyway helpful, but I know that the topic of manifests came up very briefly in MountainMan's tooltip class (A Tooltips Class-VBForums), but it seems that the proposed manifest is contained in a res file (which I haven't yet worked out how to access from VBA).
 
Upvote 0
Thank you! That's a very helpful explanation- by comparing it to the Ribbon, it makes a whole lot of sense.

I dont know if its in anyway helpful, but I know that the topic of manifests came up very briefly in MountainMan's tooltip class (A Tooltips Class-VBForums), but it seems that the proposed manifest is contained in a res file (which I haven't yet worked out how to access from VBA).
Hi Dan,
MountainMan's tooltip zip doesn't contain a compiled exe so no res file with manifest is included.
I think he also mentions he couldn't turn off Windows visual themes in order to apply his own attributes to the tooltip such as text color, backcolor and so on.
Anyways, I will be posting next the code that I have just finished writing... The manifest is going to be added at runtime from the xml file bytes which I are extracted from a byte array prior and written to a temp file.

EDIT:
Here is the manifest xml for future reference:
VBA Code:
<?xml version="1.0" encoding="UTF-8" standalone="yes"?>
<assembly xmlns="urn:schemas-microsoft-com:asm.v1" manifestVersion="1.0">
<assemblyIdentity
version="1.0.0.0"
processorArchitecture="*"
name="CompanyName.ProductName.YourApp"
type="win32"
/>
<description>Your application description here.</description>
<dependency>
<dependentAssembly>
<assemblyIdentity
type="win32"
name="Microsoft.Windows.Common-Controls"
version="6.0.0.0"
processorArchitecture="*"
publicKeyToken="6595b64144ccf1df"
language="*"
/>
</dependentAssembly>
</dependency>
</assembly>
 
Upvote 0
Sorry, I meant the proposed manifest referenced in the comments to the thread (by DaveDavis) but it seems like it might be a broken ink.
 
Upvote 0
Ok, here is the new code that will hopefully prevent the issue with the Right-To-Left (Arabic & Hebrew) ToolTip screen location. and other visual style problems.

Download:
TabTipsUnicodeWithManifest.xlsm







1- CTabTips Class:
VBA Code:
Option Explicit

Private WithEvents CmndBars As CommandBars

'__________________________________________ Class Init\Term Events ___________________________________________

Private Sub Class_Initialize()
    Call Init
End Sub

Private Sub Class_Terminate()
    Call Term
End Sub


'___________________________________________ Public Class Methods ______________________________________________

Public Sub AddToolTip( _
    ByVal Sh As Worksheet, _
    ByVal TipText As String, _
    Optional ByVal Icon As ICON_TYPE, _
    Optional ByVal Title As String, _
    Optional ByVal ForeColor As Long = -1&, _
    Optional ByVal BackColor As Long = -1&, _
    Optional ByVal Balloon As Boolean, _
    Optional ByVal FontName As String = "Segoe UI", _
    Optional ByVal FontSize As Long = 12&, _
    Optional ByVal FontBold As Boolean, _
    Optional ByVal PlaySound As Boolean, _
    Optional ByVal RightToLeftReadingOrder As Boolean, _
    Optional ByVal VisibleTime As Long = 5000& _
)


    If (Not sSheetCodeNamesArray) = -1& Then
        ReDim sSheetCodeNamesArray(0&) As String
        ReDim arText(0&) As String
        ReDim arIcon(0&) As Long
        ReDim arTitle(0&) As String
        ReDim arForeColor(0&) As Long
        ReDim arBackColor(0&) As Long
        ReDim arBalloon(0&) As Boolean
        ReDim arFontName(0&) As String
        ReDim arFontSize(0&) As Long
        ReDim arFontBold(0&) As Boolean
        ReDim arPlaySound(0&) As Boolean
        ReDim arRightToLeftReadingOrder(0&) As Boolean
        ReDim arVisibleTime(0&) As Long
    Else
        ReDim Preserve sSheetCodeNamesArray(UBound(sSheetCodeNamesArray) + 1&)
        ReDim Preserve arText(UBound(arText) + 1&)
        ReDim Preserve arIcon(UBound(arIcon) + 1&)
        ReDim Preserve arTitle(UBound(arTitle) + 1&)
        ReDim Preserve arForeColor(UBound(arForeColor) + 1&)
        ReDim Preserve arBackColor(UBound(arBackColor) + 1&)
        ReDim Preserve arBalloon(UBound(arBalloon) + 1&)
        ReDim Preserve arFontName(UBound(arFontName) + 1&)
        ReDim Preserve arFontSize(UBound(arFontSize) + 1&)
        ReDim Preserve arFontBold(UBound(arFontBold) + 1&)
        ReDim Preserve arPlaySound(UBound(arPlaySound) + 1&)
        ReDim Preserve arRightToLeftReadingOrder(UBound(arRightToLeftReadingOrder) + 1&)
        ReDim Preserve arVisibleTime(UBound(arVisibleTime) + 1&)
    End If
    
    sSheetCodeNamesArray(UBound(sSheetCodeNamesArray)) = Sh.Name
    arText(UBound(arText)) = TipText
    arIcon(UBound(arIcon)) = Icon
    arTitle(UBound(arTitle)) = Title
    arForeColor(UBound(arForeColor)) = ForeColor
    arBackColor(UBound(arBackColor)) = BackColor
    arBalloon(UBound(arBalloon)) = Balloon
    arFontName(UBound(arFontName)) = FontName
    arFontSize(UBound(arFontSize)) = FontSize
    arFontBold(UBound(arFontBold)) = FontBold
    arPlaySound(UBound(arPlaySound)) = PlaySound
    arRightToLeftReadingOrder(UBound(arRightToLeftReadingOrder)) = RightToLeftReadingOrder
    arVisibleTime(UBound(arVisibleTime)) = VisibleTime

End Sub

Public Sub Activate()
    If (Not sSheetCodeNamesArray) = -1& Then
        MsgBox "No tooltips have been added yet.", vbCritical, "Oops!!"
        Exit Sub
    End If
    Set CmndBars = Application.CommandBars
End Sub


'_________________________________________ Private Class Routines _______________________________________________

Private Sub CmndBars_OnUpdate()
    Call WatchObjUnderMousePointer
End Sub


2- API calls in a Standard Module:
VBA Code:
Option Explicit

Public Enum ICON_TYPE
    I_NoIcon
    I_Info
    I_Warning
    I_Error
End Enum

Public sSheetCodeNamesArray()      As String
Public arText()                    As String
Public arIcon()                    As Long
Public arTitle()                   As String
Public arForeColor()               As Long
Public arBackColor()               As Long
Public arBalloon()                 As Boolean
Public arFontName()                As String
Public arFontSize()                As Long
Public arFontBold()                As Boolean
Public arPlaySound()               As Boolean
Public arRightToLeftReadingOrder() As Boolean
Public arVisibleTime()             As Long

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

#If VBA7 Then
    #If Win64 Then
        Private Declare PtrSafe Function WindowFromPoint Lib "user32" (ByVal Point As LongLong) As LongLong
        Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal arg1 As LongLong, ppacc As Any, pvarChild As Variant) As Long
    #Else
        Private Declare PtrSafe Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As Long
        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
        Private Declare PtrSafe Function ActivateActCtx Lib "kernel32" (ByVal hActCtx As LongPtr, ByRef Cookie As LongPtr) As Long
        Private Declare PtrSafe Function CreateActCtx Lib "kernel32" Alias "CreateActCtxW" (ByRef ACTCTX As ACTCTXW) As LongPtr
        Private Declare PtrSafe Function DeactivateActCtx Lib "kernel32" (ByVal dwFlags As Long, ByVal Cookie As LongPtr) As Long
        Private Declare PtrSafe Sub ReleaseActCtx Lib "kernel32" (ByVal hActCtx As LongPtr)
        Private Declare PtrSafe Function InitCommonControls Lib "Comctl32" () As Long
        Private Declare PtrSafe Function IsUserAnAdmin Lib "Shell32" () As Long
        Private Declare PtrSafe Function SetWindowTheme Lib "UxTheme.dll" (ByVal hwnd As LongPtr, ByVal pszSubAppName As LongPtr, ByVal pszSubIdList As LongPtr) As Long
        Private Declare PtrSafe Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleW" (ByVal pModuleName As LongPtr) As LongPtr
        Private Declare PtrSafe Function SetProp Lib "user32" Alias "SetPropA" (ByVal hwnd As LongPtr, ByVal lpString As String, ByVal hData As LongPtr) As Long
        Private Declare PtrSafe Function GetProp Lib "user32" Alias "GetPropA" (ByVal hwnd As LongPtr, ByVal lpString As String) As LongPtr
        Private Declare PtrSafe Function RemoveProp Lib "user32" Alias "RemovePropA" (ByVal hwnd As LongPtr, ByVal lpString As String) As LongPtr
        Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
        Private Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
        Private Declare PtrSafe Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As LongPtr, ByVal hWnd2 As LongPtr, ByVal lpsz1 As String, ByVal lpsz2 As String) As LongPtr
        Private Declare PtrSafe Function IsWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
        Private Declare PtrSafe Function GetActiveWindow Lib "user32" () As LongPtr
        Private Declare PtrSafe Function InitCommonControlsEx Lib "comctl32.dll" (iccex As InitCommonControlsEx) As Long
        Private Declare PtrSafe Function CreateWindowEx Lib "user32" Alias "CreateWindowExW" (ByVal dwExStyle As Long, ByVal lpClassName As LongPtr, ByVal lpWindowName As LongPtr, 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 DestroyWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
        Private Declare PtrSafe Function SendMessage Lib "user32.dll" Alias "SendMessageW" (ByVal hwnd As LongPtr, ByVal wMsg As Long, ByVal wParam As LongPtr, ByRef lParam As Any) As LongPtr
        Private Declare PtrSafe Function SendMessageLong Lib "user32.dll" Alias "SendMessageW" (ByVal hwnd As LongPtr, ByVal wMsg As Long, ByVal wParam As LongPtr, ByVal lParam As LongPtr) As LongPtr
        Private Declare PtrSafe Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As LongPtr
        Private Declare PtrSafe Function SetThreadExecutionState Lib "Kernel32.dll" (ByVal esFlags As Long) 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 DeleteObject Lib "gdi32" (ByVal hObject As LongPtr) As Long
        Private Declare PtrSafe Function CreateFontIndirect Lib "gdi32" Alias "CreateFontIndirectA" (lpLogFont As LOGFONT) As LongPtr
        Private Declare PtrSafe Function sndPlaySound Lib "winmm.dll" Alias "sndPlaySoundA" (lpszSoundName As Any, ByVal uFlags As Long) As Long
        Private Declare PtrSafe Function waveOutGetNumDevs Lib "winmm.dll" () As Long
        Private Declare PtrSafe Function GetTempFileName Lib "kernel32" Alias "GetTempFileNameA" (ByVal lpszPath As String, ByVal lpPrefixString As String, ByVal wUnique As Long, ByVal lpTempFileName As String) As Long
        Private Declare PtrSafe Function GetAncestor Lib "user32" (ByVal hUF As LongPtr, ByVal gaFlags As Long) As LongPtr
        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
#Else
    Private Enum LongPtr
        [_]
    End Enum
    Private Declare Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As Long
    Private Declare Function AccessibleObjectFromPoint Lib "oleacc" (ByVal lX As Long, ByVal lY As Long, ppacc As IAccessible, pvarChild As Variant) As Long
    Private Declare Function ActivateActCtx Lib "kernel32" (ByVal hActCtx As LongPtr, ByRef Cookie As LongPtr) As Long
    Private Declare Function CreateActCtx Lib "kernel32" Alias "CreateActCtxW" (ByRef ACTCTX As ACTCTXW) As LongPtr
    Private Declare Function DeactivateActCtx Lib "kernel32" (ByVal dwFlags As Long, ByVal Cookie As LongPtr) As Long
    Private Declare Sub ReleaseActCtx Lib "kernel32" (ByVal hActCtx As LongPtr)
    Private Declare Function InitCommonControls Lib "Comctl32" () As Long
    Private Declare Function IsUserAnAdmin Lib "Shell32" () As Long
    Private Declare Function SetWindowTheme Lib "UxTheme.dll" (ByVal hwnd As LongPtr, ByVal pszSubAppName As LongPtr, ByVal pszSubIdList As LongPtr) As Long
    Private Declare Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleW" (ByVal pModuleName As LongPtr) As LongPtr
    Private Declare Function SetProp Lib "user32" Alias "SetPropA" (ByVal hwnd As LongPtr, ByVal lpString As String, ByVal hData As LongPtr) As Long
    Private Declare Function GetProp Lib "user32" Alias "GetPropA" (ByVal hwnd As LongPtr, ByVal lpString As String) As LongPtr
    Private Declare Function RemoveProp Lib "user32" Alias "RemovePropA" (ByVal hwnd As LongPtr, ByVal lpString As String) As LongPtr
    Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
    Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
    Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As LongPtr, ByVal hWnd2 As LongPtr, ByVal lpsz1 As String, ByVal lpsz2 As String) As LongPtr
    Private Declare Function IsWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
    Private Declare Function GetActiveWindow Lib "user32" () As LongPtr
    Private Declare Function InitCommonControlsEx Lib "comctl32.dll" (iccex As InitCommonControlsEx) As Long
    Private Declare Function CreateWindowEx Lib "user32" Alias "CreateWindowExW" (ByVal dwExStyle As Long, ByVal lpClassName As LongPtr, ByVal lpWindowName As LongPtr, 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 Function DestroyWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
    Private Declare Function SendMessage Lib "user32.dll" Alias "SendMessageW" (ByVal hwnd As LongPtr, ByVal wMsg As Long, ByVal wParam As LongPtr, ByRef lParam As Any) As LongPtr
    Private Declare Function SendMessageLong Lib "user32.dll" Alias "SendMessageW" (ByVal hwnd As LongPtr, ByVal wMsg As Long, ByVal wParam As LongPtr, ByVal lParam As LongPtr) As LongPtr
    Private Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As LongPtr
    Private Declare Function SetThreadExecutionState Lib "Kernel32.dll" (ByVal esFlags As Long) 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 DeleteObject Lib "gdi32" (ByVal hObject As LongPtr) As Long
    Private Declare Function CreateFontIndirect Lib "gdi32" Alias "CreateFontIndirectA" (lpLogFont As LOGFONT) As LongPtr
    Private Declare Function sndPlaySound Lib "winmm.dll" Alias "sndPlaySoundA" (lpszSoundName As Any, ByVal uFlags As Long) As Long
    Private Declare Function waveOutGetNumDevs Lib "winmm.dll" () As Long
    Private Declare Function GetTempFileName Lib "kernel32" Alias "GetTempFileNameA" (ByVal lpszPath As String, ByVal lpPrefixString As String, ByVal wUnique As Long, ByVal lpTempFileName As String) As Long
    Private Declare Function GetAncestor Lib "user32" (ByVal hUF As LongPtr, ByVal gaFlags As Long) As LongPtr
    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
#End If

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
    lfA           As Long
    lfB           As Long
    lfFaceName(LF_FACESIZE) As Byte
End Type

Private Type TOOLINFOW
    cbSize    As Long
    uFlags    As Long
    hwnd      As LongPtr
    uId       As LongPtr
    cRect     As RECT
    hinst     As LongPtr
    lpszText  As LongPtr
    lParam    As LongPtr
End Type

Private Type InitCommonControlsEx
   Size As Long
   ICC  As Long
End Type

Private Type ACTCTXW
    cbSize                 As Long
    dwFlags                As Long
    lpSource               As LongPtr
    wProcessorArchitecture As Integer
    wLangId                As Integer
    lpAssemblyDirectory    As LongPtr
    lpResourceName         As LongPtr
    lpApplicationName      As LongPtr
    hModule                As LongPtr
End Type


Private arWavBytes() As Byte, sTmpManifestFile As String


'___________________________________________ Public Routines ______________________________________________

  
Public Sub Init(Optional ByVal Dummy As Boolean)
    Call BuildWAVSoundArrayFromBytes
    If GetProp(Application.hwnd, "ActCtxCookie") Then
        Call Application.OnTime(Now, "ReleaseCC6ActCtx")
    End
    End If
    Call InitCC6ActCtx
End Sub
 
Public Sub Term(Optional ByVal Dummy As Boolean)
    Call Application.OnTime(Now, "ReleaseCC6ActCtx")
    Erase sSheetCodeNamesArray: Erase arText: Erase arIcon: Erase arTitle
    Erase arForeColor: Erase arBackColor: Erase arBalloon:  Erase arFontName: Erase arVisibleTime
    Erase arFontSize:  Erase arFontBold:  Erase arPlaySound: Erase arRightToLeftReadingOrder
    'Debug.Print "Class Terminated."
End Sub

Public Sub WatchObjUnderMousePointer(Optional ByVal Dummy As Boolean)
    Call WatchObjUnderMousePointerNow
End Sub



'___________________________________________ Private Routines ______________________________________________

    
Private Sub InitCC6ActCtx()

    Const ICC_WIN95_CLASSES = &HFF
    Dim tIccex As InitCommonControlsEx
    Dim ACTCTX As ACTCTXW
    Dim hActCtx As LongPtr, ActCtxCookie As LongPtr
 
    Call IsUserAnAdmin
    With tIccex
        .Size = LenB(tIccex)
        .ICC = ICC_WIN95_CLASSES
    End With
    If InitCommonControlsEx(tIccex) = False Then
        Call InitCommonControls
    End If
    sTmpManifestFile = String(1000&, 0&)
    Call GetTempFileName(Environ("TEMP"), "Manifest", 0&, sTmpManifestFile)
    sTmpManifestFile = Left(sTmpManifestFile, InStr(sTmpManifestFile, vbNullChar) - 1&)
    Call CreateTempManifest(sTmpManifestFile)
    Do: DoEvents: Loop Until Len(Dir(sTmpManifestFile))
    If GetModuleHandle(StrPtr(vbNullString)) <> NULL_PTR Then
        With ACTCTX
            .cbSize = LenB(ACTCTX)
            .lpSource = StrPtr(sTmpManifestFile)
        End With
        hActCtx = CreateActCtx(ACTCTX)
        Call ActivateActCtx(hActCtx, ActCtxCookie)
        Call SetProp(Application.hwnd, "ActCtxCookie", ActCtxCookie)
        Call SetProp(Application.hwnd, "ACTCTX", hActCtx)
    End If
    
End Sub

Private Sub ReleaseCC6ActCtx()

    Const DEACTIVATE_ACTCTX_FLAG_NORMAL = 0&
    Dim hActCtx As LongPtr, ActCtxCookie As LongPtr
    
    hActCtx = GetProp(Application.hwnd, "ACTCTX")
    ActCtxCookie = GetProp(Application.hwnd, "ActCtxCookie")
    If hActCtx Then
        Call DeactivateActCtx(DEACTIVATE_ACTCTX_FLAG_NORMAL, ActCtxCookie)
        Call ReleaseActCtx(hActCtx)
        Call RemoveProp(Application.hwnd, "ACTCTX")
        Call RemoveProp(Application.hwnd, "ActCtxCookie")
        If Len(sTmpManifestFile) Then
            Call Kill(sTmpManifestFile)
        End If
    End If

End Sub

Private Sub WatchObjUnderMousePointerNow()

    Const ROLE_SYSTEM_PAGETAB = &H25, ROLE_SYSTEM_PAGETABLIST = &H3C&
    Const CHILDID_SELF = &H0&, S_OK = &H0
    Const GA_ROOT = 2&

    Static oPrveAcc As IAccessible
    
    Dim oIAcc As IAccessible, oIAParent As IAccessible
    Dim tCurPos As POINTAPI, sTextUnderMouse As String, indx As Long
    Dim hwnd As LongPtr

    On Error Resume Next

    If Not ActiveWorkbook Is ThisWorkbook Then Call RemoveToolTip: GoTo Xit
    If GetActiveWindow <> Application.hwnd Then Call RemoveToolTip: GoTo Xit
    
    Call GetCursorPos(tCurPos)
    
    #If Win64 Then
        Dim lP As LongLong
        Call CopyMemory(lP, tCurPos, LenB(lP))
        hwnd = WindowFromPoint(lP)
    #Else
        hwnd = WindowFromPoint(tCurPos.x, tCurPos.y)
    #End If
    If GetAncestor(hwnd, GA_ROOT) <> Application.hwnd Then
        Call RemoveToolTip: GoTo Xit
    End If
    
    #If Win64 Then
        Dim lPt As LongLong
        Call CopyMemory(lPt, tCurPos, LenB(lPt))
        If AccessibleObjectFromPoint(lPt, oIAcc, NULL_PTR) = S_OK Then
    #Else
        If AccessibleObjectFromPoint(tCurPos.x, tCurPos.y, oIAcc, NULL_PTR) = S_OK Then
    #End If
            If oIAcc.accRole(CHILDID_SELF) = ROLE_SYSTEM_PAGETAB Then
                If oPrveAcc.accName(CHILDID_SELF) <> oIAcc.accName(CHILDID_SELF) Then
                Set oIAParent = oIAcc.accParent
                    If oIAParent.accRole(CHILDID_SELF) = ROLE_SYSTEM_PAGETABLIST Then
                        sTextUnderMouse = oIAcc.accName(CHILDID_SELF)
                        If Not IsError(Application.Match(sTextUnderMouse, sSheetCodeNamesArray, 0&)) Then
                            indx = Application.Match(sTextUnderMouse, sSheetCodeNamesArray, 0&)
                            If indx Then
                                indx = indx - 1&
                                Call CreateToolTip(arText(indx), arIcon(indx), arTitle(indx), _
                                     arForeColor(indx), arBackColor(indx), arBalloon(indx), arFontName(indx), _
                                     arFontSize(indx), arFontBold(indx), arPlaySound(indx), _
                                     arRightToLeftReadingOrder(indx), arVisibleTime(indx))
                            End If
                        Else
                            Call RemoveToolTip
                        End If
                    End If
                End If
            Else
                Call RemoveToolTip
            End If
        End If
Xit:

    Set oPrveAcc = oIAcc
    With Application.CommandBars
        .FindControl(id:=2040&).Enabled = Not .FindControl(id:=2040&).Enabled
    End With
    PreventSleepMode = True

End Sub

Private Sub RemoveToolTip()
    Dim hFont As LongPtr
    If IsWindow(FindWindow("tooltips_class32", "MyToolTip")) Then
        hFont = GetProp(Application.hwnd, "hFont")
        Call DeleteObject(hFont)
        Call DestroyWindow(FindWindow("tooltips_class32", "MyToolTip"))
        'Debug.Print "Tooltip Destroyed."
    End If
End Sub

Private Property Let PreventSleepMode(ByVal bPrevent As Boolean)
    Const ES_SYSTEM_REQUIRED As Long = &H1
    Const ES_DISPLAY_REQUIRED As Long = &H2
    Const ES_AWAYMODE_REQUIRED = &H40
    Const ES_CONTINUOUS As Long = &H80000000
    If bPrevent Then
        Call SetThreadExecutionState _
             (ES_CONTINUOUS Or ES_DISPLAY_REQUIRED Or ES_SYSTEM_REQUIRED Or ES_AWAYMODE_REQUIRED)
    Else
        Call SetThreadExecutionState(ES_CONTINUOUS)
    End If
End Property

Private Sub CreateToolTip( _
        ByVal TipText As String, _
        ByVal Icon As Long, _
        ByVal Title As String, _
        ByVal ForeColor As Long, _
        ByVal BackColor As Long, _
        ByVal Balloon As Boolean, _
        ByVal FontName As String, _
        ByVal FontSize As Long, _
        ByVal FontBold As Boolean, _
        ByVal PlaySound As Boolean, _
        ByVal RightToLeftReadingOrder As Boolean, _
        ByVal VisibleTime As Long _
    )
                          
    Const TOOLTIPS_CLASSA = "tooltips_class32"
    Const CW_USEDEFAULT = &H80000000
    Const WS_EX_NOACTIVATE = &H8000000
    Const WS_EX_LAYOUTRTL = &H400000
    Const WM_USER = &H400
    Const TTM_ADDTOOLW = WM_USER + 4&
    Const TTM_SETDELAYTIME = WM_USER + 3&
    Const TTM_SETMAXTIPWIDTH = WM_USER + 24&
    Const TTM_SETTITLEW = WM_USER + 33&
    Const TTM_UPDATETIPTEXTW = WM_USER + 57&
    Const TTM_SETTIPBKCOLOR = WM_USER + 19&
    Const TTM_SETTIPTEXTCOLOR = WM_USER + 20&
    Const TTM_SETTITLE = WM_USER + 32&
    Const TTS_NOPREFIX = &H2
    Const TTS_BALLOON = &H40
    Const TTS_ALWAYSTIP = &H1
    Const TTF_IDISHWND = &H1
    Const TTF_SUBCLASS = &H10
    Const TTDT_AUTOPOP = &H2
    Const WM_SETFONT = &H30
    
    Dim hToolTip As LongPtr, hParent As LongPtr, hFont As LongPtr
    Dim lWinStyle As Long, lWinExStyle As Long, lRealColor As Long
    Dim uTTInfo As TOOLINFOW, tFont As LOGFONT, tCurPos As POINTAPI
    Dim arFaceName() As Byte
        
    Call RemoveToolTip
    
    lWinExStyle = WS_EX_NOACTIVATE + IIf(RightToLeftReadingOrder, WS_EX_LAYOUTRTL, 0&)
    lWinStyle = TTS_ALWAYSTIP Or TTS_NOPREFIX
    If Balloon Then lWinStyle = lWinStyle Or TTS_BALLOON
    hToolTip = CreateWindowEx(lWinExStyle, ByVal StrPtr(TOOLTIPS_CLASSA), ByVal StrPtr("MyToolTip"), _
               lWinStyle, CW_USEDEFAULT, CW_USEDEFAULT, CW_USEDEFAULT, CW_USEDEFAULT, _
               NULL_PTR, NULL_PTR, GetModuleHandle(StrPtr(vbNullString)), NULL_PTR)
    
    Call SetWindowTheme(hToolTip, StrPtr(""), StrPtr(""))
    
    arFaceName = StrConv(FontName & vbNullChar, vbFromUnicode)
    With tFont
        .lfHeight = -FontSize
        .lfWeight = IIf(FontBold, 800&, .lfWeight)
        Call CopyMemory(.lfFaceName(0&), arFaceName(0&), UBound(arFaceName))
    End With
    hFont = CreateFontIndirect(tFont)
    Call SendMessage(hToolTip, WM_SETFONT, hFont, True)
    Call SetProp(Application.hwnd, "hFont", hFont)
    
    hParent = FindWindowEx(FindWindowEx(Application.hwnd, NULL_PTR, "XLDESK", vbNullString) _
    , NULL_PTR, "EXCEL7", vbNullString)
      
    With uTTInfo
        .uFlags = TTF_SUBCLASS Or TTF_IDISHWND
        .hwnd = hParent
        .uId = hParent
        .hinst = GetModuleHandle(StrPtr(vbNullString))
        .lpszText = StrPtr(TipText)
        .cbSize = LenB(uTTInfo)
    End With
        
    Call SendMessage(hToolTip, TTM_SETMAXTIPWIDTH, NULL_PTR, ByVal 2048)
    Call SendMessage(hToolTip, TTM_ADDTOOLW, NULL_PTR, uTTInfo)
    Call SendMessage(hToolTip, TTM_UPDATETIPTEXTW, NULL_PTR, uTTInfo)
    
    If ForeColor <> -1& Then
        Call SendMessage(hToolTip, TTM_SETTIPTEXTCOLOR, ForeColor, NULL_PTR)
    End If
    
    If BackColor <> -1& Then
        Call TranslateColor(BackColor, NULL_PTR, lRealColor)
        Call SendMessage(hToolTip, TTM_SETTIPBKCOLOR, lRealColor, NULL_PTR)
    End If
    
    If Icon <> I_NoIcon Or Title <> vbNullString Then
        Call SendMessage(hToolTip, TTM_SETTITLEW, CLng(Icon), ByVal StrPtr(Title))
        Call SendMessageLong(hToolTip, TTM_SETDELAYTIME, TTDT_AUTOPOP, VisibleTime)
    End If
    
    If PlaySound Then
    Call SetTimer(Application.hwnd, NULL_PTR, 500, AddressOf PlayBeep)
    End If

End Sub

Private Sub PlayBeep()
    Const SND_ASYNC = &H1, SND_NODEFAULT = &H2, SND_MEMORY = &H4
    Call KillTimer(Application.hwnd, NULL_PTR)
    If waveOutGetNumDevs > 0& Then
        Call sndPlaySound(arWavBytes(0&), SND_ASYNC Or SND_NODEFAULT Or SND_MEMORY)
    End If
End Sub

Private Sub BuildWAVSoundArrayFromBytes()

    ReDim b(0& To 2725&) As Byte
    
    b(0) = 82: b(1) = 73: b(2) = 70: b(3) = 70: b(4) = 158: b(5) = 10: b(6) = 0: b(7) = 0: b(8) = 87: b(9) = 65: b(10) = 86: b(11) = 69: b(12) = 102: b(13) = 109: b(14) = 116: b(15) = 32: b(16) = 16: b(17) = 0: b(18) = 0: b(19) = 0: b(20) = 1: b(21) = 0: b(22) = 2: b(23) = 0: b(24) = 34: b(25) = 86: b(26) = 0: b(27) = 0: b(28) = 136: b(29) = 88
    b(30) = 1: b(31) = 0: b(32) = 4: b(33) = 0: b(34) = 16: b(35) = 0: b(36) = 76: b(37) = 73: b(38) = 83: b(39) = 84: b(40) = 26: b(41) = 0: b(42) = 0: b(43) = 0: b(44) = 73: b(45) = 78: b(46) = 70: b(47) = 79: b(48) = 73: b(49) = 83: b(50) = 70: b(51) = 84: b(52) = 14: b(53) = 0: b(54) = 0: b(55) = 0: b(56) = 76: b(57) = 97: b(58) = 118: b(59) = 102
    b(60) = 53: b(61) = 56: b(62) = 46: b(63) = 55: b(64) = 54: b(65) = 46: b(66) = 49: b(67) = 48: b(68) = 48: b(69) = 0: b(70) = 100: b(71) = 97: b(72) = 116: b(73) = 97: b(74) = 88: b(75) = 10: b(76) = 0: b(77) = 0: b(78) = 255: b(79) = 255: b(80) = 254: b(81) = 255: b(82) = 1: b(83) = 0: b(84) = 1: b(85) = 0: b(86) = 0: b(87) = 0: b(88) = 0: b(89) = 0
    b(90) = 0: b(91) = 0: b(92) = 0: b(93) = 0: b(94) = 0: b(95) = 0: b(96) = 1: b(97) = 0: b(98) = 0: b(99) = 0: b(100) = 255: b(101) = 255: b(102) = 0: b(103) = 0: b(104) = 0: b(105) = 0: b(106) = 0: b(107) = 0: b(108) = 0: b(109) = 0: b(110) = 0: b(111) = 0: b(112) = 0: b(113) = 0: b(114) = 0: b(115) = 0: b(116) = 255: b(117) = 255: b(118) = 0: b(119) = 0
    b(120) = 1: b(121) = 0: b(122) = 0: b(123) = 0: b(124) = 0: b(125) = 0: b(126) = 0: b(127) = 0: b(128) = 0: b(129) = 0: b(130) = 0: b(131) = 0: b(132) = 0: b(133) = 0: b(134) = 0: b(135) = 0: b(136) = 0: b(137) = 0: b(138) = 0: b(139) = 0: b(140) = 0: b(141) = 0: b(142) = 0: b(143) = 0: b(144) = 0: b(145) = 0: b(146) = 1: b(147) = 0: b(148) = 0: b(149) = 0
    b(150) = 255: b(151) = 255: b(152) = 0: b(153) = 0: b(154) = 1: b(155) = 0: b(156) = 1: b(157) = 0: b(158) = 0: b(159) = 0: b(160) = 255: b(161) = 255: b(162) = 0: b(163) = 0: b(164) = 0: b(165) = 0: b(166) = 255: b(167) = 255: b(168) = 0: b(169) = 0: b(170) = 1: b(171) = 0: b(172) = 0: b(173) = 0: b(174) = 255: b(175) = 255: b(176) = 0: b(177) = 0: b(178) = 0: b(179) = 0
    b(180) = 0: b(181) = 0: b(182) = 0: b(183) = 0: b(184) = 0: b(185) = 0: b(186) = 0: b(187) = 0: b(188) = 0: b(189) = 0: b(190) = 0: b(191) = 0: b(192) = 0: b(193) = 0: b(194) = 255: b(195) = 255: b(196) = 0: b(197) = 0: b(198) = 0: b(199) = 0: b(200) = 0: b(201) = 0: b(202) = 0: b(203) = 0: b(204) = 0: b(205) = 0: b(206) = 1: b(207) = 0: b(208) = 0: b(209) = 0
    b(210) = 0: b(211) = 0: b(212) = 0: b(213) = 0: b(214) = 1: b(215) = 0: b(216) = 0: b(217) = 0: b(218) = 0: b(219) = 0: b(220) = 0: b(221) = 0: b(222) = 0: b(223) = 0: b(224) = 0: b(225) = 0: b(226) = 0: b(227) = 0: b(228) = 0: b(229) = 0: b(230) = 0: b(231) = 0: b(232) = 0: b(233) = 0: b(234) = 0: b(235) = 0: b(236) = 0: b(237) = 0: b(238) = 0: b(239) = 0
    b(240) = 255: b(241) = 255: b(242) = 0: b(243) = 0: b(244) = 1: b(245) = 0: b(246) = 1: b(247) = 0: b(248) = 0: b(249) = 0: b(250) = 0: b(251) = 0: b(252) = 0: b(253) = 0: b(254) = 0: b(255) = 0: b(256) = 255: b(257) = 255: b(258) = 0: b(259) = 0: b(260) = 0: b(261) = 0: b(262) = 0: b(263) = 0: b(264) = 255: b(265) = 255: b(266) = 0: b(267) = 0: b(268) = 0: b(269) = 0
    b(270) = 0: b(271) = 0: b(272) = 0: b(273) = 0: b(274) = 0: b(275) = 0: b(276) = 0: b(277) = 0: b(278) = 0: b(279) = 0: b(280) = 0: b(281) = 0: b(282) = 0: b(283) = 0: b(284) = 0: b(285) = 0: b(286) = 0: b(287) = 0: b(288) = 0: b(289) = 0: b(290) = 1: b(291) = 0: b(292) = 0: b(293) = 0: b(294) = 255: b(295) = 255: b(296) = 0: b(297) = 0: b(298) = 0: b(299) = 0
    b(300) = 0: b(301) = 0: b(302) = 1: b(303) = 0: b(304) = 1: b(305) = 0: b(306) = 0: b(307) = 0: b(308) = 0: b(309) = 0: b(310) = 2: b(311) = 0: b(312) = 0: b(313) = 0: b(314) = 0: b(315) = 0: b(316) = 1: b(317) = 0: b(318) = 1: b(319) = 0: b(320) = 1: b(321) = 0: b(322) = 1: b(323) = 0: b(324) = 1: b(325) = 0: b(326) = 0: b(327) = 0: b(328) = 0: b(329) = 0
    b(330) = 0: b(331) = 0: b(332) = 0: b(333) = 0: b(334) = 0: b(335) = 0: b(336) = 0: b(337) = 0: b(338) = 0: b(339) = 0: b(340) = 255: b(341) = 255: b(342) = 0: b(343) = 0: b(344) = 0: b(345) = 0: b(346) = 0: b(347) = 0: b(348) = 0: b(349) = 0: b(350) = 0: b(351) = 0: b(352) = 0: b(353) = 0: b(354) = 1: b(355) = 0: b(356) = 0: b(357) = 0: b(358) = 255: b(359) = 255
    b(360) = 255: b(361) = 255: b(362) = 1: b(363) = 0: b(364) = 1: b(365) = 0: b(366) = 0: b(367) = 0: b(368) = 0: b(369) = 0: b(370) = 0: b(371) = 0: b(372) = 0: b(373) = 0: b(374) = 0: b(375) = 0: b(376) = 0: b(377) = 0: b(378) = 0: b(379) = 0: b(380) = 0: b(381) = 0: b(382) = 1: b(383) = 0: b(384) = 2: b(385) = 0: b(386) = 0: b(387) = 0: b(388) = 0: b(389) = 0
    b(390) = 1: b(391) = 0: b(392) = 0: b(393) = 0: b(394) = 1: b(395) = 0: b(396) = 255: b(397) = 255: b(398) = 0: b(399) = 0: b(400) = 1: b(401) = 0: b(402) = 0: b(403) = 0: b(404) = 255: b(405) = 255: b(406) = 0: b(407) = 0: b(408) = 0: b(409) = 0: b(410) = 0: b(411) = 0: b(412) = 0: b(413) = 0: b(414) = 1: b(415) = 0: b(416) = 0: b(417) = 0: b(418) = 255: b(419) = 255
    b(420) = 1: b(421) = 0: b(422) = 0: b(423) = 0: b(424) = 0: b(425) = 0: b(426) = 1: b(427) = 0: b(428) = 1: b(429) = 0: b(430) = 0: b(431) = 0: b(432) = 1: b(433) = 0: b(434) = 0: b(435) = 0: b(436) = 0: b(437) = 0: b(438) = 1: b(439) = 0: b(440) = 0: b(441) = 0: b(442) = 1: b(443) = 0: b(444) = 0: b(445) = 0: b(446) = 0: b(447) = 0: b(448) = 254: b(449) = 255
    b(450) = 0: b(451) = 0: b(452) = 255: b(453) = 255: b(454) = 255: b(455) = 255: b(456) = 0: b(457) = 0: b(458) = 255: b(459) = 255: b(460) = 255: b(461) = 255: b(462) = 0: b(463) = 0: b(464) = 255: b(465) = 255: b(466) = 1: b(467) = 0: b(468) = 255: b(469) = 255: b(470) = 254: b(471) = 255: b(472) = 255: b(473) = 255: b(474) = 1: b(475) = 0: b(476) = 0: b(477) = 0: b(478) = 3: b(479) = 0
    b(480) = 0: b(481) = 0: b(482) = 255: b(483) = 255: b(484) = 0: b(485) = 0: b(486) = 1: b(487) = 0: b(488) = 1: b(489) = 0: b(490) = 2: b(491) = 0: b(492) = 2: b(493) = 0: b(494) = 0: b(495) = 0: b(496) = 1: b(497) = 0: b(498) = 2: b(499) = 0: b(500) = 3: b(501) = 0: b(502) = 2: b(503) = 0: b(504) = 2: b(505) = 0: b(506) = 255: b(507) = 255: b(508) = 0: b(509) = 0
    b(510) = 255: b(511) = 255: b(512) = 0: b(513) = 0: b(514) = 254: b(515) = 255: b(516) = 0: b(517) = 0: b(518) = 253: b(519) = 255: b(520) = 2: b(521) = 0: b(522) = 253: b(523) = 255: b(524) = 2: b(525) = 0: b(526) = 0: b(527) = 0: b(528) = 254: b(529) = 255: b(530) = 254: b(531) = 255: b(532) = 1: b(533) = 0: b(534) = 255: b(535) = 255: b(536) = 255: b(537) = 255: b(538) = 255: b(539) = 255
    b(540) = 254: b(541) = 255: b(542) = 0: b(543) = 0: b(544) = 254: b(545) = 255: b(546) = 3: b(547) = 0: b(548) = 253: b(549) = 255: b(550) = 1: b(551) = 0: b(552) = 254: b(553) = 255: b(554) = 0: b(555) = 0: b(556) = 253: b(557) = 255: b(558) = 1: b(559) = 0: b(560) = 253: b(561) = 255: b(562) = 255: b(563) = 255: b(564) = 255: b(565) = 255: b(566) = 3: b(567) = 0: b(568) = 1: b(569) = 0
    b(570) = 0: b(571) = 0: b(572) = 0: b(573) = 0: b(574) = 254: b(575) = 255: b(576) = 3: b(577) = 0: b(578) = 1: b(579) = 0: b(580) = 6: b(581) = 0: b(582) = 2: b(583) = 0: b(584) = 6: b(585) = 0: b(586) = 254: b(587) = 255: b(588) = 5: b(589) = 0: b(590) = 255: b(591) = 255: b(592) = 4: b(593) = 0: b(594) = 0: b(595) = 0: b(596) = 1: b(597) = 0: b(598) = 255: b(599) = 255
    b(600) = 253: b(601) = 255: b(602) = 1: b(603) = 0: b(604) = 255: b(605) = 255: b(606) = 0: b(607) = 0: b(608) = 254: b(609) = 255: b(610) = 0: b(611) = 0: b(612) = 253: b(613) = 255: b(614) = 254: b(615) = 255: b(616) = 255: b(617) = 255: b(618) = 253: b(619) = 255: b(620) = 254: b(621) = 255: b(622) = 1: b(623) = 0: b(624) = 254: b(625) = 255: b(626) = 254: b(627) = 255: b(628) = 254: b(629) = 255
    b(630) = 1: b(631) = 0: b(632) = 2: b(633) = 0: b(634) = 254: b(635) = 255: b(636) = 3: b(637) = 0: b(638) = 255: b(639) = 255: b(640) = 2: b(641) = 0: b(642) = 1: b(643) = 0: b(644) = 2: b(645) = 0: b(646) = 255: b(647) = 255: b(648) = 0: b(649) = 0: b(650) = 3: b(651) = 0: b(652) = 1: b(653) = 0: b(654) = 5: b(655) = 0: b(656) = 3: b(657) = 0: b(658) = 3: b(659) = 0
    b(660) = 1: b(661) = 0: b(662) = 3: b(663) = 0: b(664) = 2: b(665) = 0: b(666) = 0: b(667) = 0: b(668) = 3: b(669) = 0: b(670) = 1: b(671) = 0: b(672) = 3: b(673) = 0: b(674) = 0: b(675) = 0: b(676) = 0: b(677) = 0: b(678) = 1: b(679) = 0: b(680) = 253: b(681) = 255: b(682) = 2: b(683) = 0: b(684) = 254: b(685) = 255: b(686) = 0: b(687) = 0: b(688) = 0: b(689) = 0
    b(690) = 251: b(691) = 255: b(692) = 250: b(693) = 255: b(694) = 252: b(695) = 255: b(696) = 251: b(697) = 255: b(698) = 4: b(699) = 0: b(700) = 253: b(701) = 255: b(702) = 0: b(703) = 0: b(704) = 254: b(705) = 255: b(706) = 255: b(707) = 255: b(708) = 4: b(709) = 0: b(710) = 253: b(711) = 255: b(712) = 1: b(713) = 0: b(714) = 0: b(715) = 0: b(716) = 5: b(717) = 0: b(718) = 253: b(719) = 255
    b(720) = 5: b(721) = 0: b(722) = 254: b(723) = 255: b(724) = 255: b(725) = 255: b(726) = 252: b(727) = 255: b(728) = 4: b(729) = 0: b(730) = 255: b(731) = 255: b(732) = 4: b(733) = 0: b(734) = 3: b(735) = 0: b(736) = 253: b(737) = 255: b(738) = 3: b(739) = 0: b(740) = 252: b(741) = 255: b(742) = 1: b(743) = 0: b(744) = 252: b(745) = 255: b(746) = 0: b(747) = 0: b(748) = 253: b(749) = 255
    b(750) = 2: b(751) = 0: b(752) = 253: b(753) = 255: b(754) = 1: b(755) = 0: b(756) = 255: b(757) = 255: b(758) = 1: b(759) = 0: b(760) = 252: b(761) = 255: b(762) = 5: b(763) = 0: b(764) = 252: b(765) = 255: b(766) = 6: b(767) = 0: b(768) = 255: b(769) = 255: b(770) = 1: b(771) = 0: b(772) = 4: b(773) = 0: b(774) = 255: b(775) = 255: b(776) = 1: b(777) = 0: b(778) = 252: b(779) = 255
    b(780) = 250: b(781) = 255: b(782) = 1: b(783) = 0: b(784) = 3: b(785) = 0: b(786) = 252: b(787) = 255: b(788) = 0: b(789) = 0: b(790) = 254: b(791) = 255: b(792) = 3: b(793) = 0: b(794) = 0: b(795) = 0: b(796) = 7: b(797) = 0: b(798) = 1: b(799) = 0: b(800) = 255: b(801) = 255: b(802) = 254: b(803) = 255: b(804) = 4: b(805) = 0: b(806) = 251: b(807) = 255: b(808) = 5: b(809) = 0
    b(810) = 255: b(811) = 255: b(812) = 0: b(813) = 0: b(814) = 255: b(815) = 255: b(816) = 0: b(817) = 0: b(818) = 253: b(819) = 255: b(820) = 5: b(821) = 0: b(822) = 2: b(823) = 0: b(824) = 0: b(825) = 0: b(826) = 10: b(827) = 0: b(828) = 252: b(829) = 255: b(830) = 6: b(831) = 0: b(832) = 253: b(833) = 255: b(834) = 2: b(835) = 0: b(836) = 254: b(837) = 255: b(838) = 9: b(839) = 0
    b(840) = 1: b(841) = 0: b(842) = 11: b(843) = 0: b(844) = 254: b(845) = 255: b(846) = 5: b(847) = 0: b(848) = 250: b(849) = 255: b(850) = 0: b(851) = 0: b(852) = 252: b(853) = 255: b(854) = 254: b(855) = 255: b(856) = 3: b(857) = 0: b(858) = 251: b(859) = 255: b(860) = 1: b(861) = 0: b(862) = 252: b(863) = 255: b(864) = 0: b(865) = 0: b(866) = 4: b(867) = 0: b(868) = 10: b(869) = 0
    b(870) = 0: b(871) = 0: b(872) = 9: b(873) = 0: b(874) = 253: b(875) = 255: b(876) = 3: b(877) = 0: b(878) = 251: b(879) = 255: b(880) = 10: b(881) = 0: b(882) = 1: b(883) = 0: b(884) = 4: b(885) = 0: b(886) = 255: b(887) = 255: b(888) = 1: b(889) = 0: b(890) = 0: b(891) = 0: b(892) = 2: b(893) = 0: b(894) = 6: b(895) = 0: b(896) = 254: b(897) = 255: b(898) = 255: b(899) = 255
    b(900) = 0: b(901) = 0: b(902) = 254: b(903) = 255: b(904) = 254: b(905) = 255: b(906) = 1: b(907) = 0: b(908) = 252: b(909) = 255: b(910) = 247: b(911) = 255: b(912) = 254: b(913) = 255: b(914) = 2: b(915) = 0: b(916) = 3: b(917) = 0: b(918) = 6: b(919) = 0: b(920) = 1: b(921) = 0: b(922) = 6: b(923) = 0: b(924) = 2: b(925) = 0: b(926) = 255: b(927) = 255: b(928) = 2: b(929) = 0
    b(930) = 2: b(931) = 0: b(932) = 5: b(933) = 0: b(934) = 4: b(935) = 0: b(936) = 10: b(937) = 0: b(938) = 254: b(939) = 255: b(940) = 255: b(941) = 255: b(942) = 3: b(943) = 0: b(944) = 252: b(945) = 255: b(946) = 255: b(947) = 255: b(948) = 252: b(949) = 255: b(950) = 0: b(951) = 0: b(952) = 255: b(953) = 255: b(954) = 255: b(955) = 255: b(956) = 4: b(957) = 0: b(958) = 248: b(959) = 255
    b(960) = 255: b(961) = 255: b(962) = 0: b(963) = 0: b(964) = 1: b(965) = 0: b(966) = 1: b(967) = 0: b(968) = 252: b(969) = 255: b(970) = 254: b(971) = 255: b(972) = 255: b(973) = 255: b(974) = 4: b(975) = 0: b(976) = 8: b(977) = 0: b(978) = 4: b(979) = 0: b(980) = 6: b(981) = 0: b(982) = 3: b(983) = 0: b(984) = 252: b(985) = 255: b(986) = 252: b(987) = 255: b(988) = 252: b(989) = 255
    b(990) = 2: b(991) = 0: b(992) = 4: b(993) = 0: b(994) = 4: b(995) = 0: b(996) = 5: b(997) = 0: b(998) = 254: b(999) = 255: b(1000) = 0: b(1001) = 0: b(1002) = 250: b(1003) = 255: b(1004) = 254: b(1005) = 255: b(1006) = 252: b(1007) = 255: b(1008) = 253: b(1009) = 255: b(1010) = 245: b(1011) = 255: b(1012) = 254: b(1013) = 255: b(1014) = 248: b(1015) = 255: b(1016) = 252: b(1017) = 255: b(1018) = 253: b(1019) = 255
    b(1020) = 250: b(1021) = 255: b(1022) = 2: b(1023) = 0: b(1024) = 255: b(1025) = 255: b(1026) = 254: b(1027) = 255: b(1028) = 250: b(1029) = 255: b(1030) = 1: b(1031) = 0: b(1032) = 3: b(1033) = 0: b(1034) = 1: b(1035) = 0: b(1036) = 11: b(1037) = 0: b(1038) = 3: b(1039) = 0: b(1040) = 10: b(1041) = 0: b(1042) = 12: b(1043) = 0: b(1044) = 17: b(1045) = 0: b(1046) = 5: b(1047) = 0: b(1048) = 23: b(1049) = 0
    b(1050) = 253: b(1051) = 255: b(1052) = 11: b(1053) = 0: b(1054) = 252: b(1055) = 255: b(1056) = 246: b(1057) = 255: b(1058) = 255: b(1059) = 255: b(1060) = 252: b(1061) = 255: b(1062) = 0: b(1063) = 0: b(1064) = 4: b(1065) = 0: b(1066) = 6: b(1067) = 0: b(1068) = 251: b(1069) = 255: b(1070) = 11: b(1071) = 0: b(1072) = 246: b(1073) = 255: b(1074) = 1: b(1075) = 0: b(1076) = 9: b(1077) = 0: b(1078) = 251: b(1079) = 255
    b(1080) = 10: b(1081) = 0: b(1082) = 5: b(1083) = 0: b(1084) = 250: b(1085) = 255: b(1086) = 2: b(1087) = 0: b(1088) = 10: b(1089) = 0: b(1090) = 0: b(1091) = 0: b(1092) = 16: b(1093) = 0: b(1094) = 4: b(1095) = 0: b(1096) = 3: b(1097) = 0: b(1098) = 248: b(1099) = 255: b(1100) = 244: b(1101) = 255: b(1102) = 243: b(1103) = 255: b(1104) = 236: b(1105) = 255: b(1106) = 236: b(1107) = 255: b(1108) = 242: b(1109) = 255
    b(1110) = 238: b(1111) = 255: b(1112) = 242: b(1113) = 255: b(1114) = 249: b(1115) = 255: b(1116) = 232: b(1117) = 255: b(1118) = 251: b(1119) = 255: b(1120) = 246: b(1121) = 255: b(1122) = 16: b(1123) = 0: b(1124) = 13: b(1125) = 0: b(1126) = 248: b(1127) = 255: b(1128) = 6: b(1129) = 0: b(1130) = 236: b(1131) = 255: b(1132) = 7: b(1133) = 0: b(1134) = 3: b(1135) = 0: b(1136) = 10: b(1137) = 0: b(1138) = 34: b(1139) = 0
    b(1140) = 26: b(1141) = 0: b(1142) = 55: b(1143) = 0: b(1144) = 51: b(1145) = 0: b(1146) = 33: b(1147) = 0: b(1148) = 36: b(1149) = 0: b(1150) = 13: b(1151) = 0: b(1152) = 15: b(1153) = 0: b(1154) = 249: b(1155) = 255: b(1156) = 4: b(1157) = 0: b(1158) = 241: b(1159) = 255: b(1160) = 234: b(1161) = 255: b(1162) = 251: b(1163) = 255: b(1164) = 236: b(1165) = 255: b(1166) = 223: b(1167) = 255: b(1168) = 246: b(1169) = 255
    b(1170) = 222: b(1171) = 255: b(1172) = 228: b(1173) = 255: b(1174) = 237: b(1175) = 255: b(1176) = 214: b(1177) = 255: b(1178) = 241: b(1179) = 255: b(1180) = 220: b(1181) = 255: b(1182) = 238: b(1183) = 255: b(1184) = 244: b(1185) = 255: b(1186) = 237: b(1187) = 255: b(1188) = 4: b(1189) = 0: b(1190) = 254: b(1191) = 255: b(1192) = 9: b(1193) = 0: b(1194) = 22: b(1195) = 0: b(1196) = 27: b(1197) = 0: b(1198) = 14: b(1199) = 0
    b(1200) = 20: b(1201) = 0: b(1202) = 251: b(1203) = 255: b(1204) = 6: b(1205) = 0: b(1206) = 249: b(1207) = 255: b(1208) = 6: b(1209) = 0: b(1210) = 241: b(1211) = 255: b(1212) = 13: b(1213) = 0: b(1214) = 12: b(1215) = 0: b(1216) = 19: b(1217) = 0: b(1218) = 35: b(1219) = 0: b(1220) = 12: b(1221) = 0: b(1222) = 26: b(1223) = 0: b(1224) = 4: b(1225) = 0: b(1226) = 16: b(1227) = 0: b(1228) = 21: b(1229) = 0
    b(1230) = 14: b(1231) = 0: b(1232) = 21: b(1233) = 0: b(1234) = 22: b(1235) = 0: b(1236) = 20: b(1237) = 0: b(1238) = 8: b(1239) = 0: b(1240) = 17: b(1241) = 0: b(1242) = 244: b(1243) = 255: b(1244) = 5: b(1245) = 0: b(1246) = 220: b(1247) = 255: b(1248) = 249: b(1249) = 255: b(1250) = 226: b(1251) = 255: b(1252) = 233: b(1253) = 255: b(1254) = 232: b(1255) = 255: b(1256) = 210: b(1257) = 255: b(1258) = 215: b(1259) = 255
    b(1260) = 199: b(1261) = 255: b(1262) = 207: b(1263) = 255: b(1264) = 194: b(1265) = 255: b(1266) = 216: b(1267) = 255: b(1268) = 207: b(1269) = 255: b(1270) = 247: b(1271) = 255: b(1272) = 249: b(1273) = 255: b(1274) = 16: b(1275) = 0: b(1276) = 17: b(1277) = 0: b(1278) = 48: b(1279) = 0: b(1280) = 36: b(1281) = 0: b(1282) = 62: b(1283) = 0: b(1284) = 58: b(1285) = 0: b(1286) = 47: b(1287) = 0: b(1288) = 62: b(1289) = 0
    b(1290) = 43: b(1291) = 0: b(1292) = 47: b(1293) = 0: b(1294) = 53: b(1295) = 0: b(1296) = 41: b(1297) = 0: b(1298) = 27: b(1299) = 0: b(1300) = 30: b(1301) = 0: b(1302) = 2: b(1303) = 0: b(1304) = 18: b(1305) = 0: b(1306) = 233: b(1307) = 255: b(1308) = 1: b(1309) = 0: b(1310) = 228: b(1311) = 255: b(1312) = 233: b(1313) = 255: b(1314) = 213: b(1315) = 255: b(1316) = 212: b(1317) = 255: b(1318) = 209: b(1319) = 255
    b(1320) = 209: b(1321) = 255: b(1322) = 211: b(1323) = 255: b(1324) = 218: b(1325) = 255: b(1326) = 211: b(1327) = 255: b(1328) = 224: b(1329) = 255: b(1330) = 236: b(1331) = 255: b(1332) = 243: b(1333) = 255: b(1334) = 239: b(1335) = 255: b(1336) = 254: b(1337) = 255: b(1338) = 249: b(1339) = 255: b(1340) = 3: b(1341) = 0: b(1342) = 11: b(1343) = 0: b(1344) = 7: b(1345) = 0: b(1346) = 25: b(1347) = 0: b(1348) = 18: b(1349) = 0
    b(1350) = 24: b(1351) = 0: b(1352) = 23: b(1353) = 0: b(1354) = 24: b(1355) = 0: b(1356) = 15: b(1357) = 0: b(1358) = 19: b(1359) = 0: b(1360) = 10: b(1361) = 0: b(1362) = 20: b(1363) = 0: b(1364) = 24: b(1365) = 0: b(1366) = 33: b(1367) = 0: b(1368) = 36: b(1369) = 0: b(1370) = 43: b(1371) = 0: b(1372) = 30: b(1373) = 0: b(1374) = 54: b(1375) = 0: b(1376) = 31: b(1377) = 0: b(1378) = 17: b(1379) = 0
    b(1380) = 14: b(1381) = 0: b(1382) = 2: b(1383) = 0: b(1384) = 10: b(1385) = 0: b(1386) = 253: b(1387) = 255: b(1388) = 2: b(1389) = 0: b(1390) = 226: b(1391) = 255: b(1392) = 237: b(1393) = 255: b(1394) = 214: b(1395) = 255: b(1396) = 228: b(1397) = 255: b(1398) = 193: b(1399) = 255: b(1400) = 201: b(1401) = 255: b(1402) = 189: b(1403) = 255: b(1404) = 193: b(1405) = 255: b(1406) = 202: b(1407) = 255: b(1408) = 215: b(1409) = 255
    b(1410) = 219: b(1411) = 255: b(1412) = 223: b(1413) = 255: b(1414) = 246: b(1415) = 255: b(1416) = 237: b(1417) = 255: b(1418) = 2: b(1419) = 0: b(1420) = 8: b(1421) = 0: b(1422) = 26: b(1423) = 0: b(1424) = 19: b(1425) = 0: b(1426) = 52: b(1427) = 0: b(1428) = 39: b(1429) = 0: b(1430) = 57: b(1431) = 0: b(1432) = 71: b(1433) = 0: b(1434) = 79: b(1435) = 0: b(1436) = 84: b(1437) = 0: b(1438) = 68: b(1439) = 0
    b(1440) = 72: b(1441) = 0: b(1442) = 35: b(1443) = 0: b(1444) = 35: b(1445) = 0: b(1446) = 17: b(1447) = 0: b(1448) = 12: b(1449) = 0: b(1450) = 253: b(1451) = 255: b(1452) = 0: b(1453) = 0: b(1454) = 228: b(1455) = 255: b(1456) = 229: b(1457) = 255: b(1458) = 210: b(1459) = 255: b(1460) = 207: b(1461) = 255: b(1462) = 210: b(1463) = 255: b(1464) = 194: b(1465) = 255: b(1466) = 219: b(1467) = 255: b(1468) = 193: b(1469) = 255
    b(1470) = 230: b(1471) = 255: b(1472) = 222: b(1473) = 255: b(1474) = 252: b(1475) = 255: b(1476) = 236: b(1477) = 255: b(1478) = 251: b(1479) = 255: b(1480) = 251: b(1481) = 255: b(1482) = 0: b(1483) = 0: b(1484) = 6: b(1485) = 0: b(1486) = 9: b(1487) = 0: b(1488) = 10: b(1489) = 0: b(1490) = 6: b(1491) = 0: b(1492) = 28: b(1493) = 0: b(1494) = 18: b(1495) = 0: b(1496) = 26: b(1497) = 0: b(1498) = 3: b(1499) = 0
    b(1500) = 23: b(1501) = 0: b(1502) = 248: b(1503) = 255: b(1504) = 20: b(1505) = 0: b(1506) = 28: b(1507) = 0: b(1508) = 30: b(1509) = 0: b(1510) = 30: b(1511) = 0: b(1512) = 32: b(1513) = 0: b(1514) = 14: b(1515) = 0: b(1516) = 33: b(1517) = 0: b(1518) = 15: b(1519) = 0: b(1520) = 15: b(1521) = 0: b(1522) = 12: b(1523) = 0: b(1524) = 255: b(1525) = 255: b(1526) = 35: b(1527) = 0: b(1528) = 4: b(1529) = 0
    b(1530) = 13: b(1531) = 0: b(1532) = 251: b(1533) = 255: b(1534) = 6: b(1535) = 0: b(1536) = 246: b(1537) = 255: b(1538) = 254: b(1539) = 255: b(1540) = 230: b(1541) = 255: b(1542) = 242: b(1543) = 255: b(1544) = 234: b(1545) = 255: b(1546) = 229: b(1547) = 255: b(1548) = 223: b(1549) = 255: b(1550) = 200: b(1551) = 255: b(1552) = 220: b(1553) = 255: b(1554) = 214: b(1555) = 255: b(1556) = 232: b(1557) = 255: b(1558) = 220: b(1559) = 255
    b(1560) = 225: b(1561) = 255: b(1562) = 249: b(1563) = 255: b(1564) = 255: b(1565) = 255: b(1566) = 254: b(1567) = 255: b(1568) = 21: b(1569) = 0: b(1570) = 13: b(1571) = 0: b(1572) = 23: b(1573) = 0: b(1574) = 30: b(1575) = 0: b(1576) = 41: b(1577) = 0: b(1578) = 27: b(1579) = 0: b(1580) = 30: b(1581) = 0: b(1582) = 22: b(1583) = 0: b(1584) = 41: b(1585) = 0: b(1586) = 33: b(1587) = 0: b(1588) = 61: b(1589) = 0
    b(1590) = 36: b(1591) = 0: b(1592) = 43: b(1593) = 0: b(1594) = 15: b(1595) = 0: b(1596) = 4: b(1597) = 0: b(1598) = 249: b(1599) = 255: b(1600) = 0: b(1601) = 0: b(1602) = 248: b(1603) = 255: b(1604) = 245: b(1605) = 255: b(1606) = 232: b(1607) = 255: b(1608) = 220: b(1609) = 255: b(1610) = 249: b(1611) = 255: b(1612) = 217: b(1613) = 255: b(1614) = 220: b(1615) = 255: b(1616) = 200: b(1617) = 255: b(1618) = 234: b(1619) = 255
    b(1620) = 249: b(1621) = 255: b(1622) = 31: b(1623) = 0: b(1624) = 56: b(1625) = 0: b(1626) = 245: b(1627) = 255: b(1628) = 255: b(1629) = 255: b(1630) = 194: b(1631) = 255: b(1632) = 216: b(1633) = 255: b(1634) = 10: b(1635) = 0: b(1636) = 43: b(1637) = 0: b(1638) = 71: b(1639) = 0: b(1640) = 72: b(1641) = 0: b(1642) = 20: b(1643) = 0: b(1644) = 194: b(1645) = 255: b(1646) = 208: b(1647) = 255: b(1648) = 221: b(1649) = 255
    b(1650) = 60: b(1651) = 0: b(1652) = 92: b(1653) = 0: b(1654) = 222: b(1655) = 255: b(1656) = 226: b(1657) = 255: b(1658) = 156: b(1659) = 255: b(1660) = 35: b(1661) = 255: b(1662) = 62: b(1663) = 255: b(1664) = 97: b(1665) = 255: b(1666) = 89: b(1667) = 255: b(1668) = 97: b(1669) = 0: b(1670) = 200: b(1671) = 255: b(1672) = 41: b(1673) = 0: b(1674) = 51: b(1675) = 1: b(1676) = 144: b(1677) = 0: b(1678) = 74: b(1679) = 1
    b(1680) = 99: b(1681) = 1: b(1682) = 137: b(1683) = 0: b(1684) = 89: b(1685) = 0: b(1686) = 187: b(1687) = 255: b(1688) = 39: b(1689) = 255: b(1690) = 83: b(1691) = 255: b(1692) = 157: b(1693) = 255: b(1694) = 253: b(1695) = 255: b(1696) = 228: b(1697) = 0: b(1698) = 8: b(1699) = 0: b(1700) = 12: b(1701) = 1: b(1702) = 40: b(1703) = 1: b(1704) = 214: b(1705) = 255: b(1706) = 140: b(1707) = 0: b(1708) = 19: b(1709) = 255
    b(1710) = 17: b(1711) = 255: b(1712) = 8: b(1713) = 0: b(1714) = 93: b(1715) = 255: b(1716) = 214: b(1717) = 255: b(1718) = 185: b(1719) = 255: b(1720) = 70: b(1721) = 254: b(1722) = 39: b(1723) = 255: b(1724) = 172: b(1725) = 254: b(1726) = 15: b(1727) = 254: b(1728) = 250: b(1729) = 255: b(1730) = 66: b(1731) = 255: b(1732) = 3: b(1733) = 0: b(1734) = 114: b(1735) = 0: b(1736) = 74: b(1737) = 255: b(1738) = 55: b(1739) = 0
    b(1740) = 57: b(1741) = 0: b(1742) = 94: b(1743) = 1: b(1744) = 152: b(1745) = 1: b(1746) = 97: b(1747) = 1: b(1748) = 57: b(1749) = 1: b(1750) = 39: b(1751) = 1: b(1752) = 162: b(1753) = 0: b(1754) = 158: b(1755) = 1: b(1756) = 14: b(1757) = 1: b(1758) = 65: b(1759) = 0: b(1760) = 254: b(1761) = 0: b(1762) = 26: b(1763) = 255: b(1764) = 139: b(1765) = 255: b(1766) = 176: b(1767) = 255: b(1768) = 254: b(1769) = 254
    b(1770) = 150: b(1771) = 255: b(1772) = 244: b(1773) = 255: b(1774) = 84: b(1775) = 255: b(1776) = 9: b(1777) = 0: b(1778) = 244: b(1779) = 255: b(1780) = 59: b(1781) = 255: b(1782) = 213: b(1783) = 255: b(1784) = 62: b(1785) = 255: b(1786) = 26: b(1787) = 255: b(1788) = 164: b(1789) = 255: b(1790) = 182: b(1791) = 255: b(1792) = 10: b(1793) = 0: b(1794) = 34: b(1795) = 0: b(1796) = 11: b(1797) = 0: b(1798) = 209: b(1799) = 255
    b(1800) = 116: b(1801) = 255: b(1802) = 145: b(1803) = 255: b(1804) = 206: b(1805) = 255: b(1806) = 147: b(1807) = 255: b(1808) = 235: b(1809) = 255: b(1810) = 169: b(1811) = 255: b(1812) = 4: b(1813) = 255: b(1814) = 51: b(1815) = 0: b(1816) = 123: b(1817) = 255: b(1818) = 49: b(1819) = 0: b(1820) = 84: b(1821) = 0: b(1822) = 136: b(1823) = 0: b(1824) = 141: b(1825) = 0: b(1826) = 249: b(1827) = 0: b(1828) = 26: b(1829) = 1
    b(1830) = 252: b(1831) = 0: b(1832) = 116: b(1833) = 1: b(1834) = 89: b(1835) = 1: b(1836) = 29: b(1837) = 1: b(1838) = 3: b(1839) = 1: b(1840) = 12: b(1841) = 1: b(1842) = 52: b(1843) = 0: b(1844) = 99: b(1845) = 0: b(1846) = 237: b(1847) = 255: b(1848) = 195: b(1849) = 255: b(1850) = 78: b(1851) = 255: b(1852) = 115: b(1853) = 255: b(1854) = 16: b(1855) = 255: b(1856) = 157: b(1857) = 254: b(1858) = 238: b(1859) = 254
    b(1860) = 155: b(1861) = 254: b(1862) = 189: b(1863) = 254: b(1864) = 49: b(1865) = 255: b(1866) = 197: b(1867) = 254: b(1868) = 19: b(1869) = 255: b(1870) = 171: b(1871) = 255: b(1872) = 62: b(1873) = 255: b(1874) = 92: b(1875) = 0: b(1876) = 52: b(1877) = 0: b(1878) = 70: b(1879) = 0: b(1880) = 149: b(1881) = 0: b(1882) = 128: b(1883) = 0: b(1884) = 112: b(1885) = 0: b(1886) = 7: b(1887) = 1: b(1888) = 255: b(1889) = 0
    b(1890) = 209: b(1891) = 0: b(1892) = 236: b(1893) = 0: b(1894) = 208: b(1895) = 255: b(1896) = 217: b(1897) = 255: b(1898) = 84: b(1899) = 255: b(1900) = 13: b(1901) = 255: b(1902) = 116: b(1903) = 255: b(1904) = 115: b(1905) = 255: b(1906) = 188: b(1907) = 255: b(1908) = 11: b(1909) = 0: b(1910) = 158: b(1911) = 0: b(1912) = 134: b(1913) = 0: b(1914) = 134: b(1915) = 1: b(1916) = 28: b(1917) = 1: b(1918) = 46: b(1919) = 1
    b(1920) = 199: b(1921) = 0: b(1922) = 40: b(1923) = 1: b(1924) = 102: b(1925) = 0: b(1926) = 65: b(1927) = 0: b(1928) = 114: b(1929) = 0: b(1930) = 103: b(1931) = 255: b(1932) = 156: b(1933) = 0: b(1934) = 142: b(1935) = 254: b(1936) = 33: b(1937) = 0: b(1938) = 30: b(1939) = 255: b(1940) = 205: b(1941) = 254: b(1942) = 124: b(1943) = 255: b(1944) = 22: b(1945) = 254: b(1946) = 148: b(1947) = 254: b(1948) = 186: b(1949) = 254
    b(1950) = 158: b(1951) = 254: b(1952) = 78: b(1953) = 255: b(1954) = 170: b(1955) = 255: b(1956) = 210: b(1957) = 254: b(1958) = 136: b(1959) = 0: b(1960) = 113: b(1961) = 255: b(1962) = 36: b(1963) = 0: b(1964) = 210: b(1965) = 0: b(1966) = 106: b(1967) = 0: b(1968) = 15: b(1969) = 1: b(1970) = 185: b(1971) = 1: b(1972) = 173: b(1973) = 0: b(1974) = 251: b(1975) = 0: b(1976) = 247: b(1977) = 0: b(1978) = 215: b(1979) = 0
    b(1980) = 115: b(1981) = 1: b(1982) = 176: b(1983) = 0: b(1984) = 112: b(1985) = 0: b(1986) = 215: b(1987) = 255: b(1988) = 103: b(1989) = 255: b(1990) = 25: b(1991) = 0: b(1992) = 234: b(1993) = 255: b(1994) = 25: b(1995) = 0: b(1996) = 178: b(1997) = 0: b(1998) = 58: b(1999) = 255: b(2000) = 217: b(2001) = 255: b(2002) = 122: b(2003) = 255: b(2004) = 223: b(2005) = 254: b(2006) = 231: b(2007) = 255: b(2008) = 146: b(2009) = 255
    b(2010) = 128: b(2011) = 255: b(2012) = 112: b(2013) = 0: b(2014) = 20: b(2015) = 0: b(2016) = 45: b(2017) = 0: b(2018) = 72: b(2019) = 0: b(2020) = 157: b(2021) = 255: b(2022) = 137: b(2023) = 255: b(2024) = 85: b(2025) = 255: b(2026) = 116: b(2027) = 255: b(2028) = 138: b(2029) = 255: b(2030) = 180: b(2031) = 255: b(2032) = 226: b(2033) = 255: b(2034) = 148: b(2035) = 255: b(2036) = 182: b(2037) = 255: b(2038) = 139: b(2039) = 255
    b(2040) = 123: b(2041) = 255: b(2042) = 250: b(2043) = 255: b(2044) = 224: b(2045) = 255: b(2046) = 18: b(2047) = 0: b(2048) = 217: b(2049) = 255: b(2050) = 78: b(2051) = 0: b(2052) = 40: b(2053) = 0: b(2054) = 200: b(2055) = 0: b(2056) = 195: b(2057) = 0: b(2058) = 2: b(2059) = 1: b(2060) = 181: b(2061) = 0: b(2062) = 62: b(2063) = 1: b(2064) = 7: b(2065) = 1: b(2066) = 187: b(2067) = 0: b(2068) = 79: b(2069) = 1
    b(2070) = 116: b(2071) = 0: b(2072) = 180: b(2073) = 0: b(2074) = 71: b(2075) = 0: b(2076) = 12: b(2077) = 0: b(2078) = 133: b(2079) = 255: b(2080) = 187: b(2081) = 255: b(2082) = 79: b(2083) = 255: b(2084) = 100: b(2085) = 255: b(2086) = 55: b(2087) = 255: b(2088) = 73: b(2089) = 255: b(2090) = 206: b(2091) = 254: b(2092) = 217: b(2093) = 254: b(2094) = 21: b(2095) = 255: b(2096) = 149: b(2097) = 254: b(2098) = 115: b(2099) = 255
    b(2100) = 75: b(2101) = 255: b(2102) = 198: b(2103) = 255: b(2104) = 203: b(2105) = 255: b(2106) = 70: b(2107) = 0: b(2108) = 214: b(2109) = 255: b(2110) = 126: b(2111) = 0: b(2112) = 68: b(2113) = 0: b(2114) = 103: b(2115) = 0: b(2116) = 190: b(2117) = 0: b(2118) = 112: b(2119) = 0: b(2120) = 128: b(2121) = 0: b(2122) = 128: b(2123) = 0: b(2124) = 63: b(2125) = 0: b(2126) = 21: b(2127) = 0: b(2128) = 114: b(2129) = 0
    b(2130) = 219: b(2131) = 255: b(2132) = 76: b(2133) = 0: b(2134) = 31: b(2135) = 0: b(2136) = 30: b(2137) = 0: b(2138) = 134: b(2139) = 0: b(2140) = 14: b(2141) = 0: b(2142) = 149: b(2143) = 0: b(2144) = 116: b(2145) = 0: b(2146) = 84: b(2147) = 0: b(2148) = 177: b(2149) = 0: b(2150) = 84: b(2151) = 0: b(2152) = 54: b(2153) = 0: b(2154) = 50: b(2155) = 0: b(2156) = 185: b(2157) = 255: b(2158) = 208: b(2159) = 255
    b(2160) = 174: b(2161) = 255: b(2162) = 149: b(2163) = 255: b(2164) = 190: b(2165) = 255: b(2166) = 49: b(2167) = 255: b(2168) = 82: b(2169) = 255: b(2170) = 36: b(2171) = 255: b(2172) = 53: b(2173) = 255: b(2174) = 97: b(2175) = 255: b(2176) = 138: b(2177) = 255: b(2178) = 110: b(2179) = 255: b(2180) = 164: b(2181) = 255: b(2182) = 96: b(2183) = 255: b(2184) = 101: b(2185) = 255: b(2186) = 208: b(2187) = 255: b(2188) = 177: b(2189) = 255
    b(2190) = 157: b(2191) = 0: b(2192) = 90: b(2193) = 0: b(2194) = 212: b(2195) = 0: b(2196) = 115: b(2197) = 0: b(2198) = 134: b(2199) = 0: b(2200) = 208: b(2201) = 0: b(2202) = 165: b(2203) = 0: b(2204) = 189: b(2205) = 0: b(2206) = 108: b(2207) = 0: b(2208) = 35: b(2209) = 0: b(2210) = 26: b(2211) = 0: b(2212) = 198: b(2213) = 255: b(2214) = 164: b(2215) = 255: b(2216) = 254: b(2217) = 255: b(2218) = 212: b(2219) = 255
    b(2220) = 135: b(2221) = 0: b(2222) = 252: b(2223) = 255: b(2224) = 245: b(2225) = 255: b(2226) = 229: b(2227) = 0: b(2228) = 112: b(2229) = 0: b(2230) = 223: b(2231) = 0: b(2232) = 196: b(2233) = 0: b(2234) = 228: b(2235) = 255: b(2236) = 228: b(2237) = 255: b(2238) = 229: b(2239) = 254: b(2240) = 201: b(2241) = 254: b(2242) = 44: b(2243) = 255: b(2244) = 13: b(2245) = 255: b(2246) = 183: b(2247) = 255: b(2248) = 85: b(2249) = 0
    b(2250) = 213: b(2251) = 255: b(2252) = 126: b(2253) = 0: b(2254) = 185: b(2255) = 0: b(2256) = 129: b(2257) = 255: b(2258) = 123: b(2259) = 255: b(2260) = 175: b(2261) = 254: b(2262) = 65: b(2263) = 255: b(2264) = 250: b(2265) = 255: b(2266) = 189: b(2267) = 255: b(2268) = 89: b(2269) = 0: b(2270) = 71: b(2271) = 0: b(2272) = 112: b(2273) = 255: b(2274) = 218: b(2275) = 255: b(2276) = 178: b(2277) = 255: b(2278) = 83: b(2279) = 255
    b(2280) = 252: b(2281) = 0: b(2282) = 170: b(2283) = 0: b(2284) = 31: b(2285) = 1: b(2286) = 160: b(2287) = 0: b(2288) = 175: b(2289) = 255: b(2290) = 127: b(2291) = 0: b(2292) = 253: b(2293) = 255: b(2294) = 54: b(2295) = 0: b(2296) = 149: b(2297) = 0: b(2298) = 230: b(2299) = 255: b(2300) = 218: b(2301) = 255: b(2302) = 239: b(2303) = 0: b(2304) = 208: b(2305) = 255: b(2306) = 178: b(2307) = 0: b(2308) = 241: b(2309) = 0
    b(2310) = 71: b(2311) = 0: b(2312) = 240: b(2313) = 0: b(2314) = 69: b(2315) = 255: b(2316) = 235: b(2317) = 254: b(2318) = 32: b(2319) = 255: b(2320) = 222: b(2321) = 254: b(2322) = 103: b(2323) = 255: b(2324) = 241: b(2325) = 0: b(2326) = 172: b(2327) = 255: b(2328) = 65: b(2329) = 1: b(2330) = 67: b(2331) = 1: b(2332) = 126: b(2333) = 255: b(2334) = 2: b(2335) = 1: b(2336) = 17: b(2337) = 255: b(2338) = 177: b(2339) = 255
    b(2340) = 255: b(2341) = 255: b(2342) = 211: b(2343) = 254: b(2344) = 63: b(2345) = 0: b(2346) = 53: b(2347) = 255: b(2348) = 251: b(2349) = 254: b(2350) = 72: b(2351) = 255: b(2352) = 208: b(2353) = 253: b(2354) = 38: b(2355) = 254: b(2356) = 13: b(2357) = 255: b(2358) = 228: b(2359) = 254: b(2360) = 39: b(2361) = 0: b(2362) = 149: b(2363) = 0: b(2364) = 215: b(2365) = 255: b(2366) = 22: b(2367) = 1: b(2368) = 114: b(2369) = 0
    b(2370) = 37: b(2371) = 1: b(2372) = 119: b(2373) = 1: b(2374) = 141: b(2375) = 1: b(2376) = 194: b(2377) = 1: b(2378) = 200: b(2379) = 1: b(2380) = 212: b(2381) = 1: b(2382) = 235: b(2383) = 1: b(2384) = 254: b(2385) = 1: b(2386) = 163: b(2387) = 1: b(2388) = 125: b(2389) = 1: b(2390) = 225: b(2391) = 255: b(2392) = 216: b(2393) = 255: b(2394) = 197: b(2395) = 254: b(2396) = 39: b(2397) = 254: b(2398) = 32: b(2399) = 254
    b(2400) = 20: b(2401) = 254: b(2402) = 18: b(2403) = 254: b(2404) = 181: b(2405) = 254: b(2406) = 233: b(2407) = 254: b(2408) = 106: b(2409) = 254: b(2410) = 38: b(2411) = 255: b(2412) = 132: b(2413) = 254: b(2414) = 79: b(2415) = 255: b(2416) = 85: b(2417) = 255: b(2418) = 140: b(2419) = 255: b(2420) = 97: b(2421) = 0: b(2422) = 156: b(2423) = 0: b(2424) = 242: b(2425) = 0: b(2426) = 40: b(2427) = 1: b(2428) = 9: b(2429) = 1
    b(2430) = 210: b(2431) = 0: b(2432) = 208: b(2433) = 0: b(2434) = 128: b(2435) = 0: b(2436) = 103: b(2437) = 0: b(2438) = 166: b(2439) = 255: b(2440) = 239: b(2441) = 255: b(2442) = 145: b(2443) = 255: b(2444) = 105: b(2445) = 255: b(2446) = 185: b(2447) = 255: b(2448) = 106: b(2449) = 255: b(2450) = 46: b(2451) = 0: b(2452) = 245: b(2453) = 255: b(2454) = 186: b(2455) = 0: b(2456) = 143: b(2457) = 0: b(2458) = 212: b(2459) = 0
    b(2460) = 71: b(2461) = 1: b(2462) = 58: b(2463) = 1: b(2464) = 103: b(2465) = 1: b(2466) = 116: b(2467) = 1: b(2468) = 52: b(2469) = 1: b(2470) = 5: b(2471) = 1: b(2472) = 229: b(2473) = 0: b(2474) = 97: b(2475) = 0: b(2476) = 161: b(2477) = 0: b(2478) = 97: b(2479) = 255: b(2480) = 185: b(2481) = 255: b(2482) = 10: b(2483) = 254: b(2484) = 26: b(2485) = 254: b(2486) = 118: b(2487) = 253: b(2488) = 60: b(2489) = 253
    b(2490) = 129: b(2491) = 253: b(2492) = 119: b(2493) = 253: b(2494) = 233: b(2495) = 253: b(2496) = 47: b(2497) = 254: b(2498) = 226: b(2499) = 254: b(2500) = 134: b(2501) = 254: b(2502) = 26: b(2503) = 0: b(2504) = 150: b(2505) = 255: b(2506) = 72: b(2507) = 1: b(2508) = 62: b(2509) = 1: b(2510) = 30: b(2511) = 2: b(2512) = 81: b(2513) = 2: b(2514) = 88: b(2515) = 2: b(2516) = 173: b(2517) = 2: b(2518) = 43: b(2519) = 2
    b(2520) = 121: b(2521) = 2: b(2522) = 175: b(2523) = 1: b(2524) = 208: b(2525) = 1: b(2526) = 194: b(2527) = 0: b(2528) = 180: b(2529) = 0: b(2530) = 231: b(2531) = 255: b(2532) = 150: b(2533) = 255: b(2534) = 7: b(2535) = 255: b(2536) = 182: b(2537) = 254: b(2538) = 80: b(2539) = 254: b(2540) = 147: b(2541) = 254: b(2542) = 132: b(2543) = 254: b(2544) = 182: b(2545) = 254: b(2546) = 20: b(2547) = 255: b(2548) = 173: b(2549) = 254
    b(2550) = 128: b(2551) = 255: b(2552) = 65: b(2553) = 255: b(2554) = 20: b(2555) = 0: b(2556) = 249: b(2557) = 255: b(2558) = 89: b(2559) = 0: b(2560) = 169: b(2561) = 0: b(2562) = 84: b(2563) = 0: b(2564) = 189: b(2565) = 0: b(2566) = 45: b(2567) = 0: b(2568) = 91: b(2569) = 0: b(2570) = 153: b(2571) = 255: b(2572) = 247: b(2573) = 255: b(2574) = 25: b(2575) = 255: b(2576) = 109: b(2577) = 255: b(2578) = 224: b(2579) = 254
    b(2580) = 248: b(2581) = 254: b(2582) = 133: b(2583) = 255: b(2584) = 60: b(2585) = 255: b(2586) = 55: b(2587) = 0: b(2588) = 215: b(2589) = 255: b(2590) = 148: b(2591) = 0: b(2592) = 83: b(2593) = 0: b(2594) = 243: b(2595) = 0: b(2596) = 186: b(2597) = 0: b(2598) = 122: b(2599) = 1: b(2600) = 2: b(2601) = 1: b(2602) = 206: b(2603) = 1: b(2604) = 144: b(2605) = 1: b(2606) = 108: b(2607) = 1: b(2608) = 195: b(2609) = 1
    b(2610) = 211: b(2611) = 0: b(2612) = 14: b(2613) = 1: b(2614) = 60: b(2615) = 0: b(2616) = 63: b(2617) = 0: b(2618) = 125: b(2619) = 255: b(2620) = 200: b(2621) = 255: b(2622) = 203: b(2623) = 254: b(2624) = 60: b(2625) = 255: b(2626) = 32: b(2627) = 254: b(2628) = 121: b(2629) = 254: b(2630) = 242: b(2631) = 253: b(2632) = 249: b(2633) = 253: b(2634) = 53: b(2635) = 254: b(2636) = 13: b(2637) = 254: b(2638) = 197: b(2639) = 254
    b(2640) = 143: b(2641) = 254: b(2642) = 143: b(2643) = 255: b(2644) = 76: b(2645) = 255: b(2646) = 65: b(2647) = 0: b(2648) = 23: b(2649) = 0: b(2650) = 240: b(2651) = 0: b(2652) = 221: b(2653) = 0: b(2654) = 43: b(2655) = 1: b(2656) = 17: b(2657) = 1: b(2658) = 92: b(2659) = 1: b(2660) = 47: b(2661) = 1: b(2662) = 59: b(2663) = 1: b(2664) = 51: b(2665) = 1: b(2666) = 56: b(2667) = 1: b(2668) = 94: b(2669) = 1
    b(2670) = 227: b(2671) = 0: b(2672) = 34: b(2673) = 1: b(2674) = 136: b(2675) = 0: b(2676) = 182: b(2677) = 0: b(2678) = 28: b(2679) = 0: b(2680) = 25: b(2681) = 0: b(2682) = 75: b(2683) = 255: b(2684) = 53: b(2685) = 255: b(2686) = 215: b(2687) = 254: b(2688) = 50: b(2689) = 255: b(2690) = 200: b(2691) = 254: b(2692) = 214: b(2693) = 255: b(2694) = 215: b(2695) = 255: b(2696) = 232: b(2697) = 255: b(2698) = 125: b(2699) = 0
    b(2700) = 150: b(2701) = 255: b(2702) = 149: b(2703) = 0: b(2704) = 153: b(2705) = 255: b(2706) = 0: b(2707) = 0: b(2708) = 244: b(2709) = 255: b(2710) = 222: b(2711) = 254: b(2712) = 144: b(2713) = 255: b(2714) = 231: b(2715) = 254: b(2716) = 162: b(2717) = 254: b(2718) = 125: b(2719) = 254: b(2720) = 57: b(2721) = 254: b(2722) = 191: b(2723) = 254: b(2724) = 241: b(2725) = 254:

    arWavBytes = b

End Sub

Private Sub CreateTempManifest(ByVal FilePathName As String)

    Dim fNr As Integer
    ReDim b(0& To 574&) As Byte
    
    b(0) = 60: b(1) = 63: b(2) = 120: b(3) = 109: b(4) = 108: b(5) = 32: b(6) = 118: b(7) = 101: b(8) = 114: b(9) = 115: b(10) = 105: b(11) = 111: b(12) = 110: b(13) = 61: b(14) = 34: b(15) = 49: b(16) = 46: b(17) = 48: b(18) = 34: b(19) = 32: b(20) = 101: b(21) = 110: b(22) = 99: b(23) = 111: b(24) = 100: b(25) = 105: b(26) = 110: b(27) = 103: b(28) = 61: b(29) = 34
    b(30) = 85: b(31) = 84: b(32) = 70: b(33) = 45: b(34) = 56: b(35) = 34: b(36) = 32: b(37) = 115: b(38) = 116: b(39) = 97: b(40) = 110: b(41) = 100: b(42) = 97: b(43) = 108: b(44) = 111: b(45) = 110: b(46) = 101: b(47) = 61: b(48) = 34: b(49) = 121: b(50) = 101: b(51) = 115: b(52) = 34: b(53) = 63: b(54) = 62: b(55) = 13: b(56) = 10: b(57) = 60: b(58) = 97: b(59) = 115
    b(60) = 115: b(61) = 101: b(62) = 109: b(63) = 98: b(64) = 108: b(65) = 121: b(66) = 32: b(67) = 120: b(68) = 109: b(69) = 108: b(70) = 110: b(71) = 115: b(72) = 61: b(73) = 34: b(74) = 117: b(75) = 114: b(76) = 110: b(77) = 58: b(78) = 115: b(79) = 99: b(80) = 104: b(81) = 101: b(82) = 109: b(83) = 97: b(84) = 115: b(85) = 45: b(86) = 109: b(87) = 105: b(88) = 99: b(89) = 114
    b(90) = 111: b(91) = 115: b(92) = 111: b(93) = 102: b(94) = 116: b(95) = 45: b(96) = 99: b(97) = 111: b(98) = 109: b(99) = 58: b(100) = 97: b(101) = 115: b(102) = 109: b(103) = 46: b(104) = 118: b(105) = 49: b(106) = 34: b(107) = 32: b(108) = 109: b(109) = 97: b(110) = 110: b(111) = 105: b(112) = 102: b(113) = 101: b(114) = 115: b(115) = 116: b(116) = 86: b(117) = 101: b(118) = 114: b(119) = 115
    b(120) = 105: b(121) = 111: b(122) = 110: b(123) = 61: b(124) = 34: b(125) = 49: b(126) = 46: b(127) = 48: b(128) = 34: b(129) = 62: b(130) = 13: b(131) = 10: b(132) = 60: b(133) = 97: b(134) = 115: b(135) = 115: b(136) = 101: b(137) = 109: b(138) = 98: b(139) = 108: b(140) = 121: b(141) = 73: b(142) = 100: b(143) = 101: b(144) = 110: b(145) = 116: b(146) = 105: b(147) = 116: b(148) = 121: b(149) = 13
    b(150) = 10: b(151) = 118: b(152) = 101: b(153) = 114: b(154) = 115: b(155) = 105: b(156) = 111: b(157) = 110: b(158) = 61: b(159) = 34: b(160) = 49: b(161) = 46: b(162) = 48: b(163) = 46: b(164) = 48: b(165) = 46: b(166) = 48: b(167) = 34: b(168) = 13: b(169) = 10: b(170) = 112: b(171) = 114: b(172) = 111: b(173) = 99: b(174) = 101: b(175) = 115: b(176) = 115: b(177) = 111: b(178) = 114: b(179) = 65
    b(180) = 114: b(181) = 99: b(182) = 104: b(183) = 105: b(184) = 116: b(185) = 101: b(186) = 99: b(187) = 116: b(188) = 117: b(189) = 114: b(190) = 101: b(191) = 61: b(192) = 34: b(193) = 42: b(194) = 34: b(195) = 13: b(196) = 10: b(197) = 110: b(198) = 97: b(199) = 109: b(200) = 101: b(201) = 61: b(202) = 34: b(203) = 67: b(204) = 111: b(205) = 109: b(206) = 112: b(207) = 97: b(208) = 110: b(209) = 121
    b(210) = 78: b(211) = 97: b(212) = 109: b(213) = 101: b(214) = 46: b(215) = 80: b(216) = 114: b(217) = 111: b(218) = 100: b(219) = 117: b(220) = 99: b(221) = 116: b(222) = 78: b(223) = 97: b(224) = 109: b(225) = 101: b(226) = 46: b(227) = 89: b(228) = 111: b(229) = 117: b(230) = 114: b(231) = 65: b(232) = 112: b(233) = 112: b(234) = 34: b(235) = 13: b(236) = 10: b(237) = 116: b(238) = 121: b(239) = 112
    b(240) = 101: b(241) = 61: b(242) = 34: b(243) = 119: b(244) = 105: b(245) = 110: b(246) = 51: b(247) = 50: b(248) = 34: b(249) = 13: b(250) = 10: b(251) = 47: b(252) = 62: b(253) = 13: b(254) = 10: b(255) = 60: b(256) = 100: b(257) = 101: b(258) = 115: b(259) = 99: b(260) = 114: b(261) = 105: b(262) = 112: b(263) = 116: b(264) = 105: b(265) = 111: b(266) = 110: b(267) = 62: b(268) = 89: b(269) = 111
    b(270) = 117: b(271) = 114: b(272) = 32: b(273) = 97: b(274) = 112: b(275) = 112: b(276) = 108: b(277) = 105: b(278) = 99: b(279) = 97: b(280) = 116: b(281) = 105: b(282) = 111: b(283) = 110: b(284) = 32: b(285) = 100: b(286) = 101: b(287) = 115: b(288) = 99: b(289) = 114: b(290) = 105: b(291) = 112: b(292) = 116: b(293) = 105: b(294) = 111: b(295) = 110: b(296) = 32: b(297) = 104: b(298) = 101: b(299) = 114
    b(300) = 101: b(301) = 46: b(302) = 60: b(303) = 47: b(304) = 100: b(305) = 101: b(306) = 115: b(307) = 99: b(308) = 114: b(309) = 105: b(310) = 112: b(311) = 116: b(312) = 105: b(313) = 111: b(314) = 110: b(315) = 62: b(316) = 13: b(317) = 10: b(318) = 60: b(319) = 100: b(320) = 101: b(321) = 112: b(322) = 101: b(323) = 110: b(324) = 100: b(325) = 101: b(326) = 110: b(327) = 99: b(328) = 121: b(329) = 62
    b(330) = 13: b(331) = 10: b(332) = 60: b(333) = 100: b(334) = 101: b(335) = 112: b(336) = 101: b(337) = 110: b(338) = 100: b(339) = 101: b(340) = 110: b(341) = 116: b(342) = 65: b(343) = 115: b(344) = 115: b(345) = 101: b(346) = 109: b(347) = 98: b(348) = 108: b(349) = 121: b(350) = 62: b(351) = 13: b(352) = 10: b(353) = 60: b(354) = 97: b(355) = 115: b(356) = 115: b(357) = 101: b(358) = 109: b(359) = 98
    b(360) = 108: b(361) = 121: b(362) = 73: b(363) = 100: b(364) = 101: b(365) = 110: b(366) = 116: b(367) = 105: b(368) = 116: b(369) = 121: b(370) = 13: b(371) = 10: b(372) = 116: b(373) = 121: b(374) = 112: b(375) = 101: b(376) = 61: b(377) = 34: b(378) = 119: b(379) = 105: b(380) = 110: b(381) = 51: b(382) = 50: b(383) = 34: b(384) = 13: b(385) = 10: b(386) = 110: b(387) = 97: b(388) = 109: b(389) = 101
    b(390) = 61: b(391) = 34: b(392) = 77: b(393) = 105: b(394) = 99: b(395) = 114: b(396) = 111: b(397) = 115: b(398) = 111: b(399) = 102: b(400) = 116: b(401) = 46: b(402) = 87: b(403) = 105: b(404) = 110: b(405) = 100: b(406) = 111: b(407) = 119: b(408) = 115: b(409) = 46: b(410) = 67: b(411) = 111: b(412) = 109: b(413) = 109: b(414) = 111: b(415) = 110: b(416) = 45: b(417) = 67: b(418) = 111: b(419) = 110
    b(420) = 116: b(421) = 114: b(422) = 111: b(423) = 108: b(424) = 115: b(425) = 34: b(426) = 13: b(427) = 10: b(428) = 118: b(429) = 101: b(430) = 114: b(431) = 115: b(432) = 105: b(433) = 111: b(434) = 110: b(435) = 61: b(436) = 34: b(437) = 54: b(438) = 46: b(439) = 48: b(440) = 46: b(441) = 48: b(442) = 46: b(443) = 48: b(444) = 34: b(445) = 13: b(446) = 10: b(447) = 112: b(448) = 114: b(449) = 111
    b(450) = 99: b(451) = 101: b(452) = 115: b(453) = 115: b(454) = 111: b(455) = 114: b(456) = 65: b(457) = 114: b(458) = 99: b(459) = 104: b(460) = 105: b(461) = 116: b(462) = 101: b(463) = 99: b(464) = 116: b(465) = 117: b(466) = 114: b(467) = 101: b(468) = 61: b(469) = 34: b(470) = 42: b(471) = 34: b(472) = 13: b(473) = 10: b(474) = 112: b(475) = 117: b(476) = 98: b(477) = 108: b(478) = 105: b(479) = 99
    b(480) = 75: b(481) = 101: b(482) = 121: b(483) = 84: b(484) = 111: b(485) = 107: b(486) = 101: b(487) = 110: b(488) = 61: b(489) = 34: b(490) = 54: b(491) = 53: b(492) = 57: b(493) = 53: b(494) = 98: b(495) = 54: b(496) = 52: b(497) = 49: b(498) = 52: b(499) = 52: b(500) = 99: b(501) = 99: b(502) = 102: b(503) = 49: b(504) = 100: b(505) = 102: b(506) = 34: b(507) = 13: b(508) = 10: b(509) = 108
    b(510) = 97: b(511) = 110: b(512) = 103: b(513) = 117: b(514) = 97: b(515) = 103: b(516) = 101: b(517) = 61: b(518) = 34: b(519) = 42: b(520) = 34: b(521) = 13: b(522) = 10: b(523) = 47: b(524) = 62: b(525) = 13: b(526) = 10: b(527) = 60: b(528) = 47: b(529) = 100: b(530) = 101: b(531) = 112: b(532) = 101: b(533) = 110: b(534) = 100: b(535) = 101: b(536) = 110: b(537) = 116: b(538) = 65: b(539) = 115
    b(540) = 115: b(541) = 101: b(542) = 109: b(543) = 98: b(544) = 108: b(545) = 121: b(546) = 62: b(547) = 13: b(548) = 10: b(549) = 60: b(550) = 47: b(551) = 100: b(552) = 101: b(553) = 112: b(554) = 101: b(555) = 110: b(556) = 100: b(557) = 101: b(558) = 110: b(559) = 99: b(560) = 121: b(561) = 62: b(562) = 13: b(563) = 10: b(564) = 60: b(565) = 47: b(566) = 97: b(567) = 115: b(568) = 115: b(569) = 101
    b(570) = 109: b(571) = 98: b(572) = 108: b(573) = 121: b(574) = 62:
    
    fNr = FreeFile()
    Open FilePathName For Binary As #fNr
        Put #fNr, 1&, b
    Close #fNr
    
End Sub


3- Code Usage test :
VBA Code:
Option Explicit

Private OToolTips As CTabTips

Sub Start()

    Set OToolTips = New CTabTips
        
    With OToolTips
    
        .AddToolTip ThisWorkbook.Sheets("Sheet1"), "This is a Multiline ToolTip with Sound." & vbCr & vbCr & "Line2 ..." & _
            vbCr & "Line3 ..." & vbCr & "Line4 ..." & vbCr & "Line5 ..." & vbCr, _
            I_Info, "Title", , , True, , , , True, , 10000     '0
        
        .AddToolTip Sheet2, "Basic Rectangular Tooltip without any formatting."
        
        .AddToolTip Sheet3, "These are 'tooltips_class32' class-based controls" _
            & vbCr & "from the COMCTL32 library.", I_Info, " ", vbWhite, RGB(20, 50, 20), True
        
        .AddToolTip Sheet4, "Hey, vba coding is fun." & vbCr & _
            "But combining vba with The Win32 api is even more fun !!!", I_Info, _
            "Hello MrExcel", vbRed, &HFFE1FF, True, "Old English Text MT", 20, , , , 20000
        
        .AddToolTip Sheet5, "This is a formatted Tooltip for : " & vbCr & _
            Sheet5.CodeName, I_Warning, "Tooltip With Sound.", , &HFFFFCC, True, , , , True, , 5000
        
        'Test for *RightToLeft* (text located in range K3:K8)... pass lang as needed.
        .AddToolTip Sheet6, Sheet1.Range("K3").Text, I_Error, Sheet1.Range("K3").Text _
            , , &H99FFCC, True, , , , True, True, 15000
    
        .Activate
    
    End With

End Sub

Sub Finish()
    Set OToolTips = Nothing
End Sub



- Sometimes, when hovering above a tab (while tooltip showing), pressing ESC causes run-time error. Upon clicking Debug, VBA jumps to 'cmb_OnUpdate'. Do you think it would be possible to prevent that? (I have tried with EnableCancelKey = False, but it did not help)
@Tobi Shi

Unfortunately, I haven't been able to get the ESC key issue fixed. I have tried a couple of ways including a call to the RegisterHotkey api in order to disable the key but it didn't work as ESC it is a reserved control key... The only thing that would disbale the key is if we install a keyboard windows hook but that would be far too risky/unstable and way too high a price to pay for the TTip functionality we are gaining here.

As mentioned earlier, the error happens sporadically and, on my side, it happens only if ESC is being pushed repeateadly. So I guess this issue is not likely to happen.
 
Upvote 0
I hadn't even seen that you had posted the text of the manifest, my apologies. I went off and used your code to recreate it, and have just been looking at it now.
So if I understand your earlier comment correctly, the critical component of the manifest in this instance is:

XML:
<assemblyIdentity
type="win32"
name="Microsoft.Windows.Common-Controls"
version="6.0.0.0"
processorArchitecture="*"
publicKeyToken="6595b64144ccf1df"
language="*"
/>

Namely this is what enables CC6 (Microsoft Windows Common Controls v 6). This is very helpful, thank you. It may explain problems I've had with other projects, but would need to look at it all a bit closer.
 
Upvote 0
Thanks Jaafar,

works fine so far in my stand-alone test. I will report how the functionality behaves if I manage to add it to a more sophisticated file.

Regarding ESC key press: I tried the following and it seems to work:


1. Added a check whether ESC is pressed
VBA Code:
Private Sub CmndBars_OnUpdate()
    If isEscPressed() Then Exit Sub
    Call WatchObjUnderMousePointer
End Sub



2. Function to determine if ESC is pressed
VBA Code:
Option Explicit
Option Private Module

  
#If VBA7 Then
  Private Declare PtrSafe Function apiGetKeyState Lib "user32" Alias "GetKeyState" (ByVal nVirtKey As Long) As Integer
  
#Else
  Private Declare Function apiGetKeyState Lib "user32" Alias "GetKeyState" (ByVal nVirtKey As Long) As Integer
  
#End If


Function isEscPressed() As Boolean
  'https://www.informit.com/articles/article.aspx?p=366892&seqNum=4
  
  Dim iKeyState As Integer
  iKeyState = apiGetKeyState(vbKeyEscape)
  iKeyState = iKeyState And &H8000
  
  isEscPressed = (iKeyState <> 0)

End Function
 
Upvote 0
Regarding ESC key press: I tried the following and it seems to work:

Private Sub CmndBars_OnUpdate()
If isEscPressed() Then Exit Sub
Call WatchObjUnderMousePointer
End Sub
Hi Tobi,

That does work for preventing the runtime error but it stops the monitoring of the mouse and doesn't resume until you select some object in excel like a worksheet cell or a commandbar etc ... In other words, if you press ESC and then directly move the mouse pointer over another sheet tab, the tooltip won't update... This can be confusing for the user.

Also, when pressing ESC and exiting, the tooltip remains visible which is not what the user would normally expect.

Having said that, it dawned on me that we should be able to prevent the commandbars from updating while the ESC key is down (which is the culprit here) and only resume the updating when the key is up by using the GetKeyState or the GetAsyncKeyState apis in a temporary/short lived timer.

I tested the above idea and it worked OK.

Download:
TabTipsUnicodeWithManifest_V2.xlsm

Here is the new api code:
VBA Code:
Option Explicit

Public Enum ICON_TYPE
    I_NoIcon
    I_Info
    I_Warning
    I_Error
End Enum

Public sSheetCodeNamesArray()      As String
Public arText()                    As String
Public arIcon()                    As Long
Public arTitle()                   As String
Public arForeColor()               As Long
Public arBackColor()               As Long
Public arBalloon()                 As Boolean
Public arFontName()                As String
Public arFontSize()                As Long
Public arFontBold()                As Boolean
Public arPlaySound()               As Boolean
Public arRightToLeftReadingOrder() As Boolean
Public arVisibleTime()             As Long

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

#If VBA7 Then
    #If Win64 Then
        Private Declare PtrSafe Function WindowFromPoint Lib "user32" (ByVal Point As LongLong) As LongLong
        Private Declare PtrSafe Function AccessibleObjectFromPoint Lib "oleacc" (ByVal arg1 As LongLong, ppacc As Any, pvarChild As Variant) As Long
    #Else
        Private Declare PtrSafe Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As Long
        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
        Private Declare PtrSafe Function ActivateActCtx Lib "kernel32" (ByVal hActCtx As LongPtr, ByRef Cookie As LongPtr) As Long
        Private Declare PtrSafe Function CreateActCtx Lib "kernel32" Alias "CreateActCtxW" (ByRef ACTCTX As ACTCTXW) As LongPtr
        Private Declare PtrSafe Function DeactivateActCtx Lib "kernel32" (ByVal dwFlags As Long, ByVal Cookie As LongPtr) As Long
        Private Declare PtrSafe Sub ReleaseActCtx Lib "kernel32" (ByVal hActCtx As LongPtr)
        Private Declare PtrSafe Function InitCommonControls Lib "Comctl32" () As Long
        Private Declare PtrSafe Function IsUserAnAdmin Lib "Shell32" () As Long
        Private Declare PtrSafe Function SetWindowTheme Lib "UxTheme.dll" (ByVal hwnd As LongPtr, ByVal pszSubAppName As LongPtr, ByVal pszSubIdList As LongPtr) As Long
        Private Declare PtrSafe Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleW" (ByVal pModuleName As LongPtr) As LongPtr
        Private Declare PtrSafe Function SetProp Lib "user32" Alias "SetPropA" (ByVal hwnd As LongPtr, ByVal lpString As String, ByVal hData As LongPtr) As Long
        Private Declare PtrSafe Function GetProp Lib "user32" Alias "GetPropA" (ByVal hwnd As LongPtr, ByVal lpString As String) As LongPtr
        Private Declare PtrSafe Function RemoveProp Lib "user32" Alias "RemovePropA" (ByVal hwnd As LongPtr, ByVal lpString As String) As LongPtr
        Private Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
        Private Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
        Private Declare PtrSafe Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As LongPtr, ByVal hWnd2 As LongPtr, ByVal lpsz1 As String, ByVal lpsz2 As String) As LongPtr
        Private Declare PtrSafe Function IsWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
        Private Declare PtrSafe Function GetActiveWindow Lib "user32" () As LongPtr
        Private Declare PtrSafe Function InitCommonControlsEx Lib "comctl32.dll" (iccex As InitCommonControlsEx) As Long
        Private Declare PtrSafe Function CreateWindowEx Lib "user32" Alias "CreateWindowExW" (ByVal dwExStyle As Long, ByVal lpClassName As LongPtr, ByVal lpWindowName As LongPtr, 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 DestroyWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
        Private Declare PtrSafe Function SendMessage Lib "user32.dll" Alias "SendMessageW" (ByVal hwnd As LongPtr, ByVal wMsg As Long, ByVal wParam As LongPtr, ByRef lParam As Any) As LongPtr
        Private Declare PtrSafe Function SendMessageLong Lib "user32.dll" Alias "SendMessageW" (ByVal hwnd As LongPtr, ByVal wMsg As Long, ByVal wParam As LongPtr, ByVal lParam As LongPtr) As LongPtr
        Private Declare PtrSafe Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As LongPtr
        Private Declare PtrSafe Function SetThreadExecutionState Lib "Kernel32.dll" (ByVal esFlags As Long) 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 DeleteObject Lib "gdi32" (ByVal hObject As LongPtr) As Long
        Private Declare PtrSafe Function CreateFontIndirect Lib "gdi32" Alias "CreateFontIndirectA" (lpLogFont As LOGFONT) As LongPtr
        Private Declare PtrSafe Function sndPlaySound Lib "winmm.dll" Alias "sndPlaySoundA" (lpszSoundName As Any, ByVal uFlags As Long) As Long
        Private Declare PtrSafe Function waveOutGetNumDevs Lib "winmm.dll" () As Long
        Private Declare PtrSafe Function GetTempFileName Lib "kernel32" Alias "GetTempFileNameA" (ByVal lpszPath As String, ByVal lpPrefixString As String, ByVal wUnique As Long, ByVal lpTempFileName As String) As Long
        Private Declare PtrSafe Function GetAncestor Lib "user32" (ByVal hUF As LongPtr, ByVal gaFlags As Long) As LongPtr
        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 apiGetKeyState Lib "user32" Alias "GetKeyState" (ByVal nVirtKey As Long) As Integer
        Private Declare PtrSafe Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
#Else
    Private Enum LongPtr
        [_]
    End Enum
    Private Declare Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As Long
    Private Declare Function AccessibleObjectFromPoint Lib "oleacc" (ByVal lX As Long, ByVal lY As Long, ppacc As IAccessible, pvarChild As Variant) As Long
    Private Declare Function ActivateActCtx Lib "kernel32" (ByVal hActCtx As LongPtr, ByRef Cookie As LongPtr) As Long
    Private Declare Function CreateActCtx Lib "kernel32" Alias "CreateActCtxW" (ByRef ACTCTX As ACTCTXW) As LongPtr
    Private Declare Function DeactivateActCtx Lib "kernel32" (ByVal dwFlags As Long, ByVal Cookie As LongPtr) As Long
    Private Declare Sub ReleaseActCtx Lib "kernel32" (ByVal hActCtx As LongPtr)
    Private Declare Function InitCommonControls Lib "Comctl32" () As Long
    Private Declare Function IsUserAnAdmin Lib "Shell32" () As Long
    Private Declare Function SetWindowTheme Lib "UxTheme.dll" (ByVal hwnd As LongPtr, ByVal pszSubAppName As LongPtr, ByVal pszSubIdList As LongPtr) As Long
    Private Declare Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleW" (ByVal pModuleName As LongPtr) As LongPtr
    Private Declare Function SetProp Lib "user32" Alias "SetPropA" (ByVal hwnd As LongPtr, ByVal lpString As String, ByVal hData As LongPtr) As Long
    Private Declare Function GetProp Lib "user32" Alias "GetPropA" (ByVal hwnd As LongPtr, ByVal lpString As String) As LongPtr
    Private Declare Function RemoveProp Lib "user32" Alias "RemovePropA" (ByVal hwnd As LongPtr, ByVal lpString As String) As LongPtr
    Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)
    Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
    Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As LongPtr, ByVal hWnd2 As LongPtr, ByVal lpsz1 As String, ByVal lpsz2 As String) As LongPtr
    Private Declare Function IsWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
    Private Declare Function GetActiveWindow Lib "user32" () As LongPtr
    Private Declare Function InitCommonControlsEx Lib "comctl32.dll" (iccex As InitCommonControlsEx) As Long
    Private Declare Function CreateWindowEx Lib "user32" Alias "CreateWindowExW" (ByVal dwExStyle As Long, ByVal lpClassName As LongPtr, ByVal lpWindowName As LongPtr, 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 Function DestroyWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
    Private Declare Function SendMessage Lib "user32.dll" Alias "SendMessageW" (ByVal hwnd As LongPtr, ByVal wMsg As Long, ByVal wParam As LongPtr, ByRef lParam As Any) As LongPtr
    Private Declare Function SendMessageLong Lib "user32.dll" Alias "SendMessageW" (ByVal hwnd As LongPtr, ByVal wMsg As Long, ByVal wParam As LongPtr, ByVal lParam As LongPtr) As LongPtr
    Private Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As LongPtr
    Private Declare Function SetThreadExecutionState Lib "Kernel32.dll" (ByVal esFlags As Long) 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 DeleteObject Lib "gdi32" (ByVal hObject As LongPtr) As Long
    Private Declare Function CreateFontIndirect Lib "gdi32" Alias "CreateFontIndirectA" (lpLogFont As LOGFONT) As LongPtr
    Private Declare Function sndPlaySound Lib "winmm.dll" Alias "sndPlaySoundA" (lpszSoundName As Any, ByVal uFlags As Long) As Long
    Private Declare Function waveOutGetNumDevs Lib "winmm.dll" () As Long
    Private Declare Function GetTempFileName Lib "kernel32" Alias "GetTempFileNameA" (ByVal lpszPath As String, ByVal lpPrefixString As String, ByVal wUnique As Long, ByVal lpTempFileName As String) As Long
    Private Declare Function GetAncestor Lib "user32" (ByVal hUF As LongPtr, ByVal gaFlags As Long) As LongPtr
    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 apiGetKeyState Lib "user32" Alias "GetKeyState" (ByVal nVirtKey As Long) As Integer
    Private Declare Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
#End If

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
    lfA           As Long
    lfB           As Long
    lfFaceName(LF_FACESIZE) As Byte
End Type

Private Type TOOLINFOW
    cbSize    As Long
    uFlags    As Long
    hwnd      As LongPtr
    uId       As LongPtr
    cRect     As RECT
    hinst     As LongPtr
    lpszText  As LongPtr
    lParam    As LongPtr
End Type

Private Type InitCommonControlsEx
   Size As Long
   ICC  As Long
End Type

Private Type ACTCTXW
    cbSize                 As Long
    dwFlags                As Long
    lpSource               As LongPtr
    wProcessorArchitecture As Integer
    wLangId                As Integer
    lpAssemblyDirectory    As LongPtr
    lpResourceName         As LongPtr
    lpApplicationName      As LongPtr
    hModule                As LongPtr
End Type

Private arWavBytes() As Byte, sTmpManifestFile As String


'___________________________________________ Public Routines ______________________________________________

 
Public Sub Init(Optional ByVal Dummy As Boolean)
    Call BuildWAVSoundArrayFromBytes
    If GetProp(Application.hwnd, "ActCtxCookie") Then
        Call Application.OnTime(Now, "ReleaseCC6ActCtx")
    End
    End If
    Call InitCC6ActCtx
End Sub
 
Public Sub Term(Optional ByVal Dummy As Boolean)
    Call Application.OnTime(Now, "ReleaseCC6ActCtx")
    Erase sSheetCodeNamesArray: Erase arText: Erase arIcon: Erase arTitle
    Erase arForeColor: Erase arBackColor: Erase arBalloon:  Erase arFontName: Erase arVisibleTime
    Erase arFontSize:  Erase arFontBold:  Erase arPlaySound: Erase arRightToLeftReadingOrder
    'Debug.Print "Class Terminated."
End Sub

Public Sub WatchObjUnderMousePointer(Optional ByVal Dummy As Boolean)
    Call WatchObjUnderMousePointerNow
End Sub



'___________________________________________ Private Routines ______________________________________________

 
Private Sub InitCC6ActCtx()

    Const ICC_WIN95_CLASSES = &HFF
    Dim tIccex As InitCommonControlsEx
    Dim ACTCTX As ACTCTXW
    Dim hActCtx As LongPtr, ActCtxCookie As LongPtr
 
    Call IsUserAnAdmin
    With tIccex
        .Size = LenB(tIccex)
        .ICC = ICC_WIN95_CLASSES
    End With
    If InitCommonControlsEx(tIccex) = False Then
        Call InitCommonControls
    End If
    sTmpManifestFile = String(1000&, 0&)
    Call GetTempFileName(Environ("TEMP"), "Manifest", 0&, sTmpManifestFile)
    sTmpManifestFile = Left(sTmpManifestFile, InStr(sTmpManifestFile, vbNullChar) - 1&)
    Call CreateTempManifest(sTmpManifestFile)
    Do: DoEvents: Loop Until Len(Dir(sTmpManifestFile))
    If GetModuleHandle(StrPtr(vbNullString)) <> NULL_PTR Then
        With ACTCTX
            .cbSize = LenB(ACTCTX)
            .lpSource = StrPtr(sTmpManifestFile)
        End With
        hActCtx = CreateActCtx(ACTCTX)
        Call ActivateActCtx(hActCtx, ActCtxCookie)
        Call SetProp(Application.hwnd, "ActCtxCookie", ActCtxCookie)
        Call SetProp(Application.hwnd, "ACTCTX", hActCtx)
    End If
 
End Sub

Private Sub ReleaseCC6ActCtx()

    Const DEACTIVATE_ACTCTX_FLAG_NORMAL = 0&
    Dim hActCtx As LongPtr, ActCtxCookie As LongPtr
 
    hActCtx = GetProp(Application.hwnd, "ACTCTX")
    ActCtxCookie = GetProp(Application.hwnd, "ActCtxCookie")
    If hActCtx Then
        Call DeactivateActCtx(DEACTIVATE_ACTCTX_FLAG_NORMAL, ActCtxCookie)
        Call ReleaseActCtx(hActCtx)
        Call RemoveProp(Application.hwnd, "ACTCTX")
        Call RemoveProp(Application.hwnd, "ActCtxCookie")
        If Len(sTmpManifestFile) Then
            Call Kill(sTmpManifestFile)
        End If
    End If

End Sub

Private Sub WatchObjUnderMousePointerNow()

    Const ROLE_SYSTEM_PAGETAB = &H25, ROLE_SYSTEM_PAGETABLIST = &H3C&
    Const CHILDID_SELF = &H0&, S_OK = &H0
    Const GA_ROOT = 2&

    Static oPrveAcc As IAccessible
 
    Dim oIAcc As IAccessible, oIAParent As IAccessible
    Dim tCurPos As POINTAPI, sTextUnderMouse As String, indx As Long
    Dim hwnd As LongPtr

    On Error Resume Next

    If Not ActiveWorkbook Is ThisWorkbook Then Call RemoveToolTip: GoTo Xit
    If GetActiveWindow <> Application.hwnd Then Call RemoveToolTip: GoTo Xit
 
    Call GetCursorPos(tCurPos)
 
    #If Win64 Then
        Dim lP As LongLong
        Call CopyMemory(lP, tCurPos, LenB(lP))
        hwnd = WindowFromPoint(lP)
    #Else
        hwnd = WindowFromPoint(tCurPos.x, tCurPos.y)
    #End If
    If GetAncestor(hwnd, GA_ROOT) <> Application.hwnd Then
        Call RemoveToolTip: GoTo Xit
    End If
 
    #If Win64 Then
        Dim lPt As LongLong
        Call CopyMemory(lPt, tCurPos, LenB(lPt))
        If AccessibleObjectFromPoint(lPt, oIAcc, NULL_PTR) = S_OK Then
    #Else
        If AccessibleObjectFromPoint(tCurPos.x, tCurPos.y, oIAcc, NULL_PTR) = S_OK Then
    #End If
            If oIAcc.accRole(CHILDID_SELF) = ROLE_SYSTEM_PAGETAB Then
                If oPrveAcc.accName(CHILDID_SELF) <> oIAcc.accName(CHILDID_SELF) Then
                Set oIAParent = oIAcc.accParent
                    If oIAParent.accRole(CHILDID_SELF) = ROLE_SYSTEM_PAGETABLIST Then
                        sTextUnderMouse = oIAcc.accName(CHILDID_SELF)
                        If Not IsError(Application.Match(sTextUnderMouse, sSheetCodeNamesArray, 0&)) Then
                            indx = Application.Match(sTextUnderMouse, sSheetCodeNamesArray, 0&)
                            If indx Then
                                indx = indx - 1&
                                Call CreateToolTip(arText(indx), arIcon(indx), arTitle(indx), _
                                     arForeColor(indx), arBackColor(indx), arBalloon(indx), arFontName(indx), _
                                     arFontSize(indx), arFontBold(indx), arPlaySound(indx), _
                                     arRightToLeftReadingOrder(indx), arVisibleTime(indx))
                            End If
                        Else
                            Call RemoveToolTip
                        End If
                    End If
                End If
            Else
                Call RemoveToolTip
            End If
        End If
Xit:

    Set oPrveAcc = oIAcc
    Call UpdateCommandBars

End Sub

Private Sub UpdateCommandBars()
    Call SetTimer(Application.hwnd, NULL_PTR, 0&, AddressOf UpdateNow)
End Sub

Private Sub UpdateNow()
    If IsEscPressed = False Then
        Call KillTimer(Application.hwnd, NULL_PTR)
        With Application.CommandBars
            .FindControl(id:=2040&).Enabled = Not .FindControl(id:=2040&).Enabled
        End With
        PreventSleepMode = True
    Else
        Call RemoveToolTip
    End If
End Sub

Private Sub RemoveToolTip()
    Dim hFont As LongPtr
    If IsWindow(FindWindow("tooltips_class32", "MyToolTip")) Then
        hFont = GetProp(Application.hwnd, "hFont")
        Call DeleteObject(hFont)
        Call DestroyWindow(FindWindow("tooltips_class32", "MyToolTip"))
        'Debug.Print "Tooltip Destroyed."
    End If
End Sub

Private Property Let PreventSleepMode(ByVal bPrevent As Boolean)
    Const ES_SYSTEM_REQUIRED As Long = &H1
    Const ES_DISPLAY_REQUIRED As Long = &H2
    Const ES_AWAYMODE_REQUIRED = &H40
    Const ES_CONTINUOUS As Long = &H80000000
    If bPrevent Then
        Call SetThreadExecutionState _
             (ES_CONTINUOUS Or ES_DISPLAY_REQUIRED Or ES_SYSTEM_REQUIRED Or ES_AWAYMODE_REQUIRED)
    Else
        Call SetThreadExecutionState(ES_CONTINUOUS)
    End If
End Property

Private Sub CreateToolTip( _
        ByVal TipText As String, _
        ByVal Icon As Long, _
        ByVal Title As String, _
        ByVal ForeColor As Long, _
        ByVal BackColor As Long, _
        ByVal Balloon As Boolean, _
        ByVal FontName As String, _
        ByVal FontSize As Long, _
        ByVal FontBold As Boolean, _
        ByVal PlaySound As Boolean, _
        ByVal RightToLeftReadingOrder As Boolean, _
        ByVal VisibleTime As Long _
    )
                       
    Const TOOLTIPS_CLASSA = "tooltips_class32"
    Const CW_USEDEFAULT = &H80000000
    Const WS_EX_NOACTIVATE = &H8000000
    Const WS_EX_LAYOUTRTL = &H400000
    Const WM_USER = &H400
    Const TTM_ADDTOOLW = WM_USER + 4&
    Const TTM_SETDELAYTIME = WM_USER + 3&
    Const TTM_SETMAXTIPWIDTH = WM_USER + 24&
    Const TTM_SETTITLEW = WM_USER + 33&
    Const TTM_UPDATETIPTEXTW = WM_USER + 57&
    Const TTM_SETTIPBKCOLOR = WM_USER + 19&
    Const TTM_SETTIPTEXTCOLOR = WM_USER + 20&
    Const TTM_SETTITLE = WM_USER + 32&
    Const TTS_NOPREFIX = &H2
    Const TTS_BALLOON = &H40
    Const TTS_ALWAYSTIP = &H1
    Const TTF_IDISHWND = &H1
    Const TTF_SUBCLASS = &H10
    Const TTDT_AUTOPOP = &H2
    Const WM_SETFONT = &H30
 
    Dim hToolTip As LongPtr, hParent As LongPtr, hFont As LongPtr
    Dim lWinStyle As Long, lWinExStyle As Long, lRealColor As Long
    Dim uTTInfo As TOOLINFOW, tFont As LOGFONT, tCurPos As POINTAPI
    Dim arFaceName() As Byte
     
    Call RemoveToolTip
 
    lWinExStyle = WS_EX_NOACTIVATE + IIf(RightToLeftReadingOrder, WS_EX_LAYOUTRTL, 0&)
    lWinStyle = TTS_ALWAYSTIP Or TTS_NOPREFIX
    If Balloon Then lWinStyle = lWinStyle Or TTS_BALLOON
    hToolTip = CreateWindowEx(lWinExStyle, ByVal StrPtr(TOOLTIPS_CLASSA), ByVal StrPtr("MyToolTip"), _
               lWinStyle, CW_USEDEFAULT, CW_USEDEFAULT, CW_USEDEFAULT, CW_USEDEFAULT, _
               NULL_PTR, NULL_PTR, GetModuleHandle(StrPtr(vbNullString)), NULL_PTR)
 
    Call SetWindowTheme(hToolTip, StrPtr(""), StrPtr(""))
 
    arFaceName = StrConv(FontName & vbNullChar, vbFromUnicode)
    With tFont
        .lfHeight = -FontSize
        .lfWeight = IIf(FontBold, 800&, .lfWeight)
        Call CopyMemory(.lfFaceName(0&), arFaceName(0&), UBound(arFaceName))
    End With
    hFont = CreateFontIndirect(tFont)
    Call SendMessage(hToolTip, WM_SETFONT, hFont, True)
    Call SetProp(Application.hwnd, "hFont", hFont)
 
    hParent = FindWindowEx(FindWindowEx(Application.hwnd, NULL_PTR, "XLDESK", vbNullString) _
    , NULL_PTR, "EXCEL7", vbNullString)
   
    With uTTInfo
        .uFlags = TTF_SUBCLASS Or TTF_IDISHWND
        .hwnd = hParent
        .uId = hParent
        .hinst = GetModuleHandle(StrPtr(vbNullString))
        .lpszText = StrPtr(TipText)
        .cbSize = LenB(uTTInfo)
    End With
     
    Call SendMessage(hToolTip, TTM_SETMAXTIPWIDTH, NULL_PTR, ByVal 2048)
    Call SendMessage(hToolTip, TTM_ADDTOOLW, NULL_PTR, uTTInfo)
    Call SendMessage(hToolTip, TTM_UPDATETIPTEXTW, NULL_PTR, uTTInfo)
 
    If ForeColor <> -1& Then
        Call SendMessage(hToolTip, TTM_SETTIPTEXTCOLOR, ForeColor, NULL_PTR)
    End If
 
    If BackColor <> -1& Then
        Call TranslateColor(BackColor, NULL_PTR, lRealColor)
        Call SendMessage(hToolTip, TTM_SETTIPBKCOLOR, lRealColor, NULL_PTR)
    End If
 
    If Icon <> I_NoIcon Or Title <> vbNullString Then
        Call SendMessage(hToolTip, TTM_SETTITLEW, CLng(Icon), ByVal StrPtr(Title))
        Call SendMessageLong(hToolTip, TTM_SETDELAYTIME, TTDT_AUTOPOP, VisibleTime)
    End If
 
    If PlaySound Then
        Call SetTimer(hToolTip, 0, 500&, AddressOf PlayBeep)
    End If

End Sub

Private Function IsEscPressed() As Boolean
  Dim iKeyState As Integer
  iKeyState = apiGetKeyState(vbKeyEscape)
  IsEscPressed = ((iKeyState And &H8000) = &H8000 Or GetAsyncKeyState(vbKeyEscape))
End Function

Private Sub PlayBeep()
    Const SND_ASYNC = &H1, SND_NODEFAULT = &H2, SND_MEMORY = &H4
    Call KillTimer(FindWindow("tooltips_class32", "MyToolTip"), NULL_PTR)
    If waveOutGetNumDevs > 0& Then
        Call sndPlaySound(arWavBytes(0&), SND_ASYNC Or SND_NODEFAULT Or SND_MEMORY)
    End If
End Sub

Private Sub BuildWAVSoundArrayFromBytes()

    ReDim b(0& To 2725&) As Byte
 
    b(0) = 82: b(1) = 73: b(2) = 70: b(3) = 70: b(4) = 158: b(5) = 10: b(6) = 0: b(7) = 0: b(8) = 87: b(9) = 65: b(10) = 86: b(11) = 69: b(12) = 102: b(13) = 109: b(14) = 116: b(15) = 32: b(16) = 16: b(17) = 0: b(18) = 0: b(19) = 0: b(20) = 1: b(21) = 0: b(22) = 2: b(23) = 0: b(24) = 34: b(25) = 86: b(26) = 0: b(27) = 0: b(28) = 136: b(29) = 88
    b(30) = 1: b(31) = 0: b(32) = 4: b(33) = 0: b(34) = 16: b(35) = 0: b(36) = 76: b(37) = 73: b(38) = 83: b(39) = 84: b(40) = 26: b(41) = 0: b(42) = 0: b(43) = 0: b(44) = 73: b(45) = 78: b(46) = 70: b(47) = 79: b(48) = 73: b(49) = 83: b(50) = 70: b(51) = 84: b(52) = 14: b(53) = 0: b(54) = 0: b(55) = 0: b(56) = 76: b(57) = 97: b(58) = 118: b(59) = 102
    b(60) = 53: b(61) = 56: b(62) = 46: b(63) = 55: b(64) = 54: b(65) = 46: b(66) = 49: b(67) = 48: b(68) = 48: b(69) = 0: b(70) = 100: b(71) = 97: b(72) = 116: b(73) = 97: b(74) = 88: b(75) = 10: b(76) = 0: b(77) = 0: b(78) = 255: b(79) = 255: b(80) = 254: b(81) = 255: b(82) = 1: b(83) = 0: b(84) = 1: b(85) = 0: b(86) = 0: b(87) = 0: b(88) = 0: b(89) = 0
    b(90) = 0: b(91) = 0: b(92) = 0: b(93) = 0: b(94) = 0: b(95) = 0: b(96) = 1: b(97) = 0: b(98) = 0: b(99) = 0: b(100) = 255: b(101) = 255: b(102) = 0: b(103) = 0: b(104) = 0: b(105) = 0: b(106) = 0: b(107) = 0: b(108) = 0: b(109) = 0: b(110) = 0: b(111) = 0: b(112) = 0: b(113) = 0: b(114) = 0: b(115) = 0: b(116) = 255: b(117) = 255: b(118) = 0: b(119) = 0
    b(120) = 1: b(121) = 0: b(122) = 0: b(123) = 0: b(124) = 0: b(125) = 0: b(126) = 0: b(127) = 0: b(128) = 0: b(129) = 0: b(130) = 0: b(131) = 0: b(132) = 0: b(133) = 0: b(134) = 0: b(135) = 0: b(136) = 0: b(137) = 0: b(138) = 0: b(139) = 0: b(140) = 0: b(141) = 0: b(142) = 0: b(143) = 0: b(144) = 0: b(145) = 0: b(146) = 1: b(147) = 0: b(148) = 0: b(149) = 0
    b(150) = 255: b(151) = 255: b(152) = 0: b(153) = 0: b(154) = 1: b(155) = 0: b(156) = 1: b(157) = 0: b(158) = 0: b(159) = 0: b(160) = 255: b(161) = 255: b(162) = 0: b(163) = 0: b(164) = 0: b(165) = 0: b(166) = 255: b(167) = 255: b(168) = 0: b(169) = 0: b(170) = 1: b(171) = 0: b(172) = 0: b(173) = 0: b(174) = 255: b(175) = 255: b(176) = 0: b(177) = 0: b(178) = 0: b(179) = 0
    b(180) = 0: b(181) = 0: b(182) = 0: b(183) = 0: b(184) = 0: b(185) = 0: b(186) = 0: b(187) = 0: b(188) = 0: b(189) = 0: b(190) = 0: b(191) = 0: b(192) = 0: b(193) = 0: b(194) = 255: b(195) = 255: b(196) = 0: b(197) = 0: b(198) = 0: b(199) = 0: b(200) = 0: b(201) = 0: b(202) = 0: b(203) = 0: b(204) = 0: b(205) = 0: b(206) = 1: b(207) = 0: b(208) = 0: b(209) = 0
    b(210) = 0: b(211) = 0: b(212) = 0: b(213) = 0: b(214) = 1: b(215) = 0: b(216) = 0: b(217) = 0: b(218) = 0: b(219) = 0: b(220) = 0: b(221) = 0: b(222) = 0: b(223) = 0: b(224) = 0: b(225) = 0: b(226) = 0: b(227) = 0: b(228) = 0: b(229) = 0: b(230) = 0: b(231) = 0: b(232) = 0: b(233) = 0: b(234) = 0: b(235) = 0: b(236) = 0: b(237) = 0: b(238) = 0: b(239) = 0
    b(240) = 255: b(241) = 255: b(242) = 0: b(243) = 0: b(244) = 1: b(245) = 0: b(246) = 1: b(247) = 0: b(248) = 0: b(249) = 0: b(250) = 0: b(251) = 0: b(252) = 0: b(253) = 0: b(254) = 0: b(255) = 0: b(256) = 255: b(257) = 255: b(258) = 0: b(259) = 0: b(260) = 0: b(261) = 0: b(262) = 0: b(263) = 0: b(264) = 255: b(265) = 255: b(266) = 0: b(267) = 0: b(268) = 0: b(269) = 0
    b(270) = 0: b(271) = 0: b(272) = 0: b(273) = 0: b(274) = 0: b(275) = 0: b(276) = 0: b(277) = 0: b(278) = 0: b(279) = 0: b(280) = 0: b(281) = 0: b(282) = 0: b(283) = 0: b(284) = 0: b(285) = 0: b(286) = 0: b(287) = 0: b(288) = 0: b(289) = 0: b(290) = 1: b(291) = 0: b(292) = 0: b(293) = 0: b(294) = 255: b(295) = 255: b(296) = 0: b(297) = 0: b(298) = 0: b(299) = 0
    b(300) = 0: b(301) = 0: b(302) = 1: b(303) = 0: b(304) = 1: b(305) = 0: b(306) = 0: b(307) = 0: b(308) = 0: b(309) = 0: b(310) = 2: b(311) = 0: b(312) = 0: b(313) = 0: b(314) = 0: b(315) = 0: b(316) = 1: b(317) = 0: b(318) = 1: b(319) = 0: b(320) = 1: b(321) = 0: b(322) = 1: b(323) = 0: b(324) = 1: b(325) = 0: b(326) = 0: b(327) = 0: b(328) = 0: b(329) = 0
    b(330) = 0: b(331) = 0: b(332) = 0: b(333) = 0: b(334) = 0: b(335) = 0: b(336) = 0: b(337) = 0: b(338) = 0: b(339) = 0: b(340) = 255: b(341) = 255: b(342) = 0: b(343) = 0: b(344) = 0: b(345) = 0: b(346) = 0: b(347) = 0: b(348) = 0: b(349) = 0: b(350) = 0: b(351) = 0: b(352) = 0: b(353) = 0: b(354) = 1: b(355) = 0: b(356) = 0: b(357) = 0: b(358) = 255: b(359) = 255
    b(360) = 255: b(361) = 255: b(362) = 1: b(363) = 0: b(364) = 1: b(365) = 0: b(366) = 0: b(367) = 0: b(368) = 0: b(369) = 0: b(370) = 0: b(371) = 0: b(372) = 0: b(373) = 0: b(374) = 0: b(375) = 0: b(376) = 0: b(377) = 0: b(378) = 0: b(379) = 0: b(380) = 0: b(381) = 0: b(382) = 1: b(383) = 0: b(384) = 2: b(385) = 0: b(386) = 0: b(387) = 0: b(388) = 0: b(389) = 0
    b(390) = 1: b(391) = 0: b(392) = 0: b(393) = 0: b(394) = 1: b(395) = 0: b(396) = 255: b(397) = 255: b(398) = 0: b(399) = 0: b(400) = 1: b(401) = 0: b(402) = 0: b(403) = 0: b(404) = 255: b(405) = 255: b(406) = 0: b(407) = 0: b(408) = 0: b(409) = 0: b(410) = 0: b(411) = 0: b(412) = 0: b(413) = 0: b(414) = 1: b(415) = 0: b(416) = 0: b(417) = 0: b(418) = 255: b(419) = 255
    b(420) = 1: b(421) = 0: b(422) = 0: b(423) = 0: b(424) = 0: b(425) = 0: b(426) = 1: b(427) = 0: b(428) = 1: b(429) = 0: b(430) = 0: b(431) = 0: b(432) = 1: b(433) = 0: b(434) = 0: b(435) = 0: b(436) = 0: b(437) = 0: b(438) = 1: b(439) = 0: b(440) = 0: b(441) = 0: b(442) = 1: b(443) = 0: b(444) = 0: b(445) = 0: b(446) = 0: b(447) = 0: b(448) = 254: b(449) = 255
    b(450) = 0: b(451) = 0: b(452) = 255: b(453) = 255: b(454) = 255: b(455) = 255: b(456) = 0: b(457) = 0: b(458) = 255: b(459) = 255: b(460) = 255: b(461) = 255: b(462) = 0: b(463) = 0: b(464) = 255: b(465) = 255: b(466) = 1: b(467) = 0: b(468) = 255: b(469) = 255: b(470) = 254: b(471) = 255: b(472) = 255: b(473) = 255: b(474) = 1: b(475) = 0: b(476) = 0: b(477) = 0: b(478) = 3: b(479) = 0
    b(480) = 0: b(481) = 0: b(482) = 255: b(483) = 255: b(484) = 0: b(485) = 0: b(486) = 1: b(487) = 0: b(488) = 1: b(489) = 0: b(490) = 2: b(491) = 0: b(492) = 2: b(493) = 0: b(494) = 0: b(495) = 0: b(496) = 1: b(497) = 0: b(498) = 2: b(499) = 0: b(500) = 3: b(501) = 0: b(502) = 2: b(503) = 0: b(504) = 2: b(505) = 0: b(506) = 255: b(507) = 255: b(508) = 0: b(509) = 0
    b(510) = 255: b(511) = 255: b(512) = 0: b(513) = 0: b(514) = 254: b(515) = 255: b(516) = 0: b(517) = 0: b(518) = 253: b(519) = 255: b(520) = 2: b(521) = 0: b(522) = 253: b(523) = 255: b(524) = 2: b(525) = 0: b(526) = 0: b(527) = 0: b(528) = 254: b(529) = 255: b(530) = 254: b(531) = 255: b(532) = 1: b(533) = 0: b(534) = 255: b(535) = 255: b(536) = 255: b(537) = 255: b(538) = 255: b(539) = 255
    b(540) = 254: b(541) = 255: b(542) = 0: b(543) = 0: b(544) = 254: b(545) = 255: b(546) = 3: b(547) = 0: b(548) = 253: b(549) = 255: b(550) = 1: b(551) = 0: b(552) = 254: b(553) = 255: b(554) = 0: b(555) = 0: b(556) = 253: b(557) = 255: b(558) = 1: b(559) = 0: b(560) = 253: b(561) = 255: b(562) = 255: b(563) = 255: b(564) = 255: b(565) = 255: b(566) = 3: b(567) = 0: b(568) = 1: b(569) = 0
    b(570) = 0: b(571) = 0: b(572) = 0: b(573) = 0: b(574) = 254: b(575) = 255: b(576) = 3: b(577) = 0: b(578) = 1: b(579) = 0: b(580) = 6: b(581) = 0: b(582) = 2: b(583) = 0: b(584) = 6: b(585) = 0: b(586) = 254: b(587) = 255: b(588) = 5: b(589) = 0: b(590) = 255: b(591) = 255: b(592) = 4: b(593) = 0: b(594) = 0: b(595) = 0: b(596) = 1: b(597) = 0: b(598) = 255: b(599) = 255
    b(600) = 253: b(601) = 255: b(602) = 1: b(603) = 0: b(604) = 255: b(605) = 255: b(606) = 0: b(607) = 0: b(608) = 254: b(609) = 255: b(610) = 0: b(611) = 0: b(612) = 253: b(613) = 255: b(614) = 254: b(615) = 255: b(616) = 255: b(617) = 255: b(618) = 253: b(619) = 255: b(620) = 254: b(621) = 255: b(622) = 1: b(623) = 0: b(624) = 254: b(625) = 255: b(626) = 254: b(627) = 255: b(628) = 254: b(629) = 255
    b(630) = 1: b(631) = 0: b(632) = 2: b(633) = 0: b(634) = 254: b(635) = 255: b(636) = 3: b(637) = 0: b(638) = 255: b(639) = 255: b(640) = 2: b(641) = 0: b(642) = 1: b(643) = 0: b(644) = 2: b(645) = 0: b(646) = 255: b(647) = 255: b(648) = 0: b(649) = 0: b(650) = 3: b(651) = 0: b(652) = 1: b(653) = 0: b(654) = 5: b(655) = 0: b(656) = 3: b(657) = 0: b(658) = 3: b(659) = 0
    b(660) = 1: b(661) = 0: b(662) = 3: b(663) = 0: b(664) = 2: b(665) = 0: b(666) = 0: b(667) = 0: b(668) = 3: b(669) = 0: b(670) = 1: b(671) = 0: b(672) = 3: b(673) = 0: b(674) = 0: b(675) = 0: b(676) = 0: b(677) = 0: b(678) = 1: b(679) = 0: b(680) = 253: b(681) = 255: b(682) = 2: b(683) = 0: b(684) = 254: b(685) = 255: b(686) = 0: b(687) = 0: b(688) = 0: b(689) = 0
    b(690) = 251: b(691) = 255: b(692) = 250: b(693) = 255: b(694) = 252: b(695) = 255: b(696) = 251: b(697) = 255: b(698) = 4: b(699) = 0: b(700) = 253: b(701) = 255: b(702) = 0: b(703) = 0: b(704) = 254: b(705) = 255: b(706) = 255: b(707) = 255: b(708) = 4: b(709) = 0: b(710) = 253: b(711) = 255: b(712) = 1: b(713) = 0: b(714) = 0: b(715) = 0: b(716) = 5: b(717) = 0: b(718) = 253: b(719) = 255
    b(720) = 5: b(721) = 0: b(722) = 254: b(723) = 255: b(724) = 255: b(725) = 255: b(726) = 252: b(727) = 255: b(728) = 4: b(729) = 0: b(730) = 255: b(731) = 255: b(732) = 4: b(733) = 0: b(734) = 3: b(735) = 0: b(736) = 253: b(737) = 255: b(738) = 3: b(739) = 0: b(740) = 252: b(741) = 255: b(742) = 1: b(743) = 0: b(744) = 252: b(745) = 255: b(746) = 0: b(747) = 0: b(748) = 253: b(749) = 255
    b(750) = 2: b(751) = 0: b(752) = 253: b(753) = 255: b(754) = 1: b(755) = 0: b(756) = 255: b(757) = 255: b(758) = 1: b(759) = 0: b(760) = 252: b(761) = 255: b(762) = 5: b(763) = 0: b(764) = 252: b(765) = 255: b(766) = 6: b(767) = 0: b(768) = 255: b(769) = 255: b(770) = 1: b(771) = 0: b(772) = 4: b(773) = 0: b(774) = 255: b(775) = 255: b(776) = 1: b(777) = 0: b(778) = 252: b(779) = 255
    b(780) = 250: b(781) = 255: b(782) = 1: b(783) = 0: b(784) = 3: b(785) = 0: b(786) = 252: b(787) = 255: b(788) = 0: b(789) = 0: b(790) = 254: b(791) = 255: b(792) = 3: b(793) = 0: b(794) = 0: b(795) = 0: b(796) = 7: b(797) = 0: b(798) = 1: b(799) = 0: b(800) = 255: b(801) = 255: b(802) = 254: b(803) = 255: b(804) = 4: b(805) = 0: b(806) = 251: b(807) = 255: b(808) = 5: b(809) = 0
    b(810) = 255: b(811) = 255: b(812) = 0: b(813) = 0: b(814) = 255: b(815) = 255: b(816) = 0: b(817) = 0: b(818) = 253: b(819) = 255: b(820) = 5: b(821) = 0: b(822) = 2: b(823) = 0: b(824) = 0: b(825) = 0: b(826) = 10: b(827) = 0: b(828) = 252: b(829) = 255: b(830) = 6: b(831) = 0: b(832) = 253: b(833) = 255: b(834) = 2: b(835) = 0: b(836) = 254: b(837) = 255: b(838) = 9: b(839) = 0
    b(840) = 1: b(841) = 0: b(842) = 11: b(843) = 0: b(844) = 254: b(845) = 255: b(846) = 5: b(847) = 0: b(848) = 250: b(849) = 255: b(850) = 0: b(851) = 0: b(852) = 252: b(853) = 255: b(854) = 254: b(855) = 255: b(856) = 3: b(857) = 0: b(858) = 251: b(859) = 255: b(860) = 1: b(861) = 0: b(862) = 252: b(863) = 255: b(864) = 0: b(865) = 0: b(866) = 4: b(867) = 0: b(868) = 10: b(869) = 0
    b(870) = 0: b(871) = 0: b(872) = 9: b(873) = 0: b(874) = 253: b(875) = 255: b(876) = 3: b(877) = 0: b(878) = 251: b(879) = 255: b(880) = 10: b(881) = 0: b(882) = 1: b(883) = 0: b(884) = 4: b(885) = 0: b(886) = 255: b(887) = 255: b(888) = 1: b(889) = 0: b(890) = 0: b(891) = 0: b(892) = 2: b(893) = 0: b(894) = 6: b(895) = 0: b(896) = 254: b(897) = 255: b(898) = 255: b(899) = 255
    b(900) = 0: b(901) = 0: b(902) = 254: b(903) = 255: b(904) = 254: b(905) = 255: b(906) = 1: b(907) = 0: b(908) = 252: b(909) = 255: b(910) = 247: b(911) = 255: b(912) = 254: b(913) = 255: b(914) = 2: b(915) = 0: b(916) = 3: b(917) = 0: b(918) = 6: b(919) = 0: b(920) = 1: b(921) = 0: b(922) = 6: b(923) = 0: b(924) = 2: b(925) = 0: b(926) = 255: b(927) = 255: b(928) = 2: b(929) = 0
    b(930) = 2: b(931) = 0: b(932) = 5: b(933) = 0: b(934) = 4: b(935) = 0: b(936) = 10: b(937) = 0: b(938) = 254: b(939) = 255: b(940) = 255: b(941) = 255: b(942) = 3: b(943) = 0: b(944) = 252: b(945) = 255: b(946) = 255: b(947) = 255: b(948) = 252: b(949) = 255: b(950) = 0: b(951) = 0: b(952) = 255: b(953) = 255: b(954) = 255: b(955) = 255: b(956) = 4: b(957) = 0: b(958) = 248: b(959) = 255
    b(960) = 255: b(961) = 255: b(962) = 0: b(963) = 0: b(964) = 1: b(965) = 0: b(966) = 1: b(967) = 0: b(968) = 252: b(969) = 255: b(970) = 254: b(971) = 255: b(972) = 255: b(973) = 255: b(974) = 4: b(975) = 0: b(976) = 8: b(977) = 0: b(978) = 4: b(979) = 0: b(980) = 6: b(981) = 0: b(982) = 3: b(983) = 0: b(984) = 252: b(985) = 255: b(986) = 252: b(987) = 255: b(988) = 252: b(989) = 255
    b(990) = 2: b(991) = 0: b(992) = 4: b(993) = 0: b(994) = 4: b(995) = 0: b(996) = 5: b(997) = 0: b(998) = 254: b(999) = 255: b(1000) = 0: b(1001) = 0: b(1002) = 250: b(1003) = 255: b(1004) = 254: b(1005) = 255: b(1006) = 252: b(1007) = 255: b(1008) = 253: b(1009) = 255: b(1010) = 245: b(1011) = 255: b(1012) = 254: b(1013) = 255: b(1014) = 248: b(1015) = 255: b(1016) = 252: b(1017) = 255: b(1018) = 253: b(1019) = 255
    b(1020) = 250: b(1021) = 255: b(1022) = 2: b(1023) = 0: b(1024) = 255: b(1025) = 255: b(1026) = 254: b(1027) = 255: b(1028) = 250: b(1029) = 255: b(1030) = 1: b(1031) = 0: b(1032) = 3: b(1033) = 0: b(1034) = 1: b(1035) = 0: b(1036) = 11: b(1037) = 0: b(1038) = 3: b(1039) = 0: b(1040) = 10: b(1041) = 0: b(1042) = 12: b(1043) = 0: b(1044) = 17: b(1045) = 0: b(1046) = 5: b(1047) = 0: b(1048) = 23: b(1049) = 0
    b(1050) = 253: b(1051) = 255: b(1052) = 11: b(1053) = 0: b(1054) = 252: b(1055) = 255: b(1056) = 246: b(1057) = 255: b(1058) = 255: b(1059) = 255: b(1060) = 252: b(1061) = 255: b(1062) = 0: b(1063) = 0: b(1064) = 4: b(1065) = 0: b(1066) = 6: b(1067) = 0: b(1068) = 251: b(1069) = 255: b(1070) = 11: b(1071) = 0: b(1072) = 246: b(1073) = 255: b(1074) = 1: b(1075) = 0: b(1076) = 9: b(1077) = 0: b(1078) = 251: b(1079) = 255
    b(1080) = 10: b(1081) = 0: b(1082) = 5: b(1083) = 0: b(1084) = 250: b(1085) = 255: b(1086) = 2: b(1087) = 0: b(1088) = 10: b(1089) = 0: b(1090) = 0: b(1091) = 0: b(1092) = 16: b(1093) = 0: b(1094) = 4: b(1095) = 0: b(1096) = 3: b(1097) = 0: b(1098) = 248: b(1099) = 255: b(1100) = 244: b(1101) = 255: b(1102) = 243: b(1103) = 255: b(1104) = 236: b(1105) = 255: b(1106) = 236: b(1107) = 255: b(1108) = 242: b(1109) = 255
    b(1110) = 238: b(1111) = 255: b(1112) = 242: b(1113) = 255: b(1114) = 249: b(1115) = 255: b(1116) = 232: b(1117) = 255: b(1118) = 251: b(1119) = 255: b(1120) = 246: b(1121) = 255: b(1122) = 16: b(1123) = 0: b(1124) = 13: b(1125) = 0: b(1126) = 248: b(1127) = 255: b(1128) = 6: b(1129) = 0: b(1130) = 236: b(1131) = 255: b(1132) = 7: b(1133) = 0: b(1134) = 3: b(1135) = 0: b(1136) = 10: b(1137) = 0: b(1138) = 34: b(1139) = 0
    b(1140) = 26: b(1141) = 0: b(1142) = 55: b(1143) = 0: b(1144) = 51: b(1145) = 0: b(1146) = 33: b(1147) = 0: b(1148) = 36: b(1149) = 0: b(1150) = 13: b(1151) = 0: b(1152) = 15: b(1153) = 0: b(1154) = 249: b(1155) = 255: b(1156) = 4: b(1157) = 0: b(1158) = 241: b(1159) = 255: b(1160) = 234: b(1161) = 255: b(1162) = 251: b(1163) = 255: b(1164) = 236: b(1165) = 255: b(1166) = 223: b(1167) = 255: b(1168) = 246: b(1169) = 255
    b(1170) = 222: b(1171) = 255: b(1172) = 228: b(1173) = 255: b(1174) = 237: b(1175) = 255: b(1176) = 214: b(1177) = 255: b(1178) = 241: b(1179) = 255: b(1180) = 220: b(1181) = 255: b(1182) = 238: b(1183) = 255: b(1184) = 244: b(1185) = 255: b(1186) = 237: b(1187) = 255: b(1188) = 4: b(1189) = 0: b(1190) = 254: b(1191) = 255: b(1192) = 9: b(1193) = 0: b(1194) = 22: b(1195) = 0: b(1196) = 27: b(1197) = 0: b(1198) = 14: b(1199) = 0
    b(1200) = 20: b(1201) = 0: b(1202) = 251: b(1203) = 255: b(1204) = 6: b(1205) = 0: b(1206) = 249: b(1207) = 255: b(1208) = 6: b(1209) = 0: b(1210) = 241: b(1211) = 255: b(1212) = 13: b(1213) = 0: b(1214) = 12: b(1215) = 0: b(1216) = 19: b(1217) = 0: b(1218) = 35: b(1219) = 0: b(1220) = 12: b(1221) = 0: b(1222) = 26: b(1223) = 0: b(1224) = 4: b(1225) = 0: b(1226) = 16: b(1227) = 0: b(1228) = 21: b(1229) = 0
    b(1230) = 14: b(1231) = 0: b(1232) = 21: b(1233) = 0: b(1234) = 22: b(1235) = 0: b(1236) = 20: b(1237) = 0: b(1238) = 8: b(1239) = 0: b(1240) = 17: b(1241) = 0: b(1242) = 244: b(1243) = 255: b(1244) = 5: b(1245) = 0: b(1246) = 220: b(1247) = 255: b(1248) = 249: b(1249) = 255: b(1250) = 226: b(1251) = 255: b(1252) = 233: b(1253) = 255: b(1254) = 232: b(1255) = 255: b(1256) = 210: b(1257) = 255: b(1258) = 215: b(1259) = 255
    b(1260) = 199: b(1261) = 255: b(1262) = 207: b(1263) = 255: b(1264) = 194: b(1265) = 255: b(1266) = 216: b(1267) = 255: b(1268) = 207: b(1269) = 255: b(1270) = 247: b(1271) = 255: b(1272) = 249: b(1273) = 255: b(1274) = 16: b(1275) = 0: b(1276) = 17: b(1277) = 0: b(1278) = 48: b(1279) = 0: b(1280) = 36: b(1281) = 0: b(1282) = 62: b(1283) = 0: b(1284) = 58: b(1285) = 0: b(1286) = 47: b(1287) = 0: b(1288) = 62: b(1289) = 0
    b(1290) = 43: b(1291) = 0: b(1292) = 47: b(1293) = 0: b(1294) = 53: b(1295) = 0: b(1296) = 41: b(1297) = 0: b(1298) = 27: b(1299) = 0: b(1300) = 30: b(1301) = 0: b(1302) = 2: b(1303) = 0: b(1304) = 18: b(1305) = 0: b(1306) = 233: b(1307) = 255: b(1308) = 1: b(1309) = 0: b(1310) = 228: b(1311) = 255: b(1312) = 233: b(1313) = 255: b(1314) = 213: b(1315) = 255: b(1316) = 212: b(1317) = 255: b(1318) = 209: b(1319) = 255
    b(1320) = 209: b(1321) = 255: b(1322) = 211: b(1323) = 255: b(1324) = 218: b(1325) = 255: b(1326) = 211: b(1327) = 255: b(1328) = 224: b(1329) = 255: b(1330) = 236: b(1331) = 255: b(1332) = 243: b(1333) = 255: b(1334) = 239: b(1335) = 255: b(1336) = 254: b(1337) = 255: b(1338) = 249: b(1339) = 255: b(1340) = 3: b(1341) = 0: b(1342) = 11: b(1343) = 0: b(1344) = 7: b(1345) = 0: b(1346) = 25: b(1347) = 0: b(1348) = 18: b(1349) = 0
    b(1350) = 24: b(1351) = 0: b(1352) = 23: b(1353) = 0: b(1354) = 24: b(1355) = 0: b(1356) = 15: b(1357) = 0: b(1358) = 19: b(1359) = 0: b(1360) = 10: b(1361) = 0: b(1362) = 20: b(1363) = 0: b(1364) = 24: b(1365) = 0: b(1366) = 33: b(1367) = 0: b(1368) = 36: b(1369) = 0: b(1370) = 43: b(1371) = 0: b(1372) = 30: b(1373) = 0: b(1374) = 54: b(1375) = 0: b(1376) = 31: b(1377) = 0: b(1378) = 17: b(1379) = 0
    b(1380) = 14: b(1381) = 0: b(1382) = 2: b(1383) = 0: b(1384) = 10: b(1385) = 0: b(1386) = 253: b(1387) = 255: b(1388) = 2: b(1389) = 0: b(1390) = 226: b(1391) = 255: b(1392) = 237: b(1393) = 255: b(1394) = 214: b(1395) = 255: b(1396) = 228: b(1397) = 255: b(1398) = 193: b(1399) = 255: b(1400) = 201: b(1401) = 255: b(1402) = 189: b(1403) = 255: b(1404) = 193: b(1405) = 255: b(1406) = 202: b(1407) = 255: b(1408) = 215: b(1409) = 255
    b(1410) = 219: b(1411) = 255: b(1412) = 223: b(1413) = 255: b(1414) = 246: b(1415) = 255: b(1416) = 237: b(1417) = 255: b(1418) = 2: b(1419) = 0: b(1420) = 8: b(1421) = 0: b(1422) = 26: b(1423) = 0: b(1424) = 19: b(1425) = 0: b(1426) = 52: b(1427) = 0: b(1428) = 39: b(1429) = 0: b(1430) = 57: b(1431) = 0: b(1432) = 71: b(1433) = 0: b(1434) = 79: b(1435) = 0: b(1436) = 84: b(1437) = 0: b(1438) = 68: b(1439) = 0
    b(1440) = 72: b(1441) = 0: b(1442) = 35: b(1443) = 0: b(1444) = 35: b(1445) = 0: b(1446) = 17: b(1447) = 0: b(1448) = 12: b(1449) = 0: b(1450) = 253: b(1451) = 255: b(1452) = 0: b(1453) = 0: b(1454) = 228: b(1455) = 255: b(1456) = 229: b(1457) = 255: b(1458) = 210: b(1459) = 255: b(1460) = 207: b(1461) = 255: b(1462) = 210: b(1463) = 255: b(1464) = 194: b(1465) = 255: b(1466) = 219: b(1467) = 255: b(1468) = 193: b(1469) = 255
    b(1470) = 230: b(1471) = 255: b(1472) = 222: b(1473) = 255: b(1474) = 252: b(1475) = 255: b(1476) = 236: b(1477) = 255: b(1478) = 251: b(1479) = 255: b(1480) = 251: b(1481) = 255: b(1482) = 0: b(1483) = 0: b(1484) = 6: b(1485) = 0: b(1486) = 9: b(1487) = 0: b(1488) = 10: b(1489) = 0: b(1490) = 6: b(1491) = 0: b(1492) = 28: b(1493) = 0: b(1494) = 18: b(1495) = 0: b(1496) = 26: b(1497) = 0: b(1498) = 3: b(1499) = 0
    b(1500) = 23: b(1501) = 0: b(1502) = 248: b(1503) = 255: b(1504) = 20: b(1505) = 0: b(1506) = 28: b(1507) = 0: b(1508) = 30: b(1509) = 0: b(1510) = 30: b(1511) = 0: b(1512) = 32: b(1513) = 0: b(1514) = 14: b(1515) = 0: b(1516) = 33: b(1517) = 0: b(1518) = 15: b(1519) = 0: b(1520) = 15: b(1521) = 0: b(1522) = 12: b(1523) = 0: b(1524) = 255: b(1525) = 255: b(1526) = 35: b(1527) = 0: b(1528) = 4: b(1529) = 0
    b(1530) = 13: b(1531) = 0: b(1532) = 251: b(1533) = 255: b(1534) = 6: b(1535) = 0: b(1536) = 246: b(1537) = 255: b(1538) = 254: b(1539) = 255: b(1540) = 230: b(1541) = 255: b(1542) = 242: b(1543) = 255: b(1544) = 234: b(1545) = 255: b(1546) = 229: b(1547) = 255: b(1548) = 223: b(1549) = 255: b(1550) = 200: b(1551) = 255: b(1552) = 220: b(1553) = 255: b(1554) = 214: b(1555) = 255: b(1556) = 232: b(1557) = 255: b(1558) = 220: b(1559) = 255
    b(1560) = 225: b(1561) = 255: b(1562) = 249: b(1563) = 255: b(1564) = 255: b(1565) = 255: b(1566) = 254: b(1567) = 255: b(1568) = 21: b(1569) = 0: b(1570) = 13: b(1571) = 0: b(1572) = 23: b(1573) = 0: b(1574) = 30: b(1575) = 0: b(1576) = 41: b(1577) = 0: b(1578) = 27: b(1579) = 0: b(1580) = 30: b(1581) = 0: b(1582) = 22: b(1583) = 0: b(1584) = 41: b(1585) = 0: b(1586) = 33: b(1587) = 0: b(1588) = 61: b(1589) = 0
    b(1590) = 36: b(1591) = 0: b(1592) = 43: b(1593) = 0: b(1594) = 15: b(1595) = 0: b(1596) = 4: b(1597) = 0: b(1598) = 249: b(1599) = 255: b(1600) = 0: b(1601) = 0: b(1602) = 248: b(1603) = 255: b(1604) = 245: b(1605) = 255: b(1606) = 232: b(1607) = 255: b(1608) = 220: b(1609) = 255: b(1610) = 249: b(1611) = 255: b(1612) = 217: b(1613) = 255: b(1614) = 220: b(1615) = 255: b(1616) = 200: b(1617) = 255: b(1618) = 234: b(1619) = 255
    b(1620) = 249: b(1621) = 255: b(1622) = 31: b(1623) = 0: b(1624) = 56: b(1625) = 0: b(1626) = 245: b(1627) = 255: b(1628) = 255: b(1629) = 255: b(1630) = 194: b(1631) = 255: b(1632) = 216: b(1633) = 255: b(1634) = 10: b(1635) = 0: b(1636) = 43: b(1637) = 0: b(1638) = 71: b(1639) = 0: b(1640) = 72: b(1641) = 0: b(1642) = 20: b(1643) = 0: b(1644) = 194: b(1645) = 255: b(1646) = 208: b(1647) = 255: b(1648) = 221: b(1649) = 255
    b(1650) = 60: b(1651) = 0: b(1652) = 92: b(1653) = 0: b(1654) = 222: b(1655) = 255: b(1656) = 226: b(1657) = 255: b(1658) = 156: b(1659) = 255: b(1660) = 35: b(1661) = 255: b(1662) = 62: b(1663) = 255: b(1664) = 97: b(1665) = 255: b(1666) = 89: b(1667) = 255: b(1668) = 97: b(1669) = 0: b(1670) = 200: b(1671) = 255: b(1672) = 41: b(1673) = 0: b(1674) = 51: b(1675) = 1: b(1676) = 144: b(1677) = 0: b(1678) = 74: b(1679) = 1
    b(1680) = 99: b(1681) = 1: b(1682) = 137: b(1683) = 0: b(1684) = 89: b(1685) = 0: b(1686) = 187: b(1687) = 255: b(1688) = 39: b(1689) = 255: b(1690) = 83: b(1691) = 255: b(1692) = 157: b(1693) = 255: b(1694) = 253: b(1695) = 255: b(1696) = 228: b(1697) = 0: b(1698) = 8: b(1699) = 0: b(1700) = 12: b(1701) = 1: b(1702) = 40: b(1703) = 1: b(1704) = 214: b(1705) = 255: b(1706) = 140: b(1707) = 0: b(1708) = 19: b(1709) = 255
    b(1710) = 17: b(1711) = 255: b(1712) = 8: b(1713) = 0: b(1714) = 93: b(1715) = 255: b(1716) = 214: b(1717) = 255: b(1718) = 185: b(1719) = 255: b(1720) = 70: b(1721) = 254: b(1722) = 39: b(1723) = 255: b(1724) = 172: b(1725) = 254: b(1726) = 15: b(1727) = 254: b(1728) = 250: b(1729) = 255: b(1730) = 66: b(1731) = 255: b(1732) = 3: b(1733) = 0: b(1734) = 114: b(1735) = 0: b(1736) = 74: b(1737) = 255: b(1738) = 55: b(1739) = 0
    b(1740) = 57: b(1741) = 0: b(1742) = 94: b(1743) = 1: b(1744) = 152: b(1745) = 1: b(1746) = 97: b(1747) = 1: b(1748) = 57: b(1749) = 1: b(1750) = 39: b(1751) = 1: b(1752) = 162: b(1753) = 0: b(1754) = 158: b(1755) = 1: b(1756) = 14: b(1757) = 1: b(1758) = 65: b(1759) = 0: b(1760) = 254: b(1761) = 0: b(1762) = 26: b(1763) = 255: b(1764) = 139: b(1765) = 255: b(1766) = 176: b(1767) = 255: b(1768) = 254: b(1769) = 254
    b(1770) = 150: b(1771) = 255: b(1772) = 244: b(1773) = 255: b(1774) = 84: b(1775) = 255: b(1776) = 9: b(1777) = 0: b(1778) = 244: b(1779) = 255: b(1780) = 59: b(1781) = 255: b(1782) = 213: b(1783) = 255: b(1784) = 62: b(1785) = 255: b(1786) = 26: b(1787) = 255: b(1788) = 164: b(1789) = 255: b(1790) = 182: b(1791) = 255: b(1792) = 10: b(1793) = 0: b(1794) = 34: b(1795) = 0: b(1796) = 11: b(1797) = 0: b(1798) = 209: b(1799) = 255
    b(1800) = 116: b(1801) = 255: b(1802) = 145: b(1803) = 255: b(1804) = 206: b(1805) = 255: b(1806) = 147: b(1807) = 255: b(1808) = 235: b(1809) = 255: b(1810) = 169: b(1811) = 255: b(1812) = 4: b(1813) = 255: b(1814) = 51: b(1815) = 0: b(1816) = 123: b(1817) = 255: b(1818) = 49: b(1819) = 0: b(1820) = 84: b(1821) = 0: b(1822) = 136: b(1823) = 0: b(1824) = 141: b(1825) = 0: b(1826) = 249: b(1827) = 0: b(1828) = 26: b(1829) = 1
    b(1830) = 252: b(1831) = 0: b(1832) = 116: b(1833) = 1: b(1834) = 89: b(1835) = 1: b(1836) = 29: b(1837) = 1: b(1838) = 3: b(1839) = 1: b(1840) = 12: b(1841) = 1: b(1842) = 52: b(1843) = 0: b(1844) = 99: b(1845) = 0: b(1846) = 237: b(1847) = 255: b(1848) = 195: b(1849) = 255: b(1850) = 78: b(1851) = 255: b(1852) = 115: b(1853) = 255: b(1854) = 16: b(1855) = 255: b(1856) = 157: b(1857) = 254: b(1858) = 238: b(1859) = 254
    b(1860) = 155: b(1861) = 254: b(1862) = 189: b(1863) = 254: b(1864) = 49: b(1865) = 255: b(1866) = 197: b(1867) = 254: b(1868) = 19: b(1869) = 255: b(1870) = 171: b(1871) = 255: b(1872) = 62: b(1873) = 255: b(1874) = 92: b(1875) = 0: b(1876) = 52: b(1877) = 0: b(1878) = 70: b(1879) = 0: b(1880) = 149: b(1881) = 0: b(1882) = 128: b(1883) = 0: b(1884) = 112: b(1885) = 0: b(1886) = 7: b(1887) = 1: b(1888) = 255: b(1889) = 0
    b(1890) = 209: b(1891) = 0: b(1892) = 236: b(1893) = 0: b(1894) = 208: b(1895) = 255: b(1896) = 217: b(1897) = 255: b(1898) = 84: b(1899) = 255: b(1900) = 13: b(1901) = 255: b(1902) = 116: b(1903) = 255: b(1904) = 115: b(1905) = 255: b(1906) = 188: b(1907) = 255: b(1908) = 11: b(1909) = 0: b(1910) = 158: b(1911) = 0: b(1912) = 134: b(1913) = 0: b(1914) = 134: b(1915) = 1: b(1916) = 28: b(1917) = 1: b(1918) = 46: b(1919) = 1
    b(1920) = 199: b(1921) = 0: b(1922) = 40: b(1923) = 1: b(1924) = 102: b(1925) = 0: b(1926) = 65: b(1927) = 0: b(1928) = 114: b(1929) = 0: b(1930) = 103: b(1931) = 255: b(1932) = 156: b(1933) = 0: b(1934) = 142: b(1935) = 254: b(1936) = 33: b(1937) = 0: b(1938) = 30: b(1939) = 255: b(1940) = 205: b(1941) = 254: b(1942) = 124: b(1943) = 255: b(1944) = 22: b(1945) = 254: b(1946) = 148: b(1947) = 254: b(1948) = 186: b(1949) = 254
    b(1950) = 158: b(1951) = 254: b(1952) = 78: b(1953) = 255: b(1954) = 170: b(1955) = 255: b(1956) = 210: b(1957) = 254: b(1958) = 136: b(1959) = 0: b(1960) = 113: b(1961) = 255: b(1962) = 36: b(1963) = 0: b(1964) = 210: b(1965) = 0: b(1966) = 106: b(1967) = 0: b(1968) = 15: b(1969) = 1: b(1970) = 185: b(1971) = 1: b(1972) = 173: b(1973) = 0: b(1974) = 251: b(1975) = 0: b(1976) = 247: b(1977) = 0: b(1978) = 215: b(1979) = 0
    b(1980) = 115: b(1981) = 1: b(1982) = 176: b(1983) = 0: b(1984) = 112: b(1985) = 0: b(1986) = 215: b(1987) = 255: b(1988) = 103: b(1989) = 255: b(1990) = 25: b(1991) = 0: b(1992) = 234: b(1993) = 255: b(1994) = 25: b(1995) = 0: b(1996) = 178: b(1997) = 0: b(1998) = 58: b(1999) = 255: b(2000) = 217: b(2001) = 255: b(2002) = 122: b(2003) = 255: b(2004) = 223: b(2005) = 254: b(2006) = 231: b(2007) = 255: b(2008) = 146: b(2009) = 255
    b(2010) = 128: b(2011) = 255: b(2012) = 112: b(2013) = 0: b(2014) = 20: b(2015) = 0: b(2016) = 45: b(2017) = 0: b(2018) = 72: b(2019) = 0: b(2020) = 157: b(2021) = 255: b(2022) = 137: b(2023) = 255: b(2024) = 85: b(2025) = 255: b(2026) = 116: b(2027) = 255: b(2028) = 138: b(2029) = 255: b(2030) = 180: b(2031) = 255: b(2032) = 226: b(2033) = 255: b(2034) = 148: b(2035) = 255: b(2036) = 182: b(2037) = 255: b(2038) = 139: b(2039) = 255
    b(2040) = 123: b(2041) = 255: b(2042) = 250: b(2043) = 255: b(2044) = 224: b(2045) = 255: b(2046) = 18: b(2047) = 0: b(2048) = 217: b(2049) = 255: b(2050) = 78: b(2051) = 0: b(2052) = 40: b(2053) = 0: b(2054) = 200: b(2055) = 0: b(2056) = 195: b(2057) = 0: b(2058) = 2: b(2059) = 1: b(2060) = 181: b(2061) = 0: b(2062) = 62: b(2063) = 1: b(2064) = 7: b(2065) = 1: b(2066) = 187: b(2067) = 0: b(2068) = 79: b(2069) = 1
    b(2070) = 116: b(2071) = 0: b(2072) = 180: b(2073) = 0: b(2074) = 71: b(2075) = 0: b(2076) = 12: b(2077) = 0: b(2078) = 133: b(2079) = 255: b(2080) = 187: b(2081) = 255: b(2082) = 79: b(2083) = 255: b(2084) = 100: b(2085) = 255: b(2086) = 55: b(2087) = 255: b(2088) = 73: b(2089) = 255: b(2090) = 206: b(2091) = 254: b(2092) = 217: b(2093) = 254: b(2094) = 21: b(2095) = 255: b(2096) = 149: b(2097) = 254: b(2098) = 115: b(2099) = 255
    b(2100) = 75: b(2101) = 255: b(2102) = 198: b(2103) = 255: b(2104) = 203: b(2105) = 255: b(2106) = 70: b(2107) = 0: b(2108) = 214: b(2109) = 255: b(2110) = 126: b(2111) = 0: b(2112) = 68: b(2113) = 0: b(2114) = 103: b(2115) = 0: b(2116) = 190: b(2117) = 0: b(2118) = 112: b(2119) = 0: b(2120) = 128: b(2121) = 0: b(2122) = 128: b(2123) = 0: b(2124) = 63: b(2125) = 0: b(2126) = 21: b(2127) = 0: b(2128) = 114: b(2129) = 0
    b(2130) = 219: b(2131) = 255: b(2132) = 76: b(2133) = 0: b(2134) = 31: b(2135) = 0: b(2136) = 30: b(2137) = 0: b(2138) = 134: b(2139) = 0: b(2140) = 14: b(2141) = 0: b(2142) = 149: b(2143) = 0: b(2144) = 116: b(2145) = 0: b(2146) = 84: b(2147) = 0: b(2148) = 177: b(2149) = 0: b(2150) = 84: b(2151) = 0: b(2152) = 54: b(2153) = 0: b(2154) = 50: b(2155) = 0: b(2156) = 185: b(2157) = 255: b(2158) = 208: b(2159) = 255
    b(2160) = 174: b(2161) = 255: b(2162) = 149: b(2163) = 255: b(2164) = 190: b(2165) = 255: b(2166) = 49: b(2167) = 255: b(2168) = 82: b(2169) = 255: b(2170) = 36: b(2171) = 255: b(2172) = 53: b(2173) = 255: b(2174) = 97: b(2175) = 255: b(2176) = 138: b(2177) = 255: b(2178) = 110: b(2179) = 255: b(2180) = 164: b(2181) = 255: b(2182) = 96: b(2183) = 255: b(2184) = 101: b(2185) = 255: b(2186) = 208: b(2187) = 255: b(2188) = 177: b(2189) = 255
    b(2190) = 157: b(2191) = 0: b(2192) = 90: b(2193) = 0: b(2194) = 212: b(2195) = 0: b(2196) = 115: b(2197) = 0: b(2198) = 134: b(2199) = 0: b(2200) = 208: b(2201) = 0: b(2202) = 165: b(2203) = 0: b(2204) = 189: b(2205) = 0: b(2206) = 108: b(2207) = 0: b(2208) = 35: b(2209) = 0: b(2210) = 26: b(2211) = 0: b(2212) = 198: b(2213) = 255: b(2214) = 164: b(2215) = 255: b(2216) = 254: b(2217) = 255: b(2218) = 212: b(2219) = 255
    b(2220) = 135: b(2221) = 0: b(2222) = 252: b(2223) = 255: b(2224) = 245: b(2225) = 255: b(2226) = 229: b(2227) = 0: b(2228) = 112: b(2229) = 0: b(2230) = 223: b(2231) = 0: b(2232) = 196: b(2233) = 0: b(2234) = 228: b(2235) = 255: b(2236) = 228: b(2237) = 255: b(2238) = 229: b(2239) = 254: b(2240) = 201: b(2241) = 254: b(2242) = 44: b(2243) = 255: b(2244) = 13: b(2245) = 255: b(2246) = 183: b(2247) = 255: b(2248) = 85: b(2249) = 0
    b(2250) = 213: b(2251) = 255: b(2252) = 126: b(2253) = 0: b(2254) = 185: b(2255) = 0: b(2256) = 129: b(2257) = 255: b(2258) = 123: b(2259) = 255: b(2260) = 175: b(2261) = 254: b(2262) = 65: b(2263) = 255: b(2264) = 250: b(2265) = 255: b(2266) = 189: b(2267) = 255: b(2268) = 89: b(2269) = 0: b(2270) = 71: b(2271) = 0: b(2272) = 112: b(2273) = 255: b(2274) = 218: b(2275) = 255: b(2276) = 178: b(2277) = 255: b(2278) = 83: b(2279) = 255
    b(2280) = 252: b(2281) = 0: b(2282) = 170: b(2283) = 0: b(2284) = 31: b(2285) = 1: b(2286) = 160: b(2287) = 0: b(2288) = 175: b(2289) = 255: b(2290) = 127: b(2291) = 0: b(2292) = 253: b(2293) = 255: b(2294) = 54: b(2295) = 0: b(2296) = 149: b(2297) = 0: b(2298) = 230: b(2299) = 255: b(2300) = 218: b(2301) = 255: b(2302) = 239: b(2303) = 0: b(2304) = 208: b(2305) = 255: b(2306) = 178: b(2307) = 0: b(2308) = 241: b(2309) = 0
    b(2310) = 71: b(2311) = 0: b(2312) = 240: b(2313) = 0: b(2314) = 69: b(2315) = 255: b(2316) = 235: b(2317) = 254: b(2318) = 32: b(2319) = 255: b(2320) = 222: b(2321) = 254: b(2322) = 103: b(2323) = 255: b(2324) = 241: b(2325) = 0: b(2326) = 172: b(2327) = 255: b(2328) = 65: b(2329) = 1: b(2330) = 67: b(2331) = 1: b(2332) = 126: b(2333) = 255: b(2334) = 2: b(2335) = 1: b(2336) = 17: b(2337) = 255: b(2338) = 177: b(2339) = 255
    b(2340) = 255: b(2341) = 255: b(2342) = 211: b(2343) = 254: b(2344) = 63: b(2345) = 0: b(2346) = 53: b(2347) = 255: b(2348) = 251: b(2349) = 254: b(2350) = 72: b(2351) = 255: b(2352) = 208: b(2353) = 253: b(2354) = 38: b(2355) = 254: b(2356) = 13: b(2357) = 255: b(2358) = 228: b(2359) = 254: b(2360) = 39: b(2361) = 0: b(2362) = 149: b(2363) = 0: b(2364) = 215: b(2365) = 255: b(2366) = 22: b(2367) = 1: b(2368) = 114: b(2369) = 0
    b(2370) = 37: b(2371) = 1: b(2372) = 119: b(2373) = 1: b(2374) = 141: b(2375) = 1: b(2376) = 194: b(2377) = 1: b(2378) = 200: b(2379) = 1: b(2380) = 212: b(2381) = 1: b(2382) = 235: b(2383) = 1: b(2384) = 254: b(2385) = 1: b(2386) = 163: b(2387) = 1: b(2388) = 125: b(2389) = 1: b(2390) = 225: b(2391) = 255: b(2392) = 216: b(2393) = 255: b(2394) = 197: b(2395) = 254: b(2396) = 39: b(2397) = 254: b(2398) = 32: b(2399) = 254
    b(2400) = 20: b(2401) = 254: b(2402) = 18: b(2403) = 254: b(2404) = 181: b(2405) = 254: b(2406) = 233: b(2407) = 254: b(2408) = 106: b(2409) = 254: b(2410) = 38: b(2411) = 255: b(2412) = 132: b(2413) = 254: b(2414) = 79: b(2415) = 255: b(2416) = 85: b(2417) = 255: b(2418) = 140: b(2419) = 255: b(2420) = 97: b(2421) = 0: b(2422) = 156: b(2423) = 0: b(2424) = 242: b(2425) = 0: b(2426) = 40: b(2427) = 1: b(2428) = 9: b(2429) = 1
    b(2430) = 210: b(2431) = 0: b(2432) = 208: b(2433) = 0: b(2434) = 128: b(2435) = 0: b(2436) = 103: b(2437) = 0: b(2438) = 166: b(2439) = 255: b(2440) = 239: b(2441) = 255: b(2442) = 145: b(2443) = 255: b(2444) = 105: b(2445) = 255: b(2446) = 185: b(2447) = 255: b(2448) = 106: b(2449) = 255: b(2450) = 46: b(2451) = 0: b(2452) = 245: b(2453) = 255: b(2454) = 186: b(2455) = 0: b(2456) = 143: b(2457) = 0: b(2458) = 212: b(2459) = 0
    b(2460) = 71: b(2461) = 1: b(2462) = 58: b(2463) = 1: b(2464) = 103: b(2465) = 1: b(2466) = 116: b(2467) = 1: b(2468) = 52: b(2469) = 1: b(2470) = 5: b(2471) = 1: b(2472) = 229: b(2473) = 0: b(2474) = 97: b(2475) = 0: b(2476) = 161: b(2477) = 0: b(2478) = 97: b(2479) = 255: b(2480) = 185: b(2481) = 255: b(2482) = 10: b(2483) = 254: b(2484) = 26: b(2485) = 254: b(2486) = 118: b(2487) = 253: b(2488) = 60: b(2489) = 253
    b(2490) = 129: b(2491) = 253: b(2492) = 119: b(2493) = 253: b(2494) = 233: b(2495) = 253: b(2496) = 47: b(2497) = 254: b(2498) = 226: b(2499) = 254: b(2500) = 134: b(2501) = 254: b(2502) = 26: b(2503) = 0: b(2504) = 150: b(2505) = 255: b(2506) = 72: b(2507) = 1: b(2508) = 62: b(2509) = 1: b(2510) = 30: b(2511) = 2: b(2512) = 81: b(2513) = 2: b(2514) = 88: b(2515) = 2: b(2516) = 173: b(2517) = 2: b(2518) = 43: b(2519) = 2
    b(2520) = 121: b(2521) = 2: b(2522) = 175: b(2523) = 1: b(2524) = 208: b(2525) = 1: b(2526) = 194: b(2527) = 0: b(2528) = 180: b(2529) = 0: b(2530) = 231: b(2531) = 255: b(2532) = 150: b(2533) = 255: b(2534) = 7: b(2535) = 255: b(2536) = 182: b(2537) = 254: b(2538) = 80: b(2539) = 254: b(2540) = 147: b(2541) = 254: b(2542) = 132: b(2543) = 254: b(2544) = 182: b(2545) = 254: b(2546) = 20: b(2547) = 255: b(2548) = 173: b(2549) = 254
    b(2550) = 128: b(2551) = 255: b(2552) = 65: b(2553) = 255: b(2554) = 20: b(2555) = 0: b(2556) = 249: b(2557) = 255: b(2558) = 89: b(2559) = 0: b(2560) = 169: b(2561) = 0: b(2562) = 84: b(2563) = 0: b(2564) = 189: b(2565) = 0: b(2566) = 45: b(2567) = 0: b(2568) = 91: b(2569) = 0: b(2570) = 153: b(2571) = 255: b(2572) = 247: b(2573) = 255: b(2574) = 25: b(2575) = 255: b(2576) = 109: b(2577) = 255: b(2578) = 224: b(2579) = 254
    b(2580) = 248: b(2581) = 254: b(2582) = 133: b(2583) = 255: b(2584) = 60: b(2585) = 255: b(2586) = 55: b(2587) = 0: b(2588) = 215: b(2589) = 255: b(2590) = 148: b(2591) = 0: b(2592) = 83: b(2593) = 0: b(2594) = 243: b(2595) = 0: b(2596) = 186: b(2597) = 0: b(2598) = 122: b(2599) = 1: b(2600) = 2: b(2601) = 1: b(2602) = 206: b(2603) = 1: b(2604) = 144: b(2605) = 1: b(2606) = 108: b(2607) = 1: b(2608) = 195: b(2609) = 1
    b(2610) = 211: b(2611) = 0: b(2612) = 14: b(2613) = 1: b(2614) = 60: b(2615) = 0: b(2616) = 63: b(2617) = 0: b(2618) = 125: b(2619) = 255: b(2620) = 200: b(2621) = 255: b(2622) = 203: b(2623) = 254: b(2624) = 60: b(2625) = 255: b(2626) = 32: b(2627) = 254: b(2628) = 121: b(2629) = 254: b(2630) = 242: b(2631) = 253: b(2632) = 249: b(2633) = 253: b(2634) = 53: b(2635) = 254: b(2636) = 13: b(2637) = 254: b(2638) = 197: b(2639) = 254
    b(2640) = 143: b(2641) = 254: b(2642) = 143: b(2643) = 255: b(2644) = 76: b(2645) = 255: b(2646) = 65: b(2647) = 0: b(2648) = 23: b(2649) = 0: b(2650) = 240: b(2651) = 0: b(2652) = 221: b(2653) = 0: b(2654) = 43: b(2655) = 1: b(2656) = 17: b(2657) = 1: b(2658) = 92: b(2659) = 1: b(2660) = 47: b(2661) = 1: b(2662) = 59: b(2663) = 1: b(2664) = 51: b(2665) = 1: b(2666) = 56: b(2667) = 1: b(2668) = 94: b(2669) = 1
    b(2670) = 227: b(2671) = 0: b(2672) = 34: b(2673) = 1: b(2674) = 136: b(2675) = 0: b(2676) = 182: b(2677) = 0: b(2678) = 28: b(2679) = 0: b(2680) = 25: b(2681) = 0: b(2682) = 75: b(2683) = 255: b(2684) = 53: b(2685) = 255: b(2686) = 215: b(2687) = 254: b(2688) = 50: b(2689) = 255: b(2690) = 200: b(2691) = 254: b(2692) = 214: b(2693) = 255: b(2694) = 215: b(2695) = 255: b(2696) = 232: b(2697) = 255: b(2698) = 125: b(2699) = 0
    b(2700) = 150: b(2701) = 255: b(2702) = 149: b(2703) = 0: b(2704) = 153: b(2705) = 255: b(2706) = 0: b(2707) = 0: b(2708) = 244: b(2709) = 255: b(2710) = 222: b(2711) = 254: b(2712) = 144: b(2713) = 255: b(2714) = 231: b(2715) = 254: b(2716) = 162: b(2717) = 254: b(2718) = 125: b(2719) = 254: b(2720) = 57: b(2721) = 254: b(2722) = 191: b(2723) = 254: b(2724) = 241: b(2725) = 254:

    arWavBytes = b

End Sub

Private Sub CreateTempManifest(ByVal FilePathName As String)

    Dim fNr As Integer
    ReDim b(0& To 574&) As Byte
 
    b(0) = 60: b(1) = 63: b(2) = 120: b(3) = 109: b(4) = 108: b(5) = 32: b(6) = 118: b(7) = 101: b(8) = 114: b(9) = 115: b(10) = 105: b(11) = 111: b(12) = 110: b(13) = 61: b(14) = 34: b(15) = 49: b(16) = 46: b(17) = 48: b(18) = 34: b(19) = 32: b(20) = 101: b(21) = 110: b(22) = 99: b(23) = 111: b(24) = 100: b(25) = 105: b(26) = 110: b(27) = 103: b(28) = 61: b(29) = 34
    b(30) = 85: b(31) = 84: b(32) = 70: b(33) = 45: b(34) = 56: b(35) = 34: b(36) = 32: b(37) = 115: b(38) = 116: b(39) = 97: b(40) = 110: b(41) = 100: b(42) = 97: b(43) = 108: b(44) = 111: b(45) = 110: b(46) = 101: b(47) = 61: b(48) = 34: b(49) = 121: b(50) = 101: b(51) = 115: b(52) = 34: b(53) = 63: b(54) = 62: b(55) = 13: b(56) = 10: b(57) = 60: b(58) = 97: b(59) = 115
    b(60) = 115: b(61) = 101: b(62) = 109: b(63) = 98: b(64) = 108: b(65) = 121: b(66) = 32: b(67) = 120: b(68) = 109: b(69) = 108: b(70) = 110: b(71) = 115: b(72) = 61: b(73) = 34: b(74) = 117: b(75) = 114: b(76) = 110: b(77) = 58: b(78) = 115: b(79) = 99: b(80) = 104: b(81) = 101: b(82) = 109: b(83) = 97: b(84) = 115: b(85) = 45: b(86) = 109: b(87) = 105: b(88) = 99: b(89) = 114
    b(90) = 111: b(91) = 115: b(92) = 111: b(93) = 102: b(94) = 116: b(95) = 45: b(96) = 99: b(97) = 111: b(98) = 109: b(99) = 58: b(100) = 97: b(101) = 115: b(102) = 109: b(103) = 46: b(104) = 118: b(105) = 49: b(106) = 34: b(107) = 32: b(108) = 109: b(109) = 97: b(110) = 110: b(111) = 105: b(112) = 102: b(113) = 101: b(114) = 115: b(115) = 116: b(116) = 86: b(117) = 101: b(118) = 114: b(119) = 115
    b(120) = 105: b(121) = 111: b(122) = 110: b(123) = 61: b(124) = 34: b(125) = 49: b(126) = 46: b(127) = 48: b(128) = 34: b(129) = 62: b(130) = 13: b(131) = 10: b(132) = 60: b(133) = 97: b(134) = 115: b(135) = 115: b(136) = 101: b(137) = 109: b(138) = 98: b(139) = 108: b(140) = 121: b(141) = 73: b(142) = 100: b(143) = 101: b(144) = 110: b(145) = 116: b(146) = 105: b(147) = 116: b(148) = 121: b(149) = 13
    b(150) = 10: b(151) = 118: b(152) = 101: b(153) = 114: b(154) = 115: b(155) = 105: b(156) = 111: b(157) = 110: b(158) = 61: b(159) = 34: b(160) = 49: b(161) = 46: b(162) = 48: b(163) = 46: b(164) = 48: b(165) = 46: b(166) = 48: b(167) = 34: b(168) = 13: b(169) = 10: b(170) = 112: b(171) = 114: b(172) = 111: b(173) = 99: b(174) = 101: b(175) = 115: b(176) = 115: b(177) = 111: b(178) = 114: b(179) = 65
    b(180) = 114: b(181) = 99: b(182) = 104: b(183) = 105: b(184) = 116: b(185) = 101: b(186) = 99: b(187) = 116: b(188) = 117: b(189) = 114: b(190) = 101: b(191) = 61: b(192) = 34: b(193) = 42: b(194) = 34: b(195) = 13: b(196) = 10: b(197) = 110: b(198) = 97: b(199) = 109: b(200) = 101: b(201) = 61: b(202) = 34: b(203) = 67: b(204) = 111: b(205) = 109: b(206) = 112: b(207) = 97: b(208) = 110: b(209) = 121
    b(210) = 78: b(211) = 97: b(212) = 109: b(213) = 101: b(214) = 46: b(215) = 80: b(216) = 114: b(217) = 111: b(218) = 100: b(219) = 117: b(220) = 99: b(221) = 116: b(222) = 78: b(223) = 97: b(224) = 109: b(225) = 101: b(226) = 46: b(227) = 89: b(228) = 111: b(229) = 117: b(230) = 114: b(231) = 65: b(232) = 112: b(233) = 112: b(234) = 34: b(235) = 13: b(236) = 10: b(237) = 116: b(238) = 121: b(239) = 112
    b(240) = 101: b(241) = 61: b(242) = 34: b(243) = 119: b(244) = 105: b(245) = 110: b(246) = 51: b(247) = 50: b(248) = 34: b(249) = 13: b(250) = 10: b(251) = 47: b(252) = 62: b(253) = 13: b(254) = 10: b(255) = 60: b(256) = 100: b(257) = 101: b(258) = 115: b(259) = 99: b(260) = 114: b(261) = 105: b(262) = 112: b(263) = 116: b(264) = 105: b(265) = 111: b(266) = 110: b(267) = 62: b(268) = 89: b(269) = 111
    b(270) = 117: b(271) = 114: b(272) = 32: b(273) = 97: b(274) = 112: b(275) = 112: b(276) = 108: b(277) = 105: b(278) = 99: b(279) = 97: b(280) = 116: b(281) = 105: b(282) = 111: b(283) = 110: b(284) = 32: b(285) = 100: b(286) = 101: b(287) = 115: b(288) = 99: b(289) = 114: b(290) = 105: b(291) = 112: b(292) = 116: b(293) = 105: b(294) = 111: b(295) = 110: b(296) = 32: b(297) = 104: b(298) = 101: b(299) = 114
    b(300) = 101: b(301) = 46: b(302) = 60: b(303) = 47: b(304) = 100: b(305) = 101: b(306) = 115: b(307) = 99: b(308) = 114: b(309) = 105: b(310) = 112: b(311) = 116: b(312) = 105: b(313) = 111: b(314) = 110: b(315) = 62: b(316) = 13: b(317) = 10: b(318) = 60: b(319) = 100: b(320) = 101: b(321) = 112: b(322) = 101: b(323) = 110: b(324) = 100: b(325) = 101: b(326) = 110: b(327) = 99: b(328) = 121: b(329) = 62
    b(330) = 13: b(331) = 10: b(332) = 60: b(333) = 100: b(334) = 101: b(335) = 112: b(336) = 101: b(337) = 110: b(338) = 100: b(339) = 101: b(340) = 110: b(341) = 116: b(342) = 65: b(343) = 115: b(344) = 115: b(345) = 101: b(346) = 109: b(347) = 98: b(348) = 108: b(349) = 121: b(350) = 62: b(351) = 13: b(352) = 10: b(353) = 60: b(354) = 97: b(355) = 115: b(356) = 115: b(357) = 101: b(358) = 109: b(359) = 98
    b(360) = 108: b(361) = 121: b(362) = 73: b(363) = 100: b(364) = 101: b(365) = 110: b(366) = 116: b(367) = 105: b(368) = 116: b(369) = 121: b(370) = 13: b(371) = 10: b(372) = 116: b(373) = 121: b(374) = 112: b(375) = 101: b(376) = 61: b(377) = 34: b(378) = 119: b(379) = 105: b(380) = 110: b(381) = 51: b(382) = 50: b(383) = 34: b(384) = 13: b(385) = 10: b(386) = 110: b(387) = 97: b(388) = 109: b(389) = 101
    b(390) = 61: b(391) = 34: b(392) = 77: b(393) = 105: b(394) = 99: b(395) = 114: b(396) = 111: b(397) = 115: b(398) = 111: b(399) = 102: b(400) = 116: b(401) = 46: b(402) = 87: b(403) = 105: b(404) = 110: b(405) = 100: b(406) = 111: b(407) = 119: b(408) = 115: b(409) = 46: b(410) = 67: b(411) = 111: b(412) = 109: b(413) = 109: b(414) = 111: b(415) = 110: b(416) = 45: b(417) = 67: b(418) = 111: b(419) = 110
    b(420) = 116: b(421) = 114: b(422) = 111: b(423) = 108: b(424) = 115: b(425) = 34: b(426) = 13: b(427) = 10: b(428) = 118: b(429) = 101: b(430) = 114: b(431) = 115: b(432) = 105: b(433) = 111: b(434) = 110: b(435) = 61: b(436) = 34: b(437) = 54: b(438) = 46: b(439) = 48: b(440) = 46: b(441) = 48: b(442) = 46: b(443) = 48: b(444) = 34: b(445) = 13: b(446) = 10: b(447) = 112: b(448) = 114: b(449) = 111
    b(450) = 99: b(451) = 101: b(452) = 115: b(453) = 115: b(454) = 111: b(455) = 114: b(456) = 65: b(457) = 114: b(458) = 99: b(459) = 104: b(460) = 105: b(461) = 116: b(462) = 101: b(463) = 99: b(464) = 116: b(465) = 117: b(466) = 114: b(467) = 101: b(468) = 61: b(469) = 34: b(470) = 42: b(471) = 34: b(472) = 13: b(473) = 10: b(474) = 112: b(475) = 117: b(476) = 98: b(477) = 108: b(478) = 105: b(479) = 99
    b(480) = 75: b(481) = 101: b(482) = 121: b(483) = 84: b(484) = 111: b(485) = 107: b(486) = 101: b(487) = 110: b(488) = 61: b(489) = 34: b(490) = 54: b(491) = 53: b(492) = 57: b(493) = 53: b(494) = 98: b(495) = 54: b(496) = 52: b(497) = 49: b(498) = 52: b(499) = 52: b(500) = 99: b(501) = 99: b(502) = 102: b(503) = 49: b(504) = 100: b(505) = 102: b(506) = 34: b(507) = 13: b(508) = 10: b(509) = 108
    b(510) = 97: b(511) = 110: b(512) = 103: b(513) = 117: b(514) = 97: b(515) = 103: b(516) = 101: b(517) = 61: b(518) = 34: b(519) = 42: b(520) = 34: b(521) = 13: b(522) = 10: b(523) = 47: b(524) = 62: b(525) = 13: b(526) = 10: b(527) = 60: b(528) = 47: b(529) = 100: b(530) = 101: b(531) = 112: b(532) = 101: b(533) = 110: b(534) = 100: b(535) = 101: b(536) = 110: b(537) = 116: b(538) = 65: b(539) = 115
    b(540) = 115: b(541) = 101: b(542) = 109: b(543) = 98: b(544) = 108: b(545) = 121: b(546) = 62: b(547) = 13: b(548) = 10: b(549) = 60: b(550) = 47: b(551) = 100: b(552) = 101: b(553) = 112: b(554) = 101: b(555) = 110: b(556) = 100: b(557) = 101: b(558) = 110: b(559) = 99: b(560) = 121: b(561) = 62: b(562) = 13: b(563) = 10: b(564) = 60: b(565) = 47: b(566) = 97: b(567) = 115: b(568) = 115: b(569) = 101
    b(570) = 109: b(571) = 98: b(572) = 108: b(573) = 121: b(574) = 62:
 
    fNr = FreeFile()
    Open FilePathName For Binary As #fNr
        Put #fNr, 1&, b
    Close #fNr
 
End Sub

Private Sub Auto_Close()
    Call KillTimer(Application.hwnd, NULL_PTR)
End Sub
 
Upvote 0
Hi Jaafar,

just to let you know: somehow I cannot get the withManifest_V2 to work properly. ToolTips will only show when I click on a sheet tab but not on mouse-over.

Also I experienced Excel crashing a few times already during testing. I usually had v1 and v2 open at the same time, cannot say yet what is probably causing the crash.
 
Upvote 0

Forum statistics

Threads
1,215,206
Messages
6,123,638
Members
449,109
Latest member
Sebas8956

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