Anzeige
Anzeige
HERBERS
Excel-Forum (Archiv)
20+ Jahre Excel-Kompetenz: Von Anwendern, für Anwender
Inhaltsverzeichnis

Fensterausrichtung mit VBA

Forumthread: Fensterausrichtung mit VBA

Fensterausrichtung mit VBA
marspoki
Hallo Profis,
Ich möchte gerne mit Hilfe von VBA ein Programmfenster z.B. Outlook an eine ganz bestimmt Stelle am Bildschirm verschieben.
Mit dem Editor funktioniert der Unten aufgeführte Code wunderbar. Warum nicht mit Outlook oder anderen Programmen?
Habe natürlich die Zeilen verändert gehabt.
Vielen Dank
beste grüße
Masrpoki
Option Explicit
Private Declare Function GetForegroundWindow Lib "user32.dll" () As Long
Private Declare Function MoveWindow Lib "user32.dll" ( _
ByVal hWnd As Long, _
ByVal x As Long, _
ByVal y As Long, _
ByVal nWidth As Long, _
ByVal nHeight As Long, _
ByVal bRepaint As Long) As Long
Private Declare Function GetWindowRect Lib "user32.dll" ( _
ByVal hWnd As Long, _
ByRef lpRect As RECT) As Long
Private Declare Function GetClassName Lib "user32.dll" Alias "GetClassNameA" ( _
ByVal hWnd As Long, _
ByVal lpClassName As String, _
ByVal nMaxCount As Long) As Long
Private Type RECT
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type
Private Const GC_CLASSNAMENOTEPAD = "Notepad"
Public Sub test()
Dim hWnd As Long, lngReturn As Long
Dim udtRECT As RECT
Dim strClassName As String
AppActivate "Unbenannt - Editor", True
hWnd = GetForegroundWindow
If hWnd  0 Then
strClassName = Space(256)
lngReturn = GetClassName(hWnd, strClassName, 256)
If Left$(strClassName, lngReturn) = GC_CLASSNAMENOTEPAD Then
Call GetWindowRect(hWnd, udtRECT)
With udtRECT
Call MoveWindow(hWnd, 0, 0, .Right - .Left, .Bottom - .Top, -1)
End With
End If
End If
End Sub

Anzeige

1
Beitrag zum Forumthread
Beitrag zu diesem Forumthread

Betreff
Benutzer
Anzeige
versuche es mal hiermit.
21.11.2009 06:52:40
Tino
Hallo,
kommt als Code in Modul1
Option Explicit 
 
Private Declare Function SetForegroundWindow Lib "user32" ( _
  ByVal hwnd As Long) As Long 
   
Private Declare Function ShowWindow Lib "user32" ( _
  ByVal hwnd As Long, ByVal nCmdShow As Long) As Long 
   
Private Declare Function MoveWindow Lib "user32.dll" ( _
ByVal hwnd As Long, ByVal X As Long, ByVal y As Long, _
ByVal nWidth As Long, ByVal nHeight As Long, ByVal bRepaint As Long) As Long 
 
Private Declare Function GetWindowRect Lib "user32.dll" ( _
ByVal hwnd As Long, ByRef lpRect As RECT) As Long 
 
Private Type RECT 
    Left As Long 
    Top As Long 
    Right As Long 
    Bottom As Long 
End Type 
 
Const iNormal& = 1 
Const iMinimized& = 2 
Const iMaximized& = 3 
 
Sub Test() 
Dim LHwnd As Long 
Dim udtRECT As RECT 
 
 
LHwnd = Hwnd_Fenster("Microsoft Outlook") 
 
If LHwnd > 0 Then 
 
    SetForegroundWindow LHwnd 
    ShowWindow LHwnd, iNormal 
     
    GetWindowRect LHwnd, udtRECT 
     
    With udtRECT 
        MoveWindow LHwnd, 0, 0, .Right - .Left, .Bottom - .Top, -1 
    End With 
 
End If 
End Sub 
 
kommt als Code in Modul2
Private Declare Function GetDesktopWindow Lib "user32" () As Long 
 
