13.08.2020, 19:25
Hallöchen,
hier mal der Code zum Adobe schließen. Die API's bitte mit oben einfügen.
Die Schleife kannst Du so verlängern:
Do While Cells(iCnt, 1).Value <> "" Or Cells(iCnt, 3).Value <> ""
hier mal der Code zum Adobe schließen. Die API's bitte mit oben einfügen.
Code:
'API, hier verwendet fuer Adobe Reader schliessen
Private Declare Function FindWindow Lib "user32.dll" Alias "FindWindowA" ( _
ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Private Declare Function SendMessage Lib "user32.dll" Alias "SendMessageA" ( _
ByVal hwnd As Long, ByVal Msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Sub Close_AdobeReader()
'Variablendeklarationen
Dim strName As String, hwnd As Long
Const WM_CLOSE = &H10
'Name Adobe Window
strName = "AcrobatSDIWindow"
'Window finden
hwnd = FindWindow(strName, vbNullString)
'wenn gefunden, dann beenden
If hwnd Then SendMessage hwnd, WM_CLOSE, 0, ByVal 0&
End Sub
Die Schleife kannst Du so verlängern:
Do While Cells(iCnt, 1).Value <> "" Or Cells(iCnt, 3).Value <> ""
. \\\|/// Hoffe, geholfen zu haben.
( ô ô ) Grüße, André aus G in T
ooO-(_)-Ooo (Excel 97-2019+365)
( ô ô ) Grüße, André aus G in T
ooO-(_)-Ooo (Excel 97-2019+365)