can list ALL the contents of the cd into a text file and import that - if it helps, but it lists it in 4 collumns and all the AA numbers are in the first collumn or some of the 2nd. This unfiltered file end up at around 75 pages!
I can get the AA numbers listed into 10 collumns in Excel - and that's the format I'd like.
A version of this code was posted earlier. Run it
in a blank worksheet. It uses the current Excel
directory. To set the directory select open file,
navigate to the desired directory, and select cancel.
You can also hard code the current directory. Search
for it in help.
Sub GetAllFilesInDirectory()
Dim i
With Application.FileSearch
.NewSearch
.FileType = msoFileTypeAllFiles ' msoFileTypeExcelWorkbooks
.LookIn = CurDir()
.SearchSubFolders = True 'true searches subfolders, false does not
.Execute
For i = 1 To .FoundFiles.Count
Range("A" & i) = .FoundFiles(i)
MyLen = Len(Range("A" & i))
Next i
End With
End Sub
Does Ignore All not do it? After you search and it stops at this error do ignore all.
Thanks for that.
I did spend some time doing a search through the list but was probably looking for the wrong thing. With Application.FileSearch .NewSearch .FileType = msoFileTypeAllFiles ' msoFileTypeExcelWorkbooks .LookIn = CurDir() .SearchSubFolders = True 'true searches subfolders, false does not .Execute For i = 1 To .FoundFiles.Count Range("A" & i) = .FoundFiles(i) MyLen = Len(Range("A" & i)) Next i End With
With Application.FileSearch .NewSearch .FileType = msoFileTypeAllFiles ' msoFileTypeExcelWorkbooks .LookIn = CurDir() .SearchSubFolders = True 'true searches subfolders, false does not .Execute For i = 1 To .FoundFiles.Count Range("A" & i) = .FoundFiles(i) MyLen = Len(Range("A" & i)) Next i End With
This may work better.
Sub GetAllFilesInDirectory()
Dim i
Dim MyString As String
'set searchstring
Dim SearchString As String
SearchString = "AA"
With Application.FileSearch
.NewSearch
.FileType = msoFileTypeAllFiles ' msoFileTypeExcelWorkbooks
.LookIn = CurDir()
.SearchSubFolders = True 'true searches subfolders, false does not
.Execute
'set this range to the desired starting cell
Range("A1").Select
For i = 1 To .FoundFiles.Count
MyString = .FoundFiles(i)
If InStr(1, MyString, SearchString, 1) Then
Selection = .FoundFiles(i)
Selection.Offset(1, 0).Select
End If
Next i
End With
End Sub