1VERSION 1.0 CLASS
2BEGIN
3  MultiUse = -1  'True
4END
5Attribute VB_Name = "CollectedFiles"
6Attribute VB_GlobalNameSpace = False
7Attribute VB_Creatable = False
8Attribute VB_PredeclaredId = False
9Attribute VB_Exposed = False
10'/*************************************************************************
11' *
12' DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
13'
14' Copyright 2000, 2010 Oracle and/or its affiliates.
15'
16' OpenOffice.org - a multi-platform office productivity suite
17'
18' This file is part of OpenOffice.org.
19'
20' OpenOffice.org is free software: you can redistribute it and/or modify
21' it under the terms of the GNU Lesser General Public License version 3
22' only, as published by the Free Software Foundation.
23'
24' OpenOffice.org is distributed in the hope that it will be useful,
25' but WITHOUT ANY WARRANTY; without even the implied warranty of
26' MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
27' GNU Lesser General Public License version 3 for more details
28' (a copy is included in the LICENSE file that accompanied this code).
29'
30' You should have received a copy of the GNU Lesser General Public License
31' version 3 along with OpenOffice.org.  If not, see
32' <http://www.openoffice.org/license.html>
33' for a copy of the LGPLv3 License.
34'
35' ************************************************************************/
36Option Explicit
37
38Private Const vbDot = 46
39Private Const MAX_PATH = 260
40Private Const INVALID_HANDLE_VALUE = -1
41Private Const vbBackslash = "\"
42Private Const ALL_FILES = "*.*"
43
44Private Type FILETIME
45   dwLowDateTime As Long
46   dwHighDateTime As Long
47End Type
48
49Private Type WIN32_FIND_DATA
50   dwFileAttributes As Long
51   ftCreationTime As FILETIME
52   ftLastAccessTime As FILETIME
53   ftLastWriteTime As FILETIME
54   nFileSizeHigh As Long
55   nFileSizeLow As Long
56   dwReserved0 As Long
57   dwReserved1 As Long
58   cFileName As String * MAX_PATH
59   cAlternate As String * 14
60End Type
61
62Private Type FILE_PARAMS
63   bRecurse As Boolean
64   nSearched As Long
65   sFileNameExt As String
66   sFileRoot As String
67End Type
68
69Private Declare Function FindClose Lib "kernel32" _
70  (ByVal hFindFile As Long) As Long
71
72Private Declare Function FindFirstFile Lib "kernel32" _
73   Alias "FindFirstFileA" _
74  (ByVal lpFileName As String, _
75   lpFindFileData As WIN32_FIND_DATA) As Long
76
77Private Declare Function FindNextFile Lib "kernel32" _
78   Alias "FindNextFileA" _
79  (ByVal hFindFile As Long, _
80   lpFindFileData As WIN32_FIND_DATA) As Long
81
82Private Declare Function GetTickCount Lib "kernel32" () As Long
83
84Private Declare Function lstrlen Lib "kernel32" _
85    Alias "lstrlenW" (ByVal lpString As Long) As Long
86
87Private Declare Function PathMatchSpec Lib "shlwapi" _
88   Alias "PathMatchSpecW" _
89  (ByVal pszFileParam As Long, _
90   ByVal pszSpec As Long) As Long
91
92Private fp As FILE_PARAMS  'holds search parameters
93
94Private mWordFilesCol As Collection
95Private mExcelFilesCol As Collection
96Private mPPFilesCol As Collection
97
98Private mDocCount As Long
99Private mDotCount As Long
100Private mXlsCount As Long
101Private mXltCount As Long
102Private mPptCount As Long
103Private mPotCount As Long
104Private mbDocSearch As Boolean
105Private mbDotSearch  As Boolean
106Private mbXlsSearch As Boolean
107Private mbXltSearch As Boolean
108Private mbPptSearch As Boolean
109Private mbPotSearch As Boolean
110
111Private mBannedList As Collection
112
113Private Sub Class_Initialize()
114    Set mWordFilesCol = New Collection
115    Set mExcelFilesCol = New Collection
116    Set mPPFilesCol = New Collection
117    Set mBannedList = New Collection
118End Sub
119Private Sub Class_Terminate()
120    Set mWordFilesCol = Nothing
121    Set mExcelFilesCol = Nothing
122    Set mPPFilesCol = Nothing
123    Set mBannedList = Nothing
124End Sub
125
126Public Property Get BannedList() As Collection
127    Set BannedList = mBannedList
128End Property
129Public Property Let BannedList(ByVal theList As Collection)
130    Set mBannedList = theList
131End Property
132
133Public Property Get DocCount() As Long
134    DocCount = mDocCount
135End Property
136Public Property Get DotCount() As Long
137    DotCount = mDotCount
138End Property
139Public Property Get XlsCount() As Long
140    XlsCount = mXlsCount
141End Property
142Public Property Get XltCount() As Long
143    XltCount = mXltCount
144End Property
145Public Property Get PptCount() As Long
146    PptCount = mPptCount
147End Property
148Public Property Get PotCount() As Long
149    PotCount = mPotCount
150End Property
151
152Public Property Get WordFiles() As Collection
153    Set WordFiles = mWordFilesCol
154End Property
155Public Property Get ExcelFiles() As Collection
156    Set ExcelFiles = mExcelFilesCol
157End Property
158Public Property Get PowerPointFiles() As Collection
159    Set PowerPointFiles = mPPFilesCol
160End Property
161
162Public Function count() As Long
163    count = mWordFilesCol.count + mExcelFilesCol.count + mPPFilesCol.count
164End Function
165
166
167Public Function Search(rootDir As String, _
168    FileSpecs As Collection, IncludeSubdirs As Boolean)
169    On Error GoTo HandleErrors
170    Dim currentFunctionName As String
171    currentFunctionName = "Search"
172
173   Dim tstart As Single   'timer var for this routine only
174   Dim tend As Single     'timer var for this routine only
175   Dim spec As Variant
176   Dim allSpecs As String
177   Dim fso As New FileSystemObject
178
179    If FileSpecs.count = 0 Then Exit Function
180
181    If FileSpecs.count > 1 Then
182        For Each spec In FileSpecs
183             allSpecs = allSpecs & "; " & spec
184             SetSearchBoolean CStr(spec)
185        Next
186    Else
187        allSpecs = FileSpecs(1)
188        SetSearchBoolean CStr(FileSpecs(1))
189    End If
190
191    With fp
192       .sFileRoot = QualifyPath(rootDir)
193       .sFileNameExt = allSpecs
194       .bRecurse = IncludeSubdirs
195       .nSearched = 0
196    End With
197
198    tstart = GetTickCount()
199    Call SearchForFiles(fp.sFileRoot)
200    tend = GetTickCount()
201
202    'Debug:
203    'MsgBox "Specs " & allSpecs & vbLf & _
204    '    Format$(fp.nSearched, "###,###,###,##0") & vbLf & _
205    '     Format$(count, "###,###,###,##0") & vbLf & _
206    '     FormatNumber((tend - tstart) / 1000, 2) & "  seconds"
207
208FinalExit:
209    Set fso = Nothing
210    Exit Function
211
212HandleErrors:
213    WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
214    Resume FinalExit
215End Function
216Function isBannedFile(thePath As String) As Boolean
217
218    Dim aPath As Variant
219    Dim theResult As Boolean
220    theResult = False
221    For Each aPath In mBannedList
222        If aPath = thePath Then
223            theResult = True
224            GoTo FinalExit
225        End If
226    Next
227
228FinalExit:
229    isBannedFile = theResult
230End Function
231Sub SetSearchBoolean(spec As String)
232
233    If spec = "*.doc" Then
234        mbDocSearch = True
235    End If
236    If spec = "*.dot" Then
237        mbDotSearch = True
238    End If
239    If spec = "*.xls" Then
240        mbXlsSearch = True
241    End If
242    If spec = "*.xlt" Then
243        mbXltSearch = True
244    End If
245    If spec = "*.ppt" Then
246        mbPptSearch = True
247    End If
248    If spec = "*.pot" Then
249        mbPotSearch = True
250    End If
251
252End Sub
253
254Private Sub SearchForFiles(sRoot As String)
255    On Error GoTo HandleErrors
256    Dim currentFunctionName As String
257    currentFunctionName = "SearchForFiles"
258
259    Dim WFD As WIN32_FIND_DATA
260    Dim hFile As Long
261    Dim path As String
262    Dim WordDriverPathTemp As String
263    Dim ExcelDriverPathTemp As String
264    Dim PPDriverPathTemp As String
265
266    hFile = FindFirstFile(sRoot & ALL_FILES, WFD)
267
268    If hFile = INVALID_HANDLE_VALUE Then GoTo FinalExit
269
270    Do
271        'if a folder, and recurse specified, call
272        'method again
273        If (WFD.dwFileAttributes And vbDirectory) Then
274            If Asc(WFD.cFileName) <> vbDot Then
275                If fp.bRecurse Then
276                    SearchForFiles sRoot & TrimNull(WFD.cFileName) & vbBackslash
277                End If
278            End If
279        Else
280            'must be a file..
281            If mbDocSearch Then
282                 If MatchSpec(WFD.cFileName, "*.doc") Then
283                    path = sRoot & TrimNull(WFD.cFileName)
284                    'If StrComp(path, mWordDriverPath, vbTextCompare) <> 0 Then
285                    If Not isBannedFile(path) Then
286                       mDocCount = mDocCount + 1
287                       mWordFilesCol.Add path
288                       GoTo CONTINUE_LOOP
289                    End If
290                 End If
291            End If
292            If mbDotSearch Then
293                If MatchSpec(WFD.cFileName, "*.dot") Then
294                       mDotCount = mDotCount + 1
295                       mWordFilesCol.Add sRoot & TrimNull(WFD.cFileName)
296                        GoTo CONTINUE_LOOP
297                End If
298            End If
299            If mbXlsSearch Then
300                 If MatchSpec(WFD.cFileName, "*.xls") Then
301                    path = sRoot & TrimNull(WFD.cFileName)
302                    'If StrComp(TrimNull(WFD.cFileName), CEXCEL_DRIVER_FILE, vbTextCompare) <> 0 Then
303                    If Not isBannedFile(path) Then
304                        mXlsCount = mXlsCount + 1
305                        mExcelFilesCol.Add sRoot & TrimNull(WFD.cFileName)
306                       GoTo CONTINUE_LOOP
307                    End If
308                 End If
309            End If
310            If mbXltSearch Then
311                 If MatchSpec(WFD.cFileName, "*.xlt") Then
312                    mXltCount = mXltCount + 1
313                    mExcelFilesCol.Add sRoot & TrimNull(WFD.cFileName)
314                    GoTo CONTINUE_LOOP
315                 End If
316            End If
317            If mbPptSearch Then
318                 If MatchSpec(WFD.cFileName, "*.ppt") Then
319                    path = sRoot & TrimNull(WFD.cFileName)
320                    'If StrComp(path, mPPDriverPath, vbTextCompare) <> 0 Then
321                    If Not isBannedFile(path) Then
322                       mPptCount = mPptCount + 1
323                       mPPFilesCol.Add path
324                       GoTo CONTINUE_LOOP
325                    End If
326                 End If
327            End If
328            If mbPotSearch Then
329                 If MatchSpec(WFD.cFileName, "*.pot") Then
330                    mPotCount = mPotCount + 1
331                    mPPFilesCol.Add sRoot & TrimNull(WFD.cFileName)
332                    GoTo CONTINUE_LOOP
333                 End If
334            End If
335
336        End If 'If WFD.dwFileAttributes
337
338CONTINUE_LOOP:
339        fp.nSearched = fp.nSearched + 1
340
341    Loop While FindNextFile(hFile, WFD)
342
343FinalExit:
344    Call FindClose(hFile)
345    Exit Sub
346
347HandleErrors:
348    WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
349    Resume FinalExit
350End Sub
351
352
353Private Function QualifyPath(sPath As String) As String
354
355   If Right$(sPath, 1) <> vbBackslash Then
356         QualifyPath = sPath & vbBackslash
357   Else: QualifyPath = sPath
358   End If
359
360End Function
361
362
363Private Function TrimNull(startstr As String) As String
364
365   TrimNull = Left$(startstr, lstrlen(StrPtr(startstr)))
366
367End Function
368
369
370Private Function MatchSpec(sFile As String, sSpec As String) As Boolean
371
372   MatchSpec = PathMatchSpec(StrPtr(sFile), StrPtr(sSpec))
373
374End Function
375
376
377
378
379