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