Ständige Anzeigen können Sie zwar in Microsoft Office von VBA-Code (Makros) oder von einem COM-AddIn aus in die Status-Zeile (Application.StatusBar) ausgeben lassen. Doch irgendwie ist das wohl nicht die feine Art. Denn zum einen werden damit die vorhandenen ständigen Anzeigen überschrieben, und zum anderen könnten sich mehrere Makros oder AddIns darüber streiten, wer denn die Oberhand behält. Eleganter wäre es hingegen, wenn alle, die etwas zu melden haben, dies in einem eigenständigen Anzeigeelement erledigen könnten.
Der erste Gedanke wäre, die Ausgabe in ein UserForm, das dazu verdammt wird, immer im Vordergrund zu bleiben. Das Wahre ist das allerdings noch nicht. Denn schon ein einziges UserForm steht irgendwann nur noch störend im Weg herum - wie sehr würden dann erst mehrere UserForms stören, wenn mehrere Makros oder AddIns redselig sein sollten.
Andere Ausgabemöglichkeiten stellt Word selbst jedoch offensichtlich nicht zur Verfügung - oder doch? Natürlich - die Symbolleisten (CommandBars) können auch reine Anzeige-Controls aufnehmen (Type: msoControlLabel). Sie brauchen nur doch für die Bereitstellung und entsprechende Fütterung eines solchen Anzeige-Controls zu sorgen. Damit Ihr Makro oder Ihr AddIn tatsächlich die alleinige Kontrolle über die Anzeige behält, empfiehlt es sich, dieses Control in eine eigene Symbolleiste zu stecken. Und sollte die Anzeige zusätzlich noch in irgendeiner Form konfigurierbar sein, wäre sogar eine gewöhnliche Symbolschaltfläche (CommandBarButton, Type: msoControlButton) nahe liegend, mit reiner Textanzeige (Style: msoButtonCaption) oder mit einem Symbol kombiniert (Style: msoButtonIconAndCaption).
Das Beispiel-AddIn zu diesem Projekt (für Word 2000 und Word XP) demonstriert dies mit einer ständigen Anzeige der Anzahl der Zeichen im jeweils aktiven Dokument in einer Symbolschaltfläche. Ein Klick auf diese Schaltfläche öffnet einen kleinen Dialog (ein einfaches VB-Form im ToolBox-Stil), über den die Anzeige ein- oder ausgeschaltet werden kann.
Der Trick hinter der ständig aktuellen Anzeige besteht darin, dass ein Timer-Steuerelement, das auf dem immer im Hintergrund geladenen Form platziert ist, alle 250 Millisekunden sein Ereignis auslöst, woraufhin die aktuelle Zeichenzahl ermittelt und ausgegeben wird. Denn Word selbst bietet kein solches Ereignis, das die Veränderung des Dokumentinhalts unmittelbar mitteilen und damit auswertbar machen würde.
Das Form bietet darüber hinaus noch das kleine Komfort-Feature, dass es den Aktivierungszustand der Anzeige beim Beenden in die Windows Registrierung schreibt - der Einfachheit halber unter dem Schlüssel
HKEY_CURRENT_USER\Software\VB and VBA Program Settings\ZeichenZaehlerWW
und ihn beim nächsten Start von Word wieder ausliest. Auch die letzte Position des Dialogs wird dort abgelegt und von dort wieder eingelesen.
In der folgenden Abbildung sehen Sie zunächst die Konfiguration des AddIn-Designers:
Der Code im AddIn-Desiger-Modul:
Private WithEvents eForm As frmTimer
Private WithEvents eCommandBarButtonChars As CommandBarButton
Private mApplication As Object
Private Sub AddinInstance_OnConnection(ByVal Application As Object, _
ByVal ConnectMode As AddInDesignerObjects.ext_ConnectMode, _
ByVal AddInInst As Object, custom() As Variant)
Set mApplication = Application
zCreateCommandBarButtons
Set eForm = New frmTimer
eForm.StartTimer
End Sub
Private Sub AddinInstance_OnDisconnection(ByVal RemoveMode As _
AddInDesignerObjects.ext_DisconnectMode, custom() As Variant)
Dim nCommandBar As CommandBar
If Not (eForm Is Nothing) Then
eForm.StopTimer
Set eForm = Nothing
End If
On Error Resume Next
If Not (eCommandBarButtonChars Is Nothing) Then
Set nCommandBar = eCommandBarButtonChars.Parent
eCommandBarButtonChars.Delete
Set eCommandBarButtonChars = Nothing
nCommandBar.Delete
End If
Set mApplication = Nothing
End Sub
Private Sub eCommandBarButtonChars_Click _
(ByVal Ctrl As Office.CommandBarButton, CancelDefault As Boolean)
If Not (eForm Is Nothing) Then
eForm.ShowForm
End If
End Sub
Private Sub eForm_Deactivate()
Dim nActiveDocument As Document
On Error Resume Next
If Not (mApplication Is Nothing) Then
If Not (eCommandBarButtonChars Is Nothing) Then
With eCommandBarButtonChars
.Style = msoButtonCaption
.Caption = "Zeichen..."
End With
End If
End If
End Sub
Private Sub eForm_Timer()
Dim nActiveDocument As Document
Dim nCounter As String
If Not (mApplication Is Nothing) Then
If eCommandBarButtonChars Is Nothing Then
zCreateCommandBarButtons
End If
On Error Resume Next
If Not (eCommandBarButtonChars Is Nothing) Then
With eCommandBarButtonChars
.Style = msoButtonCaption
On Error Resume Next
Set nActiveDocument = mApplication.ActiveDocument
If nActiveDocument Is Nothing Then
.Caption = "Zeichen..."
Else
.Caption = "Zeichen: " & nActiveDocument.Characters.Count
End If
End With
End If
End If
End Sub
Private Sub zCreateCommandBarButtons()
Dim nCommandBar As CommandBar
Dim nCommandBarControl As CommandBarControl
With mApplication
On Error Resume Next
Set nCommandBar = .CommandBars("Zeichen")
If Err.Number Then
Err.Clear
Set nCommandBar = .CommandBars.Add("Zeichen", , , True)
End If
End With
If Not (nCommandBar Is Nothing) Then
With nCommandBar
.Visible = True
For Each nCommandBarControl In .Controls
If Left$(nCommandBarControl.Caption, 7) = "Zeichen" Then
Set eCommandBarButtonChars = nCommandBarControl
Exit For
End If
Next
If eCommandBarButtonChars Is Nothing Then
Set eCommandBarButtonChars = _
.Controls.Add(msoControlButton, , , , True)
End If
With eCommandBarButtonChars
.Style = msoButtonCaption
.Caption = "Zeichen..."
End With
End With
End If
End Sub
Und der Code des Dialog-Forms, das den Timer aufnimmt:
Private Declare Function SetWindowPos Lib "User32" _
(ByVal hWnd As Long, ByVal Order As Long, ByVal X As Long, _
ByVal Y As Long, ByVal cX As Long, ByVal cY As Long, _
ByVal Flags As Long) As Long
Public Event Timer()
Public Event Deactivate()
Public Sub ShowForm()
Const SWP_NOMOVE = 2
Const SWP_NOSIZE = 1
Const HWND_TOPMOST = -1
With Me
SetWindowPos .hWnd, HWND_TOPMOST, 0, 0, 0, 0, _
SWP_NOMOVE Or SWP_NOSIZE
.Show
End With
End Sub
Public Sub StartTimer()
Load Me
End Sub
Public Sub StopTimer()
With chkActive
SaveSetting App.Title, "Timer", "Active", .Value
.Value = vbUnchecked
End With
Unload Me
End Sub
Private Sub chkActive_Click()
tmr.Enabled = CBool(chkActive.Value)
If chkActive.Value = vbUnchecked Then
RaiseEvent Deactivate
End If
End Sub
Private Sub cmdClose_Click()
Me.Visible = False
End Sub
Private Sub Form_Load()
With Me
.Left = GetSetting(App.Title, "Window", "Left", _
(Screen.Width - .Width) \ 2)
.Top = GetSetting(App.Title, "Window", "Top", _
(Screen.Height - .Height) \ 2)
End With
chkActive.Value = _
GetSetting(App.Title, "Timer", "Active", vbChecked)
End Sub
Private Sub Form_QueryUnload(Cancel As Integer, _
UnloadMode As Integer)
If UnloadMode = vbFormControlMenu Then
Cancel = True
Me.Visible = False
End If
End Sub
Private Sub Form_Unload(Cancel As Integer)
With Me
SaveSetting App.Title, "Window", "Left", CLng(.Left)
SaveSetting App.Title, "Window", "Top", CLng(.Top)
End With
End Sub
Private Sub tmr_Timer()
RaiseEvent Timer
End Sub
|