xref: /AOO41X/main/migrationanalysis/src/wizard/Analyse.bas (revision cdf0e10c4e3984b49a9502b011690b615761d4a3)
1*cdf0e10cSrcweirAttribute VB_Name = "Analyse"
2*cdf0e10cSrcweir'/*************************************************************************
3*cdf0e10cSrcweir' *
4*cdf0e10cSrcweir' DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
5*cdf0e10cSrcweir'
6*cdf0e10cSrcweir' Copyright 2000, 2010 Oracle and/or its affiliates.
7*cdf0e10cSrcweir'
8*cdf0e10cSrcweir' OpenOffice.org - a multi-platform office productivity suite
9*cdf0e10cSrcweir'
10*cdf0e10cSrcweir' This file is part of OpenOffice.org.
11*cdf0e10cSrcweir'
12*cdf0e10cSrcweir' OpenOffice.org is free software: you can redistribute it and/or modify
13*cdf0e10cSrcweir' it under the terms of the GNU Lesser General Public License version 3
14*cdf0e10cSrcweir' only, as published by the Free Software Foundation.
15*cdf0e10cSrcweir'
16*cdf0e10cSrcweir' OpenOffice.org is distributed in the hope that it will be useful,
17*cdf0e10cSrcweir' but WITHOUT ANY WARRANTY; without even the implied warranty of
18*cdf0e10cSrcweir' MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
19*cdf0e10cSrcweir' GNU Lesser General Public License version 3 for more details
20*cdf0e10cSrcweir' (a copy is included in the LICENSE file that accompanied this code).
21*cdf0e10cSrcweir'
22*cdf0e10cSrcweir' You should have received a copy of the GNU Lesser General Public License
23*cdf0e10cSrcweir' version 3 along with OpenOffice.org.  If not, see
24*cdf0e10cSrcweir' <http://www.openoffice.org/license.html>
25*cdf0e10cSrcweir' for a copy of the LGPLv3 License.
26*cdf0e10cSrcweir'
27*cdf0e10cSrcweir' ************************************************************************/
28*cdf0e10cSrcweir
29*cdf0e10cSrcweirOption Explicit
30*cdf0e10cSrcweir
31*cdf0e10cSrcweirPrivate Const C_STAT_NOT_STARTED    As Integer = 1
32*cdf0e10cSrcweirPrivate Const C_STAT_RETRY          As Integer = 2
33*cdf0e10cSrcweirPrivate Const C_STAT_ERROR          As Integer = 3
34*cdf0e10cSrcweirPrivate Const C_STAT_DONE           As Integer = 4
35*cdf0e10cSrcweirPrivate Const C_STAT_ABORTED        As Integer = 5
36*cdf0e10cSrcweir
37*cdf0e10cSrcweirPrivate Const C_MAX_RETRIES         As Integer = 5
38*cdf0e10cSrcweirPrivate Const C_ABORT_TIMEOUT       As Integer = 30
39*cdf0e10cSrcweir
40*cdf0e10cSrcweirPrivate Const MAX_WAIT_TIME     As Long = 600
41*cdf0e10cSrcweir
42*cdf0e10cSrcweirPrivate Const C_STAT_FINISHED   As String = "finished"
43*cdf0e10cSrcweirPrivate Const C_STAT_ANALYSED   As String = "analysed="
44*cdf0e10cSrcweirPrivate Const C_STAT_ANALYSING  As String = "analysing="
45*cdf0e10cSrcweirPrivate Const CSINGLE_FILE      As String = "singlefile"
46*cdf0e10cSrcweirPrivate Const CFILE_LIST        As String = "filelist"
47*cdf0e10cSrcweirPrivate Const CSTAT_FILE        As String = "statfilename"
48*cdf0e10cSrcweirPrivate Const CLAST_CHECKPOINT  As String = "LastCheckpoint"
49*cdf0e10cSrcweirPrivate Const CNEXT_FILE        As String = "NextFile"
50*cdf0e10cSrcweirPrivate Const C_ABORT_ANALYSIS  As String = "AbortAnalysis"
51*cdf0e10cSrcweir
52*cdf0e10cSrcweirPrivate Const CAPPNAME_WORD         As String = "word"
53*cdf0e10cSrcweirPrivate Const CAPPNAME_EXCEL        As String = "excel"
54*cdf0e10cSrcweirPrivate Const CAPPNAME_POWERPOINT   As String = "powerpoint"
55*cdf0e10cSrcweirPrivate Const C_EXENAME_WORD        As String = "winword.exe"
56*cdf0e10cSrcweirPrivate Const C_EXENAME_EXCEL       As String = "excel.exe"
57*cdf0e10cSrcweirPrivate Const C_EXENAME_POWERPOINT  As String = "powerpnt.exe"
58*cdf0e10cSrcweir
59*cdf0e10cSrcweirConst CNEW_RESULTS_FILE = "newresultsfile"
60*cdf0e10cSrcweirConst C_LAUNCH_DRIVER = ".\resources\LaunchDrivers.exe"
61*cdf0e10cSrcweir
62*cdf0e10cSrcweir'from http://support.microsoft.com/kb/q129796
63*cdf0e10cSrcweir
64*cdf0e10cSrcweirPrivate Type STARTUPINFO
65*cdf0e10cSrcweir    cb As Long
66*cdf0e10cSrcweir    lpReserved As String
67*cdf0e10cSrcweir    lpDesktop As String
68*cdf0e10cSrcweir    lpTitle As String
69*cdf0e10cSrcweir    dwX As Long
70*cdf0e10cSrcweir    dwY As Long
71*cdf0e10cSrcweir    dwXSize As Long
72*cdf0e10cSrcweir    dwYSize As Long
73*cdf0e10cSrcweir    dwXCountChars As Long
74*cdf0e10cSrcweir    dwYCountChars As Long
75*cdf0e10cSrcweir    dwFillAttribute As Long
76*cdf0e10cSrcweir    dwFlags As Long
77*cdf0e10cSrcweir    wShowWindow As Integer
78*cdf0e10cSrcweir    cbReserved2 As Integer
79*cdf0e10cSrcweir    lpReserved2 As Long
80*cdf0e10cSrcweir    hStdInput As Long
81*cdf0e10cSrcweir    hStdOutput As Long
82*cdf0e10cSrcweir    hStdError As Long
83*cdf0e10cSrcweirEnd Type
84*cdf0e10cSrcweir
85*cdf0e10cSrcweirPrivate Type PROCESS_INFORMATION
86*cdf0e10cSrcweir    hProcess As Long
87*cdf0e10cSrcweir    hThread As Long
88*cdf0e10cSrcweir    dwProcessID As Long
89*cdf0e10cSrcweir    dwThreadID As Long
90*cdf0e10cSrcweirEnd Type
91*cdf0e10cSrcweir
92*cdf0e10cSrcweirPrivate Declare Function WaitForSingleObject Lib "kernel32" (ByVal _
93*cdf0e10cSrcweir    hHandle As Long, ByVal dwMilliseconds As Long) As Long
94*cdf0e10cSrcweir
95*cdf0e10cSrcweirPrivate Declare Function CreateProcessA Lib "kernel32" (ByVal _
96*cdf0e10cSrcweir    lpApplicationName As String, ByVal lpCommandLine As String, ByVal _
97*cdf0e10cSrcweir    lpProcessAttributes As Long, ByVal lpThreadAttributes As Long, _
98*cdf0e10cSrcweir    ByVal bInheritHandles As Long, ByVal dwCreationFlags As Long, _
99*cdf0e10cSrcweir    ByVal lpEnvironment As Long, ByVal lpCurrentDirectory As String, _
100*cdf0e10cSrcweir    lpStartupInfo As STARTUPINFO, lpProcessInformation As _
101*cdf0e10cSrcweir    PROCESS_INFORMATION) As Long
102*cdf0e10cSrcweir
103*cdf0e10cSrcweirPrivate Declare Function CloseHandle Lib "kernel32" _
104*cdf0e10cSrcweir    (ByVal hObject As Long) As Long
105*cdf0e10cSrcweir
106*cdf0e10cSrcweirPrivate Declare Function GetExitCodeProcess Lib "kernel32" _
107*cdf0e10cSrcweir    (ByVal hProcess As Long, lpExitCode As Long) As Long
108*cdf0e10cSrcweir
109*cdf0e10cSrcweirPrivate Declare Function TerminateProcess Lib "kernel32" (ByVal hProcess As Long, _
110*cdf0e10cSrcweir        ByVal uExitCode As Long) As Long
111*cdf0e10cSrcweir
112*cdf0e10cSrcweirPrivate Const NORMAL_PRIORITY_CLASS = &H20&
113*cdf0e10cSrcweirPrivate Const WAIT_TIMEOUT  As Long = &H102
114*cdf0e10cSrcweirPrivate Const ABORTED       As Long = -2
115*cdf0e10cSrcweir
116*cdf0e10cSrcweir' from http://vbnet.mvps.org/index.html?code/system/toolhelpprocesses.htm
117*cdf0e10cSrcweirPublic Const TH32CS_SNAPPROCESS As Long = 2&
118*cdf0e10cSrcweirPublic Const MAX_PATH As Long = 260
119*cdf0e10cSrcweir
120*cdf0e10cSrcweirPublic Type PROCESSENTRY32
121*cdf0e10cSrcweir    dwSize As Long
122*cdf0e10cSrcweir    cntUsage As Long
123*cdf0e10cSrcweir    th32ProcessID As Long
124*cdf0e10cSrcweir    th32DefaultHeapID As Long
125*cdf0e10cSrcweir    th32ModuleID As Long
126*cdf0e10cSrcweir    cntThreads As Long
127*cdf0e10cSrcweir    th32ParentProcessID As Long
128*cdf0e10cSrcweir    pcPriClassBase As Long
129*cdf0e10cSrcweir    dwFlags As Long
130*cdf0e10cSrcweir    szExeFile As String * MAX_PATH
131*cdf0e10cSrcweirEnd Type
132*cdf0e10cSrcweir
133*cdf0e10cSrcweirPublic Declare Function CreateToolhelp32Snapshot Lib "kernel32" _
134*cdf0e10cSrcweir   (ByVal lFlags As Long, ByVal lProcessID As Long) As Long
135*cdf0e10cSrcweir
136*cdf0e10cSrcweirPublic Declare Function ProcessFirst Lib "kernel32" _
137*cdf0e10cSrcweir    Alias "Process32First" _
138*cdf0e10cSrcweir   (ByVal hSnapShot As Long, uProcess As PROCESSENTRY32) As Long
139*cdf0e10cSrcweir
140*cdf0e10cSrcweirPublic Declare Function ProcessNext Lib "kernel32" _
141*cdf0e10cSrcweir    Alias "Process32Next" _
142*cdf0e10cSrcweir   (ByVal hSnapShot As Long, uProcess As PROCESSENTRY32) As Long
143*cdf0e10cSrcweir
144*cdf0e10cSrcweir
145*cdf0e10cSrcweirPublic Function IsOfficeAppRunning(curApplication As String) As Boolean
146*cdf0e10cSrcweir'DV: we need some error handling here
147*cdf0e10cSrcweir    Dim hSnapShot As Long
148*cdf0e10cSrcweir    Dim uProcess As PROCESSENTRY32
149*cdf0e10cSrcweir    Dim success As Long
150*cdf0e10cSrcweir    Dim bRet As Boolean
151*cdf0e10cSrcweir    Dim bAppFound As Boolean
152*cdf0e10cSrcweir    Dim exeName As String
153*cdf0e10cSrcweir    Dim curExeName As String
154*cdf0e10cSrcweir
155*cdf0e10cSrcweir    bRet = True
156*cdf0e10cSrcweir    On Error GoTo FinalExit
157*cdf0e10cSrcweir
158*cdf0e10cSrcweir    curExeName = LCase$(curApplication)
159*cdf0e10cSrcweir
160*cdf0e10cSrcweir    If (curExeName = CAPPNAME_WORD) Then
161*cdf0e10cSrcweir        exeName = C_EXENAME_WORD
162*cdf0e10cSrcweir    ElseIf (curExeName = CAPPNAME_EXCEL) Then
163*cdf0e10cSrcweir        exeName = C_EXENAME_EXCEL
164*cdf0e10cSrcweir    ElseIf (curExeName = CAPPNAME_POWERPOINT) Then
165*cdf0e10cSrcweir        exeName = C_EXENAME_POWERPOINT
166*cdf0e10cSrcweir    Else
167*cdf0e10cSrcweir        GoTo FinalExit
168*cdf0e10cSrcweir    End If
169*cdf0e10cSrcweir
170*cdf0e10cSrcweir    hSnapShot = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0&)
171*cdf0e10cSrcweir
172*cdf0e10cSrcweir    If hSnapShot = -1 Then GoTo FinalExit
173*cdf0e10cSrcweir
174*cdf0e10cSrcweir    uProcess.dwSize = Len(uProcess)
175*cdf0e10cSrcweir    success = ProcessFirst(hSnapShot, uProcess)
176*cdf0e10cSrcweir    bAppFound = False
177*cdf0e10cSrcweir
178*cdf0e10cSrcweir    While ((success = 1) And Not bAppFound)
179*cdf0e10cSrcweir        Dim i As Long
180*cdf0e10cSrcweir        i = InStr(1, uProcess.szExeFile, Chr(0))
181*cdf0e10cSrcweir        curExeName = LCase$(Left$(uProcess.szExeFile, i - 1))
182*cdf0e10cSrcweir        If (curExeName = exeName) Then
183*cdf0e10cSrcweir            bAppFound = True
184*cdf0e10cSrcweir        Else
185*cdf0e10cSrcweir            success = ProcessNext(hSnapShot, uProcess)
186*cdf0e10cSrcweir        End If
187*cdf0e10cSrcweir    Wend
188*cdf0e10cSrcweir    bRet = bAppFound
189*cdf0e10cSrcweir
190*cdf0e10cSrcweir    Call CloseHandle(hSnapShot)
191*cdf0e10cSrcweir
192*cdf0e10cSrcweirFinalExit:
193*cdf0e10cSrcweir    IsOfficeAppRunning = bRet
194*cdf0e10cSrcweir
195*cdf0e10cSrcweirEnd Function
196*cdf0e10cSrcweir
197*cdf0e10cSrcweirPrivate Sub CalculateProgress(statusFileName As String, fso As FileSystemObject, _
198*cdf0e10cSrcweir                              lastIndex As Long, docOffset As Long, _
199*cdf0e10cSrcweir                              myDocList As Collection)
200*cdf0e10cSrcweir
201*cdf0e10cSrcweir    On Error GoTo FinalExit
202*cdf0e10cSrcweir
203*cdf0e10cSrcweir    Dim curFile As String
204*cdf0e10cSrcweir    Dim fileCont As TextStream
205*cdf0e10cSrcweir    Dim myFile As file
206*cdf0e10cSrcweir
207*cdf0e10cSrcweir    If (fso.FileExists(statusFileName)) Then
208*cdf0e10cSrcweir        Dim statLine As String
209*cdf0e10cSrcweir
210*cdf0e10cSrcweir        Set fileCont = fso.OpenTextFile(statusFileName, ForReading, False, TristateTrue)
211*cdf0e10cSrcweir        statLine = fileCont.ReadLine
212*cdf0e10cSrcweir
213*cdf0e10cSrcweir        If (Left(statLine, Len(C_STAT_ANALYSED)) = C_STAT_ANALYSED) Then
214*cdf0e10cSrcweir            curFile = Mid(statLine, Len(C_STAT_ANALYSED) + 1)
215*cdf0e10cSrcweir        ElseIf (Left(statLine, Len(C_STAT_ANALYSING)) = C_STAT_ANALYSING) Then
216*cdf0e10cSrcweir            curFile = Mid(statLine, Len(C_STAT_ANALYSING) + 1)
217*cdf0e10cSrcweir        End If
218*cdf0e10cSrcweir    End If
219*cdf0e10cSrcweir
220*cdf0e10cSrcweir    ' when we don't have a file, we will show the name of the last used file in
221*cdf0e10cSrcweir    ' the progress window
222*cdf0e10cSrcweir    If (curFile = "") Then curFile = myDocList.item(lastIndex)
223*cdf0e10cSrcweir
224*cdf0e10cSrcweir    If (GetDocumentIndex(curFile, myDocList, lastIndex)) Then
225*cdf0e10cSrcweir        Set myFile = fso.GetFile(curFile)
226*cdf0e10cSrcweir        Call ShowProgress.SP_UpdateProgress(myFile.Name, myFile.ParentFolder.path, lastIndex + docOffset)
227*cdf0e10cSrcweir    End If
228*cdf0e10cSrcweir
229*cdf0e10cSrcweirFinalExit:
230*cdf0e10cSrcweir    If Not (fileCont Is Nothing) Then fileCont.Close
231*cdf0e10cSrcweir    Set fileCont = Nothing
232*cdf0e10cSrcweir    Set myFile = Nothing
233*cdf0e10cSrcweir
234*cdf0e10cSrcweirEnd Sub
235*cdf0e10cSrcweir
236*cdf0e10cSrcweirFunction CheckAliveStatus(statFileName As String, _
237*cdf0e10cSrcweir                          curApplication As String, _
238*cdf0e10cSrcweir                          lastDate As Date, _
239*cdf0e10cSrcweir                          fso As FileSystemObject) As Boolean
240*cdf0e10cSrcweir
241*cdf0e10cSrcweir    Dim isAlive As Boolean
242*cdf0e10cSrcweir    Dim currDate As Date
243*cdf0e10cSrcweir    Dim statFile As file
244*cdf0e10cSrcweir    Dim testing As Long
245*cdf0e10cSrcweir
246*cdf0e10cSrcweir    isAlive = False
247*cdf0e10cSrcweir
248*cdf0e10cSrcweir    If Not fso.FileExists(statFileName) Then
249*cdf0e10cSrcweir        currDate = Now()
250*cdf0e10cSrcweir        If (val(DateDiff("s", lastDate, currDate)) > MAX_WAIT_TIME) Then
251*cdf0e10cSrcweir            isAlive = False
252*cdf0e10cSrcweir        Else
253*cdf0e10cSrcweir            isAlive = True
254*cdf0e10cSrcweir        End If
255*cdf0e10cSrcweir    Else
256*cdf0e10cSrcweir        Set statFile = fso.GetFile(statFileName)
257*cdf0e10cSrcweir        currDate = statFile.DateLastModified
258*cdf0e10cSrcweir        If (currDate > lastDate) Then
259*cdf0e10cSrcweir            lastDate = currDate
260*cdf0e10cSrcweir            isAlive = True
261*cdf0e10cSrcweir        Else
262*cdf0e10cSrcweir            currDate = Now()
263*cdf0e10cSrcweir            If (lastDate >= currDate) Then   ' There might be some inaccuracies in file and system dates
264*cdf0e10cSrcweir                isAlive = True
265*cdf0e10cSrcweir            ElseIf (val(DateDiff("s", lastDate, currDate)) > MAX_WAIT_TIME) Then
266*cdf0e10cSrcweir                isAlive = False
267*cdf0e10cSrcweir            Else
268*cdf0e10cSrcweir                isAlive = IsOfficeAppRunning(curApplication)
269*cdf0e10cSrcweir            End If
270*cdf0e10cSrcweir        End If
271*cdf0e10cSrcweir    End If
272*cdf0e10cSrcweir
273*cdf0e10cSrcweir    CheckAliveStatus = isAlive
274*cdf0e10cSrcweirEnd Function
275*cdf0e10cSrcweir
276*cdf0e10cSrcweirSub TerminateOfficeApps(fso As FileSystemObject, aParameter As String)
277*cdf0e10cSrcweir
278*cdf0e10cSrcweir    Dim msoKillFileName As String
279*cdf0e10cSrcweir
280*cdf0e10cSrcweir    msoKillFileName = fso.GetAbsolutePathName(".\resources\msokill.exe")
281*cdf0e10cSrcweir    If fso.FileExists(msoKillFileName) Then
282*cdf0e10cSrcweir        Shell msoKillFileName & aParameter
283*cdf0e10cSrcweir    Else
284*cdf0e10cSrcweir    End If
285*cdf0e10cSrcweirEnd Sub
286*cdf0e10cSrcweir
287*cdf0e10cSrcweirPublic Function launchDriver(statFileName As String, cmdLine As String, _
288*cdf0e10cSrcweir                             curApplication As String, fso As FileSystemObject, _
289*cdf0e10cSrcweir                             myDocList As Collection, myOffset As Long, _
290*cdf0e10cSrcweir                             myIniFilePath As String) As Long
291*cdf0e10cSrcweir
292*cdf0e10cSrcweir    Dim proc As PROCESS_INFORMATION
293*cdf0e10cSrcweir    Dim start As STARTUPINFO
294*cdf0e10cSrcweir    Dim ret As Long
295*cdf0e10cSrcweir    Dim currDate As Date
296*cdf0e10cSrcweir    Dim lastIndex As Long
297*cdf0e10cSrcweir
298*cdf0e10cSrcweir    currDate = Now()
299*cdf0e10cSrcweir    lastIndex = 1
300*cdf0e10cSrcweir
301*cdf0e10cSrcweir    ' Initialize the STARTUPINFO structure:
302*cdf0e10cSrcweir    start.cb = Len(start)
303*cdf0e10cSrcweir
304*cdf0e10cSrcweir    ' Start the shelled application:
305*cdf0e10cSrcweir    ret = CreateProcessA(vbNullString, cmdLine$, 0&, 0&, 1&, _
306*cdf0e10cSrcweir                         NORMAL_PRIORITY_CLASS, 0&, vbNullString, start, proc)
307*cdf0e10cSrcweir
308*cdf0e10cSrcweir    ' Wait for the shelled application to finish:
309*cdf0e10cSrcweir    Do
310*cdf0e10cSrcweir        ret = WaitForSingleObject(proc.hProcess, 100)
311*cdf0e10cSrcweir        If ret <> WAIT_TIMEOUT Then
312*cdf0e10cSrcweir            Exit Do
313*cdf0e10cSrcweir        End If
314*cdf0e10cSrcweir        If Not CheckAliveStatus(statFileName, curApplication, currDate, fso) Then
315*cdf0e10cSrcweir            ' Try to close open office dialogs and then wait a little bit
316*cdf0e10cSrcweir            TerminateOfficeApps fso, " --close"
317*cdf0e10cSrcweir            ret = WaitForSingleObject(proc.hProcess, 1000)
318*cdf0e10cSrcweir
319*cdf0e10cSrcweir            ' next try to kill all office programs and then wait a little bit
320*cdf0e10cSrcweir            TerminateOfficeApps fso, " --kill"
321*cdf0e10cSrcweir            ret = WaitForSingleObject(proc.hProcess, 1000)
322*cdf0e10cSrcweir
323*cdf0e10cSrcweir            ret = TerminateProcess(proc.hProcess, "0")
324*cdf0e10cSrcweir            ret = WAIT_TIMEOUT
325*cdf0e10cSrcweir            Exit Do
326*cdf0e10cSrcweir        End If
327*cdf0e10cSrcweir        If (ShowProgress.g_SP_Abort) Then
328*cdf0e10cSrcweir            WriteToLog C_ABORT_ANALYSIS, True, myIniFilePath
329*cdf0e10cSrcweir            Call HandleAbort(proc.hProcess, curApplication)
330*cdf0e10cSrcweir            ret = ABORTED
331*cdf0e10cSrcweir            Exit Do
332*cdf0e10cSrcweir        End If
333*cdf0e10cSrcweir        Call CalculateProgress(statFileName, fso, lastIndex, myOffset, myDocList)
334*cdf0e10cSrcweir        DoEvents                                'allow other processes
335*cdf0e10cSrcweir    Loop While True
336*cdf0e10cSrcweir
337*cdf0e10cSrcweir    If (ret <> WAIT_TIMEOUT) And (ret <> ABORTED) Then
338*cdf0e10cSrcweir        Call GetExitCodeProcess(proc.hProcess, ret&)
339*cdf0e10cSrcweir    End If
340*cdf0e10cSrcweir    Call CloseHandle(proc.hThread)
341*cdf0e10cSrcweir    Call CloseHandle(proc.hProcess)
342*cdf0e10cSrcweir    launchDriver = ret
343*cdf0e10cSrcweirEnd Function
344*cdf0e10cSrcweir
345*cdf0e10cSrcweirFunction CheckAnalyseStatus(statusFileName As String, _
346*cdf0e10cSrcweir                            lastFile As String, _
347*cdf0e10cSrcweir                            fso As FileSystemObject) As Integer
348*cdf0e10cSrcweir
349*cdf0e10cSrcweir    Dim currStatus As Integer
350*cdf0e10cSrcweir    Dim fileCont As TextStream
351*cdf0e10cSrcweir
352*cdf0e10cSrcweir    If Not fso.FileExists(statusFileName) Then
353*cdf0e10cSrcweir        currStatus = C_STAT_NOT_STARTED
354*cdf0e10cSrcweir    Else
355*cdf0e10cSrcweir        Dim statText As String
356*cdf0e10cSrcweir        Set fileCont = fso.OpenTextFile(statusFileName, ForReading, False, TristateTrue)
357*cdf0e10cSrcweir        statText = fileCont.ReadLine
358*cdf0e10cSrcweir        If (statText = C_STAT_FINISHED) Then
359*cdf0e10cSrcweir            currStatus = C_STAT_DONE
360*cdf0e10cSrcweir        ElseIf (Left(statText, Len(C_STAT_ANALYSED)) = C_STAT_ANALYSED) Then
361*cdf0e10cSrcweir            currStatus = C_STAT_RETRY
362*cdf0e10cSrcweir            lastFile = Mid(statText, Len(C_STAT_ANALYSED) + 1)
363*cdf0e10cSrcweir        ElseIf (Left(statText, Len(C_STAT_ANALYSING)) = C_STAT_ANALYSING) Then
364*cdf0e10cSrcweir            currStatus = C_STAT_RETRY
365*cdf0e10cSrcweir            lastFile = Mid(statText, Len(C_STAT_ANALYSING) + 1)
366*cdf0e10cSrcweir        Else
367*cdf0e10cSrcweir            currStatus = C_STAT_ERROR
368*cdf0e10cSrcweir        End If
369*cdf0e10cSrcweir        fileCont.Close
370*cdf0e10cSrcweir    End If
371*cdf0e10cSrcweir
372*cdf0e10cSrcweir    CheckAnalyseStatus = currStatus
373*cdf0e10cSrcweirEnd Function
374*cdf0e10cSrcweir
375*cdf0e10cSrcweirFunction WriteDocsToAnalyze(myDocList As Collection, myApp As String, _
376*cdf0e10cSrcweir                            fso As FileSystemObject) As String
377*cdf0e10cSrcweir    On Error GoTo HandleErrors
378*cdf0e10cSrcweir    Dim currentFunctionName As String
379*cdf0e10cSrcweir    currentFunctionName = "WriteDocsToAnalyze"
380*cdf0e10cSrcweir
381*cdf0e10cSrcweir    Dim TempPath As String
382*cdf0e10cSrcweir    Dim fileName As String
383*cdf0e10cSrcweir    Dim fileContent As TextStream
384*cdf0e10cSrcweir
385*cdf0e10cSrcweir    fileName = ""
386*cdf0e10cSrcweir    TempPath = fso.GetSpecialFolder(TemporaryFolder).path
387*cdf0e10cSrcweir
388*cdf0e10cSrcweir    If (TempPath = "") Then
389*cdf0e10cSrcweir        TempPath = "."
390*cdf0e10cSrcweir    End If
391*cdf0e10cSrcweir
392*cdf0e10cSrcweir    Dim vFileName As Variant
393*cdf0e10cSrcweir    Dim Index As Long
394*cdf0e10cSrcweir    Dim limit As Long
395*cdf0e10cSrcweir
396*cdf0e10cSrcweir    limit = myDocList.count
397*cdf0e10cSrcweir    If (limit > 0) Then
398*cdf0e10cSrcweir        fileName = fso.GetAbsolutePathName(TempPath & "\FileList" & myApp & ".txt")
399*cdf0e10cSrcweir        Set fileContent = fso.OpenTextFile(fileName, ForWriting, True, TristateTrue)
400*cdf0e10cSrcweir
401*cdf0e10cSrcweir        For Index = 1 To limit
402*cdf0e10cSrcweir            vFileName = myDocList(Index)
403*cdf0e10cSrcweir            fileContent.WriteLine (vFileName)
404*cdf0e10cSrcweir        Next
405*cdf0e10cSrcweir
406*cdf0e10cSrcweir        fileContent.Close
407*cdf0e10cSrcweir    End If
408*cdf0e10cSrcweir
409*cdf0e10cSrcweirFinalExit:
410*cdf0e10cSrcweir    Set fileContent = Nothing
411*cdf0e10cSrcweir    WriteDocsToAnalyze = fileName
412*cdf0e10cSrcweir    Exit Function
413*cdf0e10cSrcweir
414*cdf0e10cSrcweirHandleErrors:
415*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
416*cdf0e10cSrcweir    Resume FinalExit
417*cdf0e10cSrcweirEnd Function
418*cdf0e10cSrcweir
419*cdf0e10cSrcweir' This function looks for the given document name in the document collection
420*cdf0e10cSrcweir' and returns TRUE and the position of the document in that collection if found,
421*cdf0e10cSrcweir' FALSE otherwise
422*cdf0e10cSrcweirFunction GetDocumentIndex(myDocument As String, _
423*cdf0e10cSrcweir                          myDocList As Collection, _
424*cdf0e10cSrcweir                          lastIndex As Long) As Boolean
425*cdf0e10cSrcweir
426*cdf0e10cSrcweir    Dim currentFunctionName As String
427*cdf0e10cSrcweir    currentFunctionName = "GetDocumentIndex"
428*cdf0e10cSrcweir
429*cdf0e10cSrcweir    On Error GoTo HandleErrors
430*cdf0e10cSrcweir
431*cdf0e10cSrcweir    Dim lastEntry As Long
432*cdf0e10cSrcweir    Dim curIndex As Long
433*cdf0e10cSrcweir    Dim curEntry As String
434*cdf0e10cSrcweir    Dim entryFound As Boolean
435*cdf0e10cSrcweir
436*cdf0e10cSrcweir    entryFound = False
437*cdf0e10cSrcweir    lastEntry = myDocList.count
438*cdf0e10cSrcweir    curIndex = lastIndex
439*cdf0e10cSrcweir
440*cdf0e10cSrcweir    ' We start the search at the position of the last found
441*cdf0e10cSrcweir    ' document
442*cdf0e10cSrcweir    While Not entryFound And curIndex <= lastEntry
443*cdf0e10cSrcweir        curEntry = myDocList.item(curIndex)
444*cdf0e10cSrcweir        If (curEntry = myDocument) Then
445*cdf0e10cSrcweir            lastIndex = curIndex
446*cdf0e10cSrcweir            entryFound = True
447*cdf0e10cSrcweir        Else
448*cdf0e10cSrcweir            curIndex = curIndex + 1
449*cdf0e10cSrcweir        End If
450*cdf0e10cSrcweir    Wend
451*cdf0e10cSrcweir
452*cdf0e10cSrcweir    ' When we could not find the document, we start the search
453*cdf0e10cSrcweir    ' from the beginning of the list
454*cdf0e10cSrcweir    If Not entryFound Then
455*cdf0e10cSrcweir        curIndex = 1
456*cdf0e10cSrcweir        While Not entryFound And curIndex <= lastIndex
457*cdf0e10cSrcweir            curEntry = myDocList.item(curIndex)
458*cdf0e10cSrcweir            If (curEntry = myDocument) Then
459*cdf0e10cSrcweir                lastIndex = curIndex
460*cdf0e10cSrcweir                entryFound = True
461*cdf0e10cSrcweir            Else
462*cdf0e10cSrcweir                curIndex = curIndex + 1
463*cdf0e10cSrcweir            End If
464*cdf0e10cSrcweir        Wend
465*cdf0e10cSrcweir    End If
466*cdf0e10cSrcweir
467*cdf0e10cSrcweirFinalExit:
468*cdf0e10cSrcweir    GetDocumentIndex = entryFound
469*cdf0e10cSrcweir    Exit Function
470*cdf0e10cSrcweirHandleErrors:
471*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
472*cdf0e10cSrcweir    Resume FinalExit
473*cdf0e10cSrcweirEnd Function
474*cdf0e10cSrcweir
475*cdf0e10cSrcweirFunction AnalyseList(myDocList As Collection, _
476*cdf0e10cSrcweir                     myApp As String, _
477*cdf0e10cSrcweir                     myIniFilePath As String, _
478*cdf0e10cSrcweir                     myOffset As Long, _
479*cdf0e10cSrcweir                     analysisAborted As Boolean) As Boolean
480*cdf0e10cSrcweir
481*cdf0e10cSrcweir    On Error GoTo HandleErrors
482*cdf0e10cSrcweir    Dim currentFunctionName As String
483*cdf0e10cSrcweir    currentFunctionName = "AnalyseList"
484*cdf0e10cSrcweir
485*cdf0e10cSrcweir    Dim cmdLine As String
486*cdf0e10cSrcweir    Dim filelist As String
487*cdf0e10cSrcweir    Dim statFileName As String
488*cdf0e10cSrcweir    Dim finished As Boolean
489*cdf0e10cSrcweir    Dim analyseStatus As Integer
490*cdf0e10cSrcweir    Dim nRetries As Integer
491*cdf0e10cSrcweir    Dim lastFile As String
492*cdf0e10cSrcweir    Dim lastHandledFile As String
493*cdf0e10cSrcweir    Dim launchStatus As Long
494*cdf0e10cSrcweir    Dim fso As New FileSystemObject
495*cdf0e10cSrcweir    Dim progressTitle As String
496*cdf0e10cSrcweir
497*cdf0e10cSrcweir    filelist = WriteDocsToAnalyze(myDocList, myApp, fso)
498*cdf0e10cSrcweir    cmdLine = fso.GetAbsolutePathName(C_LAUNCH_DRIVER) & " " & myApp
499*cdf0e10cSrcweir    finished = False
500*cdf0e10cSrcweir
501*cdf0e10cSrcweir    Dim TempPath As String
502*cdf0e10cSrcweir    TempPath = fso.GetSpecialFolder(TemporaryFolder).path
503*cdf0e10cSrcweir    If (TempPath = "") Then TempPath = "."
504*cdf0e10cSrcweir    statFileName = fso.GetAbsolutePathName(TempPath & "\StatFile" & myApp & ".txt")
505*cdf0e10cSrcweir    If (fso.FileExists(statFileName)) Then fso.DeleteFile (statFileName)
506*cdf0e10cSrcweir
507*cdf0e10cSrcweir    WriteToLog CFILE_LIST, filelist, myIniFilePath
508*cdf0e10cSrcweir    WriteToLog CSTAT_FILE, statFileName, myIniFilePath
509*cdf0e10cSrcweir    WriteToLog CLAST_CHECKPOINT, "", myIniFilePath
510*cdf0e10cSrcweir    WriteToLog CNEXT_FILE, "", myIniFilePath
511*cdf0e10cSrcweir    WriteToLog C_ABORT_ANALYSIS, "", myIniFilePath
512*cdf0e10cSrcweir
513*cdf0e10cSrcweir    ' In this loop we will restart the driver until we have finished the analysis
514*cdf0e10cSrcweir    nRetries = 0
515*cdf0e10cSrcweir    While Not finished And nRetries < C_MAX_RETRIES
516*cdf0e10cSrcweir        launchStatus = launchDriver(statFileName, cmdLine, myApp, fso, _
517*cdf0e10cSrcweir                                    myDocList, myOffset, myIniFilePath)
518*cdf0e10cSrcweir        If (launchStatus = ABORTED) Then
519*cdf0e10cSrcweir            finished = True
520*cdf0e10cSrcweir            analyseStatus = C_STAT_ABORTED
521*cdf0e10cSrcweir            analysisAborted = True
522*cdf0e10cSrcweir        Else
523*cdf0e10cSrcweir            analyseStatus = CheckAnalyseStatus(statFileName, lastHandledFile, fso)
524*cdf0e10cSrcweir        End If
525*cdf0e10cSrcweir        If (analyseStatus = C_STAT_DONE) Then
526*cdf0e10cSrcweir            finished = True
527*cdf0e10cSrcweir        ElseIf (analyseStatus = C_STAT_RETRY) Then
528*cdf0e10cSrcweir            If (lastHandledFile = lastFile) Then
529*cdf0e10cSrcweir                nRetries = nRetries + 1
530*cdf0e10cSrcweir            Else
531*cdf0e10cSrcweir                lastFile = lastHandledFile
532*cdf0e10cSrcweir                nRetries = 1
533*cdf0e10cSrcweir            End If
534*cdf0e10cSrcweir        Else
535*cdf0e10cSrcweir            nRetries = nRetries + 1
536*cdf0e10cSrcweir        End If
537*cdf0e10cSrcweir    Wend
538*cdf0e10cSrcweir
539*cdf0e10cSrcweir    If (analyseStatus = C_STAT_DONE) Then
540*cdf0e10cSrcweir        AnalyseList = True
541*cdf0e10cSrcweir    Else
542*cdf0e10cSrcweir        AnalyseList = False
543*cdf0e10cSrcweir    End If
544*cdf0e10cSrcweir
545*cdf0e10cSrcweir    'The next driver should not overwrite this result file
546*cdf0e10cSrcweir    WriteToLog CNEW_RESULTS_FILE, "False", myIniFilePath
547*cdf0e10cSrcweir
548*cdf0e10cSrcweirFinalExit:
549*cdf0e10cSrcweir    Set fso = Nothing
550*cdf0e10cSrcweir    Exit Function
551*cdf0e10cSrcweir
552*cdf0e10cSrcweirHandleErrors:
553*cdf0e10cSrcweir    AnalyseList = False
554*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
555*cdf0e10cSrcweir    Resume FinalExit
556*cdf0e10cSrcweirEnd Function
557*cdf0e10cSrcweir
558*cdf0e10cSrcweirSub HandleAbort(hProcess As Long, curApplication As String)
559*cdf0e10cSrcweir
560*cdf0e10cSrcweir    On Error Resume Next
561*cdf0e10cSrcweir
562*cdf0e10cSrcweir    Dim ret As Long
563*cdf0e10cSrcweir    Dim curDate As Date
564*cdf0e10cSrcweir    Dim stillWaiting As Boolean
565*cdf0e10cSrcweir    Dim killApplication As Boolean
566*cdf0e10cSrcweir    Dim waitTime As Long
567*cdf0e10cSrcweir
568*cdf0e10cSrcweir    curDate = Now()
569*cdf0e10cSrcweir    stillWaiting = True
570*cdf0e10cSrcweir    killApplication = False
571*cdf0e10cSrcweir
572*cdf0e10cSrcweir    While stillWaiting
573*cdf0e10cSrcweir        stillWaiting = IsOfficeAppRunning(curApplication)
574*cdf0e10cSrcweir        If (stillWaiting) Then
575*cdf0e10cSrcweir            waitTime = val(DateDiff("s", curDate, Now()))
576*cdf0e10cSrcweir            If (waitTime > C_ABORT_TIMEOUT) Then
577*cdf0e10cSrcweir                stillWaiting = False
578*cdf0e10cSrcweir                killApplication = True
579*cdf0e10cSrcweir            End If
580*cdf0e10cSrcweir        End If
581*cdf0e10cSrcweir    Wend
582*cdf0e10cSrcweir
583*cdf0e10cSrcweir    If (killApplication) Then
584*cdf0e10cSrcweir        ShowProgress.g_SP_AllowOtherDLG = True
585*cdf0e10cSrcweir        TerminateMSO.Show vbModal, ShowProgress
586*cdf0e10cSrcweir    End If
587*cdf0e10cSrcweir
588*cdf0e10cSrcweir    ret = TerminateProcess(hProcess, "0")
589*cdf0e10cSrcweirEnd Sub
590