Private Declare Function GetWindowTextLength Lib "user32" _
        Alias "GetWindowTextLengthA" (ByVal hwnd As Long) _
        As Long 
         
Private Declare Function GetWindowText Lib "user32" _
        Alias "GetWindowTextA" _
        (ByVal hwnd As Long, ByVal lpString As String, _
        ByVal cch As Long) As Long 
 
Private Declare Function GetWindowLong Lib "user32" Alias _
        "GetWindowLongA" (ByVal hwnd As Long, ByVal wIndx As _
        Long) As Long 
          
Private Declare Function GetWindow Lib "user32" _
       (ByVal hwnd As Long, ByVal wCmd As Long) As Long 
 
Const GWL_STYLE& = (-16) 
Const WS_VISIBLE = &H10000000 
Const WS_BORDER = &H800000 
Const GW_HWNDNEXT& = 2 
Const GW_CHILD& = 5 
 
Private Function GetWindowInfo(ByVal hwnd&, STitel$, Optional booVisible As Boolean = True) As Long 
Dim Result&, Style&, Title$ 
   
    'Darstellung des Fensters 
    Style = GetWindowLong(hwnd, GWL_STYLE) 
    Style = Style And (WS_VISIBLE Or WS_BORDER) 
     
    'Fensetrtitel ermitteln 
    Result = GetWindowTextLength(hwnd) + 1 
    Title = Space$(Result) 
    Result = GetWindowText(hwnd, Title, Result) 
    Title = Left$(Title, Len(Title) - 1) 
     
'prüfen ob Fenster Sichtbar 
If (Style = (WS_VISIBLE Or WS_BORDER)) Or booVisible = False Then 
      If Title Like "*" & STitel & "*" Then 
       GetWindowInfo = hwnd 
       Exit Function 
      End If 
End If 
GetWindowInfo = 0 
End Function 
 
 
Function Hwnd_Fenster(strTitel$) As Long 
Dim hwnd As Long 
 
  hwnd = GetDesktopWindow() 
  hwnd = GetWindow(hwnd, GW_CHILD) 
 
  GetWindowInfo hwnd, strTitel, True 
 
Do While hwnd <> 0 
    hwnd = GetWindow(hwnd, GW_HWNDNEXT) 
   If GetWindowInfo(hwnd, strTitel, True) = hwnd Then 
    Hwnd_Fenster = hwnd 
    Exit Function 
   End If 
Loop 
 
End Function 
 
Gruß Tino
Anzeige
;
Anzeige

Infobox / Tutorial

Fensterausrichtung mit VBA


Schritt-für-Schritt-Anleitung

  1. VBA-Editor öffnen: Drücke ALT + F11, um den VBA-Editor in Excel zu öffnen.
  2. Neues Modul erstellen: Klicke mit der rechten Maustaste auf "VBAProject (DeineDatei.xlsx)" > Einfügen > Modul.
  3. Code einfügen: Kopiere den folgenden Code in das Modul:
Option Explicit
Private Declare Function GetForegroundWindow Lib "user32.dll" () As Long
Private Declare Function MoveWindow Lib "user32.dll" ( _
    ByVal hWnd As Long, _
    ByVal x As Long, _
    ByVal y As Long, _
    ByVal nWidth As Long, _
    ByVal nHeight As Long, _
    ByVal bRepaint As Long) As Long
Private Declare Function GetWindowRect Lib "user32.dll" ( _
    ByVal hWnd As Long, _
    ByRef lpRect As RECT) As Long
Private Declare Function GetClassName Lib "user32.dll" Alias "GetClassNameA" ( _
    ByVal hWnd As Long, _
    ByVal lpClassName As String, _
    ByVal nMaxCount As Long) As Long

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

