1cdf0e10cSrcweirVERSION 1.0 CLASS
2cdf0e10cSrcweirBEGIN
3cdf0e10cSrcweir  MultiUse = -1  'True
4cdf0e10cSrcweir  Persistable = 0  'NotPersistable
5cdf0e10cSrcweir  DataBindingBehavior = 0  'vbNone
6cdf0e10cSrcweir  DataSourceBehavior  = 0  'vbNone
7cdf0e10cSrcweir  MTSTransactionMode  = 0  'NotAnMTSObject
8cdf0e10cSrcweirEND
9cdf0e10cSrcweirAttribute VB_Name = "CollectedFiles"
10cdf0e10cSrcweirAttribute VB_GlobalNameSpace = False
11cdf0e10cSrcweirAttribute VB_Creatable = True
12cdf0e10cSrcweirAttribute VB_PredeclaredId = False
13cdf0e10cSrcweirAttribute VB_Exposed = False
14*d4a3fa4bSAndrew Rist'*************************************************************************
15*d4a3fa4bSAndrew Rist'
16*d4a3fa4bSAndrew Rist'  Licensed to the Apache Software Foundation (ASF) under one
17*d4a3fa4bSAndrew Rist'  or more contributor license agreements.  See the NOTICE file
18*d4a3fa4bSAndrew Rist'  distributed with this work for additional information
19*d4a3fa4bSAndrew Rist'  regarding copyright ownership.  The ASF licenses this file
20*d4a3fa4bSAndrew Rist'  to you under the Apache License, Version 2.0 (the
21*d4a3fa4bSAndrew Rist'  "License"); you may not use this file except in compliance
22*d4a3fa4bSAndrew Rist'  with the License.  You may obtain a copy of the License at
23*d4a3fa4bSAndrew Rist'
24*d4a3fa4bSAndrew Rist'    http://www.apache.org/licenses/LICENSE-2.0
25*d4a3fa4bSAndrew Rist'
26*d4a3fa4bSAndrew Rist'  Unless required by applicable law or agreed to in writing,
27*d4a3fa4bSAndrew Rist'  software distributed under the License is distributed on an
28*d4a3fa4bSAndrew Rist'  "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
29*d4a3fa4bSAndrew Rist'  KIND, either express or implied.  See the License for the
30*d4a3fa4bSAndrew Rist'  specific language governing permissions and limitations
31*d4a3fa4bSAndrew Rist'  under the License.
32*d4a3fa4bSAndrew Rist'
33*d4a3fa4bSAndrew Rist'*************************************************************************
34cdf0e10cSrcweirOption Explicit
35cdf0e10cSrcweir
36cdf0e10cSrcweirPrivate Const vbDot = 46
37cdf0e10cSrcweirPrivate Const MAX_PATH = 260
38cdf0e10cSrcweirPrivate Const INVALID_HANDLE_VALUE = -1
39cdf0e10cSrcweirPrivate Const vbBackslash = "\"
40cdf0e10cSrcweirPrivate Const ALL_FILES = "*.*"
41cdf0e10cSrcweir
42cdf0e10cSrcweirPrivate Type FILETIME
43cdf0e10cSrcweir   dwLowDateTime As Long
44cdf0e10cSrcweir   dwHighDateTime As Long
45cdf0e10cSrcweirEnd Type
46cdf0e10cSrcweir
47cdf0e10cSrcweirPrivate Type SYSTEMTIME
48cdf0e10cSrcweir    wYear As Integer
49cdf0e10cSrcweir    wMonth As Integer
50cdf0e10cSrcweir    wDayOfWeek As Integer
51cdf0e10cSrcweir    wDay As Integer
52cdf0e10cSrcweir    wHour As Integer
53cdf0e10cSrcweir    wMinute As Integer
54cdf0e10cSrcweir    wSecond As Integer
55cdf0e10cSrcweir    wMilliseconds As Integer
56cdf0e10cSrcweirEnd Type
57cdf0e10cSrcweir
58cdf0e10cSrcweirPrivate Type WIN32_FIND_DATA
59cdf0e10cSrcweir   dwFileAttributes As Long
60cdf0e10cSrcweir   ftCreationTime As FILETIME
61cdf0e10cSrcweir   ftLastAccessTime As FILETIME
62cdf0e10cSrcweir   ftLastWriteTime As FILETIME
63cdf0e10cSrcweir   nFileSizeHigh As Long
64cdf0e10cSrcweir   nFileSizeLow As Long
65cdf0e10cSrcweir   dwReserved0 As Long
66cdf0e10cSrcweir   dwReserved1 As Long
67cdf0e10cSrcweir   cFileName As String * MAX_PATH
68cdf0e10cSrcweir   cAlternate As String * 14
69cdf0e10cSrcweirEnd Type
70cdf0e10cSrcweir
71cdf0e10cSrcweirPrivate Type FILE_PARAMS
72cdf0e10cSrcweir   bRecurse As Boolean
73cdf0e10cSrcweir   nSearched As Long
74cdf0e10cSrcweir   sFileNameExt As String
75cdf0e10cSrcweir   sFileRoot As String
76cdf0e10cSrcweirEnd Type
77cdf0e10cSrcweir
78cdf0e10cSrcweirPrivate Declare Function SystemTimeToFileTime Lib "kernel32" _
79cdf0e10cSrcweir  (lpSystemTime As SYSTEMTIME, _
80cdf0e10cSrcweir   lpFileTime As FILETIME) As Long
81cdf0e10cSrcweir
82cdf0e10cSrcweirPrivate Declare Function CompareFileTime Lib "kernel32" _
83cdf0e10cSrcweir  (lpFileTime1 As FILETIME, _
84cdf0e10cSrcweir   lpFileTime2 As FILETIME) As Long
85cdf0e10cSrcweir
86cdf0e10cSrcweirPrivate Declare Function FindClose Lib "kernel32" _
87cdf0e10cSrcweir  (ByVal hFindFile As Long) As Long
88cdf0e10cSrcweir
89cdf0e10cSrcweirPrivate Declare Function FindFirstFile Lib "kernel32" _
90cdf0e10cSrcweir   Alias "FindFirstFileA" _
91cdf0e10cSrcweir  (ByVal lpFileName As String, _
92cdf0e10cSrcweir   lpFindFileData As WIN32_FIND_DATA) As Long
93cdf0e10cSrcweir
94cdf0e10cSrcweirPrivate Declare Function FindNextFile Lib "kernel32" _
95cdf0e10cSrcweir   Alias "FindNextFileA" _
96cdf0e10cSrcweir  (ByVal hFindFile As Long, _
97cdf0e10cSrcweir   lpFindFileData As WIN32_FIND_DATA) As Long
98cdf0e10cSrcweir
99cdf0e10cSrcweirPrivate Declare Function GetTickCount Lib "kernel32" () As Long
100cdf0e10cSrcweir
101cdf0e10cSrcweirPrivate Declare Function lstrlen Lib "kernel32" _
102cdf0e10cSrcweir    Alias "lstrlenW" (ByVal lpString As Long) As Long
103cdf0e10cSrcweir
104cdf0e10cSrcweirPrivate Declare Function PathMatchSpec Lib "shlwapi" _
105cdf0e10cSrcweir   Alias "PathMatchSpecW" _
106cdf0e10cSrcweir  (ByVal pszFileParam As Long, _
107cdf0e10cSrcweir   ByVal pszSpec As Long) As Long
108cdf0e10cSrcweir
109cdf0e10cSrcweirPrivate fp As FILE_PARAMS  'holds search parameters
110cdf0e10cSrcweir
111cdf0e10cSrcweirPrivate mWordFilesCol As Collection
112cdf0e10cSrcweirPrivate mExcelFilesCol As Collection
113cdf0e10cSrcweirPrivate mPPFilesCol As Collection
114cdf0e10cSrcweir
115cdf0e10cSrcweirPrivate mLessThan3 As Long
116cdf0e10cSrcweirPrivate mLessThan6 As Long
117cdf0e10cSrcweirPrivate mLessThan12 As Long
118cdf0e10cSrcweirPrivate mMoreThan12 As Long
119cdf0e10cSrcweirPrivate m3Months As FILETIME
120cdf0e10cSrcweirPrivate m6Months As FILETIME
121cdf0e10cSrcweirPrivate m12Months As FILETIME
122cdf0e10cSrcweir
123cdf0e10cSrcweirPrivate mDocCount As Long
124cdf0e10cSrcweirPrivate mDotCount As Long
125cdf0e10cSrcweirPrivate mXlsCount As Long
126cdf0e10cSrcweirPrivate mXltCount As Long
127cdf0e10cSrcweirPrivate mPptCount As Long
128cdf0e10cSrcweirPrivate mPotCount As Long
129cdf0e10cSrcweirPrivate mIgnoredDocs As Long
130cdf0e10cSrcweirPrivate mbDocSearch As Boolean
131cdf0e10cSrcweirPrivate mbDotSearch  As Boolean
132cdf0e10cSrcweirPrivate mbXlsSearch As Boolean
133cdf0e10cSrcweirPrivate mbXltSearch As Boolean
134cdf0e10cSrcweirPrivate mbPptSearch As Boolean
135cdf0e10cSrcweirPrivate mbPotSearch As Boolean
136cdf0e10cSrcweir
137cdf0e10cSrcweirPrivate mWordDriverPath As String
138cdf0e10cSrcweirPrivate mExcelDriverPath As String
139cdf0e10cSrcweirPrivate mPPDriverPath As String
140cdf0e10cSrcweir
141cdf0e10cSrcweirPrivate Sub Class_Initialize()
142cdf0e10cSrcweir    Set mWordFilesCol = New Collection
143cdf0e10cSrcweir    Set mExcelFilesCol = New Collection
144cdf0e10cSrcweir    Set mPPFilesCol = New Collection
145cdf0e10cSrcweirEnd Sub
146cdf0e10cSrcweirPrivate Sub Class_Terminate()
147cdf0e10cSrcweir    Set mWordFilesCol = Nothing
148cdf0e10cSrcweir    Set mExcelFilesCol = Nothing
149cdf0e10cSrcweir    Set mPPFilesCol = Nothing
150cdf0e10cSrcweirEnd Sub
151cdf0e10cSrcweir
152cdf0e10cSrcweirPublic Property Get DocCount() As Long
153cdf0e10cSrcweir    DocCount = mDocCount
154cdf0e10cSrcweirEnd Property
155cdf0e10cSrcweirPublic Property Get DotCount() As Long
156cdf0e10cSrcweir    DotCount = mDotCount
157cdf0e10cSrcweirEnd Property
158cdf0e10cSrcweirPublic Property Get XlsCount() As Long
159cdf0e10cSrcweir    XlsCount = mXlsCount
160cdf0e10cSrcweirEnd Property
161cdf0e10cSrcweirPublic Property Get XltCount() As Long
162cdf0e10cSrcweir    XltCount = mXltCount
163cdf0e10cSrcweirEnd Property
164cdf0e10cSrcweirPublic Property Get PptCount() As Long
165cdf0e10cSrcweir    PptCount = mPptCount
166cdf0e10cSrcweirEnd Property
167cdf0e10cSrcweirPublic Property Get PotCount() As Long
168cdf0e10cSrcweir    PotCount = mPotCount
169cdf0e10cSrcweirEnd Property
170cdf0e10cSrcweirPublic Property Get IgnoredDocCount() As Long
171cdf0e10cSrcweir    IgnoredDocCount = mIgnoredDocs
172cdf0e10cSrcweirEnd Property
173cdf0e10cSrcweirPublic Property Get DocsLessThan3Months() As Long
174cdf0e10cSrcweir    DocsLessThan3Months = mLessThan3
175cdf0e10cSrcweirEnd Property
176cdf0e10cSrcweirPublic Property Get DocsLessThan6Months() As Long
177cdf0e10cSrcweir    DocsLessThan6Months = mLessThan6
178cdf0e10cSrcweirEnd Property
179cdf0e10cSrcweirPublic Property Get DocsLessThan12Months() As Long
180cdf0e10cSrcweir    DocsLessThan12Months = mLessThan12
181cdf0e10cSrcweirEnd Property
182cdf0e10cSrcweirPublic Property Get DocsMoreThan12Months() As Long
183cdf0e10cSrcweir    DocsMoreThan12Months = mMoreThan12
184cdf0e10cSrcweirEnd Property
185cdf0e10cSrcweir
186cdf0e10cSrcweirPublic Property Get WordFiles() As Collection
187cdf0e10cSrcweir    Set WordFiles = mWordFilesCol
188cdf0e10cSrcweirEnd Property
189cdf0e10cSrcweirPublic Property Get ExcelFiles() As Collection
190cdf0e10cSrcweir    Set ExcelFiles = mExcelFilesCol
191cdf0e10cSrcweirEnd Property
192cdf0e10cSrcweirPublic Property Get PowerPointFiles() As Collection
193cdf0e10cSrcweir    Set PowerPointFiles = mPPFilesCol
194cdf0e10cSrcweirEnd Property
195cdf0e10cSrcweir
196cdf0e10cSrcweirPublic Function count() As Long
197cdf0e10cSrcweir    count = mWordFilesCol.count + mExcelFilesCol.count + mPPFilesCol.count
198cdf0e10cSrcweirEnd Function
199cdf0e10cSrcweir
200cdf0e10cSrcweirPublic Function Search(rootDir As String, FileSpecs As Collection, IncludeSubdirs As Boolean, _
201cdf0e10cSrcweir                       ignoreOld As Boolean, Months As Integer) As Boolean
202cdf0e10cSrcweir    On Error GoTo HandleErrors
203cdf0e10cSrcweir    Dim currentFunctionName As String
204cdf0e10cSrcweir    currentFunctionName = "Search"
205cdf0e10cSrcweir
206cdf0e10cSrcweir    Dim tstart As Single   'timer var for this routine only
207cdf0e10cSrcweir    Dim tend As Single     'timer var for this routine only
208cdf0e10cSrcweir    Dim spec As Variant
209cdf0e10cSrcweir    Dim allSpecs As String
210cdf0e10cSrcweir    Dim fso As New FileSystemObject
211cdf0e10cSrcweir
212cdf0e10cSrcweir    Search = True
213cdf0e10cSrcweir
214cdf0e10cSrcweir    If FileSpecs.count = 0 Then Exit Function
215cdf0e10cSrcweir
216cdf0e10cSrcweir    If FileSpecs.count > 1 Then
217cdf0e10cSrcweir        For Each spec In FileSpecs
218cdf0e10cSrcweir             allSpecs = allSpecs & "; " & spec
219cdf0e10cSrcweir             SetSearchBoolean CStr(spec)
220cdf0e10cSrcweir        Next
221cdf0e10cSrcweir    Else
222cdf0e10cSrcweir        allSpecs = FileSpecs(1)
223cdf0e10cSrcweir        SetSearchBoolean CStr(FileSpecs(1))
224cdf0e10cSrcweir    End If
225cdf0e10cSrcweir
226cdf0e10cSrcweir    mWordDriverPath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CWORD_DRIVER_FILE)
227cdf0e10cSrcweir    mExcelDriverPath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CEXCEL_DRIVER_FILE)
228cdf0e10cSrcweir    mPPDriverPath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CPP_DRIVER_FILE)
229cdf0e10cSrcweir
230cdf0e10cSrcweir    With fp
231cdf0e10cSrcweir       .sFileRoot = QualifyPath(rootDir)
232cdf0e10cSrcweir       .sFileNameExt = allSpecs
233cdf0e10cSrcweir       .bRecurse = IncludeSubdirs
234cdf0e10cSrcweir       .nSearched = 0
235cdf0e10cSrcweir    End With
236cdf0e10cSrcweir
237cdf0e10cSrcweir    Load SearchDocs
238cdf0e10cSrcweir
239cdf0e10cSrcweir    ignoreOld = ignoreOld And InitFileTimes
240cdf0e10cSrcweir
241cdf0e10cSrcweir    Dim limDate As FILETIME
242cdf0e10cSrcweir    If ignoreOld Then
243cdf0e10cSrcweir        If Months = 3 Then
244cdf0e10cSrcweir            limDate = m3Months
245cdf0e10cSrcweir        ElseIf Months = 6 Then
246cdf0e10cSrcweir            limDate = m6Months
247cdf0e10cSrcweir        ElseIf Months = 12 Then
248cdf0e10cSrcweir            limDate = m12Months
249cdf0e10cSrcweir        Else
250cdf0e10cSrcweir            ignoreOld = False
251cdf0e10cSrcweir        End If
252cdf0e10cSrcweir    End If
253cdf0e10cSrcweir
254cdf0e10cSrcweir    'tstart = GetTickCount()
255cdf0e10cSrcweir    Search = SearchForFiles(QualifyPath(rootDir), IncludeSubdirs, ignoreOld, limDate)
256cdf0e10cSrcweir    'tend = GetTickCount()
257cdf0e10cSrcweir
258cdf0e10cSrcweir    Unload SearchDocs
259cdf0e10cSrcweir
260cdf0e10cSrcweir    'Debug:
261cdf0e10cSrcweir    'MsgBox "Specs " & allSpecs & vbLf & _
262cdf0e10cSrcweir    '    Format$(fp.nSearched, "###,###,###,##0") & vbLf & _
263cdf0e10cSrcweir    '     Format$(count, "###,###,###,##0") & vbLf & _
264cdf0e10cSrcweir    '     FormatNumber((tend - tstart) / 1000, 2) & "  seconds"
265cdf0e10cSrcweir
266cdf0e10cSrcweirFinalExit:
267cdf0e10cSrcweir    Set fso = Nothing
268cdf0e10cSrcweir    Exit Function
269cdf0e10cSrcweir
270cdf0e10cSrcweirHandleErrors:
271cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
272cdf0e10cSrcweir    Resume FinalExit
273cdf0e10cSrcweirEnd Function
274cdf0e10cSrcweirSub SetSearchBoolean(spec As String)
275cdf0e10cSrcweir
276cdf0e10cSrcweir    If spec = "*.doc" Then
277cdf0e10cSrcweir        mbDocSearch = True
278cdf0e10cSrcweir    End If
279cdf0e10cSrcweir    If spec = "*.dot" Then
280cdf0e10cSrcweir        mbDotSearch = True
281cdf0e10cSrcweir    End If
282cdf0e10cSrcweir    If spec = "*.xls" Then
283cdf0e10cSrcweir        mbXlsSearch = True
284cdf0e10cSrcweir    End If
285cdf0e10cSrcweir    If spec = "*.xlt" Then
286cdf0e10cSrcweir        mbXltSearch = True
287cdf0e10cSrcweir    End If
288cdf0e10cSrcweir    If spec = "*.ppt" Then
289cdf0e10cSrcweir        mbPptSearch = True
290cdf0e10cSrcweir    End If
291cdf0e10cSrcweir    If spec = "*.pot" Then
292cdf0e10cSrcweir        mbPotSearch = True
293cdf0e10cSrcweir    End If
294cdf0e10cSrcweir
295cdf0e10cSrcweirEnd Sub
296cdf0e10cSrcweir
297cdf0e10cSrcweirPrivate Function SearchForFiles(sRoot As String, bRecurse As Boolean, _
298cdf0e10cSrcweir                                bIgnoreOld As Boolean, limDate As FILETIME) As Boolean
299cdf0e10cSrcweir    On Error GoTo HandleErrors
300cdf0e10cSrcweir    Dim currentFunctionName As String
301cdf0e10cSrcweir    currentFunctionName = "SearchForFiles"
302cdf0e10cSrcweir
303cdf0e10cSrcweir    Dim WFD As WIN32_FIND_DATA
304cdf0e10cSrcweir    Dim hFile As Long
305cdf0e10cSrcweir    Dim path As String
306cdf0e10cSrcweir    Dim sFileName As String
307cdf0e10cSrcweir    Dim nTotal As Long
308cdf0e10cSrcweir
309cdf0e10cSrcweir    SearchForFiles = False
310cdf0e10cSrcweir
311cdf0e10cSrcweir    hFile = FindFirstFile(sRoot & ALL_FILES, WFD)
312cdf0e10cSrcweir
313cdf0e10cSrcweir    If hFile = INVALID_HANDLE_VALUE Then GoTo FinalExit
314cdf0e10cSrcweir
315cdf0e10cSrcweir    Do
316cdf0e10cSrcweir        If (SearchDocs.g_SD_Abort) Then GoTo FinalExit
317cdf0e10cSrcweir        sFileName = TrimNull(WFD.cFileName)
318cdf0e10cSrcweir        'if a folder, and recurse specified, call
319cdf0e10cSrcweir        'method again
320cdf0e10cSrcweir        If (WFD.dwFileAttributes And vbDirectory) Then
321cdf0e10cSrcweir            If (Asc(WFD.cFileName) <> vbDot) And bRecurse Then
322cdf0e10cSrcweir                SearchForFiles sRoot & sFileName & vbBackslash, bRecurse, bIgnoreOld, limDate
323cdf0e10cSrcweir            End If
324cdf0e10cSrcweir        Else
325cdf0e10cSrcweir            'must be a file..
326cdf0e10cSrcweir            nTotal = mDocCount + mDotCount + mXlsCount + _
327cdf0e10cSrcweir                     mXltCount + mPptCount + mPotCount
328cdf0e10cSrcweir            SearchDocs.SD_UpdateProgress str$(nTotal), sRoot
329cdf0e10cSrcweir            DoEvents
330cdf0e10cSrcweir
331cdf0e10cSrcweir            If mbDocSearch Then
332cdf0e10cSrcweir                 If MatchSpec(WFD.cFileName, "*.doc") Then
333cdf0e10cSrcweir                    path = sRoot & sFileName
334cdf0e10cSrcweir
335cdf0e10cSrcweir                    'If StrComp(path, mWordDriverPath, vbTextCompare) <> 0 Then
336cdf0e10cSrcweir                    If Not MatchSpec(path, mWordDriverPath) Then
337cdf0e10cSrcweir                        If (IsTooOld(WFD, limDate, bIgnoreOld)) Then
338cdf0e10cSrcweir                            mIgnoredDocs = mIgnoredDocs + 1
339cdf0e10cSrcweir                        Else
340cdf0e10cSrcweir                            mDocCount = mDocCount + 1
341cdf0e10cSrcweir                            mWordFilesCol.add path
342cdf0e10cSrcweir                        End If
343cdf0e10cSrcweir                    End If
344cdf0e10cSrcweir                    GoTo CONTINUE_LOOP
345cdf0e10cSrcweir                 End If
346cdf0e10cSrcweir            End If
347cdf0e10cSrcweir            If mbDotSearch Then
348cdf0e10cSrcweir                If MatchSpec(WFD.cFileName, "*.dot") Then
349cdf0e10cSrcweir                    If (IsTooOld(WFD, limDate, bIgnoreOld)) Then
350cdf0e10cSrcweir                        mIgnoredDocs = mIgnoredDocs + 1
351cdf0e10cSrcweir                    Else
352cdf0e10cSrcweir                         mDotCount = mDotCount + 1
353cdf0e10cSrcweir                        mWordFilesCol.add sRoot & sFileName
354cdf0e10cSrcweir                    End If
355cdf0e10cSrcweir                    GoTo CONTINUE_LOOP
356cdf0e10cSrcweir                End If
357cdf0e10cSrcweir            End If
358cdf0e10cSrcweir            If mbXlsSearch Then
359cdf0e10cSrcweir                 If MatchSpec(WFD.cFileName, "*.xls") Then
360cdf0e10cSrcweir                    'If StrComp(sFileName, CEXCEL_DRIVER_FILE, vbTextCompare) <> 0 Then
361cdf0e10cSrcweir                    If Not MatchSpec(WFD.cFileName, CEXCEL_DRIVER_FILE) Then
362cdf0e10cSrcweir                        If (IsTooOld(WFD, limDate, bIgnoreOld)) Then
363cdf0e10cSrcweir                            mIgnoredDocs = mIgnoredDocs + 1
364cdf0e10cSrcweir                        Else
365cdf0e10cSrcweir                            mXlsCount = mXlsCount + 1
366cdf0e10cSrcweir                            mExcelFilesCol.add sRoot & sFileName
367cdf0e10cSrcweir                        End If
368cdf0e10cSrcweir                    End If
369cdf0e10cSrcweir                    GoTo CONTINUE_LOOP
370cdf0e10cSrcweir                 End If
371cdf0e10cSrcweir            End If
372cdf0e10cSrcweir            If mbXltSearch Then
373cdf0e10cSrcweir                 If MatchSpec(WFD.cFileName, "*.xlt") Then
374cdf0e10cSrcweir                    If (IsTooOld(WFD, limDate, bIgnoreOld)) Then
375cdf0e10cSrcweir                        mIgnoredDocs = mIgnoredDocs + 1
376cdf0e10cSrcweir                    Else
377cdf0e10cSrcweir                        mXltCount = mXltCount + 1
378cdf0e10cSrcweir                        mExcelFilesCol.add sRoot & sFileName
379cdf0e10cSrcweir                    End If
380cdf0e10cSrcweir                    GoTo CONTINUE_LOOP
381cdf0e10cSrcweir                 End If
382cdf0e10cSrcweir            End If
383cdf0e10cSrcweir            If mbPptSearch Then
384cdf0e10cSrcweir                 If MatchSpec(WFD.cFileName, "*.ppt") Then
385cdf0e10cSrcweir                    path = sRoot & sFileName
386cdf0e10cSrcweir                    'If StrComp(path, mPPDriverPath, vbTextCompare) <> 0 Then
387cdf0e10cSrcweir                    If Not MatchSpec(path, mPPDriverPath) Then
388cdf0e10cSrcweir                        If (IsTooOld(WFD, limDate, bIgnoreOld)) Then
389cdf0e10cSrcweir                            mIgnoredDocs = mIgnoredDocs + 1
390cdf0e10cSrcweir                        Else
391cdf0e10cSrcweir                            mPptCount = mPptCount + 1
392cdf0e10cSrcweir                            mPPFilesCol.add path
393cdf0e10cSrcweir                        End If
394cdf0e10cSrcweir                    End If
395cdf0e10cSrcweir                    GoTo CONTINUE_LOOP
396cdf0e10cSrcweir                 End If
397cdf0e10cSrcweir            End If
398cdf0e10cSrcweir            If mbPotSearch Then
399cdf0e10cSrcweir                 If MatchSpec(WFD.cFileName, "*.pot") Then
400cdf0e10cSrcweir                    If (IsTooOld(WFD, limDate, bIgnoreOld)) Then
401cdf0e10cSrcweir                        mIgnoredDocs = mIgnoredDocs + 1
402cdf0e10cSrcweir                    Else
403cdf0e10cSrcweir                        mPotCount = mPotCount + 1
404cdf0e10cSrcweir                        mPPFilesCol.add sRoot & sFileName
405cdf0e10cSrcweir                    End If
406cdf0e10cSrcweir                    GoTo CONTINUE_LOOP
407cdf0e10cSrcweir                 End If
408cdf0e10cSrcweir            End If
409cdf0e10cSrcweir
410cdf0e10cSrcweir        End If 'If WFD.dwFileAttributes
411cdf0e10cSrcweir
412cdf0e10cSrcweirCONTINUE_LOOP:
413cdf0e10cSrcweir        fp.nSearched = fp.nSearched + 1
414cdf0e10cSrcweir
415cdf0e10cSrcweir    Loop While FindNextFile(hFile, WFD)
416cdf0e10cSrcweir
417cdf0e10cSrcweir    SearchForFiles = True
418cdf0e10cSrcweirFinalExit:
419cdf0e10cSrcweir    Call FindClose(hFile)
420cdf0e10cSrcweir    Exit Function
421cdf0e10cSrcweir
422cdf0e10cSrcweirHandleErrors:
423cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
424cdf0e10cSrcweir    Resume FinalExit
425cdf0e10cSrcweirEnd Function
426cdf0e10cSrcweir
427cdf0e10cSrcweirPrivate Function QualifyPath(sPath As String) As String
428cdf0e10cSrcweir
429cdf0e10cSrcweir   If Right$(sPath, 1) <> vbBackslash Then
430cdf0e10cSrcweir         QualifyPath = sPath & vbBackslash
431cdf0e10cSrcweir   Else: QualifyPath = sPath
432cdf0e10cSrcweir   End If
433cdf0e10cSrcweir
434cdf0e10cSrcweirEnd Function
435cdf0e10cSrcweir
436cdf0e10cSrcweirPrivate Function TrimNull(startstr As String) As String
437cdf0e10cSrcweir
438cdf0e10cSrcweir   TrimNull = Left$(startstr, lstrlen(StrPtr(startstr)))
439cdf0e10cSrcweir
440cdf0e10cSrcweirEnd Function
441cdf0e10cSrcweir
442cdf0e10cSrcweirPrivate Function MatchSpec(sFile As String, sSpec As String) As Boolean
443cdf0e10cSrcweir
444cdf0e10cSrcweir   MatchSpec = PathMatchSpec(StrPtr(sFile), StrPtr(sSpec))
445cdf0e10cSrcweir
446cdf0e10cSrcweirEnd Function
447cdf0e10cSrcweir
448cdf0e10cSrcweirPrivate Function IsTooOld(aWFD As WIN32_FIND_DATA, minDate As FILETIME, _
449cdf0e10cSrcweir                          ignoreOld As Boolean) As Boolean
450cdf0e10cSrcweir
451cdf0e10cSrcweir    IsTooOld = False
452cdf0e10cSrcweir
453cdf0e10cSrcweir    Dim aFileTime As FILETIME
454cdf0e10cSrcweir
455cdf0e10cSrcweir    If (aWFD.ftLastWriteTime.dwHighDateTime <> 0) Then
456cdf0e10cSrcweir        aFileTime = aWFD.ftLastWriteTime
457cdf0e10cSrcweir    ElseIf (aWFD.ftCreationTime.dwHighDateTime <> 0) Then
458cdf0e10cSrcweir        aFileTime = aWFD.ftCreationTime
459cdf0e10cSrcweir    Else
460cdf0e10cSrcweir        ' No valid time found, don't ignore file
461cdf0e10cSrcweir        mLessThan3 = mLessThan3 + 1
462cdf0e10cSrcweir        Exit Function
463cdf0e10cSrcweir    End If
464cdf0e10cSrcweir
465cdf0e10cSrcweir    If (ignoreOld) Then
466cdf0e10cSrcweir        If (CompareFileTime(aFileTime, minDate) < 0) Then
467cdf0e10cSrcweir            IsTooOld = True
468cdf0e10cSrcweir        End If
469cdf0e10cSrcweir    End If
470cdf0e10cSrcweir
471cdf0e10cSrcweir    If (CompareFileTime(aWFD.ftLastWriteTime, m12Months) < 0) Then
472cdf0e10cSrcweir        mMoreThan12 = mMoreThan12 + 1
473cdf0e10cSrcweir    ElseIf (CompareFileTime(aWFD.ftLastWriteTime, m6Months) < 0) Then
474cdf0e10cSrcweir        mLessThan12 = mLessThan12 + 1
475cdf0e10cSrcweir    ElseIf (CompareFileTime(aWFD.ftLastWriteTime, m3Months) < 0) Then
476cdf0e10cSrcweir        mLessThan6 = mLessThan6 + 1
477cdf0e10cSrcweir    Else
478cdf0e10cSrcweir        mLessThan3 = mLessThan3 + 1
479cdf0e10cSrcweir    End If
480cdf0e10cSrcweir
481cdf0e10cSrcweirEnd Function
482cdf0e10cSrcweir
483cdf0e10cSrcweirPrivate Function BasicDateToFileTime(basDate As Date, _
484cdf0e10cSrcweir                                     fileDate As FILETIME) As Boolean
485cdf0e10cSrcweir
486cdf0e10cSrcweir    Dim sysDate As SYSTEMTIME
487cdf0e10cSrcweir    Dim retval As Long
488cdf0e10cSrcweir
489cdf0e10cSrcweir    sysDate.wYear = DatePart("yyyy", basDate)
490cdf0e10cSrcweir    sysDate.wMonth = DatePart("m", basDate)
491cdf0e10cSrcweir    sysDate.wDay = DatePart("d", basDate)
492cdf0e10cSrcweir    sysDate.wHour = DatePart("h", basDate)
493cdf0e10cSrcweir    sysDate.wMinute = DatePart("m", basDate)
494cdf0e10cSrcweir    retval = SystemTimeToFileTime(sysDate, fileDate)
495cdf0e10cSrcweir    If (retval = 0) Then
496cdf0e10cSrcweir        BasicDateToFileTime = False
497cdf0e10cSrcweir    Else
498cdf0e10cSrcweir        BasicDateToFileTime = True
499cdf0e10cSrcweir    End If
500cdf0e10cSrcweirEnd Function
501cdf0e10cSrcweir
502cdf0e10cSrcweirPrivate Function InitFileTimes() As Boolean
503cdf0e10cSrcweir
504cdf0e10cSrcweir    Dim nowDate As Date
505cdf0e10cSrcweir    Dim basDate As Date
506cdf0e10cSrcweir
507cdf0e10cSrcweir    InitFileTimes = True
508cdf0e10cSrcweir
509cdf0e10cSrcweir    nowDate = Now()
510cdf0e10cSrcweir    basDate = DateAdd("m", -3, nowDate)
511cdf0e10cSrcweir    If Not BasicDateToFileTime(basDate, m3Months) Then InitFileTimes = False
512cdf0e10cSrcweir
513cdf0e10cSrcweir    basDate = DateAdd("m", -6, nowDate)
514cdf0e10cSrcweir    If Not BasicDateToFileTime(basDate, m6Months) Then InitFileTimes = False
515cdf0e10cSrcweir
516cdf0e10cSrcweir    basDate = DateAdd("yyyy", -1, nowDate)
517cdf0e10cSrcweir    If Not BasicDateToFileTime(basDate, m12Months) Then InitFileTimes = False
518cdf0e10cSrcweir
519cdf0e10cSrcweir    mMoreThan12 = 0
520cdf0e10cSrcweir    mLessThan12 = 0
521cdf0e10cSrcweir    mLessThan6 = 0
522cdf0e10cSrcweir    mLessThan3 = 0
523cdf0e10cSrcweir
524cdf0e10cSrcweirEnd Function
525