Live-Forum - Die aktuellen Beiträge
Datum
Titel
24.04.2024 19:29:30
24.04.2024 18:49:56
Anzeige
Archiv - Navigation
1144to1148
Aktuelles Verzeichnis
Verzeichnis Index
Übersicht Verzeichnisse
Vorheriger Thread
Rückwärts Blättern
Nächster Thread
Vorwärts blättern
Anzeige
HERBERS
Excel-Forum (Archiv)
20+ Jahre Excel-Kompetenz: Von Anwendern, für Anwender
Inhaltsverzeichnis

Dateinamen+Pfade auslesen und in neues Tabellenbl.

Dateinamen+Pfade auslesen und in neues Tabellenbl.
Helmut
hallo liebe vba'ler,
ich habe schon im online-archiv nachgesehen, aber nichts genau passendes für mein "problem" gefunden, obwohl das thema oft behandelt wurde.
ich möchte aus einem verzeichnis, auch aus einer partition (also z.b. komplettes laufwerk c:), alle dateien mit einer bestimmten endung auslesen (auch aus den unterordnern) und in ein neues tabellenblatt schreiben.
das laufwerk, bzw. den pfad will ich in einer inputbox eingeben können; genauso eine inputbox für die endung der dateien, die ich auslesen will.
zuletzt soll noch die länge der zeichen des kompletten pfades (inkl. \) in die danebenstehenden zellen geschrieben werden (wäre zumindest super!).
ich habe bereits aus den foren etwas zusammengebastelt, aber das skript gibt nicht die zeichenlänge aus und geht nicht in unterordner hinein!! zudem wird das letzte file mit gewünschter endung nicht ausgelesen!
was ist hier am skript falsch, bzw. kann mir jemand eine komplettlösung geben?
hier das skript:
Private Sub CommandButton1_Click()
Dim str As String
Dim DatName As String
Dim n As Long
Dim datende
Application.ScreenUpdating = False
Sheets("Tabelle2").Activate
ActiveSheet.UsedRange.Clear
str = InputBox("Bitte Pfad zu den Dateien eingeben ..." & Chr(13) _
& "z.B.: \\rss4\pdf\")
datende = InputBox("Geben Sie bitte die Dateiendung ein ..." & Chr(13) _
& "z.B.: xls; doc; prt; asm ...")
DatName = Dir$(str & "\*." & datende)
n = 0
Do While Len(DatName) > 0
n = n + 1
Sheets("Tabelle2").Range("A65000").Activate
Selection.End(xlUp).Select
ActiveCell.Offset(1, 0).Activate
ActiveCell.Value = str & "\" & DatName
DatName = Dir$()
Loop
ActiveCell.Value = "Summe: " & n - 1
Application.ScreenUpdating = True
End Sub

vielen dank im voraus!
lg,
helmut
AW: Dateinamen+Pfade auslesen und in neues Tabellenbl.
16.03.2010 10:20:46
Rudi
Hallo,
als Ansatz:
Option Explicit
Dim vntFiles(), lngFiles As Long
Sub DateiListe()
Dim FSO As Object, oFolder As Object
Dim strFolder As String
Dim wksInhalt As Worksheet
Dim strExt As String
With Application.FileDialog(4)   '1=Open; 2=SaveAs; 3=FilePicker; 4=FolderPicker
.AllowMultiSelect = False
.InitialFileName = "c:\"
.InitialView = 2 '1=Liste; 2=Details; 3=properties; 4=Preview; 5=Thumbnail; 6=LargeIcons;  _
7=SmallIcons
.Title = "Bitte einen Ordner wählen"
If .Show = -1 Then
strFolder = .SelectedItems(1)
End If
End With
strExt = InputBox("Geben Sie bitte die Dateiendung ein ..." & Chr(13) _
& "z.B.: xls; doc; prt; asm ...")
strExt = Replace(strExt, ".", "")
If strFolder = "" Then Exit Sub
GetMoreSpeed
On Error Resume Next
Set wksInhalt = ThisWorkbook.Worksheets("Inhalt")
On Error GoTo 0
If wksInhalt Is Nothing Then
Set wksInhalt = Worksheets.Add(before:=Sheets(1))
wksInhalt.Name = "Inhalt"
End If
Set FSO = CreateObject("Scripting.FileSystemObject")
Set oFolder = FSO.getfolder(strFolder)
lngFiles = 1
With wksInhalt
.Cells.ClearContents
.Cells(1, 1) = "Name"
.Cells(1, 2) = "Ext"
.Cells(1, 3) = "Bemerkung"
.Cells(1, 4) = "Ordner"
.Cells(1, 5) = "kB"
.Cells(1, 6) = "le.Änd."
.Cells(1, 7) = "Erstellt"
.Cells(1, 8) = "Pfad"
.Cells(1, 9) = "Link"
.Range(.Cells(1, 1), .Cells(1, 5)).Font.Bold = True
End With
prcFiles oFolder, strExt
prcSubFolders oFolder, strExt
With wksInhalt
.Range(.Cells(2, 1), .Cells(lngFiles, UBound(vntFiles, 1))) = WorksheetFunction.Transpose( _
vntFiles)
.Columns.AutoFit
.Activate
End With
GetMoreSpeed False
End Sub
Sub prcSubFolders(oFolder, ByVal strExt)
Dim oSubFolder As Object
For Each oSubFolder In oFolder.subfolders
prcFiles oSubFolder, strExt
prcSubFolders oSubFolder, strExt
Next
End Sub
Sub prcFiles(oFolder, ByVal strExt As String)
Dim oFile As Object
For Each oFile In oFolder.Files
If GetExtension(oFile.Name) = strExt Then
ReDim Preserve vntFiles(1 To 9, 1 To lngFiles)
vntFiles(2, lngFiles) = GetExtension(oFile.Name)
vntFiles(1, lngFiles) = Left(oFile.Name, Len(oFile.Name) - Len(vntFiles(2, lngFiles)) - 1) _
vntFiles(4, lngFiles) = oFolder
vntFiles(5, lngFiles) = Int(oFile.Size / 1024)
vntFiles(6, lngFiles) = oFile.datelastmodified
vntFiles(7, lngFiles) = oFile.datecreated
vntFiles(8, lngFiles) = oFile.Path
vntFiles(9, lngFiles) = "=hyperlink(""" & oFile.Path & """;""" & "Klick" & """)"
lngFiles = lngFiles + 1
End If
Next
End Sub
Private Function GetExtension(strFile As String) As String
If InStrRev(strFile, ".") > 0 Then
GetExtension = Right(strFile, Len(strFile) - InStrRev(strFile, "."))
Else
GetExtension = ""
End If
End Function
Sub GetMoreSpeed(Optional ByVal Modus As Boolean = True)
With Application
.ScreenUpdating = Not Modus
.EnableEvents = Not Modus
'      .DisplayAlerts = Not Modus
.Calculation = IIf(Modus = True, xlManual, xlAutomatic)
.Cursor = IIf(Modus = True, 2, -4143)
End With
End Sub

Gruß
Rudi
Anzeige
AW: Dateinamen+Pfade auslesen und in neues Tabellenbl.
16.03.2010 10:37:21
Helmut
hi rudi,
sieht ja toll aus!!! vor allem die auswahlmöglichkeit des pfades! bekomme leider die meldung "Index außerhalb des gültigen Bereichs", nachdem ich das verzeichnis gewählt habe. habe absichtlich ein verzeichnis gewählt, dass wenig (ca. 100) dateien mit endung xls hat.
wa kann da falsch sein?
lg,
helmut
AW: Dateinamen+Pfade auslesen und in neues Tabellenbl.
16.03.2010 10:50:39
Helmut
hi tino,
ist ja generell grenzgenial!! kann ich auch sehr gut gebrauchen. aber leider wird auch hier nicht zeilenweise der komplette pfad ausgegeben; auch nicht die zeichenlänge.
trotzdem herzlichen dank! bin beeindruckt von dieser version!!
liebe grüße
helmut
Anzeige
hier noch eine Version...
16.03.2010 11:01:19
Tino
Hallo,
, große Teile davon stammen von Nepumuk.
Option Explicit
Option Private Module
Private Declare Function FindFirstFile Lib "kernel32" Alias "FindFirstFileA" ( _
    ByVal lpFileName As String, _
    lpFindFileData As WIN32_FIND_DATA) As Long
Private Declare Function FindNextFile Lib "kernel32" Alias "FindNextFileA" ( _
    ByVal hFindFile As Long, _
    lpFindFileData As WIN32_FIND_DATA) As Long
Private Declare Function FindClose Lib "kernel32" ( _
    ByVal hFindFile As Long) As Long

Private Enum FILE_ATTRIBUTE
    FILE_ATTRIBUTE_READONLY = &H1
    FILE_ATTRIBUTE_HIDDEN = &H2
    FILE_ATTRIBUTE_SYSTEM = &H4
    FILE_ATTRIBUTE_DIRECTORY = &H10
    FILE_ATTRIBUTE_ARCHIVE = &H20
    FILE_ATTRIBUTE_NORMAL = &H80
    FILE_ATTRIBUTE_TEMPORARY = &H100
End Enum

Private Const INVALID_HANDLE_VALUE = -1&
Private Const MAX_PATH = 260&

Private Type FILETIME
    dwLowDateTime As Long
    dwHighDateTime As Long
End Type

Private Type WIN32_FIND_DATA
    dwFileAttributes As Long
    ftCreationTime As FILETIME
    ftLastAccessTime As FILETIME
    ftLastWriteTime As FILETIME
    nFileSizeHigh As Long
    nFileSizeLow As Long
    dwReserved0 As Long
    dwReserved1 As Long
    cFileName As String * MAX_PATH
    cAlternate As String * 14
End Type

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 GetSystemMetrics Lib "user32.dll" ( _
    ByVal nIndex As Long) As Long
Private Declare Function GetWindowRect Lib "user32.dll" ( _
    ByVal hwnd As Long, _
    ByRef lpRect As RECT) As Long
Private Declare Function SHBrowseForFolder Lib "shell32" ( _
    lpbi As InfoT) As Long
Private Declare Function CoTaskMemFree Lib "ole32" ( _
    ByVal hMem As Long) As Long
Private Declare Function lstrcat Lib "kernel32" Alias "lstrcatA" ( _
    ByVal lpStr1 As String, _
    ByVal lpStr2 As String) As Long
Private Declare Function SHGetPathFromIDList Lib "shell32" ( _
    ByVal pList As Long, _
    ByVal lpBuffer As String) As Long
Private Declare Function FindWindow Lib "user32" 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, _
    wParam As Any, _
    lParam As Any) As Long

Private Type InfoT
    hwnd As Long
    Root As Long
    DisplayName As Long
    Title As Long
    Flags As Long
    FName As Long
    lParam As Long
    Image As Long
End Type

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

Public Enum BIF_Flag
    BIF_RETURNONLYFSDIRS = &H1
    BIF_DONTGOBELOWDOMAIN = &H2
    BIF_STATUSTEXT = &H4
    BIF_RETURNFSANCESTORS = &H8
    BIF_EDITBOX = &H10
    BIF_VALIDATE = &H20
    BIF_NEWDIALOGSTYLE = &H40
    BIF_BROWSEINCLUDEURLS = &H80
    BIF_BROWSEFORCOMPUTER = &H1000
    BIF_BROWSEFORPRINTER = &H2000
    BIF_BROWSEINCLUDEFILES = &H4000
    BIF_SHAREABLE = &H8000
End Enum

Private Const SM_CXFULLSCREEN = &H10
Private Const SM_CYFULLSCREEN = &H11

Private Const BFFM_SETSELECTION = &H466
Private Const BFFM_INITIALIZED = &H1

Private s_BrowseInitDir As String

Public Function fncGetFolder( _
        Optional ByVal sMsg As String = "Bitte wählen Sie ein Verzeichnis", _
        Optional ByVal lFlag As BIF_Flag = BIF_RETURNONLYFSDIRS, _
        Optional ByVal sPath As String = "C:\") As String
    Dim xl As InfoT, IDList As Long, RVal As Long, FolderName As String
    s_BrowseInitDir = sPath
    With xl
        .hwnd = FindWindow("XLMAIN", vbNullString)
        .Root = 0
        .Title = lstrcat(sMsg, "")
        .Flags = lFlag
        .FName = FuncCallback(AddressOf BrowseCallback)
    End With
    IDList = SHBrowseForFolder(xl)
    If IDList <> 0 Then
        FolderName = Space(256)
        RVal = SHGetPathFromIDList(IDList, FolderName)
        CoTaskMemFree (IDList)
        FolderName = Trim$(FolderName)
        FolderName = Left$(FolderName, Len(FolderName) - 1)
    End If
    fncGetFolder = FolderName
End Function

Private Function BrowseCallback( _
        ByVal hwnd As Long, _
        ByVal uMsg As Long, _
        ByVal wParam As Long, _
        ByVal lParam As Long) As Long
    If uMsg = BFFM_INITIALIZED Then
        Call SendMessage(hwnd, BFFM_SETSELECTION, ByVal 1&, ByVal s_BrowseInitDir)
        Call CenterDialog(hwnd)
    End If
    BrowseCallback = 0
End Function

Private Function FuncCallback(ByVal nParam As Long) As Long
    FuncCallback = nParam
End Function

Private Sub CenterDialog(ByVal hwnd As Long)
    Dim WinRect As RECT, ScrWidth As Integer, ScrHeight As Integer
    Dim DlgWidth As Integer, DlgHeight As Integer
    GetWindowRect hwnd, WinRect
    DlgWidth = WinRect.Right - WinRect.Left
    DlgHeight = WinRect.Bottom - WinRect.Top
    ScrWidth = GetSystemMetrics(SM_CXFULLSCREEN)
    ScrHeight = GetSystemMetrics(SM_CYFULLSCREEN)
    MoveWindow hwnd, (ScrWidth - DlgWidth) / 2, _
        (ScrHeight - DlgHeight) / 2, DlgWidth, DlgHeight, 1
End Sub

Sub FindFiles(ByVal strFolderPath As String, ByVal strSearch As String, _
        ByRef lngFilecount As Long, Optional SubFolder As Boolean = True)
    Dim WFD As WIN32_FIND_DATA, lngSearch As Long, strDirName As String
    
    lngSearch = FindFirstFile(strFolderPath & "*.*", WFD)
    
    If lngSearch <> INVALID_HANDLE_VALUE Then
        GetFilesInFolder strFolderPath, strSearch, lngFilecount
        Do
            If (WFD.dwFileAttributes And FILE_ATTRIBUTE_DIRECTORY) Then
                strDirName = Left$(WFD.cFileName, InStr(WFD.cFileName, Chr(0)) - 1)
                If SubFolder = False Then Exit Sub 'ohne Unterordner 
                If (strDirName <> ".") And (strDirName <> "..") Then _
                    FindFiles strFolderPath & strDirName & "\", strSearch, lngFilecount
            End If
        Loop While FindNextFile(lngSearch, WFD)
        FindClose lngSearch
    End If
End Sub

Sub GetFilesInFolder(ByVal strFolderPath As String, ByVal strSearch As String, _
        ByRef lngFilecount As Long)
    Dim WFD As WIN32_FIND_DATA, lngSearch As Long, strFileName As String
    lngSearch = FindFirstFile(strFolderPath & strSearch, WFD)
    If lngSearch <> INVALID_HANDLE_VALUE Then
        Do
            If (WFD.dwFileAttributes And FILE_ATTRIBUTE_DIRECTORY) <> _
                FILE_ATTRIBUTE_DIRECTORY Then
                strFileName = Left$(WFD.cFileName, InStr(WFD.cFileName, Chr(0)) - 1)
                lngFilecount = lngFilecount + 1
                Cells(lngFilecount, 1) = strFolderPath & strFileName 'auflisten in Zelle 
            End If
        Loop While FindNextFile(lngSearch, WFD)
        FindClose lngSearch
    End If
End Sub


'************************************************************************************ 
'Um einzelne Laufwerke / Ordner zu durchsuchen, ergänze das ganze mit dieser Routine: 

Public Sub start2()
    Dim myFileSystemObject As Object, myDrive As Object
    Dim lngFilecount As Long
    Dim strFolder As String
    Dim Pfad As String
    Dim FileFilter As String
    
    FileFilter = InputBox("Filter angeben (Platzhalter verwenden z. Bsp. *.xls", "Filter", "*.*")
    If FileFilter = "" Then Exit Sub
    strFolder = Trim$(fncGetFolder(sPath:="C:\"))
    
    If strFolder <> "" Then
        If Right$(strFolder, 1) <> "\" Then strFolder = strFolder & "\"
        Application.ScreenUpdating = False
        Columns(1).ClearContents
        'Suchordner - Suchformat - Zähler - False ohne Subfolder######## 
        FindFiles strFolder, FileFilter, lngFilecount, True
        Columns(1).AutoFit
        Application.ScreenUpdating = True
    End If
End Sub
Gruß Tino
Anzeige
ach du brauchst noch die Länge vom Pfad...
16.03.2010 11:18:36
Tino
Hallo,
habe den Code etwas umgebaut, ich gehe davon aus das in Zeile 1 eine Überschrift ist.
kommt als Code in Modul1
Option Explicit 
Option Private Module 
Private Declare Function FindFirstFile Lib "kernel32" Alias "FindFirstFileA" ( _
    ByVal lpFileName As String, _
    lpFindFileData As WIN32_FIND_DATA) As Long 
Private Declare Function FindNextFile Lib "kernel32" Alias "FindNextFileA" ( _
    ByVal hFindFile As Long, _
    lpFindFileData As WIN32_FIND_DATA) As Long 
Private Declare Function FindClose Lib "kernel32" ( _
    ByVal hFindFile As Long) As Long 
 
Private Enum FILE_ATTRIBUTE 
    FILE_ATTRIBUTE_READONLY = &H1 
    FILE_ATTRIBUTE_HIDDEN = &H2 
    FILE_ATTRIBUTE_SYSTEM = &H4 
    FILE_ATTRIBUTE_DIRECTORY = &H10 
    FILE_ATTRIBUTE_ARCHIVE = &H20 
    FILE_ATTRIBUTE_NORMAL = &H80 
    FILE_ATTRIBUTE_TEMPORARY = &H100 
End Enum 
 
Private Const INVALID_HANDLE_VALUE = -1& 
Private Const MAX_PATH = 260& 
 
Private Type FILETIME 
    dwLowDateTime As Long 
    dwHighDateTime As Long 
End Type 
 
Private Type WIN32_FIND_DATA 
    dwFileAttributes As Long 
    ftCreationTime As FILETIME 
    ftLastAccessTime As FILETIME 
    ftLastWriteTime As FILETIME 
    nFileSizeHigh As Long 
    nFileSizeLow As Long 
    dwReserved0 As Long 
    dwReserved1 As Long 
    cFileName As String * MAX_PATH 
    cAlternate As String * 14 
End Type 
 
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 GetSystemMetrics Lib "user32.dll" ( _
    ByVal nIndex As Long) As Long 
Private Declare Function GetWindowRect Lib "user32.dll" ( _
    ByVal hwnd As Long, _
    ByRef lpRect As RECT) As Long 
Private Declare Function SHBrowseForFolder Lib "shell32" ( _
    lpbi As InfoT) As Long 
Private Declare Function CoTaskMemFree Lib "ole32" ( _
    ByVal hMem As Long) As Long 
Private Declare Function lstrcat Lib "kernel32" Alias "lstrcatA" ( _
    ByVal lpStr1 As String, _
    ByVal lpStr2 As String) As Long 
Private Declare Function SHGetPathFromIDList Lib "shell32" ( _
    ByVal pList As Long, _
    ByVal lpBuffer As String) As Long 
Private Declare Function FindWindow Lib "user32" 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, _
    wParam As Any, _
    lParam As Any) As Long 
 
Private Type InfoT 
    hwnd As Long 
    Root As Long 
    DisplayName As Long 
    Title As Long 
    Flags As Long 
    FName As Long 
    lParam As Long 
    Image As Long 
End Type 
 
Private Type RECT 
    Left As Long 
    Top As Long 
    Right As Long 
    Bottom As Long 
End Type 
 
Public Enum BIF_Flag 
    BIF_RETURNONLYFSDIRS = &H1 
    BIF_DONTGOBELOWDOMAIN = &H2 
    BIF_STATUSTEXT = &H4 
    BIF_RETURNFSANCESTORS = &H8 
    BIF_EDITBOX = &H10 
    BIF_VALIDATE = &H20 
    BIF_NEWDIALOGSTYLE = &H40 
    BIF_BROWSEINCLUDEURLS = &H80 
    BIF_BROWSEFORCOMPUTER = &H1000 
    BIF_BROWSEFORPRINTER = &H2000 
    BIF_BROWSEINCLUDEFILES = &H4000 
    BIF_SHAREABLE = &H8000 
End Enum 
 
Private Const SM_CXFULLSCREEN = &H10 
Private Const SM_CYFULLSCREEN = &H11 
 
Private Const BFFM_SETSELECTION = &H466 
Private Const BFFM_INITIALIZED = &H1 
 
Private s_BrowseInitDir As String 
 
Public Function fncGetFolder( _
        Optional ByVal sMsg As String = "Bitte wählen Sie ein Verzeichnis", _
        Optional ByVal lFlag As BIF_Flag = BIF_RETURNONLYFSDIRS, _
        Optional ByVal sPath As String = "C:\") As String 
    Dim xl As InfoT, IDList As Long, RVal As Long, FolderName As String 
    s_BrowseInitDir = sPath 
    With xl 
        .hwnd = FindWindow("XLMAIN", vbNullString) 
        .Root = 0 
        .Title = lstrcat(sMsg, "") 
        .Flags = lFlag 
        .FName = FuncCallback(AddressOf BrowseCallback) 
    End With 
    IDList = SHBrowseForFolder(xl) 
    If IDList <> 0 Then 
        FolderName = Space(256) 
        RVal = SHGetPathFromIDList(IDList, FolderName) 
        CoTaskMemFree (IDList) 
        FolderName = Trim$(FolderName) 
        FolderName = Left$(FolderName, Len(FolderName) - 1) 
    End If 
    fncGetFolder = FolderName 
End Function 
 
Private Function BrowseCallback( _
        ByVal hwnd As Long, _
        ByVal uMsg As Long, _
        ByVal wParam As Long, _
        ByVal lParam As Long) As Long 
    If uMsg = BFFM_INITIALIZED Then 
        Call SendMessage(hwnd, BFFM_SETSELECTION, ByVal 1&, ByVal s_BrowseInitDir) 
        Call CenterDialog(hwnd) 
    End If 
    BrowseCallback = 0 
End Function 
 
Private Function FuncCallback(ByVal nParam As Long) As Long 
    FuncCallback = nParam 
End Function 
 
Private Sub CenterDialog(ByVal hwnd As Long) 
    Dim WinRect As RECT, ScrWidth As Integer, ScrHeight As Integer 
    Dim DlgWidth As Integer, DlgHeight As Integer 
    GetWindowRect hwnd, WinRect 
    DlgWidth = WinRect.Right - WinRect.Left 
    DlgHeight = WinRect.Bottom - WinRect.Top 
    ScrWidth = GetSystemMetrics(SM_CXFULLSCREEN) 
    ScrHeight = GetSystemMetrics(SM_CYFULLSCREEN) 
    MoveWindow hwnd, (ScrWidth - DlgWidth) / 2, _
        (ScrHeight - DlgHeight) / 2, DlgWidth, DlgHeight, 1 
End Sub 
 
Sub FindFiles(ByVal strFolderPath As String, ByVal strSearch As String, _
        ByRef lngFilecount As Long, ArrFiles(), Optional SubFolder As Boolean = True) 
    Dim WFD As WIN32_FIND_DATA, lngSearch As Long, strDirName As String 
     
    lngSearch = FindFirstFile(strFolderPath & "*.*", WFD) 
     
    If lngSearch <> INVALID_HANDLE_VALUE Then 
        GetFilesInFolder strFolderPath, strSearch, lngFilecount, ArrFiles 
        Do 
            If (WFD.dwFileAttributes And FILE_ATTRIBUTE_DIRECTORY) Then 
                strDirName = Left$(WFD.cFileName, InStr(WFD.cFileName, Chr(0)) - 1) 
                If SubFolder = False Then Exit Sub 'ohne Unterordner 
                If (strDirName <> ".") And (strDirName <> "..") Then _
                    FindFiles strFolderPath & strDirName & "\", strSearch, lngFilecount, ArrFiles 
            End If 
        Loop While FindNextFile(lngSearch, WFD) 
        FindClose lngSearch 
    End If 
End Sub 
 
Sub GetFilesInFolder(ByVal strFolderPath As String, ByVal strSearch As String, _
        ByRef lngFilecount As Long, ArrFiles()) 
    Dim WFD As WIN32_FIND_DATA, lngSearch As Long, strFileName As String 
    lngSearch = FindFirstFile(strFolderPath & strSearch, WFD) 
    If lngSearch <> INVALID_HANDLE_VALUE Then 
        Do 
            If (WFD.dwFileAttributes And FILE_ATTRIBUTE_DIRECTORY) <> _
                FILE_ATTRIBUTE_DIRECTORY Then 
                strFileName = Left$(WFD.cFileName, InStr(WFD.cFileName, Chr(0)) - 1) 
                lngFilecount = lngFilecount + 1 
                Redim Preserve ArrFiles(1 To 2, 1 To lngFilecount) 
                ArrFiles(1, lngFilecount) = strFolderPath & strFileName 
                ArrFiles(2, lngFilecount) = Len(strFolderPath) 
            End If 
        Loop While FindNextFile(lngSearch, WFD) 
        FindClose lngSearch 
    End If 
End Sub 
 
 
'************************************************************************************ 
'Um einzelne Laufwerke / Ordner zu durchsuchen, ergänze das ganze mit dieser Routine: 
 
Public Sub start2() 
Dim myFileSystemObject As Object, myDrive As Object 
Dim lngFilecount As Long 
Dim strFolder As String 
Dim Pfad As String 
Dim FileFilter As String 
Dim ArFiles() 
     
    FileFilter = InputBox("Filter angeben (Platzhalter verwenden z. Bsp. *.xls", "Filter", "*.*") 
    If StrPtr(FileFilter) = 0 Then Exit Sub 
    strFolder = Trim$(fncGetFolder(sPath:="C:\")) 
     
    If strFolder <> "" Then 
        If Right$(strFolder, 1) <> "\" Then strFolder = strFolder & "\" 
 
        Range("A2:B2").Resize(Rows.Count - 1).ClearContents 
         
        'Suchordner - Suchformat - Zähler - False ohne Subfolder######## 
        FindFiles strFolder, FileFilter, lngFilecount, ArFiles, True 
         
        If lngFilecount > 0 Then 
            Range("A2").Resize(Ubound(ArFiles, 2), Ubound(ArFiles)) = Application.Transpose(ArFiles) 
            Range("A2:B2").EntireColumn.AutoFit 
        End If 
    End If 
End Sub 
 
Gruß Tino
Anzeige
AW: ListView 6.0
16.03.2010 11:14:23
Alfons
Hallo,
sieh dir das mal an:
Dateiliste
Zeichenlänge kannst Du unter Extras anklicken.
Gruß
Alfons
http://vba1.de
sorry, falscher Betreff (oT)
16.03.2010 11:16:18
Alfons
.
AW: sorry, falscher Betreff (oT)
16.03.2010 11:54:23
Helmut
hi alfons,
danke dir!!!!! das ist ja echt super, was da programmiert wurde!! heftig!!
danke für den link!!!
liebe grüße,
helmut
AW: sorry, falscher Betreff (oT)
16.03.2010 12:07:11
Detlef
Hallo Helmut,
oder ganz spartanisch:
Option Explicit

Sub DateienAuflisten()
Dim lngZaehler As Long
Dim Maske As String
Dim verz As String

On Error Resume Next

'alte Einträge löschen 
Sheets("Dateien").Cells.ClearContents

verz = InputBox("Bitte Pfad zu den Dateien eingeben ..." & Chr(13) _
     & "z.B.: \\rss4\pdf\")
     
Maske = InputBox("Geben Sie bitte die Dateiendung ein ..." & Chr(13) _
     & "z.B.: xls; doc; prt; asm ...")
     
    With Application.FileSearch
        .Filename = Maske
        .LookIn = verz
        .SearchSubFolders = True
        .Execute
         For lngZaehler = 1 To .FoundFiles.Count
            Sheets("Dateien").Cells(lngZaehler, 1).Value = _
               .FoundFiles(lngZaehler)
            Sheets("Dateien").Cells(lngZaehler, 2).Value = _
               Len(Sheets("Dateien").Cells(lngZaehler, 1))
         Next lngZaehler
    End With
Sheets("Dateien").Columns("A").Columns.AutoFit
End Sub
Tabellennamen entsprechend anpassen.
       Gruß Detlef
*** RückInfo wäre nett ***

Anzeige
AW: sorry, falscher Betreff (oT)
16.03.2010 12:50:20
Helmut
hi detlef,
super, eine ganz einfache, bzw. kurze lösung zu meinem problem!
danke dir!
bei einem Versionswechsel...
17.03.2010 07:33:02
Tino
Hallo,
kannst Du die Frage nochmal stellen.
Gruß Tino

310 Forumthreads zu ähnlichen Themen

Anzeige
Anzeige
Anzeige

Links zu Excel-Dialogen

Beliebteste Forumthreads (12 Monate)

Anzeige

Beliebteste Forumthreads (12 Monate)

Anzeige
Anzeige
Anzeige