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