Public Sub FensterVerschieben()
    Dim hWnd As Long
    Dim udtRECT As RECT
    Dim strClassName As String

    hWnd = GetForegroundWindow()
    If hWnd <> 0 Then
        strClassName = Space(256)
        GetClassName hWnd, strClassName, 256
        If Left$(strClassName, Len(strClassName)) = "Notepad" Then
            GetWindowRect hWnd, udtRECT
            Call MoveWindow(hWnd, 100, 100, udtRECT.Right - udtRECT.Left, udtRECT.Bottom - udtRECT.Top, True)
        End If
    End If
End Sub
  1. Makro ausführen: Drücke F5 im VBA-Editor, um das Makro auszuführen und das Fenster zu verschieben.

Häufige Fehler und Lösungen

  • Problem: Das Fenster wird nicht verschoben.

    • Lösung: Stelle sicher, dass das Fenster, das du verschieben möchtest, im Vordergrund ist. Verwende SetForegroundWindow, um das Fenster in den Vordergrund zu holen.
  • Problem: Fehler beim Aufrufen von GetWindowRect.

    • Lösung: Überprüfe, ob der hWnd-Wert korrekt ist. Du kannst den Wert von hWnd in der Debugging-Konsole ausgeben lassen.

Alternative Methoden

Eine andere Möglichkeit, ein Fenster zu verschieben, besteht darin, die Funktionen SetForegroundWindow und ShowWindow zu kombinieren. Hier ist ein Beispiel:

Private Declare Function SetForegroundWindow Lib "user32.dll" ( _
    ByVal hwnd As Long) As Long

Private Declare Function ShowWindow Lib "user32.dll" ( _
    ByVal hwnd As Long, _
    ByVal nCmdShow As Long) As Long

Sub FensterVerschiebenMitShowWindow()
    Dim hWnd As Long
    hWnd = Hwnd_Fenster("Microsoft Outlook")
    If hWnd > 0 Then
        SetForegroundWindow hWnd
        ShowWindow hWnd, 1 ' Fenster normal anzeigen
        ' Hier kannst du die MoveWindow-Funktion aufrufen
    End If
End Sub

Praktische Beispiele

  • Beispiel 1: Verschiebe das Notepad-Fenster an die Position (50, 50):
Call MoveWindow(hWnd, 50, 50, .Right - .Left, .Bottom - .Top, -1)
  • Beispiel 2: Verschiebe das Outlook-Fenster mit GetWindowRect:
If hWnd = Hwnd_Fenster("Microsoft Outlook") Then
    GetWindowRect hWnd, udtRECT
    MoveWindow hWnd, 0, 0, .Right - .Left, .Bottom - .Top, True
End If

Tipps für Profis

  • Verwende vba getclassname, um den Klassennamen des Fensters zu ermitteln. Dies hilft dir, spezifische Fenster zu identifizieren.
  • Teste den Code in verschiedenen Excel-Versionen, um sicherzustellen, dass er kompatibel bleibt.
  • Achte darauf, dass der Code in einem Modul platziert wird, das zur entsprechenden Excel-Datei gehört.

FAQ: Häufige Fragen

1. Wie kann ich die Größe des Fensters ändern?
Du kannst die MoveWindow-Funktion verwenden, um die Breite und Höhe des Fensters anzupassen. Ändere die Parameter nWidth und nHeight entsprechend.

2. Was ist der Unterschied zwischen GetForegroundWindow und SetForegroundWindow?
GetForegroundWindow gibt das Handle des aktuell aktiven Fensters zurück, während SetForegroundWindow ein Fenster in den Vordergrund bringt.

3. Kann ich das Fenster auf einen bestimmten Bildschirm verschieben?
Ja, du kannst die Koordinaten für MoveWindow anpassen, um das Fenster auf einen bestimmten Bildschirm zu verschieben, wenn du mehrere Bildschirme verwendest.

Beliebteste Forumthreads (12 Monate)

Anzeige
Anzeige
Entdecke mehr
Finde genau, was du suchst

Die erweiterte Suchfunktion hilft dir, gezielt die besten Antworten zu finden

Suche nach den besten Antworten
Unsere beliebtesten Threads

Entdecke unsere meistgeklickten Beiträge in der Google Suche

Top 100 Threads jetzt ansehen
Anzeige