summaryrefslogtreecommitdiff
path: root/migrationanalysis/src/wizard
diff options
context:
space:
mode:
Diffstat (limited to 'migrationanalysis/src/wizard')
-rw-r--r--migrationanalysis/src/wizard/Analyse.bas580
-rw-r--r--migrationanalysis/src/wizard/CollectedFiles.cls521
-rw-r--r--migrationanalysis/src/wizard/DocAnalysisWizard.exe.manifest22
-rw-r--r--migrationanalysis/src/wizard/Get Directory Dialog.bas134
-rw-r--r--migrationanalysis/src/wizard/IniSupport.bas260
-rw-r--r--migrationanalysis/src/wizard/LaunchDrivers.vbp42
-rw-r--r--migrationanalysis/src/wizard/LaunchDrivers.vbw1
-rw-r--r--migrationanalysis/src/wizard/OOo3_Analysis.icobin295606 -> 0 bytes
-rw-r--r--migrationanalysis/src/wizard/OOo_AnalysisBitmap.pngbin8625 -> 0 bytes
-rw-r--r--migrationanalysis/src/wizard/Office10Issues.bas352
-rw-r--r--migrationanalysis/src/wizard/ProAnalysisWizard.vbp65
-rw-r--r--migrationanalysis/src/wizard/RunServer.bas190
-rw-r--r--migrationanalysis/src/wizard/ScanFolders.frm157
-rw-r--r--migrationanalysis/src/wizard/SearchDocs.frm124
-rw-r--r--migrationanalysis/src/wizard/Terminate.frm81
-rw-r--r--migrationanalysis/src/wizard/Utilities.bas543
-rw-r--r--migrationanalysis/src/wizard/Wizard.DCAbin3927 -> 0 bytes
-rw-r--r--migrationanalysis/src/wizard/Wizard.Dsr96
-rw-r--r--migrationanalysis/src/wizard/Wizard.FRXbin416643 -> 0 bytes
-rw-r--r--migrationanalysis/src/wizard/Wizard.bas642
-rw-r--r--migrationanalysis/src/wizard/Wizard.frm3453
-rw-r--r--migrationanalysis/src/wizard/makefile.mk107
-rw-r--r--migrationanalysis/src/wizard/rcfooter.txt1
-rw-r--r--migrationanalysis/src/wizard/rcheader.txt34
-rw-r--r--migrationanalysis/src/wizard/rctmpl.txt143
-rw-r--r--migrationanalysis/src/wizard/res_defines.h153
-rw-r--r--migrationanalysis/src/wizard/wizard.ulf370
27 files changed, 0 insertions, 8071 deletions
diff --git a/migrationanalysis/src/wizard/Analyse.bas b/migrationanalysis/src/wizard/Analyse.bas
deleted file mode 100644
index b37751960206..000000000000
--- a/migrationanalysis/src/wizard/Analyse.bas
+++ /dev/null
@@ -1,580 +0,0 @@
-Attribute VB_Name = "Analyse"
-'
-' This file is part of the LibreOffice project.
-'
-' This Source Code Form is subject to the terms of the Mozilla Public
-' License, v. 2.0. If a copy of the MPL was not distributed with this
-' file, You can obtain one at http://mozilla.org/MPL/2.0/.
-'
-' This file incorporates work covered by the following license notice:
-'
-' Licensed to the Apache Software Foundation (ASF) under one or more
-' contributor license agreements. See the NOTICE file distributed
-' with this work for additional information regarding copyright
-' ownership. The ASF licenses this file to you under the Apache
-' License, Version 2.0 (the "License"); you may not use this file
-' except in compliance with the License. You may obtain a copy of
-' the License at http://www.apache.org/licenses/LICENSE-2.0 .
-'
-
-Option Explicit
-
-Private Const C_STAT_NOT_STARTED As Integer = 1
-Private Const C_STAT_RETRY As Integer = 2
-Private Const C_STAT_ERROR As Integer = 3
-Private Const C_STAT_DONE As Integer = 4
-Private Const C_STAT_ABORTED As Integer = 5
-
-Private Const C_MAX_RETRIES As Integer = 5
-Private Const C_ABORT_TIMEOUT As Integer = 30
-
-Private Const MAX_WAIT_TIME As Long = 600
-
-Private Const C_STAT_FINISHED As String = "finished"
-Private Const C_STAT_ANALYSED As String = "analysed="
-Private Const C_STAT_ANALYSING As String = "analysing="
-Private Const CSINGLE_FILE As String = "singlefile"
-Private Const CFILE_LIST As String = "filelist"
-Private Const CSTAT_FILE As String = "statfilename"
-Private Const CLAST_CHECKPOINT As String = "LastCheckpoint"
-Private Const CNEXT_FILE As String = "NextFile"
-Private Const C_ABORT_ANALYSIS As String = "AbortAnalysis"
-
-Private Const CAPPNAME_WORD As String = "word"
-Private Const CAPPNAME_EXCEL As String = "excel"
-Private Const CAPPNAME_POWERPOINT As String = "powerpoint"
-Private Const C_EXENAME_WORD As String = "winword.exe"
-Private Const C_EXENAME_EXCEL As String = "excel.exe"
-Private Const C_EXENAME_POWERPOINT As String = "powerpnt.exe"
-
-Const CNEW_RESULTS_FILE = "newresultsfile"
-Const C_LAUNCH_DRIVER = ".\resources\LaunchDrivers.exe"
-
-'from http://support.microsoft.com/kb/q129796
-
-Private Type STARTUPINFO
- cb As Long
- lpReserved As String
- lpDesktop As String
- lpTitle As String
- dwX As Long
- dwY As Long
- dwXSize As Long
- dwYSize As Long
- dwXCountChars As Long
- dwYCountChars As Long
- dwFillAttribute As Long
- dwFlags As Long
- wShowWindow As Integer
- cbReserved2 As Integer
- lpReserved2 As Long
- hStdInput As Long
- hStdOutput As Long
- hStdError As Long
-End Type
-
-Private Type PROCESS_INFORMATION
- hProcess As Long
- hThread As Long
- dwProcessID As Long
- dwThreadID As Long
-End Type
-
-Private Declare Function WaitForSingleObject Lib "kernel32" (ByVal _
- hHandle As Long, ByVal dwMilliseconds As Long) As Long
-
-Private Declare Function CreateProcessA Lib "kernel32" (ByVal _
- lpApplicationName As String, ByVal lpCommandLine As String, ByVal _
- lpProcessAttributes As Long, ByVal lpThreadAttributes As Long, _
- ByVal bInheritHandles As Long, ByVal dwCreationFlags As Long, _
- ByVal lpEnvironment As Long, ByVal lpCurrentDirectory As String, _
- lpStartupInfo As STARTUPINFO, lpProcessInformation As _
- PROCESS_INFORMATION) As Long
-
-Private Declare Function CloseHandle Lib "kernel32" _
- (ByVal hObject As Long) As Long
-
-Private Declare Function GetExitCodeProcess Lib "kernel32" _
- (ByVal hProcess As Long, lpExitCode As Long) As Long
-
-Private Declare Function TerminateProcess Lib "kernel32" (ByVal hProcess As Long, _
- ByVal uExitCode As Long) As Long
-
-Private Const NORMAL_PRIORITY_CLASS = &H20&
-Private Const WAIT_TIMEOUT As Long = &H102
-Private Const ABORTED As Long = -2
-
-' from http://vbnet.mvps.org/index.html?code/system/toolhelpprocesses.htm
-Public Const TH32CS_SNAPPROCESS As Long = 2&
-Public Const MAX_PATH As Long = 260
-
-Public Type PROCESSENTRY32
- dwSize As Long
- cntUsage As Long
- th32ProcessID As Long
- th32DefaultHeapID As Long
- th32ModuleID As Long
- cntThreads As Long
- th32ParentProcessID As Long
- pcPriClassBase As Long
- dwFlags As Long
- szExeFile As String * MAX_PATH
-End Type
-
-Public Declare Function CreateToolhelp32Snapshot Lib "kernel32" _
- (ByVal lFlags As Long, ByVal lProcessID As Long) As Long
-
-Public Declare Function ProcessFirst Lib "kernel32" _
- Alias "Process32First" _
- (ByVal hSnapShot As Long, uProcess As PROCESSENTRY32) As Long
-
-Public Declare Function ProcessNext Lib "kernel32" _
- Alias "Process32Next" _
- (ByVal hSnapShot As Long, uProcess As PROCESSENTRY32) As Long
-
-
-Public Function IsOfficeAppRunning(curApplication As String) As Boolean
-'DV: we need some error handling here
- Dim hSnapShot As Long
- Dim uProcess As PROCESSENTRY32
- Dim success As Long
- Dim bRet As Boolean
- Dim bAppFound As Boolean
- Dim exeName As String
- Dim curExeName As String
-
- bRet = True
- On Error GoTo FinalExit
-
- curExeName = LCase$(curApplication)
-
- If (curExeName = CAPPNAME_WORD) Then
- exeName = C_EXENAME_WORD
- ElseIf (curExeName = CAPPNAME_EXCEL) Then
- exeName = C_EXENAME_EXCEL
- ElseIf (curExeName = CAPPNAME_POWERPOINT) Then
- exeName = C_EXENAME_POWERPOINT
- Else
- GoTo FinalExit
- End If
-
- hSnapShot = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0&)
-
- If hSnapShot = -1 Then GoTo FinalExit
-
- uProcess.dwSize = Len(uProcess)
- success = ProcessFirst(hSnapShot, uProcess)
- bAppFound = False
-
- While ((success = 1) And Not bAppFound)
- Dim i As Long
- i = InStr(1, uProcess.szExeFile, Chr(0))
- curExeName = LCase$(Left$(uProcess.szExeFile, i - 1))
- If (curExeName = exeName) Then
- bAppFound = True
- Else
- success = ProcessNext(hSnapShot, uProcess)
- End If
- Wend
- bRet = bAppFound
-
- Call CloseHandle(hSnapShot)
-
-FinalExit:
- IsOfficeAppRunning = bRet
-
-End Function
-
-Private Sub CalculateProgress(statusFileName As String, fso As FileSystemObject, _
- lastIndex As Long, docOffset As Long, _
- myDocList As Collection)
-
- On Error GoTo FinalExit
-
- Dim curFile As String
- Dim fileCont As TextStream
- Dim myFile As file
-
- If (fso.FileExists(statusFileName)) Then
- Dim statLine As String
-
- Set fileCont = fso.OpenTextFile(statusFileName, ForReading, False, TristateTrue)
- statLine = fileCont.ReadLine
-
- If (Left(statLine, Len(C_STAT_ANALYSED)) = C_STAT_ANALYSED) Then
- curFile = Mid(statLine, Len(C_STAT_ANALYSED) + 1)
- ElseIf (Left(statLine, Len(C_STAT_ANALYSING)) = C_STAT_ANALYSING) Then
- curFile = Mid(statLine, Len(C_STAT_ANALYSING) + 1)
- End If
- End If
-
- ' when we don't have a file, we will show the name of the last used file in
- ' the progress window
- If (curFile = "") Then curFile = myDocList.item(lastIndex)
-
- If (GetDocumentIndex(curFile, myDocList, lastIndex)) Then
- Set myFile = fso.GetFile(curFile)
- Call ShowProgress.SP_UpdateProgress(myFile.Name, myFile.ParentFolder.path, lastIndex + docOffset)
- End If
-
-FinalExit:
- If Not (fileCont Is Nothing) Then fileCont.Close
- Set fileCont = Nothing
- Set myFile = Nothing
-
-End Sub
-
-Function CheckAliveStatus(statFileName As String, _
- curApplication As String, _
- lastDate As Date, _
- fso As FileSystemObject) As Boolean
-
- Dim isAlive As Boolean
- Dim currDate As Date
- Dim statFile As file
- Dim testing As Long
-
- isAlive = False
-
- If Not fso.FileExists(statFileName) Then
- currDate = Now()
- If (val(DateDiff("s", lastDate, currDate)) > MAX_WAIT_TIME) Then
- isAlive = False
- Else
- isAlive = True
- End If
- Else
- Set statFile = fso.GetFile(statFileName)
- currDate = statFile.DateLastModified
- If (currDate > lastDate) Then
- lastDate = currDate
- isAlive = True
- Else
- currDate = Now()
- If (lastDate >= currDate) Then ' There might be some inaccuracies in file and system dates
- isAlive = True
- ElseIf (val(DateDiff("s", lastDate, currDate)) > MAX_WAIT_TIME) Then
- isAlive = False
- Else
- isAlive = IsOfficeAppRunning(curApplication)
- End If
- End If
- End If
-
- CheckAliveStatus = isAlive
-End Function
-
-Sub TerminateOfficeApps(fso As FileSystemObject, aParameter As String)
-
- Dim msoKillFileName As String
-
- msoKillFileName = fso.GetAbsolutePathName(".\resources\msokill.exe")
- If fso.FileExists(msoKillFileName) Then
- Shell msoKillFileName & aParameter
- Else
- End If
-End Sub
-
-Public Function launchDriver(statFileName As String, cmdLine As String, _
- curApplication As String, fso As FileSystemObject, _
- myDocList As Collection, myOffset As Long, _
- myIniFilePath As String) As Long
-
- Dim proc As PROCESS_INFORMATION
- Dim start As STARTUPINFO
- Dim ret As Long
- Dim currDate As Date
- Dim lastIndex As Long
-
- currDate = Now()
- lastIndex = 1
-
- ' Initialize the STARTUPINFO structure:
- start.cb = Len(start)
-
- ' Start the shelled application:
- ret = CreateProcessA(vbNullString, cmdLine$, 0&, 0&, 1&, _
- NORMAL_PRIORITY_CLASS, 0&, vbNullString, start, proc)
-
- ' Wait for the shelled application to finish:
- Do
- ret = WaitForSingleObject(proc.hProcess, 100)
- If ret <> WAIT_TIMEOUT Then
- Exit Do
- End If
- If Not CheckAliveStatus(statFileName, curApplication, currDate, fso) Then
- ' Try to close open office dialogs and then wait a little bit
- TerminateOfficeApps fso, " --close"
- ret = WaitForSingleObject(proc.hProcess, 1000)
-
- ' next try to kill all office programs and then wait a little bit
- TerminateOfficeApps fso, " --kill"
- ret = WaitForSingleObject(proc.hProcess, 1000)
-
- ret = TerminateProcess(proc.hProcess, "0")
- ret = WAIT_TIMEOUT
- Exit Do
- End If
- If (ShowProgress.g_SP_Abort) Then
- WriteToLog C_ABORT_ANALYSIS, True, myIniFilePath
- Call HandleAbort(proc.hProcess, curApplication)
- ret = ABORTED
- Exit Do
- End If
- Call CalculateProgress(statFileName, fso, lastIndex, myOffset, myDocList)
- DoEvents 'allow other processes
- Loop While True
-
- If (ret <> WAIT_TIMEOUT) And (ret <> ABORTED) Then
- Call GetExitCodeProcess(proc.hProcess, ret&)
- End If
- Call CloseHandle(proc.hThread)
- Call CloseHandle(proc.hProcess)
- launchDriver = ret
-End Function
-
-Function CheckAnalyseStatus(statusFileName As String, _
- lastFile As String, _
- fso As FileSystemObject) As Integer
-
- Dim currStatus As Integer
- Dim fileCont As TextStream
-
- If Not fso.FileExists(statusFileName) Then
- currStatus = C_STAT_NOT_STARTED
- Else
- Dim statText As String
- Set fileCont = fso.OpenTextFile(statusFileName, ForReading, False, TristateTrue)
- statText = fileCont.ReadLine
- If (statText = C_STAT_FINISHED) Then
- currStatus = C_STAT_DONE
- ElseIf (Left(statText, Len(C_STAT_ANALYSED)) = C_STAT_ANALYSED) Then
- currStatus = C_STAT_RETRY
- lastFile = Mid(statText, Len(C_STAT_ANALYSED) + 1)
- ElseIf (Left(statText, Len(C_STAT_ANALYSING)) = C_STAT_ANALYSING) Then
- currStatus = C_STAT_RETRY
- lastFile = Mid(statText, Len(C_STAT_ANALYSING) + 1)
- Else
- currStatus = C_STAT_ERROR
- End If
- fileCont.Close
- End If
-
- CheckAnalyseStatus = currStatus
-End Function
-
-Function WriteDocsToAnalyze(myDocList As Collection, myApp As String, _
- fso As FileSystemObject) As String
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "WriteDocsToAnalyze"
-
- Dim TempPath As String
- Dim fileName As String
- Dim fileContent As TextStream
-
- fileName = ""
- TempPath = fso.GetSpecialFolder(TemporaryFolder).path
-
- If (TempPath = "") Then
- TempPath = "."
- End If
-
- Dim vFileName As Variant
- Dim Index As Long
- Dim limit As Long
-
- limit = myDocList.count
- If (limit > 0) Then
- fileName = fso.GetAbsolutePathName(TempPath & "\FileList" & myApp & ".txt")
- Set fileContent = fso.OpenTextFile(fileName, ForWriting, True, TristateTrue)
-
- For Index = 1 To limit
- vFileName = myDocList(Index)
- fileContent.WriteLine (vFileName)
- Next
-
- fileContent.Close
- End If
-
-FinalExit:
- Set fileContent = Nothing
- WriteDocsToAnalyze = fileName
- Exit Function
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Function
-
-' This function looks for the given document name in the document collection
-' and returns TRUE and the position of the document in that collection if found,
-' FALSE otherwise
-Function GetDocumentIndex(myDocument As String, _
- myDocList As Collection, _
- lastIndex As Long) As Boolean
-
- Dim currentFunctionName As String
- currentFunctionName = "GetDocumentIndex"
-
- On Error GoTo HandleErrors
-
- Dim lastEntry As Long
- Dim curIndex As Long
- Dim curEntry As String
- Dim entryFound As Boolean
-
- entryFound = False
- lastEntry = myDocList.count
- curIndex = lastIndex
-
- ' We start the search at the position of the last found
- ' document
- While Not entryFound And curIndex <= lastEntry
- curEntry = myDocList.item(curIndex)
- If (curEntry = myDocument) Then
- lastIndex = curIndex
- entryFound = True
- Else
- curIndex = curIndex + 1
- End If
- Wend
-
- ' When we could not find the document, we start the search
- ' from the beginning of the list
- If Not entryFound Then
- curIndex = 1
- While Not entryFound And curIndex <= lastIndex
- curEntry = myDocList.item(curIndex)
- If (curEntry = myDocument) Then
- lastIndex = curIndex
- entryFound = True
- Else
- curIndex = curIndex + 1
- End If
- Wend
- End If
-
-FinalExit:
- GetDocumentIndex = entryFound
- Exit Function
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Function
-
-Function AnalyseList(myDocList As Collection, _
- myApp As String, _
- myIniFilePath As String, _
- myOffset As Long, _
- analysisAborted As Boolean) As Boolean
-
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "AnalyseList"
-
- Dim cmdLine As String
- Dim filelist As String
- Dim statFileName As String
- Dim finished As Boolean
- Dim analyseStatus As Integer
- Dim nRetries As Integer
- Dim lastFile As String
- Dim lastHandledFile As String
- Dim launchStatus As Long
- Dim fso As New FileSystemObject
- Dim progressTitle As String
-
- filelist = WriteDocsToAnalyze(myDocList, myApp, fso)
- cmdLine = fso.GetAbsolutePathName(C_LAUNCH_DRIVER) & " " & myApp
- finished = False
-
- Dim TempPath As String
- TempPath = fso.GetSpecialFolder(TemporaryFolder).path
- If (TempPath = "") Then TempPath = "."
- statFileName = fso.GetAbsolutePathName(TempPath & "\StatFile" & myApp & ".txt")
- If (fso.FileExists(statFileName)) Then fso.DeleteFile (statFileName)
-
- WriteToLog CFILE_LIST, filelist, myIniFilePath
- WriteToLog CSTAT_FILE, statFileName, myIniFilePath
- WriteToLog CLAST_CHECKPOINT, "", myIniFilePath
- WriteToLog CNEXT_FILE, "", myIniFilePath
- WriteToLog C_ABORT_ANALYSIS, "", myIniFilePath
-
- ' In this loop we will restart the driver until we have finished the analysis
- nRetries = 0
- While Not finished And nRetries < C_MAX_RETRIES
- launchStatus = launchDriver(statFileName, cmdLine, myApp, fso, _
- myDocList, myOffset, myIniFilePath)
- If (launchStatus = ABORTED) Then
- finished = True
- analyseStatus = C_STAT_ABORTED
- analysisAborted = True
- Else
- analyseStatus = CheckAnalyseStatus(statFileName, lastHandledFile, fso)
- End If
- If (analyseStatus = C_STAT_DONE) Then
- finished = True
- ElseIf (analyseStatus = C_STAT_RETRY) Then
- If (lastHandledFile = lastFile) Then
- nRetries = nRetries + 1
- Else
- lastFile = lastHandledFile
- nRetries = 1
- End If
- Else
- nRetries = nRetries + 1
- End If
- Wend
-
- If (analyseStatus = C_STAT_DONE) Then
- AnalyseList = True
- Else
- AnalyseList = False
- End If
-
- 'The next driver should not overwrite this result file
- WriteToLog CNEW_RESULTS_FILE, "False", myIniFilePath
-
-FinalExit:
- Set fso = Nothing
- Exit Function
-
-HandleErrors:
- AnalyseList = False
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Function
-
-Sub HandleAbort(hProcess As Long, curApplication As String)
-
- On Error Resume Next
-
- Dim ret As Long
- Dim curDate As Date
- Dim stillWaiting As Boolean
- Dim killApplication As Boolean
- Dim waitTime As Long
-
- curDate = Now()
- stillWaiting = True
- killApplication = False
-
- While stillWaiting
- stillWaiting = IsOfficeAppRunning(curApplication)
- If (stillWaiting) Then
- waitTime = val(DateDiff("s", curDate, Now()))
- If (waitTime > C_ABORT_TIMEOUT) Then
- stillWaiting = False
- killApplication = True
- End If
- End If
- Wend
-
- If (killApplication) Then
- ShowProgress.g_SP_AllowOtherDLG = True
- TerminateMSO.Show vbModal, ShowProgress
- End If
-
- ret = TerminateProcess(hProcess, "0")
-End Sub
diff --git a/migrationanalysis/src/wizard/CollectedFiles.cls b/migrationanalysis/src/wizard/CollectedFiles.cls
deleted file mode 100644
index 6fe7b721b802..000000000000
--- a/migrationanalysis/src/wizard/CollectedFiles.cls
+++ /dev/null
@@ -1,521 +0,0 @@
-VERSION 1.0 CLASS
-BEGIN
- MultiUse = -1 'True
- Persistable = 0 'NotPersistable
- DataBindingBehavior = 0 'vbNone
- DataSourceBehavior = 0 'vbNone
- MTSTransactionMode = 0 'NotAnMTSObject
-END
-Attribute VB_Name = "CollectedFiles"
-Attribute VB_GlobalNameSpace = False
-Attribute VB_Creatable = True
-Attribute VB_PredeclaredId = False
-Attribute VB_Exposed = False
-'
-' This file is part of the LibreOffice project.
-'
-' This Source Code Form is subject to the terms of the Mozilla Public
-' License, v. 2.0. If a copy of the MPL was not distributed with this
-' file, You can obtain one at http://mozilla.org/MPL/2.0/.
-'
-' This file incorporates work covered by the following license notice:
-'
-' Licensed to the Apache Software Foundation (ASF) under one or more
-' contributor license agreements. See the NOTICE file distributed
-' with this work for additional information regarding copyright
-' ownership. The ASF licenses this file to you under the Apache
-' License, Version 2.0 (the "License"); you may not use this file
-' except in compliance with the License. You may obtain a copy of
-' the License at http://www.apache.org/licenses/LICENSE-2.0 .
-'
-Option Explicit
-
-Private Const vbDot = 46
-Private Const MAX_PATH = 260
-Private Const INVALID_HANDLE_VALUE = -1
-Private Const vbBackslash = "\"
-Private Const ALL_FILES = "*.*"
-
-Private Type FILETIME
- dwLowDateTime As Long
- dwHighDateTime As Long
-End Type
-
-Private Type SYSTEMTIME
- wYear As Integer
- wMonth As Integer
- wDayOfWeek As Integer
- wDay As Integer
- wHour As Integer
- wMinute As Integer
- wSecond As Integer
- wMilliseconds As Integer
-End Type
-
-Private Type WIN32_FIND_DATA
- dwFileAttributes As Long
- ftCreationTime As FILETIME
- ftLastAccessTime As FILETIME
- ftLastWriteTime As FILETIME
- nFileSizeHigh As Long
- nFileSizeLow As Long
- dwReserved0 As Long
- dwReserved1 As Long
- cFileName As String * MAX_PATH
- cAlternate As String * 14
-End Type
-
-Private Type FILE_PARAMS
- bRecurse As Boolean
- nSearched As Long
- sFileNameExt As String
- sFileRoot As String
-End Type
-
-Private Declare Function SystemTimeToFileTime Lib "kernel32" _
- (lpSystemTime As SYSTEMTIME, _
- lpFileTime As FILETIME) As Long
-
-Private Declare Function CompareFileTime Lib "kernel32" _
- (lpFileTime1 As FILETIME, _
- lpFileTime2 As FILETIME) As Long
-
-Private Declare Function FindClose Lib "kernel32" _
- (ByVal hFindFile As Long) As Long
-
-Private Declare Function FindFirstFile Lib "kernel32" _
- Alias "FindFirstFileA" _
- (ByVal lpFileName As String, _
- lpFindFileData As WIN32_FIND_DATA) As Long
-
-Private Declare Function FindNextFile Lib "kernel32" _
- Alias "FindNextFileA" _
- (ByVal hFindFile As Long, _
- lpFindFileData As WIN32_FIND_DATA) As Long
-
-Private Declare Function GetTickCount Lib "kernel32" () As Long
-
-Private Declare Function lstrlen Lib "kernel32" _
- Alias "lstrlenW" (ByVal lpString As Long) As Long
-
-Private Declare Function PathMatchSpec Lib "shlwapi" _
- Alias "PathMatchSpecW" _
- (ByVal pszFileParam As Long, _
- ByVal pszSpec As Long) As Long
-
-Private fp As FILE_PARAMS 'holds search parameters
-
-Private mWordFilesCol As Collection
-Private mExcelFilesCol As Collection
-Private mPPFilesCol As Collection
-
-Private mLessThan3 As Long
-Private mLessThan6 As Long
-Private mLessThan12 As Long
-Private mMoreThan12 As Long
-Private m3Months As FILETIME
-Private m6Months As FILETIME
-Private m12Months As FILETIME
-
-Private mDocCount As Long
-Private mDotCount As Long
-Private mXlsCount As Long
-Private mXltCount As Long
-Private mPptCount As Long
-Private mPotCount As Long
-Private mIgnoredDocs As Long
-Private mbDocSearch As Boolean
-Private mbDotSearch As Boolean
-Private mbXlsSearch As Boolean
-Private mbXltSearch As Boolean
-Private mbPptSearch As Boolean
-Private mbPotSearch As Boolean
-
-Private mWordDriverPath As String
-Private mExcelDriverPath As String
-Private mPPDriverPath As String
-
-Private Sub Class_Initialize()
- Set mWordFilesCol = New Collection
- Set mExcelFilesCol = New Collection
- Set mPPFilesCol = New Collection
-End Sub
-Private Sub Class_Terminate()
- Set mWordFilesCol = Nothing
- Set mExcelFilesCol = Nothing
- Set mPPFilesCol = Nothing
-End Sub
-
-Public Property Get DocCount() As Long
- DocCount = mDocCount
-End Property
-Public Property Get DotCount() As Long
- DotCount = mDotCount
-End Property
-Public Property Get XlsCount() As Long
- XlsCount = mXlsCount
-End Property
-Public Property Get XltCount() As Long
- XltCount = mXltCount
-End Property
-Public Property Get PptCount() As Long
- PptCount = mPptCount
-End Property
-Public Property Get PotCount() As Long
- PotCount = mPotCount
-End Property
-Public Property Get IgnoredDocCount() As Long
- IgnoredDocCount = mIgnoredDocs
-End Property
-Public Property Get DocsLessThan3Months() As Long
- DocsLessThan3Months = mLessThan3
-End Property
-Public Property Get DocsLessThan6Months() As Long
- DocsLessThan6Months = mLessThan6
-End Property
-Public Property Get DocsLessThan12Months() As Long
- DocsLessThan12Months = mLessThan12
-End Property
-Public Property Get DocsMoreThan12Months() As Long
- DocsMoreThan12Months = mMoreThan12
-End Property
-
-Public Property Get WordFiles() As Collection
- Set WordFiles = mWordFilesCol
-End Property
-Public Property Get ExcelFiles() As Collection
- Set ExcelFiles = mExcelFilesCol
-End Property
-Public Property Get PowerPointFiles() As Collection
- Set PowerPointFiles = mPPFilesCol
-End Property
-
-Public Function count() As Long
- count = mWordFilesCol.count + mExcelFilesCol.count + mPPFilesCol.count
-End Function
-
-Public Function Search(rootDir As String, FileSpecs As Collection, IncludeSubdirs As Boolean, _
- ignoreOld As Boolean, Months As Integer) As Boolean
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "Search"
-
- Dim tstart As Single 'timer var for this routine only
- Dim tend As Single 'timer var for this routine only
- Dim spec As Variant
- Dim allSpecs As String
- Dim fso As New FileSystemObject
-
- Search = True
-
- If FileSpecs.count = 0 Then Exit Function
-
- If FileSpecs.count > 1 Then
- For Each spec In FileSpecs
- allSpecs = allSpecs & "; " & spec
- SetSearchBoolean CStr(spec)
- Next
- Else
- allSpecs = FileSpecs(1)
- SetSearchBoolean CStr(FileSpecs(1))
- End If
-
- mWordDriverPath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CWORD_DRIVER_FILE)
- mExcelDriverPath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CEXCEL_DRIVER_FILE)
- mPPDriverPath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CPP_DRIVER_FILE)
-
- With fp
- .sFileRoot = QualifyPath(rootDir)
- .sFileNameExt = allSpecs
- .bRecurse = IncludeSubdirs
- .nSearched = 0
- End With
-
- Load SearchDocs
-
- ignoreOld = ignoreOld And InitFileTimes
-
- Dim limDate As FILETIME
- If ignoreOld Then
- If Months = 3 Then
- limDate = m3Months
- ElseIf Months = 6 Then
- limDate = m6Months
- ElseIf Months = 12 Then
- limDate = m12Months
- Else
- ignoreOld = False
- End If
- End If
-
- 'tstart = GetTickCount()
- Search = SearchForFiles(QualifyPath(rootDir), IncludeSubdirs, ignoreOld, limDate)
- 'tend = GetTickCount()
-
- Unload SearchDocs
-
- 'Debug:
- 'MsgBox "Specs " & allSpecs & vbLf & _
- ' Format$(fp.nSearched, "###,###,###,##0") & vbLf & _
- ' Format$(count, "###,###,###,##0") & vbLf & _
- ' FormatNumber((tend - tstart) / 1000, 2) & " seconds"
-
-FinalExit:
- Set fso = Nothing
- Exit Function
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Function
-Sub SetSearchBoolean(spec As String)
-
- If spec = "*.doc" Then
- mbDocSearch = True
- End If
- If spec = "*.dot" Then
- mbDotSearch = True
- End If
- If spec = "*.xls" Then
- mbXlsSearch = True
- End If
- If spec = "*.xlt" Then
- mbXltSearch = True
- End If
- If spec = "*.ppt" Then
- mbPptSearch = True
- End If
- If spec = "*.pot" Then
- mbPotSearch = True
- End If
-
-End Sub
-
-Private Function SearchForFiles(sRoot As String, bRecurse As Boolean, _
- bIgnoreOld As Boolean, limDate As FILETIME) As Boolean
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "SearchForFiles"
-
- Dim WFD As WIN32_FIND_DATA
- Dim hFile As Long
- Dim path As String
- Dim sFileName As String
- Dim nTotal As Long
-
- SearchForFiles = False
-
- hFile = FindFirstFile(sRoot & ALL_FILES, WFD)
-
- If hFile = INVALID_HANDLE_VALUE Then GoTo FinalExit
-
- Do
- If (SearchDocs.g_SD_Abort) Then GoTo FinalExit
- sFileName = TrimNull(WFD.cFileName)
- 'if a folder, and recurse specified, call
- 'method again
- If (WFD.dwFileAttributes And vbDirectory) Then
- If (Asc(WFD.cFileName) <> vbDot) And bRecurse Then
- SearchForFiles sRoot & sFileName & vbBackslash, bRecurse, bIgnoreOld, limDate
- End If
- Else
- 'must be a file..
- nTotal = mDocCount + mDotCount + mXlsCount + _
- mXltCount + mPptCount + mPotCount
- SearchDocs.SD_UpdateProgress str$(nTotal), sRoot
- DoEvents
-
- If mbDocSearch Then
- If MatchSpec(WFD.cFileName, "*.doc") Then
- path = sRoot & sFileName
-
- 'If StrComp(path, mWordDriverPath, vbTextCompare) <> 0 Then
- If Not MatchSpec(path, mWordDriverPath) Then
- If (IsTooOld(WFD, limDate, bIgnoreOld)) Then
- mIgnoredDocs = mIgnoredDocs + 1
- Else
- mDocCount = mDocCount + 1
- mWordFilesCol.add path
- End If
- End If
- GoTo CONTINUE_LOOP
- End If
- End If
- If mbDotSearch Then
- If MatchSpec(WFD.cFileName, "*.dot") Then
- If (IsTooOld(WFD, limDate, bIgnoreOld)) Then
- mIgnoredDocs = mIgnoredDocs + 1
- Else
- mDotCount = mDotCount + 1
- mWordFilesCol.add sRoot & sFileName
- End If
- GoTo CONTINUE_LOOP
- End If
- End If
- If mbXlsSearch Then
- If MatchSpec(WFD.cFileName, "*.xls") Then
- 'If StrComp(sFileName, CEXCEL_DRIVER_FILE, vbTextCompare) <> 0 Then
- If Not MatchSpec(WFD.cFileName, CEXCEL_DRIVER_FILE) Then
- If (IsTooOld(WFD, limDate, bIgnoreOld)) Then
- mIgnoredDocs = mIgnoredDocs + 1
- Else
- mXlsCount = mXlsCount + 1
- mExcelFilesCol.add sRoot & sFileName
- End If
- End If
- GoTo CONTINUE_LOOP
- End If
- End If
- If mbXltSearch Then
- If MatchSpec(WFD.cFileName, "*.xlt") Then
- If (IsTooOld(WFD, limDate, bIgnoreOld)) Then
- mIgnoredDocs = mIgnoredDocs + 1
- Else
- mXltCount = mXltCount + 1
- mExcelFilesCol.add sRoot & sFileName
- End If
- GoTo CONTINUE_LOOP
- End If
- End If
- If mbPptSearch Then
- If MatchSpec(WFD.cFileName, "*.ppt") Then
- path = sRoot & sFileName
- 'If StrComp(path, mPPDriverPath, vbTextCompare) <> 0 Then
- If Not MatchSpec(path, mPPDriverPath) Then
- If (IsTooOld(WFD, limDate, bIgnoreOld)) Then
- mIgnoredDocs = mIgnoredDocs + 1
- Else
- mPptCount = mPptCount + 1
- mPPFilesCol.add path
- End If
- End If
- GoTo CONTINUE_LOOP
- End If
- End If
- If mbPotSearch Then
- If MatchSpec(WFD.cFileName, "*.pot") Then
- If (IsTooOld(WFD, limDate, bIgnoreOld)) Then
- mIgnoredDocs = mIgnoredDocs + 1
- Else
- mPotCount = mPotCount + 1
- mPPFilesCol.add sRoot & sFileName
- End If
- GoTo CONTINUE_LOOP
- End If
- End If
-
- End If 'If WFD.dwFileAttributes
-
-CONTINUE_LOOP:
- fp.nSearched = fp.nSearched + 1
-
- Loop While FindNextFile(hFile, WFD)
-
- SearchForFiles = True
-FinalExit:
- Call FindClose(hFile)
- Exit Function
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Function
-
-Private Function QualifyPath(sPath As String) As String
-
- If Right$(sPath, 1) <> vbBackslash Then
- QualifyPath = sPath & vbBackslash
- Else: QualifyPath = sPath
- End If
-
-End Function
-
-Private Function TrimNull(startstr As String) As String
-
- TrimNull = Left$(startstr, lstrlen(StrPtr(startstr)))
-
-End Function
-
-Private Function MatchSpec(sFile As String, sSpec As String) As Boolean
-
- MatchSpec = PathMatchSpec(StrPtr(sFile), StrPtr(sSpec))
-
-End Function
-
-Private Function IsTooOld(aWFD As WIN32_FIND_DATA, minDate As FILETIME, _
- ignoreOld As Boolean) As Boolean
-
- IsTooOld = False
-
- Dim aFileTime As FILETIME
-
- If (aWFD.ftLastWriteTime.dwHighDateTime <> 0) Then
- aFileTime = aWFD.ftLastWriteTime
- ElseIf (aWFD.ftCreationTime.dwHighDateTime <> 0) Then
- aFileTime = aWFD.ftCreationTime
- Else
- ' No valid time found, don't ignore file
- mLessThan3 = mLessThan3 + 1
- Exit Function
- End If
-
- If (ignoreOld) Then
- If (CompareFileTime(aFileTime, minDate) < 0) Then
- IsTooOld = True
- End If
- End If
-
- If (CompareFileTime(aWFD.ftLastWriteTime, m12Months) < 0) Then
- mMoreThan12 = mMoreThan12 + 1
- ElseIf (CompareFileTime(aWFD.ftLastWriteTime, m6Months) < 0) Then
- mLessThan12 = mLessThan12 + 1
- ElseIf (CompareFileTime(aWFD.ftLastWriteTime, m3Months) < 0) Then
- mLessThan6 = mLessThan6 + 1
- Else
- mLessThan3 = mLessThan3 + 1
- End If
-
-End Function
-
-Private Function BasicDateToFileTime(basDate As Date, _
- fileDate As FILETIME) As Boolean
-
- Dim sysDate As SYSTEMTIME
- Dim retval As Long
-
- sysDate.wYear = DatePart("yyyy", basDate)
- sysDate.wMonth = DatePart("m", basDate)
- sysDate.wDay = DatePart("d", basDate)
- sysDate.wHour = DatePart("h", basDate)
- sysDate.wMinute = DatePart("m", basDate)
- retval = SystemTimeToFileTime(sysDate, fileDate)
- If (retval = 0) Then
- BasicDateToFileTime = False
- Else
- BasicDateToFileTime = True
- End If
-End Function
-
-Private Function InitFileTimes() As Boolean
-
- Dim nowDate As Date
- Dim basDate As Date
-
- InitFileTimes = True
-
- nowDate = Now()
- basDate = DateAdd("m", -3, nowDate)
- If Not BasicDateToFileTime(basDate, m3Months) Then InitFileTimes = False
-
- basDate = DateAdd("m", -6, nowDate)
- If Not BasicDateToFileTime(basDate, m6Months) Then InitFileTimes = False
-
- basDate = DateAdd("yyyy", -1, nowDate)
- If Not BasicDateToFileTime(basDate, m12Months) Then InitFileTimes = False
-
- mMoreThan12 = 0
- mLessThan12 = 0
- mLessThan6 = 0
- mLessThan3 = 0
-
-End Function
diff --git a/migrationanalysis/src/wizard/DocAnalysisWizard.exe.manifest b/migrationanalysis/src/wizard/DocAnalysisWizard.exe.manifest
deleted file mode 100644
index 911bdc94297d..000000000000
--- a/migrationanalysis/src/wizard/DocAnalysisWizard.exe.manifest
+++ /dev/null
@@ -1,22 +0,0 @@
-<?xml version="1.0" encoding="UTF-8" standalone="yes"?>
-<assembly xmlns="urn:schemas-microsoft-com:asm.v1" manifestVersion="1.0">
-<assemblyIdentity
- version="1.0.0.0"
- processorArchitecture="X86"
- name="SunMicrosystems.WinXPStyle.DocumentAnalysis"
- type="win32"
-/>
-<description>Windows XP Style for Document Analysis Wizard</description>
-<dependency>
- <dependentAssembly>
- <assemblyIdentity
- type="win32"
- name="Microsoft.Windows.Common-Controls"
- version="6.0.0.0"
- processorArchitecture="X86"
- publicKeyToken="6595b64144ccf1df"
- language="*"
- />
- </dependentAssembly>
-</dependency>
-</assembly> \ No newline at end of file
diff --git a/migrationanalysis/src/wizard/Get Directory Dialog.bas b/migrationanalysis/src/wizard/Get Directory Dialog.bas
deleted file mode 100644
index d047ad2283aa..000000000000
--- a/migrationanalysis/src/wizard/Get Directory Dialog.bas
+++ /dev/null
@@ -1,134 +0,0 @@
-Attribute VB_Name = "BrowseDirectorysOnly"
-'
-' This file is part of the LibreOffice project.
-'
-' This Source Code Form is subject to the terms of the Mozilla Public
-' License, v. 2.0. If a copy of the MPL was not distributed with this
-' file, You can obtain one at http://mozilla.org/MPL/2.0/.
-'
-' This file incorporates work covered by the following license notice:
-'
-' Licensed to the Apache Software Foundation (ASF) under one or more
-' contributor license agreements. See the NOTICE file distributed
-' with this work for additional information regarding copyright
-' ownership. The ASF licenses this file to you under the Apache
-' License, Version 2.0 (the "License"); you may not use this file
-' except in compliance with the License. You may obtain a copy of
-' the License at http://www.apache.org/licenses/LICENSE-2.0 .
-'
-
-' Modified as BIF_STATUSTEXT overflows for nested folders so is no longer
-' shown.
-
-'=====================================================================================
-' Browse for a Folder using SHBrowseForFolder API function with a callback
-' function BrowseCallbackProc.
-'
-' This Extends the functionality that was given in the
-' MSDN Knowledge Base article Q179497 "HOWTO: Select a Directory
-' Without the Common Dialog Control".
-'
-' After reading the MSDN knowledge base article Q179378 "HOWTO: Browse for
-' Folders from the Current Directory", I was able to figure out how to add
-' a callback function that sets the starting directory and displays the
-' currently selected path in the "Browse For Folder" dialog.
-'
-'
-' Stephen Fonnesbeck
-' steev@xmission.com
-' http://www.xmission.com/~steev
-' Feb 20, 2000
-'
-'=====================================================================================
-' Usage:
-'
-' Dim folder As String
-' folder = BrowseForFolder(Me, "Select A Directory", "C:\startdir\anywhere")
-' If Len(folder) = 0 Then Exit Sub 'User Selected Cancel
-'
-'=====================================================================================
-
-Option Explicit
-
-Private Const BIF_STATUSTEXT = &H4&
-Private Const BIF_RETURNONLYFSDIRS = 1
-Private Const BIF_DONTGOBELOWDOMAIN = 2
-Private Const MAX_PATH = 260
-
-Private Const WM_USER = &H400
-Private Const BFFM_INITIALIZED = 1
-Private Const BFFM_SELCHANGED = 2
-Private Const BFFM_SETSELECTION = (WM_USER + 102)
-
-Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As String) As Long
-Private Declare Function SHBrowseForFolder Lib "shell32" (lpbi As BrowseInfo) As Long
-Private Declare Function SHGetPathFromIDList Lib "shell32" (ByVal pidList As Long, ByVal lpBuffer As String) As Long
-Private Declare Function lstrcat Lib "kernel32" Alias "lstrcatA" (ByVal lpString1 As String, ByVal lpString2 As String) As Long
-
-Private Type BrowseInfo
- hWndOwner As Long
- pIDLRoot As Long
- pszDisplayName As Long
- lpszTitle As Long
- ulFlags As Long
- lpfnCallback As Long
- lParam As Long
- iImage As Long
-End Type
-
-Private m_CurrentDirectory As String 'The current directory
-'
-
-Public Function BrowseForFolder(owner As Form, Title As String, StartDir As String) As String
- 'Opens a Treeview control that displays the directories in a computer
-
- Dim lpIDList As Long
- Dim szTitle As String
- Dim sBuffer As String
- Dim tBrowseInfo As BrowseInfo
- m_CurrentDirectory = StartDir & vbNullChar
-
- szTitle = Title
- With tBrowseInfo
- .hWndOwner = owner.hWnd
- .lpszTitle = lstrcat(szTitle, "")
- .ulFlags = BIF_RETURNONLYFSDIRS + BIF_DONTGOBELOWDOMAIN '+ BIF_STATUSTEXT
- .lpfnCallback = GetAddressofFunction(AddressOf BrowseCallbackProc) 'get address of function.
- End With
-
- lpIDList = SHBrowseForFolder(tBrowseInfo)
- If (lpIDList) Then
- sBuffer = Space(MAX_PATH)
- SHGetPathFromIDList lpIDList, sBuffer
- sBuffer = Left(sBuffer, InStr(sBuffer, vbNullChar) - 1)
- BrowseForFolder = sBuffer
- Else
- BrowseForFolder = ""
- End If
-
-End Function
-
-Private Function BrowseCallbackProc(ByVal hWnd As Long, ByVal uMsg As Long, ByVal lp As Long, ByVal pData As Long) As Long
-
- Dim lpIDList As Long
- Dim ret As Long
- Dim sBuffer As String
-
- On Error Resume Next 'Sugested by MS to prevent an error from
- 'propagating back into the calling process.
-
- Select Case uMsg
-
- Case BFFM_INITIALIZED
- Call SendMessage(hWnd, BFFM_SETSELECTION, 1, m_CurrentDirectory)
-
- End Select
-
- BrowseCallbackProc = 0
-
-End Function
-
-' This function allows you to assign a function pointer to a vaiable.
-Private Function GetAddressofFunction(add As Long) As Long
- GetAddressofFunction = add
-End Function
diff --git a/migrationanalysis/src/wizard/IniSupport.bas b/migrationanalysis/src/wizard/IniSupport.bas
deleted file mode 100644
index 6187a26bbcba..000000000000
--- a/migrationanalysis/src/wizard/IniSupport.bas
+++ /dev/null
@@ -1,260 +0,0 @@
-Attribute VB_Name = "IniSupport"
-'
-' This file is part of the LibreOffice project.
-'
-' This Source Code Form is subject to the terms of the Mozilla Public
-' License, v. 2.0. If a copy of the MPL was not distributed with this
-' file, You can obtain one at http://mozilla.org/MPL/2.0/.
-'
-' This file incorporates work covered by the following license notice:
-'
-' Licensed to the Apache Software Foundation (ASF) under one or more
-' contributor license agreements. See the NOTICE file distributed
-' with this work for additional information regarding copyright
-' ownership. The ASF licenses this file to you under the Apache
-' License, Version 2.0 (the "License"); you may not use this file
-' except in compliance with the License. You may obtain a copy of
-' the License at http://www.apache.org/licenses/LICENSE-2.0 .
-'
-Option Explicit
-
-Private Declare Function GetPrivateProfileString Lib "kernel32" _
- Alias "GetPrivateProfileStringA" _
- (ByVal lpSectionName As String, _
- ByVal lpKeyName As Any, _
- ByVal lpDefault As String, _
- ByVal lpReturnedString As String, _
- ByVal nSize As Long, _
- ByVal lpFileName As String) As Long
-
-Private Declare Function WritePrivateProfileString Lib "kernel32" _
- Alias "WritePrivateProfileStringA" _
- (ByVal lpSectionName As String, _
- ByVal lpKeyName As Any, _
- ByVal lpString As Any, _
- ByVal lpFileName As String) As Long
-
-
-Public Function ProfileGetItem(lpSectionName As String, _
- lpKeyName As String, _
- defaultValue As String, _
- inifile As String) As String
-
-'Retrieves a value from an ini file corresponding
-'to the section and key name passed.
-
- Dim success As Long
- Dim nSize As Long
- Dim ret As String
-
- 'call the API with the parameters passed.
- 'The return value is the length of the string
- 'in ret, including the terminating null. If a
- 'default value was passed, and the section or
- 'key name are not in the file, that value is
- 'returned. If no default value was passed (""),
- 'then success will = 0 if not found.
-
- 'Pad a string large enough to hold the data.
- ret = Space$(2048)
- nSize = Len(ret)
- success = GetPrivateProfileString(lpSectionName, _
- lpKeyName, _
- defaultValue, _
- ret, _
- nSize, _
- inifile)
-
- If success Then
- ProfileGetItem = Left$(ret, success)
- End If
-
-End Function
-
-
-Public Sub ProfileDeleteItem(lpSectionName As String, _
- lpKeyName As String, _
- inifile As String)
-
-'this call will remove the keyname and its
-'corresponding value from the section specified
-'in lpSectionName. This is accomplished by passing
-'vbNullString as the lpValue parameter. For example,
-'assuming that an ini file had:
-' [Colours]
-' Colour1=Red
-' Colour2=Blue
-' Colour3=Green
-'
-'and this sub was called passing "Colour2"
-'as lpKeyName, the resulting ini file
-'would contain:
-' [Colours]
-' Colour1=Red
-' Colour3=Green
-
- Call WritePrivateProfileString(lpSectionName, _
- lpKeyName, _
- vbNullString, _
- inifile)
-
-End Sub
-
-
-Public Sub ProfileDeleteSection(lpSectionName As String, _
- inifile As String)
-
-'this call will remove the entire section
-'corresponding to lpSectionName. This is
-'accomplished by passing vbNullString
-'as both the lpKeyName and lpValue parameters.
-'For example, assuming that an ini file had:
-' [Colours]
-' Colour1=Red
-' Colour2=Blue
-' Colour3=Green
-'
-'and this sub was called passing "Colours"
-'as lpSectionName, the resulting Colours
-'section in the ini file would be deleted.
-
- Call WritePrivateProfileString(lpSectionName, _
- vbNullString, _
- vbNullString, _
- inifile)
-
-End Sub
-
-Private Function StripNulls(startStrg As String) As String
-
-'take a string separated by nulls, split off 1 item, and shorten the string
-'so the next item is ready for removal.
-'The passed string must have a terminating null for this function to work correctly.
-'If you remain in a loop, check this first!
-
- Dim pos As Long
- Dim item As String
-
- pos = InStr(1, startStrg, Chr$(0))
-
- If pos Then
-
- item = Mid$(startStrg, 1, pos - 1)
- startStrg = Mid$(startStrg, pos + 1, Len(startStrg))
- StripNulls = item
-
- End If
-
-End Function
-
-Public Function ProfileLoadList(lst As ComboBox, _
- lpSectionName As String, _
- inifile As String) As Long
- Dim success As Long
- Dim c As Long
- Dim nSize As Long
- Dim KeyData As String
- Dim lpKeyName As String
- Dim ret As String
-
- ' call the API passing lpKeyName = null. This causes
- ' the API to return a list of all keys under that section.
- ' Pad the passed string large enough to hold the data.
- ret = Space$(2048)
- nSize = Len(ret)
- success = GetPrivateProfileString( _
- lpSectionName, vbNullString, "", ret, nSize, inifile)
-
- ' The returned string is a null-separated list of key names,
- ' terminated by a pair of null characters.
- ' If the Get call was successful, success holds the length of the
- ' string in ret up to but not including that second terminating null.
- ' The ProfileGetItem function below extracts each key item using the
- ' nulls as markers, so trim off the terminating null.
- If success Then
-
- 'trim terminating null and trailing spaces
- ret = Left$(ret, success)
-
- 'with the resulting string extract each element
- Do Until ret = ""
- 'strip off an item (i.e. "Item1", "Item2")
- lpKeyName = StripNulls(ret)
-
- 'pass the lpKeyName received to a routine that
- 'again calls GetPrivateProfileString, this
- 'time passing the real key name. Returned
- 'is the value associated with that key,
- 'ie the "Apple" corresponding to the ini
- 'entry "Item1=Apple"
- KeyData = ProfileGetItem( _
- lpSectionName, lpKeyName, "", inifile)
-
- 'add the item retruned to the listbox
- lst.AddItem KeyData
- Loop
-
- End If
-
- 'return the number of items as an
- 'indicator of success
- ProfileLoadList = lst.ListCount
-End Function
-
-Public Function ProfileLoadDict(dict As Scripting.Dictionary, _
- lpSectionName As String, _
- inifile As String) As Long
- Dim success As Long
- Dim c As Long
- Dim nSize As Long
- Dim KeyData As String
- Dim lpKeyName As String
- Dim ret As String
-
- ' call the API passing lpKeyName = null. This causes
- ' the API to return a list of all keys under that section.
- ' Pad the passed string large enough to hold the data.
- ret = Space$(2048)
- nSize = Len(ret)
- success = GetPrivateProfileString( _
- lpSectionName, vbNullString, "", ret, nSize, inifile)
-
- ' The returned string is a null-separated list of key names,
- ' terminated by a pair of null characters.
- ' If the Get call was successful, success holds the length of the
- ' string in ret up to but not including that second terminating null.
- ' The ProfileGetItem function below extracts each key item using the
- ' nulls as markers, so trim off the terminating null.
- If success Then
-
- 'trim terminating null and trailing spaces
- ret = Left$(ret, success)
-
- 'with the resulting string extract each element
- Do Until ret = ""
- 'strip off an item (i.e. "Item1", "Item2")
- lpKeyName = StripNulls(ret)
-
- 'pass the lpKeyName received to a routine that
- 'again calls GetPrivateProfileString, this
- 'time passing the real key name. Returned
- 'is the value associated with that key,
- 'ie the "Apple" corresponding to the ini
- 'entry "Item1=Apple"
- KeyData = ProfileGetItem( _
- lpSectionName, lpKeyName, "", inifile)
-
- dict.add lpKeyName, KeyData
- Loop
-
- End If
-
- ProfileLoadDict = dict.count
-End Function
-
-
-
-
-
-
-
diff --git a/migrationanalysis/src/wizard/LaunchDrivers.vbp b/migrationanalysis/src/wizard/LaunchDrivers.vbp
deleted file mode 100644
index ac94808700dd..000000000000
--- a/migrationanalysis/src/wizard/LaunchDrivers.vbp
+++ /dev/null
@@ -1,42 +0,0 @@
-Type=Exe
-Reference=*\G{00020430-0000-0000-C000-000000000046}#2.0#0#C:\WINDOWS\system32\stdole2.tlb#OLE Automation
-Reference=*\G{00020813-0000-0000-C000-000000000046}#1.3#0#C:\Program Files\Microsoft Office\Office\EXCEL9.OLB#Microsoft Excel 9.0 Object Library
-Reference=*\G{2DF8D04C-5BFA-101B-BDE5-00AA0044DE52}#2.1#0#C:\Program Files\Microsoft Office\Office\mso9.dll#Microsoft Office 9.0 Object Library
-Reference=*\G{91493440-5A91-11CF-8700-00AA0060263B}#2.6#0#C:\Program Files\Microsoft Office\Office\msppt9.olb#Microsoft PowerPoint 9.0 Object Library
-Reference=*\G{00020905-0000-0000-C000-000000000046}#8.1#0#C:\Program Files\Microsoft Office\Office\MSWORD9.OLB#Microsoft Word 9.0 Object Library
-Reference=*\G{420B2830-E718-11CF-893D-00A0C9054228}#1.0#0#C:\WINDOWS\system32\scrrun.dll#Microsoft Scripting Runtime
-Module=RunServer; ..\..\src\wizard\RunServer.bas
-Startup="Sub Main"
-HelpFile=""
-Title="LaunchDrivers"
-ExeName32="LaunchDrivers.exe"
-Path32="..\bin"
-Command32=""
-Name="LaunchDrivers"
-HelpContextID="0"
-CompatibleMode="0"
-MajorVer=2
-MinorVer=0
-RevisionVer=000
-AutoIncrementVer=0
-ServerSupportFiles=0
-VersionCompanyName="OpenOffice.org"
-VersionLegalCopyright="Copyright 2000, 2010 Oracle and/or its affiliates."
-CompilationType=0
-OptimizationType=0
-FavorPentiumPro(tm)=0
-CodeViewDebugInfo=0
-NoAliasing=0
-BoundsCheck=0
-OverflowCheck=0
-FlPointCheck=0
-FDIVCheck=0
-UnroundedFP=0
-StartMode=0
-Unattended=0
-Retained=0
-ThreadPerObject=0
-MaxNumberOfThreads=1
-
-[MS Transaction Server]
-AutoRefresh=1
diff --git a/migrationanalysis/src/wizard/LaunchDrivers.vbw b/migrationanalysis/src/wizard/LaunchDrivers.vbw
deleted file mode 100644
index af96d226e68a..000000000000
--- a/migrationanalysis/src/wizard/LaunchDrivers.vbw
+++ /dev/null
@@ -1 +0,0 @@
-RunServer = 22, 22, 301, 626, Z
diff --git a/migrationanalysis/src/wizard/OOo3_Analysis.ico b/migrationanalysis/src/wizard/OOo3_Analysis.ico
deleted file mode 100644
index d12f42d2f868..000000000000
--- a/migrationanalysis/src/wizard/OOo3_Analysis.ico
+++ /dev/null
Binary files differ
diff --git a/migrationanalysis/src/wizard/OOo_AnalysisBitmap.png b/migrationanalysis/src/wizard/OOo_AnalysisBitmap.png
deleted file mode 100644
index 6d852d90c5ae..000000000000
--- a/migrationanalysis/src/wizard/OOo_AnalysisBitmap.png
+++ /dev/null
Binary files differ
diff --git a/migrationanalysis/src/wizard/Office10Issues.bas b/migrationanalysis/src/wizard/Office10Issues.bas
deleted file mode 100644
index 948cd096ffed..000000000000
--- a/migrationanalysis/src/wizard/Office10Issues.bas
+++ /dev/null
@@ -1,352 +0,0 @@
-Attribute VB_Name = "Office10Issues"
-'
-' This file is part of the LibreOffice project.
-'
-' This Source Code Form is subject to the terms of the Mozilla Public
-' License, v. 2.0. If a copy of the MPL was not distributed with this
-' file, You can obtain one at http://mozilla.org/MPL/2.0/.
-'
-' This file incorporates work covered by the following license notice:
-'
-' Licensed to the Apache Software Foundation (ASF) under one or more
-' contributor license agreements. See the NOTICE file distributed
-' with this work for additional information regarding copyright
-' ownership. The ASF licenses this file to you under the Apache
-' License, Version 2.0 (the "License"); you may not use this file
-' except in compliance with the License. You may obtain a copy of
-' the License at http://www.apache.org/licenses/LICENSE-2.0 .
-'
-
-'Disable Option Explicit so this will compile on earlier Office versions
-'Option Explicit
-Public Declare Function RegCloseKey Lib "advapi32.dll" _
- (ByVal hKey As Long) As Long
-Public Declare Function RegQueryValueEx Lib "advapi32.dll" _
- Alias "RegQueryValueExA" (ByVal hKey As Long, ByVal lpValueName As String, _
- ByVal lpReserved As Long, lpType As Long, lpData As Any, _
- lpcbData As Long) As Long
-Public Declare Function RegSetValueEx Lib "advapi32.dll" _
- Alias "RegSetValueExA" (ByVal hKey As Long, ByVal lpValueName As String, _
- ByVal Reserved As Long, ByVal dwType As Long, lpData As Any, _
- ByVal cbData As Long) As Long
-Public Declare Function RegCreateKeyEx Lib "advapi32.dll" Alias "RegCreateKeyExA" (ByVal _
- hKey As Long, ByVal lpSubKey As String, ByVal Reserved As Long, ByVal lpClass _
- As String, ByVal dwOptions As Long, ByVal samDesired As Long, lpSecurityAttributes _
- As SECURITY_ATTRIBUTES, phkResult As Long, lpdwDisposition As Long) As Long
-Public Declare Function RegOpenKey Lib "advapi32.dll" _
- Alias "RegOpenKeyA" (ByVal hKey As Long, ByVal lpSubKey As String, _
- phkResult As Long) As Long
-Public Declare Function RegCreateKey Lib "advapi32.dll" _
- Alias "RegCreateKeyA" (ByVal hKey As Long, ByVal lpSubKey As String, _
- phkResult As Long) As Long
-Public Declare Function RegDeleteValue Lib "advapi32.dll" _
- Alias "RegDeleteValueA" (ByVal hKey As Long, _
- ByVal lpValueName As String) As Long
-Public Declare Function RegOpenKeyEx Lib "advapi32.dll" Alias "RegOpenKeyExA" (ByVal _
- hKey As Long, ByVal lpSubKey As String, ByVal ulOptions As Long, ByVal samDesired _
- As Long, phkResult As Long) As Long
-
-Type SECURITY_ATTRIBUTES
- nLength As Long
- lpSecurityDescriptor As Long
- bInheritHandle As Long
-End Type
-
-Enum RegHive
- 'HKEY_CLASSES_ROOT = &H80000000
- HK_CR = &H80000000
- HKEY_CURRENT_USER = &H80000001
- HK_CU = &H80000001
- HKEY_LOCAL_MACHINE = &H80000002
- HK_LM = &H80000002
- HKEY_USERS = &H80000003
- HK_US = &H80000003
- HKEY_CURRENT_CONFIG = &H80000005
- HK_CC = &H80000005
- HKEY_DYN_DATA = &H80000006
- HK_DD = &H80000006
-End Enum
-
-Enum RegType
- REG_SZ = 1 'Unicode nul terminated string
- REG_BINARY = 3 'Free form binary
- REG_DWORD = 4 '32-bit number
-End Enum
-
-Const ERROR_SUCCESS = 0
-Const KEY_WRITE = &H20006
-Const APP_EXCEL = "Excel"
-Const APP_WORD = "Word"
-Const APP_PP = "PowerPoint"
-
-Public Function CreateRegKey(hKey As RegHive, strPath As String)
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "CreateRegKey"
-
- Dim heKey As Long
- Dim secattr As SECURITY_ATTRIBUTES ' security settings for the key
- Dim subkey As String ' name of the subkey to create or open
- Dim neworused As Long ' receives flag for if the key was created or opened
- Dim stringbuffer As String ' the string to put into the registry
- Dim retval As Long ' return value
-
- ' Set the name of the new key and the default security settings
- secattr.nLength = Len(secattr)
- secattr.lpSecurityDescriptor = 0
- secattr.bInheritHandle = 1
-
- retval = RegCreateKeyEx(hKey, strPath, 0, "", 0, KEY_WRITE, _
- secattr, heKey, neworused)
- If retval = 0 Then
- retval = RegCloseKey(hKey)
- Exit Function
- End If
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
-End Function
-
-Public Function CreateRegKey2(hKey As RegHive, strPath As String) As Long
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "CreateRegKey"
- CreateRegKey2 = 0
-
- Dim heKey As Long
- Dim secattr As SECURITY_ATTRIBUTES ' security settings for the key
- Dim subkey As String ' name of the subkey to create or open
- Dim neworused As Long ' receives flag for if the key was created or opened
- Dim stringbuffer As String ' the string to put into the registry
- Dim retval As Long ' return value
-
- ' Set the name of the new key and the default security settings
- secattr.nLength = Len(secattr)
- secattr.lpSecurityDescriptor = 0
- secattr.bInheritHandle = 1
-
- retval = RegCreateKeyEx(hKey, strPath, 0, "", 0, KEY_WRITE, _
- secattr, heKey, neworused)
- If retval = ERROR_SUCCESS Then
- CreateRegKey2 = heKey
- Exit Function
- End If
-
-FinalExit:
- Exit Function
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- CreateRegKey2 = 0
- GoTo FinalExit
-End Function
-
-
-Public Function GetRegLong(ByVal hKey As RegHive, ByVal strPath As String, ByVal strValue As String) As Long
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "GetRegLong"
-
- Dim lRegResult As Long
- Dim lValueType As Long
- Dim lBuffer As Long
- Dim lDataBufferSize As Long
- Dim hCurKey As Long
-
- GetRegLong = 0
- lRegResult = RegOpenKey(hKey, strPath, hCurKey)
- lDataBufferSize = 4 '4 bytes = 32 bits = long
-
- lRegResult = RegQueryValueEx(hCurKey, strValue, 0, REG_DWORD, lBuffer, lDataBufferSize)
- If lRegResult = ERROR_SUCCESS Then
- GetRegLong = lBuffer
- End If
- lRegResult = RegCloseKey(hCurKey)
- Exit Function
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
-End Function
-
-Public Function SaveRegLong(ByVal hKey As RegHive, ByVal strPath As String, ByVal strValue As String, ByVal lData As Long)
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "SaveRegLong"
-
- Const NumofByte = 4
- Dim hCurKey As Long
- Dim lRegResult As Long
-
- lRegResult = RegCreateKey(hKey, strPath, hCurKey)
- lRegResult = RegSetValueEx(hCurKey, strValue, 0&, REG_DWORD, lData, NumofByte)
- If lRegResult = ERROR_SUCCESS Then
- lRegResult = RegCloseKey(hCurKey)
- Exit Function
- End If
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
-End Function
-
-
-Public Function GiveAccessToMacroProject(application As String, sVersion As String, oldvalue As Long) As Boolean
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "SaveRegLong"
- GiveAccessToMacroProject = False
-
- Const OfficePath = "Software\Policies\Microsoft\Office\"
- Const security = "\Security"
- Const AccessVBOM = "AccessVBOM"
- Const AccessVBOMValue = 1
- Dim subpath As String
- Dim RegistryValue As Long
-
- subpath = OfficePath & sVersion & "\" & application & security
- CreateRegKey HKEY_CURRENT_USER, subpath
- RegistryValue = GetRegLong(HKEY_CURRENT_USER, subpath, AccessVBOM)
- oldvalue = RegistryValue
- SaveRegLong HKEY_CURRENT_USER, subpath, AccessVBOM, AccessVBOMValue
- GiveAccessToMacroProject = True
- Exit Function
-
-HandleErrors:
- GiveAccessToMacroProject = False
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
-End Function
-
-Public Function SetDefaultRegValue(application As String, sVersion As String, sValue As Long)
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "SaveRegLong"
-
- Const OfficePath = "Software\Policies\Microsoft\Office\"
- Const security = "\Security"
- Const AccessVBOM = "AccessVBOM"
- Dim subpath As String
-
- subpath = OfficePath & sVersion & "\" & application & security
- SaveRegLong HKEY_CURRENT_USER, subpath, AccessVBOM, sValue
- Exit Function
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
-End Function
-Public Function DeleteRegValue(application As String, sVersion As String)
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "SaveRegLong"
-
- Const OfficePath = "Software\Policies\Microsoft\Office\"
- Const security = "\Security"
- Const AccessVBOM = "AccessVBOM"
- Dim subpath As String
- Dim retval As Long
- Dim hKey As Long
-
- subpath = OfficePath & sVersion & "\" & application & security
- retval = RegOpenKeyEx(HKEY_CURRENT_USER, subpath, 0, KEY_WRITE, hKey)
- If retval = ERROR_SUCCESS Then
- retval = RegDeleteValue(hKey, AccessVBOM)
- retval = RegCloseKey(hKey)
- Exit Function
- End If
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
-End Function
-
-Public Function CheckForAccesToWordVBProject1(wrd As Word.application, RestoreValue As Long) As Boolean
- On Error Resume Next
- CheckForAccesToWordVBProject1 = True
- RestoreValue = -1
- If val(wrd.Version) < 10# Then Exit Function
-
- Set myProject = wrd.ActiveDocument.VBProject
- If Err.Number <> 0 Then
- Dim RegValue As Long
- If GiveAccessToMacroProject(APP_WORD, wrd.Version, RegValue) Then
- CheckForAccesToWordVBProject1 = True
- RestoreValue = RegValue
- Else
- CheckForAccesToWordVBProject1 = False
- End If
- End If
-
-End Function
-Public Function CheckForAccesToWordVBProject(wrd As Word.application) As Boolean
- On Error Resume Next
- CheckForAccesToWordVBProject = True
- If val(wrd.Version) < 10# Then Exit Function
-
- Set myProject = wrd.ActiveDocument.VBProject
- If Err.Number <> 0 Then
- CheckForAccesToWordVBProject = False
- End If
-
-End Function
-Public Function CheckForAccesToExcelVBProject1(xl As Excel.application, RestoreValue As Long) As Boolean
- On Error Resume Next
- CheckForAccesToExcelVBProject1 = True
- RestoreValue = -1
- If val(xl.Version) < 10# Then Exit Function
-
- Dim displayAlerts As Boolean
- displayAlerts = xl.displayAlerts
- xl.displayAlerts = False
- Set myProject = xl.ActiveWorkbook.VBProject
- If Err.Number <> 0 Then
- Dim RegValue As Long
- If GiveAccessToMacroProject(APP_EXCEL, xl.Version, RegValue) Then
- CheckForAccesToExcelVBProject1 = True
- RestoreValue = RegValue
- Else
- CheckForAccesToExcelVBProject1 = False
- End If
- End If
- xl.displayAlerts = displayAlerts
-
-End Function
-Public Function CheckForAccesToExcelVBProject(xl As Excel.application) As Boolean
- On Error Resume Next
- CheckForAccesToExcelVBProject = True
- If val(xl.Version) < 10# Then Exit Function
-
- Dim displayAlerts As Boolean
- displayAlerts = xl.displayAlerts
- xl.displayAlerts = False
- Set myProject = xl.ActiveWorkbook.VBProject
- If Err.Number <> 0 Then
- CheckForAccesToExcelVBProject = False
- End If
- xl.displayAlerts = displayAlerts
-
-End Function
-Public Function CheckForAccesToPPVBProject1(pp As PowerPoint.application, pres As PowerPoint.Presentation, RestoreValue As Long) As Boolean
- On Error Resume Next
- CheckForAccesToPPVBProject1 = True
- RestoreValue = -1
- If val(pp.Version) < 10# Then Exit Function
-
- Set myProject = pres.VBProject
- If Err.Number <> 0 Then
- Dim RegValue As Long
- If GiveAccessToMacroProject(APP_PP, pp.Version, RegValue) Then
- CheckForAccesToPPVBProject1 = True
- RestoreValue = RegValue
- Else
- CheckForAccesToPPVBProject1 = False
- End If
- End If
-End Function
-
-Public Function CheckForAccesToPPVBProject(pp As PowerPoint.application, pres As PowerPoint.Presentation) As Boolean
- On Error Resume Next
- CheckForAccesToPPVBProject = True
- If val(pp.Version) < 10# Then Exit Function
-
- Set myProject = pres.VBProject
- If Err.Number <> 0 Then
- CheckForAccesToPPVBProject = False
- End If
-End Function
diff --git a/migrationanalysis/src/wizard/ProAnalysisWizard.vbp b/migrationanalysis/src/wizard/ProAnalysisWizard.vbp
deleted file mode 100644
index 982f96631d5a..000000000000
--- a/migrationanalysis/src/wizard/ProAnalysisWizard.vbp
+++ /dev/null
@@ -1,65 +0,0 @@
-Type=Exe
-Reference=*\G{00020430-0000-0000-C000-000000000046}#2.0#0#..\..\..\..\..\WINDOWS\System32\stdole2.tlb#Standard OLE Types
-Reference=*\G{EF404E00-EDA6-101A-8DAF-00DD010F7EBB}#5.0#0#..\..\..\..\..\Program Files\Microsoft Visual Studio\VB98\VB6EXT.OLB#Microsoft Visual Basic Extensibility
-Reference=*\G{AC0714F2-3D04-11D1-AE7D-00A0C90F26F4}#1.0#0#..\..\..\..\..\Program Files\Common Files\Designer\MSADDNDR.DLL#Add-In Designer/Instance Control Library
-Reference=*\G{00025E01-0000-0000-C000-000000000046}#4.0#0#..\..\..\..\..\Program Files\Common Files\Microsoft Shared\DAO\DAO350.DLL#Microsoft DAO 3.51 Object Library
-Reference=*\G{420B2830-E718-11CF-893D-00A0C9054228}#1.0#0#..\..\..\..\..\WINDOWS\System32\scrrun.dll#Microsoft Scripting Runtime
-Reference=*\G{00020813-0000-0000-C000-000000000046}#1.3#0#..\..\..\..\..\Program Files\Microsoft Office\Office\EXCEL9.OLB#Microsoft Excel 9.0 Object Library
-Reference=*\G{2DF8D04C-5BFA-101B-BDE5-00AA0044DE52}#2.1#0#..\..\..\..\..\Program Files\Microsoft Office\Office\mso9.dll#Microsoft Office 9.0 Object Library
-Reference=*\G{00020905-0000-0000-C000-000000000046}#8.1#0#..\..\..\..\..\Program Files\Microsoft Office\Office\MSWORD9.OLB#Microsoft Word 9.0 Object Library
-Reference=*\G{91493440-5A91-11CF-8700-00AA0060263B}#2.6#0#..\..\..\..\..\Program Files\Microsoft Office\Office\msppt9.olb#Microsoft PowerPoint 9.0 Object Library
-Module=modWizard; ..\..\..\src\wizard\Wizard.bas
-Form=..\..\..\src\wizard\Wizard.frm
-Designer=..\..\..\src\wizard\Wizard.Dsr
-Module=BrowseDirectorysOnly; ..\..\..\src\wizard\Get Directory Dialog.bas
-Class=CollectedFiles; ..\..\..\src\wizard\CollectedFiles.cls
-Module=IniSupport; ..\..\..\src\wizard\IniSupport.bas
-Module=Utilities; ..\..\..\src\wizard\Utilities.bas
-Module=Office10Issues; ..\..\..\src\wizard\Office10Issues.bas
-Module=Analyse; ..\..\..\src\wizard\Analyse.bas
-Form=..\..\..\src\wizard\ScanFolders.frm
-Form=..\..\..\src\wizard\SearchDocs.frm
-Form=..\..\..\src\wizard\Terminate.frm
-Object={86CF1D34-0C5F-11D2-A9FC-0000F8754DA1}#2.0#0; MSCOMCT2.OCX
-Object={831FDD16-0C5C-11D2-A9FC-0000F8754DA1}#2.0#0; mscomctl.ocx
-IconForm="frmWizard"
-Startup="frmWizard"
-HelpFile=""
-Title="Professional Analysis Wizard"
-ExeName32="ProAnalysisWizard.exe"
-Path32="..\..\bin\ProAnalysisWizard"
-Command32=""
-Name="ProAnalysisWizard"
-HelpContextID="0"
-Description="Professional Analysis Wizard"
-CompatibleMode="0"
-MajorVer=2
-MinorVer=0
-RevisionVer=000
-AutoIncrementVer=0
-ServerSupportFiles=0
-VersionComments="A tool for analyzing issues and working around some of them when migrating documents from Microsoft Office"
-VersionCompanyName="OpenOffice.org"
-VersionFileDescription="ProAnalysisWizard.exe"
-VersionLegalCopyright="Copyright 2000, 2010 Oracle and/or its affiliates."
-VersionProductName="ProAnalysisWizard"
-CondComp="VB5 = 1 : PREPARATION = 1"
-CompilationType=-1
-OptimizationType=0
-FavorPentiumPro(tm)=0
-CodeViewDebugInfo=-1
-NoAliasing=0
-BoundsCheck=0
-OverflowCheck=0
-FlPointCheck=0
-FDIVCheck=0
-UnroundedFP=0
-StartMode=0
-Unattended=0
-Retained=0
-ThreadPerObject=0
-MaxNumberOfThreads=1
-DebugStartupOption=0
-
-[MS Transaction Server]
-AutoRefresh=1
diff --git a/migrationanalysis/src/wizard/RunServer.bas b/migrationanalysis/src/wizard/RunServer.bas
deleted file mode 100644
index 4ccab5629929..000000000000
--- a/migrationanalysis/src/wizard/RunServer.bas
+++ /dev/null
@@ -1,190 +0,0 @@
-Attribute VB_Name = "RunServer"
-'
-' This file is part of the LibreOffice project.
-'
-' This Source Code Form is subject to the terms of the Mozilla Public
-' License, v. 2.0. If a copy of the MPL was not distributed with this
-' file, You can obtain one at http://mozilla.org/MPL/2.0/.
-'
-' This file incorporates work covered by the following license notice:
-'
-' Licensed to the Apache Software Foundation (ASF) under one or more
-' contributor license agreements. See the NOTICE file distributed
-' with this work for additional information regarding copyright
-' ownership. The ASF licenses this file to you under the Apache
-' License, Version 2.0 (the "License"); you may not use this file
-' except in compliance with the License. You may obtain a copy of
-' the License at http://www.apache.org/licenses/LICENSE-2.0 .
-'
-
-Option Explicit
-
-Private Declare Function WritePrivateProfileString Lib "kernel32" _
- Alias "WritePrivateProfileStringA" _
- (ByVal lpSectionName As String, _
- ByVal lpKeyName As Any, _
- ByVal lpString As Any, _
- ByVal lpFileName As String) As Long
-
-Const CWORD_DRIVER = "_OOoDocAnalysisWordDriver.doc"
-Const CEXCEL_DRIVER = "_OOoDocAnalysisExcelDriver.xls"
-Const CPP_DRIVER = "_OOoDocAnalysisPPTDriver.ppt"
-
-Const CWORD_APP = "word"
-Const CEXCEL_APP = "excel"
-Const CPP_APP = "pp"
-
-Const CSTART_FILE = "PAW_Start_Analysis"
-Const CSTOP_FILE = "PAW_Stop_Analysis"
-
-Sub Main()
-
- Dim serverType As String
- serverType = LCase(Command$)
- If (serverType <> CWORD_APP) And (serverType <> CEXCEL_APP) And (serverType <> CPP_APP) Then
- MsgBox "Unknown server type: " & serverType
- GoTo FinalExit
- End If
-
- Dim fso As New FileSystemObject
- Dim driverName As String
-
- If (serverType = CWORD_APP) Then
- driverName = fso.GetAbsolutePathName(".\" & CWORD_DRIVER)
- ElseIf (serverType = CEXCEL_APP) Then
- driverName = fso.GetAbsolutePathName(".\" & CEXCEL_DRIVER)
- ElseIf (serverType = CPP_APP) Then
- driverName = fso.GetAbsolutePathName(".\" & CPP_DRIVER)
- End If
-
- If Not fso.FileExists(driverName) Then
- If (serverType = CWORD_APP) Then
- driverName = fso.GetAbsolutePathName(".\Resources\" & CWORD_DRIVER)
- ElseIf (serverType = CEXCEL_APP) Then
- driverName = fso.GetAbsolutePathName(".\Resources\" & CEXCEL_DRIVER)
- ElseIf (serverType = CPP_APP) Then
- driverName = fso.GetAbsolutePathName(".\Resources\" & CPP_DRIVER)
- End If
- End If
-
- If Not fso.FileExists(driverName) Then
- WriteToLog fso, "ALL", "LaunchDrivers: Could not find: " & driverName
- GoTo FinalExit
- End If
-
- If (serverType = CWORD_APP) Then
- OpenWordDriverDoc fso, driverName
- ElseIf (serverType = CEXCEL_APP) Then
- OpenExcelDriverDoc fso, driverName
- ElseIf (serverType = CPP_APP) Then
- OpenPPDriverDoc fso, driverName
- End If
-
-FinalExit:
-
- Set fso = Nothing
-End Sub
-
-Sub OpenWordDriverDoc(fso As FileSystemObject, driverName As String)
-
- Dim wrdApp As Word.Application
- Dim wrdDriverDoc As Word.Document
-
- On Error GoTo HandleErrors
-
- Set wrdApp = New Word.Application
- Set wrdDriverDoc = wrdApp.Documents.Open(driverName)
-
- wrdApp.Run ("AnalysisTool.AnalysisDriver.AnalyseDirectory")
- If Err.Number <> 0 Then
- WriteToLog fso, CWORD_APP, "OpenWordDriverDoc: " & Err.Number & " " & Err.Description & " " & Err.Source
- End If
-
- wrdDriverDoc.Close wdDoNotSaveChanges
- wrdApp.Quit False
-
-FinalExit:
- Set wrdDriverDoc = Nothing
- Set wrdApp = Nothing
- Exit Sub
-
-HandleErrors:
- WriteToLog fso, CWORD_APP, "OpenWordDriverDoc: " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Sub
-
-Sub OpenExcelDriverDoc(fso As FileSystemObject, driverName As String)
-
- Dim excelApp As Excel.Application
- Dim excelDriverDoc As Excel.Workbook
-
- On Error GoTo HandleErrors
-
- Set excelApp = New Excel.Application
- Set excelDriverDoc = Excel.Workbooks.Open(driverName)
- excelApp.Run ("AnalysisTool.AnalysisDriver.AnalyseDirectory")
-
- If Err.Number <> 0 Then
- WriteToLog fso, CEXCEL_APP, "OpenExcelDriverDoc: " & Err.Number & " " & Err.Description & " " & Err.Source
- End If
-
- excelDriverDoc.Close False
- excelApp.Quit
-
-FinalExit:
- Set excelDriverDoc = Nothing
- Set excelApp = Nothing
- Exit Sub
-
-HandleErrors:
- WriteToLog fso, CEXCEL_APP, "OpenExcelDriverDoc: " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Sub
-
-Sub OpenPPDriverDoc(fso As FileSystemObject, driverName As String)
-
- Dim ppApp As PowerPoint.Application
- Dim ppDriverDoc As PowerPoint.Presentation
- Dim ppDummy(0) As Variant
-
- On Error GoTo HandleErrors
-
- Set ppApp = New PowerPoint.Application
- ppApp.Visible = msoTrue
- Set ppDriverDoc = ppApp.Presentations.Open(driverName) ', msoTrue, msoFalse, msoFalse)
- ppApp.Run ("AnalysisDriver.AnalyseDirectory")
-
- If Err.Number <> 0 Then
- WriteToLog fso, CPP_APP, "OpenPPDriverDoc: " & Err.Number & " " & Err.Description & " " & Err.Source
- End If
-
- ppDriverDoc.Close
- ppApp.Quit
-
-FinalExit:
- Set ppDriverDoc = Nothing
- Set ppApp = Nothing
- Exit Sub
-
-HandleErrors:
- WriteToLog fso, CPP_APP, "OpenPPDriverDoc: " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Sub
-
-Sub WriteToLog(fso As FileSystemObject, currApp As String, errMsg As String)
-
- On Error Resume Next
-
- Static ErrCount As Long
- Dim logFileName As String
- Dim tempPath As String
-
- tempPath = fso.GetSpecialFolder(TemporaryFolder).Path
- If (tempPath = "") Then tempPath = "."
- logFileName = fso.GetAbsolutePathName(tempPath & "\LauchDrivers.log")
- ErrCount = ErrCount + 1
-
- Call WritePrivateProfileString("ERRORS", currApp & "_log" & ErrCount, _
- errMsg, logFileName)
-End Sub
-
diff --git a/migrationanalysis/src/wizard/ScanFolders.frm b/migrationanalysis/src/wizard/ScanFolders.frm
deleted file mode 100644
index 4c725f5dbeb3..000000000000
--- a/migrationanalysis/src/wizard/ScanFolders.frm
+++ /dev/null
@@ -1,157 +0,0 @@
-VERSION 5.00
-Object = "{831FDD16-0C5C-11D2-A9FC-0000F8754DA1}#2.0#0"; "MSCOMCTL.ocx"
-Begin VB.Form ShowProgress
- BorderStyle = 1 'Fixed Single
- Caption = "Looking for Files"
- ClientHeight = 2160
- ClientLeft = 2505
- ClientTop = 2325
- ClientWidth = 7110
- ControlBox = 0 'False
- LinkTopic = "Form1"
- MaxButton = 0 'False
- MinButton = 0 'False
- ScaleHeight = 2160
- ScaleWidth = 7110
- ShowInTaskbar = 0 'False
- Visible = 0 'False
- Begin MSComctlLib.ProgressBar ScanProgress
- Height = 255
- Left = 120
- TabIndex = 2
- Top = 1400
- Width = 5500
- _ExtentX = 9710
- _ExtentY = 450
- _Version = 393216
- Appearance = 1
- End
- Begin VB.CommandButton AbortScan
- Cancel = -1 'True
- Caption = "Cancel"
- CausesValidation= 0 'False
- Height = 375
- Left = 2880
- TabIndex = 1
- Top = 1760
- Width = 1455
- End
- Begin VB.Label Label6
- Caption = "X / Y"
- Height = 195
- Left = 5760
- TabIndex = 7
- Top = 1430
- Width = 1200
- End
- Begin VB.Label Label5
- Caption = "Label5"
- Height = 440
- Left = 120
- TabIndex = 6
- Top = 120
- Width = 6870
- End
- Begin VB.Label Label4
- Caption = "Label4"
- Height = 195
- Left = 120
- TabIndex = 5
- Top = 995
- Width = 1155
- End
- Begin VB.Label Label3
- Caption = "Label3"
- Height = 195
- Left = 120
- TabIndex = 4
- Top = 680
- Width = 1155
- End
- Begin VB.Label Label2
- Caption = "Label2"
- Height = 195
- Left = 1395
- TabIndex = 3
- Top = 995
- Width = 5595
- End
- Begin VB.Label Label1
- Caption = "Label1"
- Height = 195
- Left = 1395
- TabIndex = 0
- Top = 680
- Width = 5595
- End
-End
-Attribute VB_Name = "ShowProgress"
-Attribute VB_GlobalNameSpace = False
-Attribute VB_Creatable = False
-Attribute VB_PredeclaredId = True
-Attribute VB_Exposed = False
-Option Explicit
-
-Private Declare Function GetTickCount Lib "kernel32" () As Long
-
-Private Const C_MIN_WAIT_TIME As Long = 0
-Private Const C_MIN_UPDATE_TIME As Long = 100
-
-Private g_SP_StartTime As Long
-Private g_SP_LastUpdate As Long
-
-Public g_SP_Abort As Boolean
-Public g_SP_AllowOtherDLG As Boolean
-
-Public Sub SP_Init(maxIndex As Long)
- g_SP_Abort = False
- g_SP_AllowOtherDLG = False
- g_SP_StartTime = GetTickCount()
- g_SP_LastUpdate = g_SP_StartTime
-
- ShowProgress.Visible = False
- ShowProgress.Caption = GetResString(PROGRESS_CAPTION)
-
- Label3.Caption = GetResString(PROGRESS_PATH_LABEL)
- Label4.Caption = GetResString(PROGRESS_FILE_LABEL)
- Label5.Caption = GetResString(PROGRESS_INFO_LABEL)
- ScanProgress.Max = maxIndex
-
- ShowProgress.Top = frmWizard.Top + 3200
- ShowProgress.Left = frmWizard.Left + 500
-End Sub
-
-Public Sub SP_UpdateProgress(curObject As String, curParent As String, _
- curIndex As Long)
-
- Dim currTicks As Long
- currTicks = GetTickCount()
-
- ScanProgress.value = curIndex
-
- If (Not ShowProgress.Visible) Then
- If (currTicks - g_SP_StartTime > C_MIN_WAIT_TIME) Then
- ShowProgress.Visible = True
- End If
- End If
- If (currTicks - g_SP_LastUpdate > C_MIN_UPDATE_TIME) Then
- g_SP_LastUpdate = currTicks
- Label1.Caption = curParent
- Label2.Caption = curObject
- Label6.Caption = "(" & str$(curIndex) & "/" & str$(ScanProgress.Max) & ")"
- End If
-End Sub
-
-Private Sub AbortScan_Click()
- g_SP_Abort = True
- Label5.Caption = GetResString(PROGRESS_WAIT_LABEL)
- AbortScan.Caption = GetResString(PROGRESS_ABORTING)
- AbortScan.Enabled = False
-End Sub
-
-Private Sub Form_Deactivate()
- If Not g_SP_AllowOtherDLG Then
- ShowProgress.ZOrder (0)
- End If
-End Sub
-
diff --git a/migrationanalysis/src/wizard/SearchDocs.frm b/migrationanalysis/src/wizard/SearchDocs.frm
deleted file mode 100644
index 571f8a23cc9b..000000000000
--- a/migrationanalysis/src/wizard/SearchDocs.frm
+++ /dev/null
@@ -1,124 +0,0 @@
-VERSION 5.00
-Begin VB.Form SearchDocs
- BorderStyle = 3 'Fixed Dialog
- Caption = "Looking for Files"
- ClientHeight = 1830
- ClientLeft = 2505
- ClientTop = 2325
- ClientWidth = 7110
- ControlBox = 0 'False
- LinkTopic = "Form1"
- MaxButton = 0 'False
- MinButton = 0 'False
- ScaleHeight = 1830
- ScaleWidth = 7110
- ShowInTaskbar = 0 'False
- Visible = 0 'False
- Begin VB.CommandButton AbortScan
- Cancel = -1 'True
- Caption = "Cancel"
- CausesValidation= 0 'False
- Height = 375
- Left = 2880
- TabIndex = 1
- Top = 1350
- Width = 1455
- End
- Begin VB.Label Label5
- Caption = "Label5"
- Height = 440
- Left = 120
- TabIndex = 5
- Top = 120
- Width = 6870
- WordWrap = -1 'True
- End
- Begin VB.Label Label4
- Caption = "gefundene Dokumente:"
- Height = 195
- Left = 120
- TabIndex = 4
- Top = 960
- Width = 1800
- End
- Begin VB.Label Label3
- Caption = "Pfad:"
- Height = 195
- Left = 120
- TabIndex = 3
- Top = 680
- Width = 1800
- End
- Begin VB.Label Label2
- Caption = "Label2"
- Height = 195
- Left = 2040
- TabIndex = 2
- Top = 995
- Width = 5595
- End
- Begin VB.Label Label1
- Caption = "Label1"
- Height = 195
- Left = 2040
- TabIndex = 0
- Top = 680
- Width = 5595
- End
-End
-Attribute VB_Name = "SearchDocs"
-Attribute VB_GlobalNameSpace = False
-Attribute VB_Creatable = False
-Attribute VB_PredeclaredId = True
-Attribute VB_Exposed = False
-Option Explicit
-
-Private Declare Function GetTickCount Lib "kernel32" () As Long
-
-Private Const C_MIN_WAIT_TIME As Long = 1000
-Private Const C_MIN_UPDATE_TIME As Long = 100
-
-Private g_SD_StartTime As Long
-Private g_SD_LastUpdate As Long
-
-Public g_SD_Abort As Boolean
-
-Private Sub Form_Load()
-
- g_SD_Abort = False
- g_SD_StartTime = GetTickCount()
- g_SD_LastUpdate = g_SD_StartTime
-
- SearchDocs.Visible = False
- SearchDocs.Caption = GetResString(SEARCH_CAPTION)
-
- Label3.Caption = GetResString(SEARCH_PATH_LABEL)
- Label4.Caption = GetResString(SEARCH_FOUND_LABEL)
- Label5.Caption = GetResString(SEARCH_INFO_LABEL)
-End Sub
-
-Public Sub SD_UpdateProgress(curObject As String, curParent As String)
-
- Dim currTicks As Long
- currTicks = GetTickCount()
-
- If (Not SearchDocs.Visible) Then
- If (currTicks - g_SD_StartTime > C_MIN_WAIT_TIME) Then
- SearchDocs.Visible = True
- End If
- End If
- If (currTicks - g_SD_LastUpdate > C_MIN_UPDATE_TIME) Then
- g_SD_LastUpdate = currTicks
- Label1.Caption = curParent
- Label2.Caption = curObject
- End If
-End Sub
-
-Private Sub AbortScan_Click()
- g_SD_Abort = True
-End Sub
-
-Private Sub Form_Deactivate()
- SearchDocs.ZOrder (0)
-End Sub
-
diff --git a/migrationanalysis/src/wizard/Terminate.frm b/migrationanalysis/src/wizard/Terminate.frm
deleted file mode 100644
index c196528fbd11..000000000000
--- a/migrationanalysis/src/wizard/Terminate.frm
+++ /dev/null
@@ -1,81 +0,0 @@
-VERSION 5.00
-Begin VB.Form TerminateMSO
- BorderStyle = 3 'Fixed Dialog
- Caption = "Dialog Caption"
- ClientHeight = 2280
- ClientLeft = 3165
- ClientTop = 2835
- ClientWidth = 6030
- ControlBox = 0 'False
- LinkTopic = "Form1"
- MaxButton = 0 'False
- MinButton = 0 'False
- ScaleHeight = 2280
- ScaleWidth = 6030
- ShowInTaskbar = 0 'False
- Begin VB.CommandButton NoButton
- Cancel = -1 'True
- Caption = "No"
- CausesValidation= 0 'False
- Default = -1 'True
- Height = 375
- Left = 4560
- TabIndex = 0
- Top = 1800
- Width = 1215
- End
- Begin VB.CommandButton YesButton
- Caption = "Yes"
- CausesValidation= 0 'False
- Height = 375
- Left = 3120
- TabIndex = 1
- Top = 1800
- Width = 1215
- End
- Begin VB.Label Info
- Caption = "Label1"
- Height = 1455
- Left = 120
- TabIndex = 2
- Top = 120
- Width = 5775
- End
-End
-Attribute VB_Name = "TerminateMSO"
-Attribute VB_GlobalNameSpace = False
-Attribute VB_Creatable = False
-Attribute VB_PredeclaredId = True
-Attribute VB_Exposed = False
-Option Explicit
-
-Const CR_STR = "<CR>"
-
-Private Sub Form_Activate()
- NoButton.Default = True
-End Sub
-
-Private Sub Form_Load()
-
- TerminateMSO.Top = frmWizard.Top + 3000
- TerminateMSO.Left = frmWizard.Left + 1000
-
- TerminateMSO.Caption = GetResString(TERMINATE_CAPTION)
- Info.Caption = ReplaceTopicTokens(GetResString(TERMINATE_INFO), CR_STR, Chr(13))
- YesButton.Caption = GetResString(TERMINATE_YES)
- NoButton.Caption = GetResString(TERMINATE_NO)
- NoButton.Default = True
-End Sub
-
-Private Sub YesButton_Click()
- Dim fso As New FileSystemObject
- TerminateOfficeApps fso, " --kill"
- TerminateMSO.Hide
- Set fso = Nothing
-End Sub
-
-Private Sub NoButton_Click()
- TerminateMSO.Hide
-End Sub
-
-
diff --git a/migrationanalysis/src/wizard/Utilities.bas b/migrationanalysis/src/wizard/Utilities.bas
deleted file mode 100644
index d51093fc9653..000000000000
--- a/migrationanalysis/src/wizard/Utilities.bas
+++ /dev/null
@@ -1,543 +0,0 @@
-Attribute VB_Name = "Utilities"
-'
-' This file is part of the LibreOffice project.
-'
-' This Source Code Form is subject to the terms of the Mozilla Public
-' License, v. 2.0. If a copy of the MPL was not distributed with this
-' file, You can obtain one at http://mozilla.org/MPL/2.0/.
-'
-' This file incorporates work covered by the following license notice:
-'
-' Licensed to the Apache Software Foundation (ASF) under one or more
-' contributor license agreements. See the NOTICE file distributed
-' with this work for additional information regarding copyright
-' ownership. The ASF licenses this file to you under the Apache
-' License, Version 2.0 (the "License"); you may not use this file
-' except in compliance with the License. You may obtain a copy of
-' the License at http://www.apache.org/licenses/LICENSE-2.0 .
-'
-Option Explicit
-
-Public Const LOCALE_ILANGUAGE As Long = &H1 'language id
-Public Const LOCALE_SLANGUAGE As Long = &H2 'localized name of lang
-Public Const LOCALE_SENGLANGUAGE As Long = &H1001 'English name of lang
-Public Const LOCALE_SABBREVLANGNAME As Long = &H3 'abbreviated lang name
-Public Const LOCALE_SNATIVELANGNAME As Long = &H4 'native name of lang
-Public Const LOCALE_ICOUNTRY As Long = &H5 'country code
-Public Const LOCALE_SCOUNTRY As Long = &H6 'localized name of country
-Public Const LOCALE_SENGCOUNTRY As Long = &H1002 'English name of country
-Public Const LOCALE_SABBREVCTRYNAME As Long = &H7 'abbreviated country name
-Public Const LOCALE_SNATIVECTRYNAME As Long = &H8 'native name of country
-Public Const LOCALE_SINTLSYMBOL As Long = &H15 'intl monetary symbol
-Public Const LOCALE_IDEFAULTLANGUAGE As Long = &H9 'def language id
-Public Const LOCALE_IDEFAULTCOUNTRY As Long = &HA 'def country code
-Public Const LOCALE_IDEFAULTCODEPAGE As Long = &HB 'def oem code page
-Public Const LOCALE_IDEFAULTANSICODEPAGE As Long = &H1004 'def ansi code page
-Public Const LOCALE_IDEFAULTMACCODEPAGE As Long = &H1011 'def mac code page
-
-Public Const LOCALE_IMEASURE As Long = &HD '0 = metric, 1 = US
-Public Const LOCALE_SSHORTDATE As Long = &H1F 'short date format string
-
-'#if(WINVER >= &H0400)
-Public Const LOCALE_SISO639LANGNAME As Long = &H59 'ISO abbreviated language name
-Public Const LOCALE_SISO3166CTRYNAME As Long = &H5A 'ISO abbreviated country name
-'#endif /* WINVER >= as long = &H0400 */
-
-'#if(WINVER >= &H0500)
-Public Const LOCALE_SNATIVECURRNAME As Long = &H1008 'native name of currency
-Public Const LOCALE_IDEFAULTEBCDICCODEPAGE As Long = &H1012 'default ebcdic code page
-Public Const LOCALE_SSORTNAME As Long = &H1013 'sort name
-'#endif /* WINVER >= &H0500 */
-
-Public Const CSTR_LOG_FILE_NAME = "analysis.log"
-
-Public Declare Function GetThreadLocale Lib "kernel32" () As Long
-
-Public Declare Function GetSystemDefaultLCID Lib "kernel32" () As Long
-Public Declare Function GetUserDefaultLCID Lib "kernel32" () As Long
-Public Declare Function GetUserDefaultLangID Lib "kernel32" () As Long
-Public Declare Function GetSystemDefaultLangID Lib "kernel32" () As Long
-
-Public Declare Function GetLocaleInfo Lib "kernel32" _
- Alias "GetLocaleInfoA" _
- (ByVal Locale As Long, _
- ByVal LCType As Long, _
- ByVal lpLCData As String, _
- ByVal cchData As Long) As Long
-
-Private Const VER_PLATFORM_WIN32s = 0
-Private Const VER_PLATFORM_WIN32_WINDOWS = 1
-Private Const VER_PLATFORM_WIN32_NT = 2
-
-Private Type OSVERSIONINFO
- OSVSize As Long 'size, in bytes, of this data structure
- dwVerMajor As Long 'ie NT 3.51, dwVerMajor = 3; NT 4.0, dwVerMajor = 4.
- dwVerMinor As Long 'ie NT 3.51, dwVerMinor = 51; NT 4.0, dwVerMinor= 0.
- dwBuildNumber As Long 'NT: build number of the OS
- 'Win9x: build number of the OS in low-order word.
- ' High-order word contains major & minor ver nos.
- PlatformID As Long 'Identifies the operating system platform.
- szCSDVersion As String * 128 'NT: string, such as "Service Pack 3"
- 'Win9x: string providing arbitrary additional information
-End Type
-
-Public Type RGB_WINVER
- PlatformID As Long
- VersionName As String
- VersionNo As String
- ServicePack As String
- BuildNo As String
-End Type
-
-'defined As Any to support OSVERSIONINFO and OSVERSIONINFOEX
-Private Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" _
- (lpVersionInformation As Any) As Long
-
-Private Declare Function GetDesktopWindow Lib "user32" () As Long
-
-Private Declare Function ShellExecute Lib "shell32" _
- Alias "ShellExecuteA" _
- (ByVal hWnd As Long, _
- ByVal lpOperation As String, _
- ByVal lpFile As String, _
- ByVal lpParameters As String, _
- ByVal lpDirectory As String, _
- ByVal nShowCmd As Long) As Long
-
-Public Const SW_SHOWNORMAL As Long = 1
-Public Const SW_SHOWMAXIMIZED As Long = 3
-Public Const SW_SHOWDEFAULT As Long = 10
-Public Const SE_ERR_NOASSOC As Long = 31
-
-Public Const CNO_OPTIONAL_PARAM = "_NoOptionalParam_"
-Private Declare Function WritePrivateProfileString Lib "kernel32" _
- Alias "WritePrivateProfileStringA" _
- (ByVal lpSectionName As String, _
- ByVal lpKeyName As Any, _
- ByVal lpString As Any, _
- ByVal lpFileName As String) As Long
-
-
-Public Const HKEY_LOCAL_MACHINE As Long = &H80000002
-Public Const HKEY_CLASSES_ROOT = &H80000000
-Private Const ERROR_MORE_DATA = 234
-Private Const ERROR_SUCCESS As Long = 0
-Private Const KEY_QUERY_VALUE As Long = &H1
-Private Const KEY_ENUMERATE_SUB_KEYS As Long = &H8
-Private Const KEY_NOTIFY As Long = &H10
-Private Const STANDARD_RIGHTS_READ As Long = &H20000
-Private Const SYNCHRONIZE As Long = &H100000
-Private Const KEY_READ As Long = ((STANDARD_RIGHTS_READ Or _
- KEY_QUERY_VALUE Or _
- KEY_ENUMERATE_SUB_KEYS Or _
- KEY_NOTIFY) And _
- (Not SYNCHRONIZE))
-
-Private Declare Function RegOpenKeyEx Lib "advapi32.dll" _
- Alias "RegOpenKeyExA" _
- (ByVal hKey As Long, _
- ByVal lpSubKey As String, _
- ByVal ulOptions As Long, _
- ByVal samDesired As Long, _
- phkResult As Long) As Long
-
-Private Declare Function RegQueryValueEx Lib "advapi32.dll" _
- Alias "RegQueryValueExA" _
- (ByVal hKey As Long, _
- ByVal lpValueName As String, _
- ByVal lpReserved As Long, _
- lpType As Long, _
- lpData As Any, _
- lpcbData As Long) As Long
-
-Private Declare Function RegCloseKey Lib "advapi32.dll" _
- (ByVal hKey As Long) As Long
-
-Private Declare Function lstrlenW Lib "kernel32" _
- (ByVal lpString As Long) As Long
-
-Private Type ShortItemId
- cb As Long
- abID As Byte
-End Type
-
-Private Type ITEMIDLIST
- mkid As ShortItemId
-End Type
-
-Private Declare Function SHGetPathFromIDList Lib "shell32.dll" _
- (ByVal pidl As Long, ByVal pszPath As String) As Long
-
-Private Declare Function SHGetSpecialFolderLocation Lib _
- "shell32.dll" (ByVal hWndOwner As Long, ByVal nFolder _
- As Long, pidl As ITEMIDLIST) As Long
-
-
-Public Function IsWin98Plus() As Boolean
- 'returns True if running Windows 2000 or later
- Dim osv As OSVERSIONINFO
-
- osv.OSVSize = Len(osv)
-
- If GetVersionEx(osv) = 1 Then
-
- Select Case osv.PlatformID 'win 32
- Case VER_PLATFORM_WIN32s:
- IsWin98Plus = False
- Exit Function
- Case VER_PLATFORM_WIN32_NT: 'win nt, 2000, xp
- IsWin98Plus = True
- Exit Function
- Case VER_PLATFORM_WIN32_WINDOWS:
- Select Case osv.dwVerMinor
- Case 0: 'win95
- IsWin98Plus = False
- Exit Function
- Case 90: 'Windows ME
- IsWin98Plus = True
- Exit Function
- Case 10: ' Windows 98
- If osv.dwBuildNumber >= 2222 Then 'second edition
- IsWin98Plus = True
- Exit Function
- Else
- IsWin98Plus = False
- Exit Function
- End If
- End Select
- Case Else
- IsWin98Plus = False
- Exit Function
- End Select
-
- End If
-
-End Function
-
-Public Function GetWinVersion(WIN As RGB_WINVER) As String
-
-'returns a structure (RGB_WINVER)
-'filled with OS information
-
- #If Win32 Then
-
- Dim osv As OSVERSIONINFO
- Dim pos As Integer
- Dim sVer As String
- Dim sBuild As String
-
- osv.OSVSize = Len(osv)
-
- If GetVersionEx(osv) = 1 Then
-
- 'PlatformId contains a value representing the OS
- WIN.PlatformID = osv.PlatformID
-
- Select Case osv.PlatformID
- Case VER_PLATFORM_WIN32s: WIN.VersionName = "Win32s"
- Case VER_PLATFORM_WIN32_NT: WIN.VersionName = "Windows NT"
-
- Select Case osv.dwVerMajor
- Case 4: WIN.VersionName = "Windows NT"
- Case 5:
- Select Case osv.dwVerMinor
- Case 0: WIN.VersionName = "Windows 2000"
- Case 1: WIN.VersionName = "Windows XP"
- End Select
- End Select
-
- Case VER_PLATFORM_WIN32_WINDOWS:
-
- 'The dwVerMinor bit tells if its 95 or 98.
- Select Case osv.dwVerMinor
- Case 0: WIN.VersionName = "Windows 95"
- Case 90: WIN.VersionName = "Windows ME"
- Case Else: WIN.VersionName = "Windows 98"
- End Select
-
- End Select
-
-
- 'Get the version number
- WIN.VersionNo = osv.dwVerMajor & "." & osv.dwVerMinor
-
- 'Get the build
- WIN.BuildNo = (osv.dwBuildNumber And &HFFFF&)
-
- 'Any additional info. In Win9x, this can be
- '"any arbitrary string" provided by the
- 'manufacturer. In NT, this is the service pack.
- pos = InStr(osv.szCSDVersion, Chr$(0))
- If pos Then
- WIN.ServicePack = Left$(osv.szCSDVersion, pos - 1)
- End If
-
- End If
-
- #Else
-
- 'can only return that this does not
- 'support the 32 bit call, so must be Win3x
- WIN.VersionName = "Windows 3.x"
- #End If
- GetWinVersion = WIN.VersionName
-
-End Function
-
-Public Sub RunShellExecute(sTopic As String, _
- sFile As Variant, _
- sParams As Variant, _
- sDirectory As Variant, _
- nShowCmd As Long)
-
- Dim hWndDesk As Long
- Dim success As Long
-
- 'the desktop will be the
- 'default for error messages
- hWndDesk = GetDesktopWindow()
-
- 'execute the passed operation
- success = ShellExecute(hWndDesk, sTopic, sFile, sParams, sDirectory, nShowCmd)
-
- 'This is optional. Uncomment the three lines
- 'below to have the "Open With.." dialog appear
- 'when the ShellExecute API call fails
- If success = SE_ERR_NOASSOC Then
- Call Shell("rundll32.exe shell32.dll,OpenAs_RunDLL " & sFile, vbNormalFocus)
- End If
-
-End Sub
-
-Public Sub WriteToLog(key As String, value As String, _
- Optional path As String = CNO_OPTIONAL_PARAM, _
- Optional section As String = WIZARD_NAME)
-
- Static logFile As String
-
- If logFile = "" Then
- logFile = GetLogFilePath
- End If
-
- If path = "" Then
- Exit Sub
- End If
-
- If path = CNO_OPTIONAL_PARAM Then
- path = logFile
- End If
- Call WritePrivateProfileString(section, key, value, path)
-End Sub
-
-Public Sub WriteDebug(value As String)
- Static ErrCount As Long
- Static logFile As String
- Static debugLevel As Long
-
- If logFile = "" Then
- logFile = GetLogFilePath
- End If
-
- Dim sSection As String
- sSection = WIZARD_NAME & "Debug"
-
- Call WritePrivateProfileString(sSection, "Analysis" & "_debug" & ErrCount, _
- value, logFile)
- ErrCount = ErrCount + 1
-End Sub
-
-Public Function GetDebug(section As String, key As String) As String
- Static logFile As String
-
- If logFile = "" Then
- logFile = GetLogFilePath
- End If
-
- GetDebug = ProfileGetItem(section, key, "", logFile)
-End Function
-
-Public Function GetUserLocaleInfo(ByVal dwLocaleID As Long, ByVal dwLCType As Long) As String
-
- Dim sReturn As String
- Dim r As Long
-
- 'call the function passing the Locale type
- 'variable to retrieve the required size of
- 'the string buffer needed
- r = GetLocaleInfo(dwLocaleID, dwLCType, sReturn, Len(sReturn))
-
- 'if successful..
- If r Then
-
- 'pad the buffer with spaces
- sReturn = Space$(r)
-
- 'and call again passing the buffer
- r = GetLocaleInfo(dwLocaleID, dwLCType, sReturn, Len(sReturn))
-
- 'if successful (r > 0)
- If r Then
-
- 'r holds the size of the string
- 'including the terminating null
- GetUserLocaleInfo = Left$(sReturn, r - 1)
-
- End If
-
- End If
-
-End Function
-
-Public Function GetRegistryInfo(sHive As String, sSubKey As String, sKey As String) As String
- GetRegistryInfo = ""
- Dim hKey As Long
-
- hKey = OpenRegKey(sHive, sSubKey)
-
- If hKey <> 0 Then
- GetRegistryInfo = GetRegValue(hKey, sKey)
-
- 'the opened key must be closed
- Call RegCloseKey(hKey)
- End If
-End Function
-
-
-Private Function GetRegValue(hSubKey As Long, sKeyName As String) As String
-
- Dim lpValue As String 'value retrieved
- Dim lpcbData As Long 'length of retrieved string
-
- 'if valid
- If hSubKey <> 0 Then
-
- 'Pass an zero-length string to
- 'obtain the required buffer size
- 'required to return the result.
- 'If the key passed exists, the call
- 'will return error 234 (more data)
- 'and lpcbData will indicate the
- 'required buffer size (including
- 'the terminating null).
- lpValue = ""
- lpcbData = 0
- If RegQueryValueEx(hSubKey, _
- sKeyName, _
- 0&, _
- 0&, _
- ByVal lpValue, _
- lpcbData) = ERROR_MORE_DATA Then
-
- lpValue = Space$(lpcbData)
-
- 'retrieve the desired value
- If RegQueryValueEx(hSubKey, _
- sKeyName, _
- 0&, _
- 0&, _
- ByVal lpValue, _
- lpcbData) = ERROR_SUCCESS Then
-
- GetRegValue = TrimNull(lpValue)
-
- End If 'If RegQueryValueEx (second call)
- End If 'If RegQueryValueEx (first call)
- End If 'If hSubKey
-
-End Function
-
-Private Function OpenRegKey(ByVal hKey As Long, _
- ByVal lpSubKey As String) As Long
- Dim hSubKey As Long
- Dim retval As Long
-
- retval = RegOpenKeyEx(hKey, lpSubKey, _
- 0, KEY_READ, hSubKey)
-
- If retval = ERROR_SUCCESS Then
- OpenRegKey = hSubKey
- End If
-End Function
-
-
-Private Function TrimNull(startstr As String) As String
-
- TrimNull = Left$(startstr, lstrlenW(StrPtr(startstr)))
-
-End Function
-
-Function GetLogFilePath() As String
-
- Dim fso As New FileSystemObject
- Dim TempPath As String
-
- TempPath = fso.GetSpecialFolder(TemporaryFolder).path
-
- If (TempPath = "") Then
- TempPath = "."
- End If
-
- GetLogFilePath = fso.GetAbsolutePathName(TempPath & "\" & CSTR_LOG_FILE_NAME)
-End Function
-
-Function GetIniFilePath() As String
-
- Dim fso As New FileSystemObject
- Dim AppDataDir As String
-
- AppDataDir = GetAppDataFolder
- If (AppDataDir = "") Then
- AppDataDir = CBASE_RESOURCE_DIR
- Else
- If Not fso.FolderExists(AppDataDir) Then
- fso.CreateFolder (AppDataDir)
- End If
- AppDataDir = AppDataDir & "\Sun"
- If Not fso.FolderExists(AppDataDir) Then
- fso.CreateFolder (AppDataDir)
- End If
- AppDataDir = AppDataDir & "\AnalysisWizard"
- If Not fso.FolderExists(AppDataDir) Then
- fso.CreateFolder (AppDataDir)
- End If
- End If
-
- GetIniFilePath = fso.GetAbsolutePathName(AppDataDir & "\" & CANALYSIS_INI_FILE)
-End Function
-
-' This function returns the Application Data Folder Path
-Function GetAppDataFolder() As String
- Dim idlstr As Long
- Dim sPath As String
- Dim IDL As ITEMIDLIST
- Const NOERROR = 0
- Const MAX_LENGTH = 260
- Const CSIDL_APPDATA = &H1A
-
- On Error GoTo Err_GetFolder
-
- ' Fill the idl structure with the specified folder item.
- idlstr = SHGetSpecialFolderLocation(0, CSIDL_APPDATA, IDL)
-
- If idlstr = NOERROR Then
- ' Get the path from the idl list, and return
- ' the folder with a slash at the end.
- sPath = Space$(MAX_LENGTH)
- idlstr = SHGetPathFromIDList(ByVal IDL.mkid.cb, ByVal sPath)
- If idlstr Then
- GetAppDataFolder = Left$(sPath, InStr(sPath, Chr$(0)) - 1)
- End If
- End If
-
-Exit_GetFolder:
- Exit Function
-
-Err_GetFolder:
- MsgBox "An Error was Encountered" & Chr(13) & Err.Description, _
- vbCritical Or vbOKOnly
- Resume Exit_GetFolder
-
-End Function
-
-
-
diff --git a/migrationanalysis/src/wizard/Wizard.DCA b/migrationanalysis/src/wizard/Wizard.DCA
deleted file mode 100644
index 56ef0d79e381..000000000000
--- a/migrationanalysis/src/wizard/Wizard.DCA
+++ /dev/null
Binary files differ
diff --git a/migrationanalysis/src/wizard/Wizard.Dsr b/migrationanalysis/src/wizard/Wizard.Dsr
deleted file mode 100644
index c84dde296c59..000000000000
--- a/migrationanalysis/src/wizard/Wizard.Dsr
+++ /dev/null
@@ -1,96 +0,0 @@
-'
-' This file is part of the LibreOffice project.
-'
-' This Source Code Form is subject to the terms of the Mozilla Public
-' License, v. 2.0. If a copy of the MPL was not distributed with this
-' file, You can obtain one at http://mozilla.org/MPL/2.0/.
-'
-' This file incorporates work covered by the following license notice:
-'
-' Licensed to the Apache Software Foundation (ASF) under one or more
-' contributor license agreements. See the NOTICE file distributed
-' with this work for additional information regarding copyright
-' ownership. The ASF licenses this file to you under the Apache
-' License, Version 2.0 (the "License"); you may not use this file
-' except in compliance with the License. You may obtain a copy of
-' the License at http://www.apache.org/licenses/LICENSE-2.0 .
-'
-VERSION 5.00
-Begin {AC0714F6-3D04-11D1-AE7D-00A0C90F26F4} Wizard
- ClientHeight = 7470
- ClientLeft = 1740
- ClientTop = 1545
- ClientWidth = 6585
- _ExtentX = 11615
- _ExtentY = 13176
- _Version = 393216
- DisplayName = "AnalysisWizard"
- AppName = "Visual Basic"
- AppVer = "Visual Basic 6.0"
- LoadName = "Command Line / Startup"
- LoadBehavior = 5
- RegLocation = "HKEY_CURRENT_USER\Software\Microsoft\Visual Basic\6.0"
- CmdLineSupport = -1 'True
-End
-Attribute VB_Name = "Wizard"
-Attribute VB_GlobalNameSpace = False
-Attribute VB_Creatable = True
-Attribute VB_PredeclaredId = False
-Attribute VB_Exposed = False
-Option Explicit
-
-Dim mcbMenuCommandBar As Office.CommandBarControl 'command bar object
-Public WithEvents MenuHandler As CommandBarEvents 'command bar event handler
-Attribute MenuHandler.VB_VarHelpID = -1
-Dim mfrmWizard As frmWizard
-Dim VBInstance As VBIDE.VBE
-
-
-'------------------------------------------------------
-'this method adds the Add-In to the VB menu
-'it is called by the VB addin manager
-'------------------------------------------------------
-Private Sub AddinInstance_OnConnection(ByVal application As Object, ByVal ConnectMode As AddInDesignerObjects.ext_ConnectMode, ByVal AddInInst As Object, custom() As Variant)
- On Error GoTo error_handler
-
- Set VBInstance = application
-
- If ConnectMode = ext_cm_External Then
- 'Used by the wizard toolbar to start this wizard
- LoadMe
- Else
- Set mcbMenuCommandBar = AddToAddInCommandBar(VBInstance, LoadResString(15), LoadResPicture(5000, 0))
- 'sink the event
- Set Me.MenuHandler = VBInstance.Events.CommandBarEvents(mcbMenuCommandBar)
- End If
-
- Exit Sub
-
-error_handler:
- MsgBox Err.Description
-End Sub
-
-'------------------------------------------------------
-'this method removes the Add-In from the VB menu
-'it is called by the VB addin manager
-'------------------------------------------------------
-Private Sub AddinInstance_OnDisconnection(ByVal RemoveMode As AddInDesignerObjects.ext_DisconnectMode, custom() As Variant)
- 'delete the command bar entry
- mcbMenuCommandBar.Delete
-End Sub
-
-'this event fires when the menu is clicked in the IDE
-Private Sub MenuHandler_Click(ByVal CommandBarControl As Object, handled As Boolean, CancelDefault As Boolean)
- LoadMe
-End Sub
-
-Private Sub LoadMe()
- Set mfrmWizard = New frmWizard
- 'pass the vb instance to the wizard module
- Set mfrmWizard.VBInst = VBInstance
- 'load and show the form
- mfrmWizard.Show vbModal
- Set mfrmWizard = Nothing
-End Sub
-
-
diff --git a/migrationanalysis/src/wizard/Wizard.FRX b/migrationanalysis/src/wizard/Wizard.FRX
deleted file mode 100644
index 20c068343090..000000000000
--- a/migrationanalysis/src/wizard/Wizard.FRX
+++ /dev/null
Binary files differ
diff --git a/migrationanalysis/src/wizard/Wizard.bas b/migrationanalysis/src/wizard/Wizard.bas
deleted file mode 100644
index d316ea805c56..000000000000
--- a/migrationanalysis/src/wizard/Wizard.bas
+++ /dev/null
@@ -1,642 +0,0 @@
-Attribute VB_Name = "modWizard"
-'
-' This file is part of the LibreOffice project.
-'
-' This Source Code Form is subject to the terms of the Mozilla Public
-' License, v. 2.0. If a copy of the MPL was not distributed with this
-' file, You can obtain one at http://mozilla.org/MPL/2.0/.
-'
-' This file incorporates work covered by the following license notice:
-'
-' Licensed to the Apache Software Foundation (ASF) under one or more
-' contributor license agreements. See the NOTICE file distributed
-' with this work for additional information regarding copyright
-' ownership. The ASF licenses this file to you under the Apache
-' License, Version 2.0 (the "License"); you may not use this file
-' except in compliance with the License. You may obtain a copy of
-' the License at http://www.apache.org/licenses/LICENSE-2.0 .
-'
-Option Explicit
-
-Global Const WIZARD_NAME = "Analysis"
-
-'Implementation details - not required for localisation
-Public Const CWORD_DRIVER_FILE = "_OOoDocAnalysisWordDriver.doc"
-Public Const CEXCEL_DRIVER_FILE = "_OOoDocAnalysisExcelDriver.xls"
-Public Const CPP_DRIVER_FILE = "_OOoDocAnalysisPPTDriver.ppt"
-Public Const CRESULTS_TEMPLATE_FILE = "results.xlt"
-Public Const CISSUES_LIST_FILE = "issues.list"
-Public Const CANALYSIS_INI_FILE = "analysis.ini"
-Public Const CLAUNCH_DRIVERS_EXE = "LaunchDrivers.exe"
-Public Const CMSO_KILL_EXE = "msokill.exe"
-Public Const CRESOURCE_DLL = "Resources.dll"
-
-' Preparation String ID's from DocAnalysisWizard.rc
-Public Const RID_STR_ENG_TITLE_PREP_ID = 1030
-Public Const RID_STR_ENG_SIDEBAR_ANALYZE_PREP_ID = 1074
-
-Public Const RID_STR_ENG_INTRODUCTION_INTRO1_PREP_ID = 1131
-Public Const RID_STR_ENG_INTRODUCTION_INTRO2_PREP_ID = 1132
-Public Const RID_STR_ENG_INTRODUCTION_INTRO3_PREP_ID = 1134
-
-Public Const RID_STR_ENG_DOCUMENTS_CHOOSE_DOCUMENTS_PREP_ID = 1230
-Public Const RID_STR_ENG_DOCUMENTS_CHOOSE_DOC_TYPES_PREP_ID = 1236
-Public Const RID_STR_ENG_DOCUMENTS_INCLUDE_SUBDIRECTORIES_PREP_ID = 1232
-
-Public Const RID_STR_IGNORE_OLDER_CB_ID = 1231
-Public Const RID_STR_IGNORE_OLDER_3_MONTHS_ID = 1233
-Public Const RID_STR_IGNORE_OLDER_6_MONTHS_ID = 1234
-Public Const RID_STR_IGNORE_OLDER_12_MONTHS_ID = 1235
-
-Public Const RID_STR_ENG_RESULTS_CHOOSE_OPTIONS_PREP_ID = 1330
-Public Const RID_STR_ENG_RESULTS_ANALYSIS_XLS_PREP_ID = 1332
-
-Public Const RID_STR_ENG_ANALYZE_NUM_DOCS_PREP_ID = 1431
-Public Const RID_STR_ENG_ANALYZE_SETUP_COMPLETE_PREP_ID = 1430
-Public Const RID_STR_ENG_ANALYZE_IGNORED_DOCS_ID = 1435
-Public Const RID_STR_ENG_ANALYZE_START_ID = 1413
-Public Const RID_STR_ENG_ANALYZE_COMPLETED_ID = 1412
-Public Const RID_STR_ENG_ANALYZE_VIEW_NOW_ID = 1414
-Public Const RID_STR_ENG_ANALYZE_VIEW_LATER_ID = 1415
-Public Const RID_STR_ENG_ANALYSE_NOT_RUN = 1416
-
-Public Const RID_STR_ENG_OTHER_PLEASE_REFER_TO_README_PREP_ID = 1838
-Public Const RID_STR_ENG_OTHER_XML_RESULTS_PREP_ID = 1845
-Public Const RID_STR_ENG_OTHER_PREPARE_PROMPT_PREP_ID = 1846
-Public Const RID_STR_ENG_OTHER_PREPARE_COMPLETED_PREP_ID = 1847
-
-'Resource Strings Codes
-' NOTE: to make a resource the default it must be the first string table inserted
-' in the resource table - if it is not, just create several new string tables and
-' copy what you want as default into the first new one you create, copy the others
-' then delete the originals.
-'
-' To provide same string table for all English variants or all German variants
-' I have added code to set LANG_BASE_ID dependent on current locale
-' Refer to p.414 VBA in a Nutshell, Lomax
-' I now have a single string table with each lang variant suitably offset:
-' New locale - increase ofsets by 1000 - refer to DocAnalysisWizard.rc
-'
-' English - eng - Start at 1000
-' German - ger - Start at 2000
-' BrazilianPortugese - por - Start at 4000
-' French - fre - Start at 5000
-' Italian - ita - Start at 6000
-' Spanish - spa - Start at 7000
-' Swedish - swe - Start at 8000
-
-
-' String ID's must match those in DocAnalysisWizard.rc
-Const LANG_BASE_ID = 1000
-Const INTERNAL_RESOURCE_BASE_ID = LANG_BASE_ID + 800
-
-' Setup Doc Preparation specific strings
-#If PREPARATION Then
-Global Const gBoolPreparation = True
-
-Public Const TITLE_ID = RID_STR_ENG_TITLE_PREP_ID
-Public Const CHK_SUBDIRS_ID = RID_STR_ENG_DOCUMENTS_INCLUDE_SUBDIRECTORIES_PREP_ID
-Public Const SETUP_ANALYSIS_XLS_ID = RID_STR_ENG_RESULTS_ANALYSIS_XLS_PREP_ID
-Public Const ANALYZE_TOTAL_NUM_DOCS_ID = RID_STR_ENG_ANALYZE_NUM_DOCS_PREP_ID
-Public Const XML_RESULTS_ID = RID_STR_ENG_OTHER_XML_RESULTS_PREP_ID
-
-#Else
-Global Const gBoolPreparation = False
-
-Public Const TITLE_ID = LANG_BASE_ID + 0
-Public Const CHK_SUBDIRS_ID = LANG_BASE_ID + 202
-Public Const SETUP_ANALYSIS_XLS_ID = LANG_BASE_ID + 302
-Public Const ANALYZE_TOTAL_NUM_DOCS_ID = LANG_BASE_ID + 401
-Public Const XML_RESULTS_ID = INTERNAL_RESOURCE_BASE_ID + 15
-#End If
-
-Public Const PRODUCTNAME_ID = LANG_BASE_ID + 1
-Public Const LBL_STEPS_ID = LANG_BASE_ID + 40
-Public Const INTRO1_ID = LANG_BASE_ID + 101
-
-Public Const ANALYZE_DOCUMENTS_ID = LANG_BASE_ID + 402
-Public Const ANALYZE_TEMPLATES_ID = LANG_BASE_ID + 403
-Public Const ANALYZE_DOCUMENTS_XLS_ID = LANG_BASE_ID + 408
-Public Const ANALYZE_DOCUMENTS_PPT_ID = LANG_BASE_ID + 409
-Public Const RUNBTN_START_ID = LANG_BASE_ID + 404
-Public Const PREPAREBTN_START_ID = LANG_BASE_ID + 411
-
-Public Const README_FILE_ID = INTERNAL_RESOURCE_BASE_ID + 5 'Readme.doc
-Public Const BROWSE_FOR_DOC_DIR_ID = INTERNAL_RESOURCE_BASE_ID + 6
-Public Const BROWSE_FOR_RES_DIR_ID = INTERNAL_RESOURCE_BASE_ID + 7
-Public Const RUNBTN_RUNNING_ID = INTERNAL_RESOURCE_BASE_ID + 10
-
-Public Const PROGRESS_CAPTION = INTERNAL_RESOURCE_BASE_ID + 20
-Public Const PROGRESS_ABORTING = INTERNAL_RESOURCE_BASE_ID + 21
-Public Const PROGRESS_PATH_LABEL = INTERNAL_RESOURCE_BASE_ID + 22
-Public Const PROGRESS_FILE_LABEL = INTERNAL_RESOURCE_BASE_ID + 23
-Public Const PROGRESS_INFO_LABEL = INTERNAL_RESOURCE_BASE_ID + 24
-Public Const PROGRESS_WAIT_LABEL = INTERNAL_RESOURCE_BASE_ID + 25
-
-Public Const SEARCH_PATH_LABEL = PROGRESS_PATH_LABEL
-Public Const SEARCH_CAPTION = INTERNAL_RESOURCE_BASE_ID + 26
-Public Const SEARCH_INFO_LABEL = INTERNAL_RESOURCE_BASE_ID + 27
-Public Const SEARCH_FOUND_LABEL = INTERNAL_RESOURCE_BASE_ID + 28
-
-Public Const TERMINATE_CAPTION = INTERNAL_RESOURCE_BASE_ID + 30
-Public Const TERMINATE_INFO = INTERNAL_RESOURCE_BASE_ID + 31
-Public Const TERMINATE_YES = INTERNAL_RESOURCE_BASE_ID + 32
-Public Const TERMINATE_NO = INTERNAL_RESOURCE_BASE_ID + 33
-
-'Error Resource Strings Codes
-Const ERROR_BASE_ID = LANG_BASE_ID + 900
-Public Const ERR_MISSING_RESULTS_DOC = ERROR_BASE_ID + 0
-Public Const ERR_NO_DOC_DIR = ERROR_BASE_ID + 1
-Public Const ERR_NO_DOC_TYPES = ERROR_BASE_ID + 2
-Public Const ERR_NO_RES_DIR = ERROR_BASE_ID + 3
-Public Const ERR_CREATE_DIR = ERROR_BASE_ID + 4
-Public Const ERR_MISSING_RESULTS_TEMPLATE = ERROR_BASE_ID + 5
-Public Const ERR_MISSING_EXCEL_DRIVER = ERROR_BASE_ID + 6
-Public Const ERR_EXCEL_DRIVER_CRASH = ERROR_BASE_ID + 7
-Public Const ERR_MISSING_WORD_DRIVER = ERROR_BASE_ID + 8
-Public Const ERR_WORD_DRIVER_CRASH = ERROR_BASE_ID + 9
-Public Const ERR_MISSING_README = ERROR_BASE_ID + 10
-Public Const ERR_MISSING_PP_DRIVER = ERROR_BASE_ID + 11
-Public Const ERR_PP_DRIVER_CRASH = ERROR_BASE_ID + 12
-Public Const ERR_SUPPORTED_VERSION = ERROR_BASE_ID + 13
-Public Const ERR_ISSUES_VERSION_MISMATCH = ERROR_BASE_ID + 14
-Public Const ERR_ISSUES_LIST_MISSING = ERROR_BASE_ID + 15
-Public Const ERR_SUPPORTED_OSVERSION = ERROR_BASE_ID + 16
-Public Const ERR_OPEN_RESULTS_SPREADSHEET = ERROR_BASE_ID + 17
-Public Const ERR_EXCEL_OPEN = ERROR_BASE_ID + 18
-Public Const ERR_NO_ACCESS_TO_VBPROJECT = ERROR_BASE_ID + 19
-Public Const ERR_AUTOMATION_FAILURE = ERROR_BASE_ID + 20
-Public Const ERR_NO_RESULTS_DIRECTORY = ERROR_BASE_ID + 21
-Public Const ERR_CREATE_FILE = ERROR_BASE_ID + 22
-Public Const ERR_XML_RESULTS_ONLY = ERROR_BASE_ID + 23
-Public Const ERR_NOT_INSTALLED = ERROR_BASE_ID + 24
-Public Const ERR_CDROM_NOT_ALLOWED = ERROR_BASE_ID + 25
-Public Const ERR_CDROM_NOT_READY = ERROR_BASE_ID + 26
-Public Const ERR_NO_WRITE_TO_READ_ONLY_FOLDER = ERROR_BASE_ID + 27
-Public Const ERR_APPLICATION_IN_USE = ERROR_BASE_ID + 28
-Public Const ERR_MISSING_IMPORTANT_FILE = ERROR_BASE_ID + 29
-
-
-Private Const LOCALE_ILANGUAGE As Long = &H1 'language id
-Private Const LOCALE_SLANGUAGE As Long = &H2 'localized name of language
-Private Const LOCALE_SENGLANGUAGE As Long = &H1001 'English name of language
-Private Const LOCALE_SABBREVLANGNAME As Long = &H3 'abbreviated language name
-Private Const LOCALE_SCOUNTRY As Long = &H6 'localized name of country
-Private Const LOCALE_SENGCOUNTRY As Long = &H1002 'English name of country
-Private Const LOCALE_SABBREVCTRYNAME As Long = &H7 'abbreviated country name
-Private Const LOCALE_SISO639LANGNAME As Long = &H59 'ISO abbreviated language name
-Private Const LOCALE_SISO3166CTRYNAME As Long = &H5A 'ISO abbreviated country name
-
-Private Const LOCALE_JAPAN As Long = &H411
-Private Const LOCALE_KOREA As Long = &H412
-Private Const LOCALE_ZH_CN As Long = &H404
-Private Const LOCALE_ZH_TW As Long = &H804
-
-Private Const RES_PREFIX = ".\Resources\Resources.dll"
-
-Declare Function GetLocaleInfo Lib "kernel32" Alias _
-"GetLocaleInfoA" (ByVal Locale As Long, ByVal LCType As Long, ByVal lpLCData As String, _
-ByVal cchData As Long) As Long
-
-Declare Function WritePrivateProfileString& Lib "kernel32" Alias "WritePrivateProfileStringA" (ByVal AppName$, ByVal KeyName$, ByVal keydefault$, ByVal fileName$)
-Declare Function LoadLibrary Lib "kernel32" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As Long
-Private Declare Function LoadString Lib "user32" Alias "LoadStringA" _
- (ByVal hInstance As Long, ByVal wID As Long, ByVal lpBuffer As String, _
- ByVal nBufferMax As Long) As Long
-
-'WinHelp Commands
-'Declare Function WinHelp Lib "user32" Alias "WinHelpA" (ByVal hWnd As Long, ByVal lpHelpFile As String, ByVal wCommand As Long, ByVal dwData As Long) As Long
-'Public Const HELP_QUIT = &H2 ' Terminate help
-'Public Const HELP_CONTENTS = &H3& ' Display index/contents
-'Public Const HELP_CONTEXT = &H1 ' Display topic in ulTopic
-'Public Const HELP_INDEX = &H3 ' Display index
-
-Public Const CBASE_RESOURCE_DIR = ".\resources"
-Private mStrTrue As String
-Private mLocaleDir As String
-Private ghInst As Long
-
-
-Function getLocaleDir() As String
- If mLocaleDir = "" Then
- getLocaleLangBaseIDandSetLocaleDir
- End If
- getLocaleDir = mLocaleDir
-End Function
-
-Public Function GetLocaleLanguage() As String
- Dim lReturn As Long
- Dim lLocID As Long
- Dim sData As String
- Dim lDataLen As Long
-
- lDataLen = 0
- lReturn = GetLocaleInfo(lLocID, LOCALE_SENGLANGUAGE, sData, lDataLen)
- sData = String(lReturn, 0) & vbNullChar
- lDataLen = lReturn
- lReturn = GetLocaleInfo(lLocID, LOCALE_SENGLANGUAGE, sData, lDataLen)
-
-End Function
-
-Function getLocaleLangBaseIDandSetLocaleDir() As Integer
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "getLocaleLangBaseIDandSetLocaleDir"
-
- Dim baseID As Long
- Dim bUseLocale As Boolean
- Dim fso As FileSystemObject
- Set fso = New FileSystemObject
-
- Dim isoLangStr As String
- Dim isoCountryStr As String
- Dim langStr As String
-
- Dim userLCID As Long
- userLCID = GetUserDefaultLCID()
- Dim sysLCID As Long
- sysLCID = GetSystemDefaultLCID()
-
- isoLangStr = GetUserLocaleInfo(sysLCID, LOCALE_SISO639LANGNAME)
- isoCountryStr = GetUserLocaleInfo(sysLCID, LOCALE_SISO3166CTRYNAME)
- langStr = GetUserLocaleInfo(sysLCID, LOCALE_SENGLANGUAGE)
-
- baseID = 0
- mLocaleDir = ""
-
- If fso.FileExists(fso.GetAbsolutePathName("debug.ini")) Then
- Dim overrideLangStr As String
- overrideLangStr = ProfileGetItem("debug", "langoverride", "", fso.GetAbsolutePathName("debug.ini"))
- If overrideLangStr <> "" Then
- Debug.Print "Overriding language " & isoLangStr & " with " & overrideLangStr & "\n"
- isoLangStr = overrideLangStr
- End If
- End If
-
- 'check for locale dirs in following order:
- ' CBASE_RESOURCE_DIR & "\" & isoLangStr
- ' CBASE_RESOURCE_DIR & "\" & isoLangStr & "-" & isoCountryStr
- ' CBASE_RESOURCE_DIR & "\" & "eng"
- 'If fso.FolderExists(fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & isoLangStr)) Then
- ' mLocaleDir = CBASE_RESOURCE_DIR & "\" & isoLangStr
- ' baseID = getBaseID(isoLangStr)
- 'ElseIf fso.FolderExists(fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & isoLangStr & "-" & isoCountryStr)) Then
- ' mLocaleDir = CBASE_RESOURCE_DIR & "\" & isoLangStr & "-" & isoCountryStr
- ' baseID = getBaseID(isoLangStr & "-" & isoCountryStr)
- 'Else
- mLocaleDir = CBASE_RESOURCE_DIR
- baseID = 1000
- 'End If
-
- getLocaleLangBaseIDandSetLocaleDir = CInt(baseID)
-
-FinalExit:
- Set fso = Nothing
-
- Exit Function
-
-HandleErrors:
- Debug.Print currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Function
-'--------------------------------------------------------------------------
-'this sub must be executed from the immediate window
-'it will add the entry to VBADDIN.INI if it doesn't already exist
-'so that the add-in is on available next time VB is loaded
-'--------------------------------------------------------------------------
-Sub AddToINI()
- Debug.Print WritePrivateProfileString("Add-Ins32", WIZARD_NAME & ".Wizard", "0", "VBADDIN.INI")
-End Sub
-
-Function GetResString(nRes As Integer) As String
- Dim sTmp As String
- Dim sRes As String * 1024
- Dim sRetStr As String
- Dim nRet As Long
-
- Do
- 'sTmp = LoadResString(nRes)
- nRet = LoadString(ghInst, nRes, sRes, 1024)
- sTmp = Left$(sRes, nRet)
-
- If Right(sTmp, 1) = "_" Then
- sRetStr = sRetStr + VBA.Left(sTmp, Len(sTmp) - 1)
- Else
- sRetStr = sRetStr + sTmp
- End If
- nRes = nRes + 1
- Loop Until Right(sTmp, 1) <> "_"
- GetResString = sRetStr
-
-End Function
-
-Function GetField(sBuffer As String, sSep As String) As String
- Dim p As Integer
-
- p = InStr(sBuffer & sSep, sSep)
- GetField = VBA.Left(sBuffer, p - 1)
- sBuffer = Mid(sBuffer, p + Len(sSep))
-
-End Function
-' Parts of the following code are from:
-' http://support.microsoft.com/default.aspx?scid=kb;en-us;232625&Product=vb6
-
-Private Function GetCharSet(sCdpg As String) As Integer
- Select Case sCdpg
- Case "932" ' Japanese
- GetCharSet = 128
- Case "936" ' Simplified Chinese
- GetCharSet = 134
- Case "949" ' Korean
- GetCharSet = 129
- Case "950" ' Traditional Chinese
- GetCharSet = 136
- Case "1250" ' Eastern Europe
- GetCharSet = 238
- Case "1251" ' Russian
- GetCharSet = 204
- Case "1252" ' Western European Languages
- GetCharSet = 0
- Case "1253" ' Greek
- GetCharSet = 161
- Case "1254" ' Turkish
- GetCharSet = 162
- Case "1255" ' Hebrew
- GetCharSet = 177
- Case "1256" ' Arabic
- GetCharSet = 178
- Case "1257" ' Baltic
- GetCharSet = 186
- Case Else
- GetCharSet = 0
- End Select
-End Function
-
-Private Function StripNullTerminator(sCP As String)
- Dim posNull As Long
- posNull = InStr(sCP, Chr$(0))
- StripNullTerminator = Left$(sCP, posNull - 1)
-End Function
-
-Private Function GetResourceDataFileName() As String
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "GetResourceDataFileName"
-
- Dim fileName As String
- Dim fso As FileSystemObject
- Set fso = New FileSystemObject
-
- GetResourceDataFileName = fso.GetAbsolutePathName(RES_PREFIX)
-
- GoTo FinalExit
-
- ' use the following code when we have one resource file for each language
- Dim isoLangStr As String
- Dim isoCountryStr As String
-
- Dim userLCID As Long
- userLCID = GetUserDefaultLangID()
- Dim sysLCID As Long
- sysLCID = GetSystemDefaultLangID()
-
- isoLangStr = GetUserLocaleInfo(userLCID, LOCALE_SISO639LANGNAME)
- isoCountryStr = GetUserLocaleInfo(userLCID, LOCALE_SISO3166CTRYNAME)
-
- 'check for locale data in following order:
- ' user language
- ' isoLangStr & "_" & isoCountryStr & ".dll"
- ' isoLangStr & ".dll"
- ' system language
- ' isoLangStr & "_" & isoCountryStr & ".dll"
- ' isoLangStr & ".dll"
- ' "en_US" & ".dll"
-
- fileName = fso.GetAbsolutePathName(RES_PREFIX & isoLangStr & "-" & isoCountryStr & ".dll")
- If fso.FileExists(fileName) Then
- GetResourceDataFileName = fileName
- Else
- fileName = fso.GetAbsolutePathName(RES_PREFIX & isoLangStr & ".dll")
- If fso.FileExists(fileName) Then
- GetResourceDataFileName = fileName
- Else
- isoLangStr = GetUserLocaleInfo(sysLCID, LOCALE_SISO639LANGNAME)
- isoCountryStr = GetUserLocaleInfo(sysLCID, LOCALE_SISO3166CTRYNAME)
-
- fileName = fso.GetAbsolutePathName(RES_PREFIX & isoLangStr & "-" & isoCountryStr & ".dll")
- If fso.FileExists(fileName) Then
- GetResourceDataFileName = fileName
- Else
- fileName = fso.GetAbsolutePathName(RES_PREFIX & isoLangStr & ".dll")
- If fso.FileExists(fileName) Then
- GetResourceDataFileName = fileName
- Else
- GetResourceDataFileName = fso.GetAbsolutePathName(RES_PREFIX & "en-US.dll")
- End If
- End If
- End If
- End If
-FinalExit:
- Set fso = Nothing
- Exit Function
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Function
-
-Sub LoadResStrings(frm As Form)
- Dim ctl As Control
- Dim obj As Object
-
- Dim LCID As Long, X As Long
- Dim sCodePage As String
- Dim nCharSet As Integer
- Dim currentFunctionName As String
- currentFunctionName = "LoadResStrings"
-
- On Error GoTo HandleErrors
- ghInst = LoadLibrary(GetResourceDataFileName())
-
- On Error Resume Next
-
- sCodePage = String$(16, " ")
- LCID = GetThreadLocale() 'Get Current locale
-
- X = GetLocaleInfo(LCID, LOCALE_IDEFAULTANSICODEPAGE, _
- sCodePage, Len(sCodePage)) 'Get code page
- sCodePage = StripNullTerminator(sCodePage)
- nCharSet = GetCharSet(sCodePage) 'Convert code page to charset
-
- 'set the form's caption
- If IsNumeric(frm.Tag) Then
- frm.Caption = LoadResString(CInt(frm.Tag))
- End If
-
- 'set the controls' captions using the caption
- 'property for menu items and the Tag property
- 'for all other controls
- For Each ctl In frm.Controls
- Err = 0
- If (nCharSet <> 0) Then
- ctl.Font.Charset = nCharSet
- End If
- If TypeName(ctl) = "Menu" Then
- If IsNumeric(ctl.Caption) Then
- ctl.Caption = LoadResString(CInt(ctl.Caption))
- End If
- ElseIf TypeName(ctl) = "TabStrip" Then
- For Each obj In ctl.Tabs
- If IsNumeric(obj.Tag) Then
- obj.Caption = LoadResString(CInt(obj.Tag))
- End If
- 'check for a tooltip
- If IsNumeric(obj.ToolTipText) Then
- If Err = 0 Then
- obj.ToolTipText = LoadResString(CInt(obj.ToolTipText))
- End If
- End If
- Next
- ElseIf TypeName(ctl) = "Toolbar" Then
- For Each obj In ctl.Buttons
- If IsNumeric(obj.Tag) Then
- obj.ToolTipText = LoadResString(CInt(obj.Tag))
- End If
- Next
- ElseIf TypeName(ctl) = "ListView" Then
- For Each obj In ctl.ColumnHeaders
- If IsNumeric(obj.Tag) Then
- obj.Text = LoadResString(CInt(obj.Tag))
- End If
- Next
- ElseIf TypeName(ctl) = "TextBox" Then
- If IsNumeric(ctl.Tag) Then
- ctl.Text = LoadResString(CInt(ctl.Tag))
- End If
- Else
- If IsNumeric(ctl.Tag) Then
- ctl.Caption = GetResString(CInt(ctl.Tag))
- End If
- 'check for a tooltip
- If IsNumeric(ctl.ToolTipText) Then
- If Err = 0 Then
- ctl.ToolTipText = LoadResString(CInt(ctl.ToolTipText))
- End If
- End If
- End If
- Next
-
-FinalExit:
- Exit Sub
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-
-End Sub
-
-'==================================================
-'Purpose: Replace the sToken string(s) in
-' res file string for correct placement
-' of localized tokens
-'
-'Inputs: sString = String to search and replace in
-' sToken = token to replace
-' sReplacement = String to replace token with
-'
-'Outputs: New string with token replaced throughout
-'==================================================
-Function ReplaceTopicTokens(sString As String, _
- sToken As String, _
- sReplacement As String) As String
- On Error Resume Next
-
- Dim p As Integer
- Dim sTmp As String
-
- sTmp = sString
- Do
- p = InStr(sTmp, sToken)
- If p Then
- sTmp = VBA.Left(sTmp, p - 1) + sReplacement + Mid(sTmp, p + Len(sToken))
- End If
- Loop While p
-
-
- ReplaceTopicTokens = sTmp
-
-End Function
-'==================================================
-'Purpose: Replace the sToken1 and sToken2 strings in
-' res file string for correct placement
-' of localized tokens
-'
-'Inputs: sString = String to search and replace in
-' sToken1 = 1st token to replace
-' sReplacement1 = 1st String to replace token with
-' sToken2 = 2nd token to replace
-' sReplacement2 = 2nd String to replace token with
-'
-'Outputs: New string with token replaced throughout
-'==================================================
-Function ReplaceTopic2Tokens(sString As String, _
- sToken1 As String, _
- sReplacement1 As String, _
- sToken2 As String, _
- sReplacement2 As String) As String
- On Error Resume Next
-
- ReplaceTopic2Tokens = _
- ReplaceTopicTokens(ReplaceTopicTokens(sString, sToken1, sReplacement1), _
- sToken2, sReplacement2)
-End Function
-
-
-Public Function GetResData(sResName As String, sResType As String) As String
- Dim sTemp As String
- Dim p As Integer
-
- sTemp = StrConv(LoadResData(sResName, sResType), vbUnicode)
- p = InStr(sTemp, vbNullChar)
- If p Then sTemp = VBA.Left$(sTemp, p - 1)
- GetResData = sTemp
-End Function
-
-Function AddToAddInCommandBar(VBInst As Object, sCaption As String, oBitmap As Object) As Object 'Office.CommandBarControl
- On Error GoTo AddToAddInCommandBarErr
-
- Dim c As Integer
- Dim cbMenuCommandBar As Object 'Office.CommandBarControl 'command bar object
- Dim cbMenu As Object
-
- 'see if we can find the Add-Ins menu
- Set cbMenu = VBInst.CommandBars("Add-Ins")
- If cbMenu Is Nothing Then
- 'not available so we fail
- Exit Function
- End If
-
- 'add it to the command bar
- Set cbMenuCommandBar = cbMenu.Controls.add(1)
- c = cbMenu.Controls.count - 1
- If cbMenu.Controls(c).BeginGroup And _
- Not cbMenu.Controls(c - 1).BeginGroup Then
- 'this s the first addin being added so it needs a separator
- cbMenuCommandBar.BeginGroup = True
- End If
- 'set the caption
- cbMenuCommandBar.Caption = sCaption
- 'undone:set the onaction (required at this point)
- cbMenuCommandBar.OnAction = "hello"
- 'copy the icon to the clipboard
- Clipboard.SetData oBitmap
- 'set the icon for the button
- cbMenuCommandBar.PasteFace
-
- Set AddToAddInCommandBar = cbMenuCommandBar
-
- Exit Function
-AddToAddInCommandBarErr:
-
-End Function
-
diff --git a/migrationanalysis/src/wizard/Wizard.frm b/migrationanalysis/src/wizard/Wizard.frm
deleted file mode 100644
index ebb955386c68..000000000000
--- a/migrationanalysis/src/wizard/Wizard.frm
+++ /dev/null
@@ -1,3453 +0,0 @@
-VERSION 5.00
-Begin VB.Form frmWizard
- Appearance = 0 'Flat
- BackColor = &H80000005&
- BorderStyle = 1 'Fixed Single
- Caption = "OpenOffice.org Document Analysis Wizard"
- ClientHeight = 5520
- ClientLeft = 1965
- ClientTop = 1815
- ClientWidth = 8175
- BeginProperty Font
- Name = "Arial"
- Size = 8.25
- Charset = 0
- Weight = 400
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- Icon = "Wizard.frx":0000
- KeyPreview = -1 'True
- LinkTopic = "Form1"
- LockControls = -1 'True
- MaxButton = 0 'False
- MinButton = 0 'False
- ScaleHeight = 5520
- ScaleWidth = 8175
- Tag = "1000"
- Begin VB.Frame fraStep
- BorderStyle = 0 'None
- Caption = "Introduction"
- ClipControls = 0 'False
- Enabled = 0 'False
- BeginProperty Font
- Name = "MS Sans Serif"
- Size = 8.25
- Charset = 0
- Weight = 400
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- Height = 4905
- Index = 0
- Left = -10000
- TabIndex = 25
- Tag = "1000"
- Top = 0
- Width = 8235
- Begin VB.PictureBox Picture4
- Appearance = 0 'Flat
- BackColor = &H80000005&
- BorderStyle = 0 'None
- ForeColor = &H80000008&
- Height = 4935
- Index = 0
- Left = 0
- ScaleHeight = 4935
- ScaleWidth = 2565
- TabIndex = 2
- TabStop = 0 'False
- Top = 0
- Width = 2565
- Begin VB.PictureBox Picture10
- Height = 735
- Left = 2580
- ScaleHeight = 735
- ScaleWidth = 30
- TabIndex = 68
- TabStop = 0 'False
- Top = 2610
- Width = 30
- End
- Begin VB.PictureBox Picture6
- Appearance = 0 'Flat
- BackColor = &H80000005&
- BorderStyle = 0 'None
- ForeColor = &H80000008&
- Height = 1485
- Left = 150
- ScaleHeight = 1485
- ScaleWidth = 2355
- TabIndex = 67
- TabStop = 0 'False
- Top = 3390
- Width = 2355
- Begin VB.PictureBox Picture1
- Appearance = 0 'Flat
- BackColor = &H80000005&
- BorderStyle = 0 'None
- ForeColor = &H80000008&
- Height = 1200
- Index = 0
- Left = 200
- Picture = "Wizard.frx":482C2
- ScaleHeight = 1200
- ScaleWidth = 1980
- TabIndex = 7
- TabStop = 0 'False
- Tag = "1060"
- Top = 300
- Width = 1980
- End
- End
- Begin VB.Label lblStep1_4
- BackColor = &H00EED3C2&
- BackStyle = 0 'Transparent
- Caption = "4. Analyze"
- ForeColor = &H00BF4F59&
- Height = 195
- Left = 120
- TabIndex = 89
- Tag = "1044"
- Top = 1800
- Width = 2140
- End
- Begin VB.Line Line2
- BorderColor = &H00808080&
- Index = 2
- X1 = 2550
- X2 = 2550
- Y1 = 0
- Y2 = 4920
- End
- Begin VB.Line Line3
- Index = 1
- X1 = 120
- X2 = 2280
- Y1 = 480
- Y2 = 480
- End
- Begin VB.Label Label7
- BackColor = &H00EED3C2&
- Caption = "1. Introduction"
- ForeColor = &H00BF4F59&
- Height = 255
- Index = 1
- Left = 120
- TabIndex = 11
- Tag = "1041"
- Top = 720
- Width = 2140
- End
- Begin VB.Label Label8
- BackColor = &H00EED3C2&
- BackStyle = 0 'Transparent
- Caption = "3. Results"
- ForeColor = &H00BF4F59&
- Height = 255
- Index = 1
- Left = 120
- TabIndex = 9
- Tag = "1043"
- Top = 1440
- Width = 2140
- End
- Begin VB.Label Label9
- BackColor = &H00EED3C2&
- BackStyle = 0 'Transparent
- Caption = "2. Documents"
- ForeColor = &H00BF4F59&
- Height = 255
- Index = 1
- Left = 120
- TabIndex = 10
- Tag = "1042"
- Top = 1080
- Width = 2140
- End
- Begin VB.Label Label12
- BackStyle = 0 'Transparent
- Caption = "Steps"
- BeginProperty Font
- Name = "Arial"
- Size = 8.25
- Charset = 0
- Weight = 700
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- Height = 255
- Index = 1
- Left = 120
- TabIndex = 8
- Tag = "1040"
- Top = 240
- Width = 2115
- End
- End
- Begin VB.PictureBox Picture8
- Appearance = 0 'Flat
- BorderStyle = 0 'None
- ForeColor = &H80000008&
- Height = 4935
- Left = 2400
- ScaleHeight = 4935
- ScaleWidth = 5925
- TabIndex = 3
- TabStop = 0 'False
- Top = -30
- Width = 5925
- Begin VB.CheckBox chkShowIntro
- Caption = "Do not show this introduction again"
- Enabled = 0 'False
- Height = 315
- Left = 690
- MaskColor = &H00000000&
- TabIndex = 6
- Tag = "1103"
- Top = 4890
- Visible = 0 'False
- Width = 3810
- End
- Begin VB.Label lblIntroduction1
- AutoSize = -1 'True
- Caption = $"Wizard.frx":4F8B8
- Height = 585
- Left = 690
- TabIndex = 93
- Tag = "1101"
- Top = 750
- Width = 4890
- WordWrap = -1 'True
- End
- Begin VB.Label lblIntroduction3
- AutoSize = -1 'True
- Caption = "The wizard will remain on screen while the analysis is carried out."
- Height = 195
- Left = 690
- TabIndex = 0
- Tag = "1104"
- Top = 2670
- Width = 4845
- WordWrap = -1 'True
- End
- Begin VB.Label lblIntroduction2
- AutoSize = -1 'True
- Caption = "You will be able to select which documents you want to analyze as well as where you want the results to the analysis to be saved. "
- Height = 390
- Left = 690
- TabIndex = 1
- Tag = "1102"
- Top = 1800
- Width = 4875
- WordWrap = -1 'True
- End
- Begin VB.Label Label12
- BackStyle = 0 'Transparent
- Caption = "Introduction"
- BeginProperty Font
- Name = "Arial"
- Size = 8.25
- Charset = 0
- Weight = 700
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- Height = 255
- Index = 2
- Left = 450
- TabIndex = 5
- Tag = "1100"
- Top = 270
- Width = 4000
- End
- End
- End
- Begin VB.Frame fraStep
- BorderStyle = 0 'None
- Caption = "Setup"
- Enabled = 0 'False
- BeginProperty Font
- Name = "MS Sans Serif"
- Size = 8.25
- Charset = 0
- Weight = 400
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- Height = 4905
- Index = 1
- Left = -10000
- TabIndex = 32
- Tag = "2000"
- Top = 0
- Width = 8235
- Begin VB.PictureBox Picture4
- Appearance = 0 'Flat
- BackColor = &H80000005&
- BorderStyle = 0 'None
- ForeColor = &H80000008&
- Height = 4905
- Index = 1
- Left = 0
- ScaleHeight = 4905
- ScaleWidth = 2565
- TabIndex = 61
- TabStop = 0 'False
- Top = 0
- Width = 2565
- Begin VB.PictureBox Picture1
- Appearance = 0 'Flat
- BackColor = &H80000005&
- BorderStyle = 0 'None
- ForeColor = &H80000008&
- Height = 1200
- Index = 1
- Left = 350
- Picture = "Wizard.frx":4F971
- ScaleHeight = 1200
- ScaleWidth = 1980
- TabIndex = 62
- TabStop = 0 'False
- Tag = "1060"
- Top = 3690
- Width = 1980
- End
- Begin VB.Label lblStep2_4
- BackColor = &H00EED3C2&
- BackStyle = 0 'Transparent
- Caption = "4. Analyze"
- ForeColor = &H00BF4F59&
- Height = 195
- Left = 120
- TabIndex = 90
- Tag = "1044"
- Top = 1800
- Width = 2140
- End
- Begin VB.Line Line2
- BorderColor = &H00808080&
- Index = 1
- X1 = 2550
- X2 = 2550
- Y1 = 0
- Y2 = 4920
- End
- Begin VB.Label Label12
- BackStyle = 0 'Transparent
- Caption = "Steps"
- BeginProperty Font
- Name = "Arial"
- Size = 8.25
- Charset = 0
- Weight = 700
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- Height = 255
- Index = 3
- Left = 120
- TabIndex = 66
- Tag = "1040"
- Top = 240
- Width = 1335
- End
- Begin VB.Label Label9
- BackColor = &H00EED3C2&
- Caption = "2. Documents"
- ForeColor = &H00BF4F59&
- Height = 255
- Index = 2
- Left = 120
- TabIndex = 65
- Tag = "1042"
- Top = 1080
- Width = 2140
- End
- Begin VB.Label Label8
- BackColor = &H00EED3C2&
- BackStyle = 0 'Transparent
- Caption = "3. Results"
- ForeColor = &H00BF4F59&
- Height = 255
- Index = 2
- Left = 120
- TabIndex = 64
- Tag = "1043"
- Top = 1440
- Width = 2140
- End
- Begin VB.Label Label7
- BackColor = &H00EED3C2&
- BackStyle = 0 'Transparent
- Caption = "1. Introduction"
- ForeColor = &H00BF4F59&
- Height = 255
- Index = 2
- Left = 120
- TabIndex = 63
- Tag = "1041"
- Top = 720
- Width = 2140
- End
- Begin VB.Line Line3
- Index = 2
- X1 = 120
- X2 = 2280
- Y1 = 480
- Y2 = 480
- End
- End
- Begin VB.PictureBox Picture7
- Appearance = 0 'Flat
- BorderStyle = 0 'None
- ForeColor = &H80000008&
- Height = 4725
- Left = 2580
- ScaleHeight = 4725
- ScaleWidth = 5535
- TabIndex = 58
- TabStop = 0 'False
- Top = 0
- Width = 5535
- Begin VB.ComboBox cbIgnoreOld
- Height = 330
- ItemData = "Wizard.frx":56F67
- Left = 3950
- List = "Wizard.frx":56F74
- Style = 2 'Dropdown List
- TabIndex = 99
- Top = 1570
- Width = 1215
- End
- Begin VB.CheckBox chkIgnoreOld
- Caption = "Ignore documents older than"
- Height = 225
- Left = 450
- TabIndex = 98
- Top = 1600
- Width = 3400
- End
- Begin VB.CheckBox chkWordDoc
- Caption = "Documents (*.doc)"
- Height = 225
- Left = 2160
- TabIndex = 19
- Tag = "1208"
- Top = 2600
- Value = 1 'Checked
- Width = 3200
- End
- Begin VB.CheckBox chkWordTemplate
- Caption = "Templates (*.dot)"
- Height = 225
- Left = 2160
- TabIndex = 20
- Tag = "1209"
- Top = 2900
- Width = 3200
- End
- Begin VB.CheckBox chkPPTemplate
- Caption = "Templates (*.pot)"
- Height = 225
- Left = 2160
- TabIndex = 24
- Tag = "1215"
- Top = 4400
- Width = 3200
- End
- Begin VB.CheckBox chkPPDoc
- Caption = "Presentations (*.ppt)"
- Height = 225
- Left = 2160
- TabIndex = 23
- Tag = "1214"
- Top = 4100
- Width = 3200
- End
- Begin VB.CheckBox chkExcelDoc
- Caption = "Spreadsheets (*.xls)"
- Height = 225
- Left = 2160
- TabIndex = 21
- Tag = "1211"
- Top = 3350
- Width = 3200
- End
- Begin VB.CheckBox chkExcelTemplate
- Caption = "Templates (*.xlt)"
- Height = 225
- Left = 2160
- TabIndex = 22
- Tag = "1212"
- Top = 3650
- Width = 3200
- End
- Begin VB.CommandButton btnBrowseDirInput
- Caption = "..."
- Height = 315
- Left = 4740
- TabIndex = 17
- Top = 900
- Width = 400
- End
- Begin VB.TextBox txtInputDir
- Height = 315
- Left = 450
- TabIndex = 16
- Tag = "1205"
- Text = "C:\"
- Top = 900
- Width = 4155
- End
- Begin VB.CheckBox chkIncludeSubdirs
- Caption = "Include subdirectories in the analysis"
- Height = 225
- Left = 450
- TabIndex = 18
- Tag = "1202"
- Top = 1300
- Width = 4965
- End
- Begin VB.Label lblDocTypes
- Caption = "Document types to analyze"
- Height = 225
- Left = 450
- TabIndex = 95
- Tag = "1206"
- Top = 2250
- Width = 4905
- End
- Begin VB.Label lblChooseDocs
- AutoSize = -1 'True
- Caption = "Choose the documents you want to analyze"
- BeginProperty Font
- Name = "Arial"
- Size = 8.25
- Charset = 0
- Weight = 700
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- Height = 195
- Left = 300
- TabIndex = 94
- Tag = "1200"
- Top = 240
- Width = 5115
- WordWrap = -1 'True
- End
- Begin VB.Label Label13
- AutoSize = -1 'True
- Caption = "PowerPoint"
- Height = 225
- Index = 2
- Left = 690
- TabIndex = 74
- Tag = "1213"
- Top = 4100
- Width = 1245
- WordWrap = -1 'True
- End
- Begin VB.Label Label13
- AutoSize = -1 'True
- Caption = "Excel"
- Height = 225
- Index = 1
- Left = 690
- TabIndex = 73
- Tag = "1210"
- Top = 3350
- Width = 1245
- WordWrap = -1 'True
- End
- Begin VB.Label Label13
- AutoSize = -1 'True
- Caption = "Word"
- Height = 225
- Index = 0
- Left = 690
- TabIndex = 72
- Tag = "1207"
- Top = 2600
- Width = 1245
- WordWrap = -1 'True
- End
- Begin VB.Label Label1
- Caption = "Location of Microsoft Office documents"
- Height = 200
- Left = 450
- TabIndex = 59
- Tag = "1201"
- Top = 600
- Width = 4935
- End
- End
- End
- Begin VB.Frame fraStep
- BorderStyle = 0 'None
- Caption = "Options"
- Enabled = 0 'False
- BeginProperty Font
- Name = "MS Sans Serif"
- Size = 8.25
- Charset = 0
- Weight = 400
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- Height = 4905
- Index = 2
- Left = -10000
- TabIndex = 33
- Tag = "2002"
- Top = 0
- Width = 8235
- Begin VB.PictureBox Picture11
- BorderStyle = 0 'None
- Height = 555
- Left = 7260
- ScaleHeight = 555
- ScaleWidth = 705
- TabIndex = 75
- Top = 1890
- Width = 705
- Begin VB.CommandButton btnBrowseDirOut
- Caption = "..."
- Height = 375
- Left = 90
- TabIndex = 28
- Top = 90
- Width = 495
- End
- End
- Begin VB.TextBox txtResultsName
- Height = 375
- Left = 3030
- TabIndex = 26
- Tag = "1302"
- Text = "Analysis Results.xls"
- Top = 1140
- Width = 3045
- End
- Begin VB.TextBox txtOutputDir
- Height = 375
- Left = 3030
- TabIndex = 27
- Top = 1980
- Width = 4185
- End
- Begin VB.PictureBox Picture5
- Appearance = 0 'Flat
- BorderStyle = 0 'None
- ForeColor = &H80000008&
- Height = 1365
- Left = 3300
- ScaleHeight = 1365
- ScaleWidth = 4635
- TabIndex = 57
- TabStop = 0 'False
- Top = 3210
- Width = 4635
- Begin VB.OptionButton rdbResultsPrompt
- Caption = "Ask me before overwriting"
- Height = 435
- Left = 0
- TabIndex = 29
- Tag = "1312"
- Top = 0
- Value = -1 'True
- Width = 4485
- End
- Begin VB.OptionButton rdbResultsOverwrite
- Caption = "Overwrite without asking me"
- Height = 435
- Left = 0
- TabIndex = 30
- Tag = "1313"
- Top = 450
- Width = 4455
- End
- Begin VB.OptionButton rdbResultsAppend
- Caption = "Append the new results to the existing results"
- Height = 675
- Left = 0
- TabIndex = 31
- Tag = "1314"
- Top = 780
- Visible = 0 'False
- Width = 4515
- End
- End
- Begin VB.Frame Frame3
- Appearance = 0 'Flat
- BackColor = &H80000005&
- BorderStyle = 0 'None
- Enabled = 0 'False
- ForeColor = &H0099A8AC&
- Height = 5175
- Index = 0
- Left = 0
- TabIndex = 39
- Top = 0
- Width = 2535
- Begin VB.PictureBox Picture1
- Appearance = 0 'Flat
- BackColor = &H80000005&
- BorderStyle = 0 'None
- ForeColor = &H80000008&
- Height = 1200
- Index = 3
- Left = 350
- Picture = "Wizard.frx":56F97
- ScaleHeight = 1200
- ScaleWidth = 1980
- TabIndex = 40
- TabStop = 0 'False
- Top = 3690
- Width = 1980
- End
- Begin VB.Label lblStep3_4
- BackColor = &H00EED3C2&
- BackStyle = 0 'Transparent
- Caption = "4. Analyze"
- ForeColor = &H00BF4F59&
- Height = 195
- Left = 120
- TabIndex = 91
- Tag = "1044"
- Top = 1800
- Width = 2140
- End
- Begin VB.Label Label12
- BackStyle = 0 'Transparent
- Caption = "Steps"
- BeginProperty Font
- Name = "Arial"
- Size = 8.25
- Charset = 0
- Weight = 700
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- Height = 255
- Index = 0
- Left = 120
- TabIndex = 53
- Tag = "1040"
- Top = 240
- Width = 1335
- End
- Begin VB.Label Label9
- BackColor = &H00EED3C2&
- BackStyle = 0 'Transparent
- Caption = "2. Documents"
- ForeColor = &H00BF4F59&
- Height = 255
- Index = 0
- Left = 120
- TabIndex = 43
- Tag = "1042"
- Top = 1080
- Width = 2140
- End
- Begin VB.Label Label8
- BackColor = &H00EED3C2&
- Caption = "3. Results"
- ForeColor = &H00BF4F59&
- Height = 255
- Index = 0
- Left = 120
- TabIndex = 42
- Tag = "1043"
- Top = 1440
- Width = 2140
- End
- Begin VB.Label Label7
- BackColor = &H00EED3C2&
- BackStyle = 0 'Transparent
- Caption = "1. Introduction"
- ForeColor = &H00BF4F59&
- Height = 255
- Index = 0
- Left = 120
- TabIndex = 41
- Tag = "1041"
- Top = 720
- Width = 2140
- End
- Begin VB.Line Line3
- Index = 0
- X1 = 120
- X2 = 2280
- Y1 = 480
- Y2 = 480
- End
- End
- Begin VB.Label Label3
- Caption = "File name for the results spreadsheet"
- Height = 195
- Left = 3030
- TabIndex = 71
- Tag = "1301"
- Top = 840
- Width = 4785
- End
- Begin VB.Label lblResultsLocation
- Caption = "Location"
- Height = 195
- Left = 3030
- TabIndex = 70
- Tag = "1304"
- Top = 1710
- Width = 4755
- End
- Begin VB.Label Label13
- AutoSize = -1 'True
- Caption = "If results already exisit under the same name and location:"
- Height = 195
- Index = 5
- Left = 3030
- TabIndex = 38
- Tag = "1311"
- Top = 2730
- Width = 4230
- WordWrap = -1 'True
- End
- Begin VB.Line Line2
- BorderColor = &H00808080&
- Index = 0
- X1 = 2550
- X2 = 2550
- Y1 = 0
- Y2 = 4920
- End
- Begin VB.Label lblChooseResults
- AutoSize = -1 'True
- Caption = "Choose where and how to save the analysis results"
- BeginProperty Font
- Name = "Arial"
- Size = 8.25
- Charset = 0
- Weight = 700
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- Height = 195
- Left = 2880
- TabIndex = 37
- Tag = "1300"
- Top = 240
- Width = 5055
- WordWrap = -1 'True
- End
- End
- Begin VB.Frame fraStep
- BorderStyle = 0 'None
- Caption = "Analyze"
- Enabled = 0 'False
- BeginProperty Font
- Name = "MS Sans Serif"
- Size = 8.25
- Charset = 0
- Weight = 400
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- Height = 4905
- Index = 3
- Left = 0
- TabIndex = 34
- Tag = "3000"
- Top = 0
- Width = 2.45745e5
- Begin VB.PictureBox Picture12
- Appearance = 0 'Flat
- BorderStyle = 0 'None
- ForeColor = &H80000008&
- Height = 4905
- Left = 10020
- ScaleHeight = 4905
- ScaleWidth = 8175
- TabIndex = 69
- TabStop = 0 'False
- Top = 0
- Width = 8175
- End
- Begin VB.CommandButton btnPrepare
- Caption = "Prepare"
- Enabled = 0 'False
- Height = 375
- Left = 3340
- TabIndex = 97
- Tag = "1411"
- Top = 4410
- Visible = 0 'False
- Width = 4000
- End
- Begin VB.CommandButton btnRunAnalysis
- Caption = "Run"
- Height = 375
- Left = 3340
- TabIndex = 35
- Tag = "1404"
- Top = 3410
- Width = 4000
- End
- Begin VB.CommandButton btnViewResults
- Caption = "View"
- Enabled = 0 'False
- Height = 375
- Left = 3340
- TabIndex = 36
- Tag = "1406"
- Top = 3910
- Width = 4000
- End
- Begin VB.Frame Frame3
- Appearance = 0 'Flat
- BackColor = &H80000005&
- BorderStyle = 0 'None
- Enabled = 0 'False
- ForeColor = &H0099A8AC&
- Height = 5175
- Index = 3
- Left = 0
- TabIndex = 44
- Top = 0
- Width = 2535
- Begin VB.PictureBox Picture4
- Appearance = 0 'Flat
- BackColor = &H80000005&
- BorderStyle = 0 'None
- ForeColor = &H80000008&
- Height = 1575
- Index = 2
- Left = 150
- ScaleHeight = 1575
- ScaleWidth = 2385
- TabIndex = 55
- TabStop = 0 'False
- Top = 3390
- Width = 2385
- Begin VB.PictureBox Picture1
- Appearance = 0 'Flat
- BackColor = &H80000005&
- BorderStyle = 0 'None
- ForeColor = &H80000008&
- Height = 1200
- Index = 2
- Left = 200
- Picture = "Wizard.frx":5E58D
- ScaleHeight = 1200
- ScaleWidth = 2475
- TabIndex = 56
- TabStop = 0 'False
- Tag = "1060"
- Top = 300
- Width = 2480
- End
- End
- Begin VB.Label lblStep4_4
- BackColor = &H00EED3C2&
- Caption = "4. Analyze"
- ForeColor = &H00BF4F59&
- Height = 255
- Left = 120
- TabIndex = 92
- Tag = "1044"
- Top = 1800
- Width = 2140
- End
- Begin VB.Label Label12
- BackStyle = 0 'Transparent
- Caption = "Steps"
- BeginProperty Font
- Name = "Arial"
- Size = 8.25
- Charset = 0
- Weight = 700
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- Height = 255
- Index = 5
- Left = 120
- TabIndex = 54
- Tag = "1040"
- Top = 240
- Width = 1335
- End
- Begin VB.Label Label9
- BackColor = &H00EED3C2&
- BackStyle = 0 'Transparent
- Caption = "2. Documents"
- ForeColor = &H00BF4F59&
- Height = 255
- Index = 3
- Left = 120
- TabIndex = 47
- Tag = "1042"
- Top = 1080
- Width = 2140
- End
- Begin VB.Label Label8
- BackColor = &H00EED3C2&
- BackStyle = 0 'Transparent
- Caption = "3. Results"
- ForeColor = &H00BF4F59&
- Height = 255
- Index = 3
- Left = 120
- TabIndex = 46
- Tag = "1043"
- Top = 1440
- Width = 2140
- End
- Begin VB.Label Label7
- BackColor = &H00EED3C2&
- BackStyle = 0 'Transparent
- Caption = "1. Introduction"
- ForeColor = &H00BF4F59&
- Height = 255
- Index = 3
- Left = 120
- TabIndex = 45
- Tag = "1041"
- Top = 720
- Width = 2140
- End
- Begin VB.Line Line3
- Index = 3
- X1 = 120
- X2 = 2280
- Y1 = 480
- Y2 = 480
- End
- End
- Begin VB.Label lblSkippedOld
- Caption = "Skipped <TOPIC> documets, because they were too old"
- Height = 195
- Left = 3180
- TabIndex = 60
- Top = 2880
- Width = 4935
- End
- Begin VB.Label lblSetupDone
- AutoSize = -1 'True
- Caption = "Run the analysis and view the results"
- BeginProperty Font
- Name = "Arial"
- Size = 8.25
- Charset = 0
- Weight = 700
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- Height = 195
- Left = 2880
- TabIndex = 96
- Tag = "1400"
- Top = 240
- Width = 4905
- WordWrap = -1 'True
- End
- Begin VB.Label lblNumPPT
- Caption = "<TOPIC> Presentations"
- Height = 255
- Left = 4620
- TabIndex = 88
- Tag = "1409"
- Top = 2280
- Width = 3375
- End
- Begin VB.Label lblNumPOT
- Caption = "<TOPIC> Templates"
- Height = 255
- Left = 4620
- TabIndex = 87
- Tag = "1403"
- Top = 2550
- Width = 3375
- End
- Begin VB.Label lblNumXLS
- Caption = "<TOPIC> Spreadsheets"
- Height = 255
- Left = 4620
- TabIndex = 86
- Tag = "1408"
- Top = 1680
- Width = 3375
- End
- Begin VB.Label lblNumXLT
- Caption = "<TOPIC> Templates"
- Height = 255
- Left = 4620
- TabIndex = 85
- Tag = "1403"
- Top = 1950
- Width = 3375
- End
- Begin VB.Label Label16
- AutoSize = -1 'True
- Caption = "PowerPoint"
- Height = 195
- Left = 3360
- TabIndex = 82
- Tag = "1213"
- Top = 2280
- Width = 1095
- WordWrap = -1 'True
- End
- Begin VB.Label Label13
- Caption = "Word"
- Height = 705
- Index = 10
- Left = 0
- TabIndex = 81
- Tag = "1207"
- Top = 0
- Width = 1245
- End
- Begin VB.Label Label13
- Caption = "Excel"
- Height = 705
- Index = 9
- Left = 0
- TabIndex = 80
- Tag = "1210"
- Top = 810
- Width = 1245
- End
- Begin VB.Label Label13
- Caption = "PowerPoint"
- Height = 585
- Index = 8
- Left = 0
- TabIndex = 79
- Tag = "1213"
- Top = 1620
- Width = 1245
- End
- Begin VB.Label Label13
- Caption = "Word"
- Height = 585
- Index = 7
- Left = 0
- TabIndex = 78
- Tag = "1207"
- Top = 0
- Width = 1245
- End
- Begin VB.Label Label13
- Caption = "Excel"
- Height = 585
- Index = 6
- Left = 0
- TabIndex = 77
- Tag = "1210"
- Top = 810
- Width = 1245
- End
- Begin VB.Label Label13
- Caption = "PowerPoint"
- Height = 465
- Index = 4
- Left = 0
- TabIndex = 76
- Tag = "1213"
- Top = 1620
- Width = 1245
- End
- Begin VB.Label lblNumTemplates
- Caption = "<TOPIC> Templates"
- Height = 255
- Left = 4620
- TabIndex = 52
- Tag = "1403"
- Top = 1350
- Width = 3375
- End
- Begin VB.Label lblNumDocs
- Caption = "<TOPIC> Documents"
- Height = 255
- Left = 4620
- TabIndex = 51
- Tag = "1402"
- Top = 1080
- Width = 3375
- End
- Begin VB.Line Line6
- BorderColor = &H00808080&
- X1 = 2640
- X2 = 8040
- Y1 = 3270
- Y2 = 3270
- End
- Begin VB.Label Label15
- AutoSize = -1 'True
- Caption = "Excel"
- Height = 195
- Left = 3360
- TabIndex = 50
- Tag = "1210"
- Top = 1680
- Width = 1095
- WordWrap = -1 'True
- End
- Begin VB.Label Label14
- AutoSize = -1 'True
- Caption = "Word"
- Height = 195
- Left = 3360
- TabIndex = 49
- Tag = "1207"
- Top = 1080
- Width = 1110
- WordWrap = -1 'True
- End
- Begin VB.Label lblTotalNumDocs
- AutoSize = -1 'True
- Caption = "A total of <TOPIC> documents will be analyzed:"
- Height = 195
- Left = 3180
- TabIndex = 48
- Tag = "1401"
- Top = 660
- Width = 4800
- WordWrap = -1 'True
- End
- Begin VB.Line Line2
- BorderColor = &H00808080&
- Index = 3
- X1 = 2550
- X2 = 2550
- Y1 = 0
- Y2 = 4920
- End
- End
- Begin VB.PictureBox picNav
- Align = 2 'Align Bottom
- Appearance = 0 'Flat
- BorderStyle = 0 'None
- BeginProperty Font
- Name = "MS Sans Serif"
- Size = 8.25
- Charset = 0
- Weight = 400
- Underline = 0 'False
- Italic = 0 'False
- Strikethrough = 0 'False
- EndProperty
- ForeColor = &H80000008&
- Height = 570
- Left = 0
- ScaleHeight = 570
- ScaleWidth = 8175
- TabIndex = 4
- TabStop = 0 'False
- Top = 4950
- Width = 8175
- Begin VB.CommandButton cmdNav
- Caption = "Finish"
- Height = 312
- Index = 4
- Left = 5325
- MaskColor = &H00000000&
- TabIndex = 14
- Tag = "1023"
- Top = 120
- Width = 1320
- End
- Begin VB.CommandButton cmdNav
- Caption = "Next >>"
- Height = 312
- Index = 3
- Left = 3870
- MaskColor = &H00000000&
- TabIndex = 13
- Tag = "1022"
- Top = 120
- Width = 1320
- End
- Begin VB.CommandButton cmdNav
- Caption = "<< Back"
- Height = 312
- Index = 2
- Left = 2535
- MaskColor = &H00000000&
- TabIndex = 12
- Tag = "1021"
- Top = 120
- Width = 1320
- End
- Begin VB.CommandButton cmdNav
- Cancel = -1 'True
- Caption = "Cancel"
- Height = 312
- Index = 1
- Left = 6750
- MaskColor = &H00000000&
- TabIndex = 15
- Tag = "1024"
- Top = 120
- Width = 1320
- End
- End
- Begin VB.Label Label18
- Caption = "<TOPIC> Documents"
- Height = 255
- Left = 0
- TabIndex = 84
- Top = 0
- Width = 2085
- WordWrap = -1 'True
- End
- Begin VB.Label Label17
- Caption = "<TOPIC> Templates"
- Height = 255
- Left = 0
- TabIndex = 83
- Top = 390
- Width = 3615
- WordWrap = -1 'True
- End
- Begin VB.Line Line4
- BorderColor = &H00808080&
- X1 = 0
- X2 = 8160
- Y1 = 4920
- Y2 = 4920
- End
-End
-Attribute VB_Name = "frmWizard"
-Attribute VB_GlobalNameSpace = False
-Attribute VB_Creatable = False
-Attribute VB_PredeclaredId = True
-Attribute VB_Exposed = False
-' *******************************************************************************
-' *
-' * Copyright 2000, 2010 Oracle and/or its affiliates. All rights reserved. Use of this
-' * product is subject to license terms.
-' *
-' *******************************************************************************
-
-Option Explicit
-
-Const TOPIC_STR = "<TOPIC>"
-Const TOPIC2_STR = "<TOPIC2>"
-Const CR_STR = "<CR>"
-Const CDEBUG_LEVEL_DEFAULT = 1 'Will output all Debug output to analysis.log file
-Const CSUPPORTED_VERSION = 9#
-
-Const NUM_STEPS = 4
-
-Const CAPPNAME_WORD = "Word"
-Const CAPPNAME_EXCEL = "Excel"
-Const CAPPNAME_POWERPOINT = "PowerPoint"
-Const CANALYZING = "Analyzing"
-
-Const BTN_CANCEL = 1
-Const BTN_BACK = 2
-Const BTN_NEXT = 3
-Const BTN_FINISH = 4
-
-Const STEP_INTRO = 0
-Const STEP_1 = 1
-Const STEP_2 = 2
-Const STEP_FINISH = 3
-
-Const DIR_NONE = 0
-Const DIR_BACK = 1
-Const DIR_NEXT = 2
-
-Const CPRODUCTNAME_STR = "<PRODUCTNAME>"
-
-Const CSTR_ANALYSIS_LOG_DONE = "Done"
-
-Const CINPUT_DIR = "indir"
-Const COUTPUT_DIR = "outdir"
-Const CRESULTS_FILE = "resultsfile"
-Const CLOG_FILE = "logfile"
-Const CRESULTS_TEMPLATE = "resultstemplate"
-Const CRESULTS_EXIST = "resultsexist"
-Const CPROMPT_FILE = "promptfile"
-Const COVERWRITE_FILE = "overwritefile"
-Const CAPPEND_FILE = "appendfile"
-Const CNEW_RESULTS_FILE = "newresultsfile"
-Const CINCLUDE_SUBDIRS = "includesubdirs"
-Const CDEBUG_LEVEL = "debuglevel"
-Const CTYPE_WORDDOC = "typeworddoc"
-Const CTYPE_WORDDOT = "typeworddot"
-Const CTYPE_EXCELDOC = "typeexceldoc"
-Const CTYPE_EXCELDOT = "typeexceldot"
-Const CTYPE_PPDOC = "typepowerpointdoc"
-Const CTYPE_PPDOT = "typepowerpointdot"
-Const COUTPUT_TYPE = "outputtype"
-Const COUTPUT_TYPE_XLS = "xls"
-Const COUTPUT_TYPE_XML = "xml"
-Const COUTPUT_TYPE_BOTH = "both"
-Const CVERSION = "version"
-Const CDOPREPARE = "prepare"
-Const CTITLE = "title"
-Const CIGNORE_OLD_DOCS = "ignoreolddocuments"
-Const CISSUE_LIMIT = "issuesmonthlimit"
-Const CISSUE_LIMIT_DAW = 6
-Private mIssueLimit As Integer
-Const CDEFAULT_PASSWORD = "defaultpassword"
-Const CSTR_TEST_PASSWORD = "test"
-Private mDefaultPassword As String
-
-Const CLAST_CHECKPOINT As String = "LastCheckpoint"
-Const CNEXT_FILE As String = "NextFile"
-Const C_ABORT_ANALYSIS As String = "AbortAnalysis"
-
-Const CNUMBER_TOTAL_DOCS = "total_numberdocs"
-Const CNUMBER_DOCS_DOC = "numberdocs_doc"
-Const CNUMBER_TEMPLATES_DOT = "numbertemplates_dot"
-Const CNUMBER_DOCS_XLS = "numberdocs_xls"
-Const CNUMBER_TEMPLATES_XLT = "numbertemplates_xlt"
-Const CNUMBER_DOCS_PPT = "numberdocs_ppt"
-Const CNUMBER_TEMPLATES_POT = "numbertemplates_pot"
-Const CSTART_TIME = "start"
-Const CEND_TIME = "end"
-Const CELAPSED_TIME = "time_for_analysis"
-Const CWINVERSION = "win_version"
-Const CUSER_LOCALE_INFO = "user_locale"
-Const CSYS_LOCALE_INFO = "system_locale"
-Const CWORD_VERSION = "word_ver"
-Const CEXCEL_VERSION = "excel_ver"
-Const CPOWERPOINT_VERSION = "powerpoint_ver"
-Const CNOT_INSTALLED = "not installed"
-
-Const CRESULTS_FILE_EXTENSION = ".xls"
-Const CCONFIG_BACKUP_EXT = "_bak"
-Const CDEFAULT_README_NAME = "UserGuide"
-
-Const C_DOCS_LESS_3_MONTH = "DocumentsYoungerThan3Month"
-Const C_DOCS_LESS_6_MONTH = "DocumentsYoungerThan6Month"
-Const C_DOCS_LESS_12_MONTH = "DocumentsYoungerThan12Month"
-Const C_DOCS_MORE_12_MONTH = "DocumentsOlderThan12Month"
-
-'module level vars
-Dim mnCurStep As Integer
-Dim mbTrue As Boolean
-Dim mbFalse As Boolean
-Dim mLblSteps As String
-Dim mChbSubdirs As String
-
-Dim mWordDocCount As Long
-Dim mExcelDocCount As Long
-Dim mPPDocCount As Long
-
-Dim mWordTemplateCount As Long
-Dim mExcelTemplateCount As Long
-Dim mPPTemplateCount As Long
-Dim mTotalDocCount As Long
-Dim mIgnoredDocCount As Long
-
-Public VBInst As VBIDE.VBE
-Dim mbFinishOK As Boolean
-Dim mbAllowExit As Boolean
-Private mStrTrue As String
-Private mLogFilePath As String
-Private mDebugLevel As String
-Private mIniFilePath As String
-Private mbDocCountCurrent As Boolean
-Private mbDoPrepare As Boolean
-
-Dim mDocFiles As CollectedFiles
-
-Private Declare Sub InitCommonControls Lib "comctl32" ()
-Private Declare Function GetTickCount Lib "kernel32" () As Long
-Private Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
-
-Const FORMAT_MESSAGE_FROM_SYSTEM = &H1000
-
-Private Declare Function FormatMessage Lib "kernel32" Alias _
- "FormatMessageA" (ByVal dwFlags As Long, lpSource As Long, _
- ByVal dwMessageId As Long, ByVal dwLanguageId As Long, _
- ByVal lpBuffer As String, ByVal nSize As Long, Arguments As Any) As Long
-
-
-Private Const HKEY_CURRENT_USER As Long = &H80000001
-Private Const HKEY_LOCAL_MACHINE As Long = &H80000002
-
-Const WORD_APP = "word"
-Const EXCEL_APP = "excel"
-Const PP_APP = "pp"
-Const REG_KEY_APP_PATH = "Software\Microsoft\Windows\CurrentVersion\App Paths\"
-
-
-Function GetAppPath(myApp As String) As String
- Dim myPath As String
-
- If (myApp = WORD_APP) Then
- myPath = GetRegistryInfo(HKEY_LOCAL_MACHINE, REG_KEY_APP_PATH & "winword.exe", "")
- ElseIf (myApp = EXCEL_APP) Then
- myPath = GetRegistryInfo(HKEY_LOCAL_MACHINE, REG_KEY_APP_PATH & "excel.exe", "")
- ElseIf (myApp = PP_APP) Then
- myPath = GetRegistryInfo(HKEY_LOCAL_MACHINE, REG_KEY_APP_PATH & "powerpnt.exe", "")
- Else
- MsgBox "Unknown application: " & myApp, vbCritical
- Exit Function
- End If
-
- If (myPath = "") Then
- If (myApp = WORD_APP) Then
- myPath = GetRegistryInfo(HKEY_CURRENT_USER, REG_KEY_APP_PATH & "winword.exe", "")
- ElseIf (myApp = EXCEL_APP) Then
- myPath = GetRegistryInfo(HKEY_CURRENT_USER, REG_KEY_APP_PATH & "excel.exe", "")
- ElseIf (myApp = PP_APP) Then
- myPath = GetRegistryInfo(HKEY_CURRENT_USER, REG_KEY_APP_PATH & "powerpnt.exe", "")
- End If
- End If
-
- GetAppPath = myPath
-End Function
-
-Function GetDriverDoc(myApp As String) As String
- Dim myPath As String
- Dim errStr As String
- Dim fso As New FileSystemObject
-
- If (myApp = WORD_APP) Then
- myPath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CWORD_DRIVER_FILE)
- ElseIf (myApp = EXCEL_APP) Then
- myPath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CEXCEL_DRIVER_FILE)
- ElseIf (myApp = PP_APP) Then
- myPath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CPP_DRIVER_FILE)
- Else
- MsgBox "Unknown application: " & myApp, vbCritical
- GoTo FinalExit
- End If
-
- If Not fso.FileExists(myPath) Then
- errStr = ReplaceTopic2Tokens(GetResString(ERR_MISSING_WORD_DRIVER), _
- TOPIC_STR, myPath, CR_STR, Chr(13))
- WriteDebug errStr
- MsgBox errStr, vbCritical
- GoTo FinalExit
- End If
-
- GetDriverDoc = myPath
-
-FinalExit:
- Set fso = Nothing
-End Function
-
-
-
-
-Private Function AutomationMessageText(lCode As Long) As String
- Dim sRtrnCode As String
- Dim lRet As Long
-
- sRtrnCode = Space$(256)
- lRet = FormatMessage(FORMAT_MESSAGE_FROM_SYSTEM, 0&, lCode, 0&, _
- sRtrnCode, 256&, 0&)
- If lRet > 0 Then
- AutomationMessageText = Left(sRtrnCode, lRet)
- Else
- AutomationMessageText = "Error not found."
- End If
-
-End Function
-
-Private Sub btnBrowseDirInput_Click()
- Dim folder As String
- Dim StartDir As String
-
- If Len(txtInputDir.Text) > 0 Then
- StartDir = txtInputDir.Text
- End If
-
- folder = BrowseForFolder(Me, GetResString(BROWSE_FOR_DOC_DIR_ID), StartDir)
- If Len(folder) = 0 Then
- Exit Sub 'User Selected Cancel
- End If
- txtInputDir.Text = folder
- txtInputDir.ToolTipText = folder
-
- If Len(txtOutputDir.Text) = 0 Then
- txtOutputDir.Text = folder
- txtOutputDir.ToolTipText = folder
- End If
-End Sub
-
-Private Sub btnBrowseDirOut_Click()
- Dim folder As String
- Dim StartDir As String
-
- If Len(txtOutputDir.Text) > 0 Then
- StartDir = txtOutputDir.Text
- End If
-
- folder = BrowseForFolder(Me, GetResString(BROWSE_FOR_RES_DIR_ID), StartDir)
- If Len(folder) = 0 Then
- Exit Sub 'User Selected Cancel
- End If
- txtOutputDir.Text = folder
- txtOutputDir.ToolTipText = folder
-End Sub
-
-Private Sub btnPrepare_Click()
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "btnPrepare_Click"
-
- mbDoPrepare = True
- mbAllowExit = True
-
- btnViewResults.Enabled = False
- btnRunAnalysis.Enabled = False
- btnPrepare.Enabled = False
-
- cmdNav(BTN_CANCEL).Enabled = False
- cmdNav(BTN_BACK).Enabled = False
- cmdNav(BTN_NEXT).Enabled = False
- cmdNav(BTN_FINISH).Enabled = False
- btnPrepare.Caption = GetResString(RUNBTN_RUNNING_ID)
-
- Dim str As String
-
- If RunAnalysis(True) Then
- cmdNav(BTN_FINISH).Enabled = True
- btnRunAnalysis.Enabled = True
- btnViewResults.Enabled = True
- btnPrepare.Enabled = True
- btnViewResults.SetFocus
- str = ReplaceTopic2Tokens(GetResString(RID_STR_ENG_OTHER_PREPARE_COMPLETED_PREP_ID), _
- TOPIC_STR, getOutputDir, CR_STR, Chr(13))
- MsgBox str, vbInformation
- Else
- cmdNav(BTN_FINISH).Enabled = False
- btnRunAnalysis.Enabled = True
- btnViewResults.Enabled = False
- btnPrepare.Enabled = False
- End If
-
-FinalExit:
- mbDoPrepare = False
- cmdNav(BTN_CANCEL).Enabled = True
- cmdNav(BTN_BACK).Enabled = True
- cmdNav(BTN_NEXT).Enabled = False
- btnPrepare.Caption = GetResString(PREPAREBTN_START_ID)
- Exit Sub
-
-HandleErrors:
- cmdNav(BTN_FINISH).Enabled = False
- btnRunAnalysis.Enabled = True
- btnViewResults.Enabled = False
- btnPrepare.Enabled = False
-
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Sub
-
-
-Private Sub cmdNav_Click(Index As Integer)
- On Error GoTo HandleError
- Dim currentFunctionName As String
- currentFunctionName = "cmdNav_Click"
- Dim nAltStep As Integer
- Dim rc As Long
- Dim fso As Scripting.FileSystemObject
-
- Select Case Index
- Case BTN_CANCEL
- 'Copy backup configuration file over existing
- If fso Is Nothing Then
- Set fso = New Scripting.FileSystemObject
- End If
- If fso.FileExists(mIniFilePath & CCONFIG_BACKUP_EXT) Then
- DeleteFile mIniFilePath
- AttemptToCopyFile mIniFilePath & CCONFIG_BACKUP_EXT, mIniFilePath
- End If
- Set mDocFiles = Nothing
-
- Unload Me
-
- Case BTN_BACK
- nAltStep = mnCurStep - 1
- SetStep nAltStep, DIR_BACK
-
- Case BTN_NEXT
- nAltStep = mnCurStep + 1
- SetStep nAltStep, DIR_NEXT
-
- Case BTN_FINISH
- If (Not mbAllowExit) Then
- Dim str As String
- Dim response As Integer
-
- str = ReplaceTopicTokens(GetResString(RID_STR_ENG_ANALYSE_NOT_RUN), CR_STR, Chr(13))
- response = MsgBox(str, vbOKCancel + vbInformation)
- If response = vbOK Then ' User chose Ok.
- mbAllowExit = True
- End If
- End If
-
- If (mbAllowExit) Then
- DeleteFile mIniFilePath & CCONFIG_BACKUP_EXT
- Set mDocFiles = Nothing
- Unload Me
- End If
- End Select
-
-FinalExit:
- Set fso = Nothing
- Exit Sub
-
-HandleError:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
-
- Resume FinalExit
-End Sub
-
-Private Sub btnRunAnalysis_Click()
- On Error GoTo HandleErrors
- Dim bViewResults As Boolean
- Dim str As String
- Dim response As Integer
-
- btnViewResults.Enabled = False
- btnRunAnalysis.Enabled = False
- btnPrepare.Enabled = False
- bViewResults = False
- mbAllowExit = True
-
- cmdNav(BTN_CANCEL).Enabled = False
- cmdNav(BTN_BACK).Enabled = False
- cmdNav(BTN_NEXT).Enabled = False
- cmdNav(BTN_FINISH).Enabled = False
- btnRunAnalysis.Caption = GetResString(RUNBTN_RUNNING_ID)
-
- If RunAnalysis(False) Then
- cmdNav(BTN_FINISH).Enabled = True
- btnRunAnalysis.Enabled = True
- btnViewResults.Enabled = True
- btnPrepare.Enabled = True
- btnViewResults.SetFocus
- btnRunAnalysis.Caption = GetResString(RUNBTN_START_ID)
-
- str = ReplaceTopicTokens(GetResString(RID_STR_ENG_ANALYZE_COMPLETED_ID), CR_STR, Chr(13))
- response = MsgBox(str, vbOKCancel + vbInformation)
- If response = vbOK Then ' User chose Ok.
- bViewResults = True
- End If
- Else
- btnRunAnalysis.Enabled = True
- btnViewResults.Enabled = False
- btnPrepare.Enabled = False
- End If
-
-FinalExit:
- cmdNav(BTN_CANCEL).Enabled = True
- cmdNav(BTN_BACK).Enabled = True
- cmdNav(BTN_NEXT).Enabled = False
- btnRunAnalysis.Caption = GetResString(RUNBTN_START_ID)
-
- If bViewResults Then
- btnViewResults_Click
- End If
-
- Exit Sub
-
-HandleErrors:
- cmdNav(BTN_FINISH).Enabled = False
- btnRunAnalysis.Enabled = True
- btnViewResults.Enabled = False
- btnPrepare.Enabled = False
- WriteDebug "Document Analysis: View Analysis Results" & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Sub
-
-Private Sub btnViewResults_Click()
- On Error GoTo HandleErrors
- Dim resultsFile As String
- Dim fso As New FileSystemObject
- Dim str As String
-
- mbAllowExit = True
-
- resultsFile = getOutputDir & "\" & txtResultsName.Text
-
- If GetIniSetting(COUTPUT_TYPE) = COUTPUT_TYPE_XML Or _
- GetIniSetting(COUTPUT_TYPE) = COUTPUT_TYPE_BOTH Then
-
- Dim base As String
- Dim path As String
- base = fso.GetParentFolderName(resultsFile) & "\" & fso.GetBaseName(txtResultsName.Text)
- If CheckWordDocsToAnalyze Then
- path = base & "_" & CAPPNAME_WORD & "." & COUTPUT_TYPE_XML
- End If
- If CheckExcelDocsToAnalyze Then
- If path <> "" Then path = path & vbLf
- path = path & base & "_" & CAPPNAME_EXCEL & "." & COUTPUT_TYPE_XML
- End If
- If CheckPPDocsToAnalyze Then
- If path <> "" Then path = path & vbLf
- path = path & base & "_" & CAPPNAME_POWERPOINT & "." & COUTPUT_TYPE_XML
- End If
-
- str = ReplaceTopic2Tokens(GetResString(XML_RESULTS_ID), _
- TOPIC_STR, path, CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbInformation
- If GetIniSetting(COUTPUT_TYPE) = COUTPUT_TYPE_XML Then
- Resume FinalExit
- End If
- End If
-
- If Not fso.FileExists(resultsFile) Then
- str = ReplaceTopic2Tokens(GetResString(ERR_MISSING_RESULTS_DOC), _
- TOPIC_STR, resultsFile, CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
- Resume FinalExit
- End If
-
- Dim xl As Excel.application
- Set xl = New Excel.application
- xl.Visible = True
- xl.Workbooks.Open resultsFile
-
-FinalExit:
- Set xl = Nothing
- Set fso = Nothing
-
- Exit Sub
-HandleErrors:
- WriteDebug "Document Analysis: View Analysis Results" & Err.Number & " " & Err.Description & " " & Err.Source
-End Sub
-
-Private Sub Form_Activate()
- Dim currentFunctionName As String
- Dim missingFile As String
- currentFunctionName = "Form_Activate"
- On Error GoTo HandleErrors
-
- If Not CheckNeededFiles(missingFile) Then
- Dim str As String
- str = ReplaceTopic2Tokens(GetResString(ERR_MISSING_WORD_DRIVER), _
- TOPIC_STR, missingFile, CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
-
- End 'Exit application - some needed files are missing
- End If
-
-FinalExit:
- Exit Sub
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- GoTo FinalExit
-End Sub
-
-Private Sub Form_Initialize()
- Dim currentFunctionName As String
- currentFunctionName = "Form_Initialize"
- On Error GoTo ErrorHandler
- Call InitCommonControls 'Use Windows XP Visual Style
-
-FinalExit:
- Exit Sub
-
-ErrorHandler:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- GoTo FinalExit
-End Sub
-
-Private Sub Form_KeyDown(KeyCode As Integer, Shift As Integer)
- If KeyCode = vbKeyF1 Then
- 'cmdNav_Click BTN_HELP
- End If
-End Sub
-
-Private Sub Form_Load()
- Const COS_CHECK = "oscheck"
-
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "Form_Load"
-
- Dim fso As New FileSystemObject
- Dim i As Integer
- 'init all vars
- mbFinishOK = False
- mbTrue = True
- mbFalse = False
-
- mLogFilePath = GetLogFilePath
- mIniFilePath = GetIniFilePath
- mbDocCountCurrent = False
- mbDoPrepare = False
- mbAllowExit = False
-
- 'Check OS before running
- Dim bOSCheck As Boolean
- bOSCheck = IIf(GetIniSetting(COS_CHECK) = "False", False, True)
-
- If bOSCheck Then
- If Not IsWin98Plus Then
- Dim str As String
- Dim winVer As RGB_WINVER
- str = ReplaceTopic2Tokens(GetResString(ERR_SUPPORTED_OSVERSION), _
- TOPIC_STR, GetWinVersion(winVer), CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
-
- End 'Exit application - unsupported OS
- End If
- Else
- Err.Clear
- WriteDebug "IsWin2000Plus OS Check bypassed by analysis.ini oscheck=False setting"
- End If
-
-
- For i = 0 To NUM_STEPS - 1
- fraStep(i).Left = -10000
- Next
-
- 'Load All string info for Form
- LoadResStrings Me
-
- frmWizard.Caption = ReplaceTopicTokens(GetResString(TITLE_ID), CPRODUCTNAME_STR, _
- GetResString(PRODUCTNAME_ID))
- lblIntroduction1.Caption = ReplaceTopicTokens(GetResString(INTRO1_ID), CPRODUCTNAME_STR, _
- GetResString(PRODUCTNAME_ID))
- mLblSteps = GetResString(LBL_STEPS_ID)
- mChbSubdirs = GetResString(CHK_SUBDIRS_ID)
-
- ' Setup Doc Preparation specific strings
- If gBoolPreparation Then
- ' Steps
- lblStep1_4.Caption = GetResString(RID_STR_ENG_SIDEBAR_ANALYZE_PREP_ID)
- lblStep2_4.Caption = GetResString(RID_STR_ENG_SIDEBAR_ANALYZE_PREP_ID)
- lblStep3_4.Caption = GetResString(RID_STR_ENG_SIDEBAR_ANALYZE_PREP_ID)
- lblStep4_4.Caption = GetResString(RID_STR_ENG_SIDEBAR_ANALYZE_PREP_ID)
-
- ' Preparation - Step 1. Introduction
- lblIntroduction1.Caption = ReplaceTopicTokens(GetResString(RID_STR_ENG_INTRODUCTION_INTRO1_PREP_ID), CPRODUCTNAME_STR, _
- GetResString(PRODUCTNAME_ID))
- lblIntroduction2.Caption = GetResString(RID_STR_ENG_INTRODUCTION_INTRO2_PREP_ID)
- lblIntroduction3.Caption = GetResString(RID_STR_ENG_INTRODUCTION_INTRO3_PREP_ID)
-
- ' Preparation - Step 2. Documents
- lblChooseDocs.Caption = GetResString(RID_STR_ENG_DOCUMENTS_CHOOSE_DOCUMENTS_PREP_ID)
- lblDocTypes.Caption = GetResString(RID_STR_ENG_DOCUMENTS_CHOOSE_DOC_TYPES_PREP_ID)
- 'mChbSubdirs = GetResString(RID_STR_ENG_DOCUMENTS_INCLUDE_SUBDIRECTORIES_PREP_ID)
- chkIgnoreOld.Caption = GetResString(RID_STR_IGNORE_OLDER_CB_ID)
-
- cbIgnoreOld.Clear
- cbIgnoreOld.AddItem (GetResString(RID_STR_IGNORE_OLDER_3_MONTHS_ID))
- cbIgnoreOld.AddItem (GetResString(RID_STR_IGNORE_OLDER_6_MONTHS_ID))
- cbIgnoreOld.AddItem (GetResString(RID_STR_IGNORE_OLDER_12_MONTHS_ID))
- cbIgnoreOld.ListIndex = 0
-
- ' Preparation - Step 3. Results
- lblChooseResults.Caption = GetResString(RID_STR_ENG_RESULTS_CHOOSE_OPTIONS_PREP_ID)
- txtResultsName.Text = GetResString(RID_STR_ENG_RESULTS_ANALYSIS_XLS_PREP_ID)
-
- 'Show Append option
- rdbResultsAppend.Visible = True
-
- ' Preparation - Step 4. Analysis
- lblSetupDone.Caption = GetResString(RID_STR_ENG_ANALYZE_SETUP_COMPLETE_PREP_ID)
- btnPrepare.Visible = True
- Else
- ' The next line is a work around for a wrong translated string and should be removed
- ' when RID_STR_ENG_RESULTS_CHOOSE_OPTIONS has been corrected
- lblChooseResults.Caption = GetResString(RID_STR_ENG_RESULTS_CHOOSE_OPTIONS_PREP_ID)
- mDefaultPassword = IIf(GetIniSetting(CDEFAULT_PASSWORD) = "", _
- CSTR_TEST_PASSWORD, GetIniSetting(CDEFAULT_PASSWORD))
- End If
-
- SetStep 0, DIR_NEXT
- Dim tmpStr As String
-
- 'Setup Params
- tmpStr = GetIniSetting(CINPUT_DIR)
- If tmpStr <> "" Then
- txtInputDir.Text = tmpStr
- txtInputDir.ToolTipText = tmpStr
- End If
- tmpStr = GetIniSetting(COUTPUT_DIR)
- If tmpStr <> "" Then
- If Right(tmpStr, 1) = ":" And Len(tmpStr) = 2 Then
- tmpStr = tmpStr & "\"
- End If
- txtOutputDir.Text = tmpStr
- txtOutputDir.ToolTipText = tmpStr
- End If
- tmpStr = GetIniSetting(CRESULTS_FILE)
- If tmpStr <> "" Then txtResultsName.Text = tmpStr
-
- rdbResultsPrompt.value = False
- rdbResultsOverwrite.value = False
- rdbResultsAppend.value = False
- Dim resultsSetting As String
- resultsSetting = GetIniSetting(CRESULTS_EXIST)
- If resultsSetting = CPROMPT_FILE Then
- rdbResultsPrompt.value = True
- ElseIf resultsSetting = CAPPEND_FILE Then
- rdbResultsAppend.value = True
- Else
- rdbResultsOverwrite.value = True
- End If
-
- chkWordDoc.value = IIf(GetIniSetting(CTYPE_WORDDOC) = CStr(True), vbChecked, 0)
- chkWordTemplate.value = IIf(GetIniSetting(CTYPE_WORDDOT) = CStr(True), vbChecked, 0)
- chkExcelDoc.value = IIf(GetIniSetting(CTYPE_EXCELDOC) = CStr(True), vbChecked, 0)
- chkExcelTemplate.value = IIf(GetIniSetting(CTYPE_EXCELDOT) = CStr(True), vbChecked, 0)
- chkPPDoc.value = IIf(GetIniSetting(CTYPE_PPDOC) = CStr(True), vbChecked, 0)
- chkPPTemplate.value = IIf(GetIniSetting(CTYPE_PPDOT) = CStr(True), vbChecked, 0)
- chkIncludeSubdirs.value = IIf(GetIniSetting(CINCLUDE_SUBDIRS) = CStr(True), vbChecked, 0)
- mDebugLevel = IIf(GetIniSetting(CDEBUG_LEVEL) = "", CDEBUG_LEVEL_DEFAULT, GetIniSetting(CDEBUG_LEVEL))
- chkIgnoreOld.value = IIf(GetIniSetting(CIGNORE_OLD_DOCS) = CStr(True), vbChecked, 0)
-
- mIssueLimit = IIf(GetIniSetting(CISSUE_LIMIT) = "", CISSUE_LIMIT_DAW, GetIniSetting(CISSUE_LIMIT))
- If (mIssueLimit <= 3) Then
- cbIgnoreOld.ListIndex = 0
- ElseIf (mIssueLimit <= 6) Then
- cbIgnoreOld.ListIndex = 1
- Else
- cbIgnoreOld.ListIndex = 2
- End If
-
- 'Always ensure at least one doc type is selected on startup
- If (chkWordDoc.value <> vbChecked) And _
- (chkWordTemplate.value <> vbChecked) And _
- (chkExcelDoc.value <> vbChecked) And _
- (chkExcelTemplate.value <> vbChecked) And _
- (chkPPDoc.value <> vbChecked) And _
- (chkPPTemplate.value <> vbChecked) Then
-
- chkWordDoc.value = vbChecked
- End If
-
-FinalExit:
- Set fso = Nothing
- Exit Sub
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Sub
-
-Private Sub SetStep(nStep As Integer, nDirection As Integer)
- On Error GoTo HandleError
- Const driveTypeIsCDROM = 4
- Dim val As String
- Dim fso As Scripting.FileSystemObject
- Set fso = New Scripting.FileSystemObject
- Dim drive
-
-
- mbDocCountCurrent = False
-
- Select Case nStep
- Case STEP_INTRO
- 'MsgBox "Enter Intro"
- Case STEP_1
- 'Leave Introduction
- 'Workaround - resource bug for SubDir checkbox, have to set it explicitly
- chkIncludeSubdirs.Caption = mChbSubdirs
- Case STEP_2
- 'Leave Documents
-
- Set drive = fso.GetDrive(fso.GetDriveName(txtInputDir.Text))
- If drive.DriveType = driveTypeIsCDROM Then
- If Not drive.IsReady Then
- MsgBox GetResString(ERR_CDROM_NOT_READY), vbCritical
- Exit Sub
- End If
- End If
-
- If txtInputDir.Text = "" Or Not fso.FolderExists(txtInputDir.Text) Then ' fso.FolderExists() has replaced dir()
- MsgBox ReplaceTopicTokens(GetResString(ERR_NO_DOC_DIR), _
- CR_STR, Chr(13)), vbCritical
- Exit Sub
- End If
-
- If Not CheckUserChosenDocsToAnalyze Then
- MsgBox GetResString(ERR_NO_DOC_TYPES), vbCritical
- Exit Sub
- End If
- 'Expand directory name only without path to full path
- txtInputDir.Text = fso.GetAbsolutePathName(txtInputDir.Text)
-
- If txtOutputDir.Text = "" Then
- txtOutputDir.Text = txtInputDir.Text
- End If
-
- mbFinishOK = False
-
- 'Workaround - label resource bug for Steps, have to set it explicitly
- Label12(0).Caption = mLblSteps
- Label12(5).Caption = mLblSteps
- Case STEP_FINISH
- 'Leave Results
- If Not CheckResultsDir(getOutputDir) Then
- Exit Sub
- End If
-
- 'Expand directory name only without path to full path
- txtOutputDir.Text = fso.GetAbsolutePathName(txtOutputDir)
-
- 'Check Results file is there and has a valid extension
- If fso.GetBaseName(txtResultsName.Text) = "" Then
- txtResultsName.Text = GetResString(SETUP_ANALYSIS_XLS_ID)
- End If
- txtResultsName.Text = fso.GetBaseName(txtResultsName.Text) & CRESULTS_FILE_EXTENSION
-
- Screen.MousePointer = vbHourglass
- DeleteFile mLogFilePath
- Set mDocFiles = Nothing
- If Not CheckNumberDocsToAnalyze Then
- Screen.MousePointer = vbDefault
- Exit Sub
- End If
-
- Screen.MousePointer = vbDefault
-
- btnRunAnalysis.Enabled = True
-
- If GetNumberOfDocsToAnalyze = 0 Then
- btnRunAnalysis.Enabled = False
- End If
-
- 'Backup configuration
- If Not AttemptToCopyFile(mIniFilePath, mIniFilePath & CCONFIG_BACKUP_EXT) Then
- Exit Sub
- End If
-
- 'Save current Wizard Settings
- WriteWizardSettingsToLog mIniFilePath
-
- 'If results file already exists, enable View and Prepare
- If fso.FileExists(getOutputDir & "\" & txtResultsName.Text) Then
- btnViewResults.Enabled = True
- btnPrepare.Enabled = True
- End If
-
- mbFinishOK = True
- End Select
-
- 'move to new step
- fraStep(mnCurStep).Enabled = False
- fraStep(nStep).Left = 0
- If nStep <> mnCurStep Then
- fraStep(mnCurStep).Left = -10000
- fraStep(mnCurStep).Enabled = False
- End If
- fraStep(nStep).Enabled = True
-
- SetNavBtns nStep
- Exit Sub
-
-FinalExit:
- Set fso = Nothing
- Set drive = Nothing
- Exit Sub
-
-HandleError:
- Screen.MousePointer = vbDefault
- WriteDebug "Document Analysis: SetStep() " & Err.Number & " " & Err.Description & " " & Err.Source
-
- Resume FinalExit
-End Sub
-
-Function CheckResultsDir(resultsDir As String) As Boolean
- On Error GoTo HandleError
- Dim fso As Scripting.FileSystemObject
- Set fso = New Scripting.FileSystemObject
- Const driveTypeIsCDROM = 4
- Const readOnlyFolderRemainder = 1
- Dim drive
- CheckResultsDir = False
-
- If resultsDir = "" Then
- MsgBox ReplaceTopicTokens(GetResString(ERR_NO_RESULTS_DIRECTORY), _
- CR_STR, Chr(13)), vbCritical
- CheckResultsDir = False
- Exit Function
- End If
-
- Set drive = fso.GetDrive(fso.GetDriveName(resultsDir))
- If drive.DriveType = driveTypeIsCDROM Then 'If CD-ROM Drive Then
- Dim Msg1 As String
- Msg1 = ReplaceTopic2Tokens(GetResString(ERR_CREATE_FILE), _
- TOPIC_STR, txtResultsName.Text, CR_STR, Chr(13))
- MsgBox Msg1, vbCritical
- CheckResultsDir = False
- Exit Function
- End If
-
-
- If Not fso.FolderExists(resultsDir) Then
- Dim Msg, Style, response
-
- Msg = ReplaceTopicTokens(GetResString(ERR_NO_RES_DIR), CR_STR, Chr(13))
- Style = vbYesNo + vbQuestion + vbDefaultButton1 ' Define buttons.
-
- response = MsgBox(Msg, Style)
- If response = vbYes Then ' User chose Yes.
- If Not CreateDir(getOutputDir) Then
- CheckResultsDir = False
- Exit Function
- End If
- Else ' User chose No.
- CheckResultsDir = False
- Exit Function
- End If
- End If
-
- Dim testFile As String
- testFile = resultsDir & "\" & fso.GetTempName
- Do While fso.FileExists(testFile)
- testFile = resultsDir & "\" & fso.GetTempName
- Loop
-
- On Error GoTo HandleReadOnly
- Dim aText As TextStream
- Set aText = fso.CreateTextFile(testFile, False, False)
- aText.WriteLine ("Dies ist ein Test.")
- aText.Close
- fso.DeleteFile (testFile)
-
-' GetAttr doesn't work reliable ( returns read only for 'my Documents' and rw for read only network folder
-' If ((GetAttr(resultsDir) Mod 2) = readOnlyFolderRemainder) Then 'If the attribute is odd then the folder is read-only
-' MsgBox GetResString(ERR_NO_WRITE_TO_READ_ONLY_FOLDER), vbCritical
-' CheckResultsDir = False
-' Exit Function
-' End If
-
- CheckResultsDir = True
-
- Exit Function
-HandleError:
- WriteDebug "Document Analysis: CheckResultsDir() " & Err.Number & " " & Err.Description & " " & Err.Source
- CheckResultsDir = False
- Exit Function
-HandleReadOnly:
- Dim str As String
- str = ReplaceTopic2Tokens(GetResString(ERR_CREATE_FILE), _
- TOPIC_STR, txtResultsName.Text, CR_STR, Chr(13))
- MsgBox str, vbCritical
- CheckResultsDir = False
- Exit Function
-End Function
-
-Function CheckUserChosenDocsToAnalyze() As Boolean
- CheckUserChosenDocsToAnalyze = Not ((chkWordDoc.value <> vbChecked) And (chkWordTemplate.value <> vbChecked) And _
- (chkExcelDoc.value <> vbChecked) And (chkExcelTemplate.value <> vbChecked) And _
- (chkPPDoc.value <> vbChecked) And (chkPPTemplate.value <> vbChecked))
-End Function
-
-Function AttemptToCopyFile(Source As String, dest As String) As Boolean
- On Error GoTo HandleErrors
- Dim fso As Scripting.FileSystemObject
- Set fso = New Scripting.FileSystemObject
-
- If fso.FileExists(Source) Then
- fso.CopyFile Source, dest
- End If
-
- 'True if no source or copy succeded
- AttemptToCopyFile = True
-
-FinalExit:
- Set fso = Nothing
- Exit Function
-
-HandleErrors:
- AttemptToCopyFile = False
- Dim str As String
- str = ReplaceTopic2Tokens(GetResString(ERR_CREATE_FILE), _
- TOPIC_STR, mIniFilePath & CCONFIG_BACKUP_EXT, CR_STR, Chr(13))
- Resume FinalExit
-
-End Function
-
-Function CreateDir(dir As String) As Boolean
- On Error GoTo HandleErrors
- Dim fso As Scripting.FileSystemObject
- Set fso = New Scripting.FileSystemObject
-
- fso.CreateFolder (dir)
-
- CreateDir = True
-
-FinalExit:
- Set fso = Nothing
- Exit Function
-
-HandleErrors:
- Dim str As String
- str = ReplaceTopic2Tokens(GetResString(ERR_CREATE_DIR), _
- TOPIC_STR, dir, CR_STR, Chr(13))
- Select Case Err.Number
- Case 76
- WriteDebug str
- MsgBox str, vbCritical
- CreateDir = False
- Case 58
- 'Don't care if it exists already
- CreateDir = True
- Case Else
- WriteDebug str
- MsgBox str, vbCritical
- CreateDir = False
- End Select
- Resume FinalExit
-
-End Function
-Private Sub SetNavBtns(nStep As Integer)
- mnCurStep = nStep
-
- If mnCurStep = 0 Then
- cmdNav(BTN_BACK).Enabled = False
- cmdNav(BTN_NEXT).Enabled = True
- ElseIf mnCurStep = NUM_STEPS - 1 Then
- cmdNav(BTN_NEXT).Enabled = False
- cmdNav(BTN_BACK).Enabled = True
- Else
- cmdNav(BTN_BACK).Enabled = True
- cmdNav(BTN_NEXT).Enabled = True
- End If
-
- If mbFinishOK Then
- cmdNav(BTN_FINISH).Enabled = True
- Else
- cmdNav(BTN_FINISH).Enabled = False
- End If
-End Sub
-Function CheckForSupportedApp(app As String, lowerVerLimit As Long) As Boolean
- Dim appRegStr As String
- Dim appVer As Long
- appRegStr = GetRegistryInfo(HKEY_CLASSES_ROOT, app & ".Application\CurVer", "")
- appVer = val(Right(appRegStr, Len(appRegStr) - Len(app & ".Application.")))
- If appVer >= lowerVerLimit Then
- CheckForSupportedApp = True
- Else
- CheckForSupportedApp = False
- End If
-End Function
-Function GetAppVersion(app As String) As Long
- Dim appRegStr As String
- Dim appVer As Long
- appRegStr = GetRegistryInfo(HKEY_CLASSES_ROOT, app & ".Application\CurVer", "")
- GetAppVersion = val(Right(appRegStr, Len(appRegStr) - Len(app & ".Application.")))
-End Function
-Function GetInstalledApp(app As String) As String
- GetInstalledApp = GetRegistryInfo(HKEY_CLASSES_ROOT, app & ".Application\CurVer", "")
-End Function
-
-Sub WriteInfoToApplicationLog(wordAppStr As String, excelAppStr As String, ppAppStr As String)
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "WriteInfoToApplicationLog"
-
- Dim userLCID As Long
- userLCID = GetUserDefaultLCID()
- Dim sysLCID As Long
- sysLCID = GetSystemDefaultLCID()
-
- WriteToLog CWORD_VERSION, IIf(wordAppStr <> "", wordAppStr, CNOT_INSTALLED)
- WriteToLog CEXCEL_VERSION, IIf(excelAppStr <> "", excelAppStr, CNOT_INSTALLED)
- WriteToLog CPOWERPOINT_VERSION, IIf(ppAppStr <> "", ppAppStr, CNOT_INSTALLED)
-
- WriteToLog CUSER_LOCALE_INFO, _
- "langid: " & GetUserLocaleInfo(userLCID, LOCALE_ILANGUAGE) & ": " & _
- GetUserLocaleInfo(userLCID, LOCALE_SENGLANGUAGE) & _
- "-" & GetUserLocaleInfo(userLCID, LOCALE_SENGCOUNTRY) & _
- " abrv: " & GetUserLocaleInfo(userLCID, LOCALE_SISO639LANGNAME) & _
- "-" & GetUserLocaleInfo(userLCID, LOCALE_SISO3166CTRYNAME) & _
- " sdate: " & GetUserLocaleInfo(userLCID, LOCALE_SSHORTDATE)
-
- WriteToLog CSYS_LOCALE_INFO, _
- "langid: " & GetUserLocaleInfo(sysLCID, LOCALE_ILANGUAGE) & ": " & _
- GetUserLocaleInfo(sysLCID, LOCALE_SENGLANGUAGE) & _
- "-" & GetUserLocaleInfo(sysLCID, LOCALE_SENGCOUNTRY) & _
- " abrv: " & GetUserLocaleInfo(sysLCID, LOCALE_SISO639LANGNAME) & _
- "-" & GetUserLocaleInfo(sysLCID, LOCALE_SISO3166CTRYNAME) & _
- " sdate: " & GetUserLocaleInfo(userLCID, LOCALE_SSHORTDATE)
-
- Dim myWinVer As RGB_WINVER
- GetWinVersion myWinVer
- WriteToLog CWINVERSION, myWinVer.VersionName & " " & myWinVer.VersionNo & _
- " " & myWinVer.ServicePack & _
- " build " & myWinVer.BuildNo
- WriteToLog CNUMBER_TOTAL_DOCS, CStr(mTotalDocCount)
- WriteToLog CNUMBER_DOCS_DOC, CStr(mWordDocCount)
- WriteToLog CNUMBER_TEMPLATES_DOT, CStr(mWordTemplateCount)
- WriteToLog CNUMBER_DOCS_XLS, CStr(mExcelDocCount)
- WriteToLog CNUMBER_TEMPLATES_XLT, CStr(mExcelTemplateCount)
- WriteToLog CNUMBER_DOCS_PPT, CStr(mPPDocCount)
- WriteToLog CNUMBER_TEMPLATES_POT, CStr(mPPTemplateCount)
-FinalExit:
- Exit Sub
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Sub
-
-Function CheckTemplatePath(sMigrationResultsTemplatePath As String, fso As FileSystemObject) As Boolean
- If Not fso.FileExists(sMigrationResultsTemplatePath) Then
- Dim str As String
- str = ReplaceTopic2Tokens(GetResString(ERR_MISSING_RESULTS_TEMPLATE), _
- TOPIC_STR, sMigrationResultsTemplatePath, CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
- CheckTemplatePath = False
- Else
- CheckTemplatePath = True
- End If
-End Function
-
-Function RunAnalysis(bDoPrepare) As Boolean
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "RunAnalysis"
- Dim tstart As Single 'timer var for this routine only
- Dim tend As Single 'timer var for this routine only
- Dim fso As New FileSystemObject
- Dim wordAppStr As String
- Dim excelAppStr As String
- Dim ppAppStr As String
- Dim sMigrationResultsTemplatePath As String
- Dim startDate As Variant
- Dim bSuccess
-
- bSuccess = True
- startDate = Now
- tstart = GetTickCount()
-
- app.OleRequestPendingMsgText = GetResString(RUNBTN_RUNNING_ID)
- app.OleRequestPendingMsgTitle = frmWizard.Caption
-
- wordAppStr = GetInstalledApp(CAPPNAME_WORD)
- excelAppStr = GetInstalledApp(CAPPNAME_EXCEL)
- ppAppStr = GetInstalledApp(CAPPNAME_POWERPOINT)
- 'Write locale, version info and settings to the Application log
- WriteInfoToApplicationLog wordAppStr, excelAppStr, ppAppStr
-
- 'Check for template
- sMigrationResultsTemplatePath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CRESULTS_TEMPLATE_FILE)
- If Not CheckTemplatePath(sMigrationResultsTemplatePath, fso) Then
- bSuccess = False
- GoTo FinalExit
- End If
-
- 'Check for installed Apps
- If Not CheckInstalledApps(wordAppStr, excelAppStr, ppAppStr) Then
- bSuccess = False
- GoTo FinalExit
- End If
-
- If bDoPrepare Then
- 'Show MsgBox ( to give apps some time to quit )
- Dim strMsgBox As String
- Dim response As Integer
-
- strMsgBox = ReplaceTopic2Tokens(GetResString(RID_STR_ENG_OTHER_PREPARE_PROMPT_PREP_ID), _
- TOPIC_STR, getOutputDir & "\" & txtResultsName.Text, TOPIC2_STR, getOutputDir)
- strMsgBox = ReplaceTopicTokens(strMsgBox, CR_STR, Chr(13))
- response = MsgBox(strMsgBox, Buttons:=vbOKCancel + vbInformation)
-
- If response <> vbOK Then
- bSuccess = False
- GoTo FinalExit
- End If
- End If
-
- 'Write Wizard Setting to Application log
- WriteWizardSettingsToLog mLogFilePath
-
- 'Write to Analysis ini file - used by driver docs
- WriteCommonParamsToLog sMigrationResultsTemplatePath, mLogFilePath, mIniFilePath, fso
-
- Screen.MousePointer = vbHourglass
- ' Doc Counts are setup by CheckNumberDocsToAnalyze() when user moves to Analysis Panel
- ' Takes account of user Options selected and inspects source directory
- Dim analysisAborted As Boolean
- analysisAborted = False
-
- SetupInputVariables mLogFilePath, fso
-
- Load ShowProgress
- Call ShowProgress.SP_Init(mDocFiles.WordFiles.count + _
- mDocFiles.ExcelFiles.count + _
- mDocFiles.PowerPointFiles.count)
-
- Dim myOffset As Long
- myOffset = 0
- If (mDocFiles.WordFiles.count > 0) Then
- bSuccess = AnalyseList(mDocFiles.WordFiles, "word", mIniFilePath, myOffset, analysisAborted)
- 'bSuccess = RunWordAnalysis(sMigrationResultsTemplatePath, mLogFilePath, fso)
- End If
-
- myOffset = mDocFiles.WordFiles.count
- If ((mDocFiles.ExcelFiles.count > 0) And (Not analysisAborted)) Then
- bSuccess = bSuccess And _
- AnalyseList(mDocFiles.ExcelFiles, "excel", mIniFilePath, myOffset, analysisAborted)
- 'bSuccess = RunExcelAnalysis(sMigrationResultsTemplatePath, mLogFilePath, fso)
- End If
-
- myOffset = myOffset + mDocFiles.ExcelFiles.count
- If ((mDocFiles.PowerPointFiles.count > 0) And (Not analysisAborted)) Then
- bSuccess = bSuccess And _
- AnalyseList(mDocFiles.PowerPointFiles, "pp", mIniFilePath, myOffset, analysisAborted)
- 'bSuccess = RunPPAnalysis(sMigrationResultsTemplatePath, mLogFilePath, fso)
- End If
-
- SetupInputVariables mLogFilePath, fso
-
- tend = GetTickCount()
- WriteToLog CELAPSED_TIME, (FormatNumber((tend - tstart) / 1000, 0) & " seconds: ") & _
- (FormatNumber((tend - tstart), 0) & " miliseconds")
-
-FinalExit:
- Unload ShowProgress
- Screen.MousePointer = vbDefault
- WriteToLog CSTART_TIME, CDate(startDate)
- WriteToLog CEND_TIME, Now
- Set fso = Nothing
-
- RunAnalysis = bSuccess
- Exit Function
-
-HandleErrors:
- bSuccess = False
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Function
-
-Function CheckInstalledApps(wordAppStr As String, excelAppStr As String, ppAppStr As String) As Boolean
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- Dim str As String
- currentFunctionName = "CheckInstalledApps"
-
- Dim missingInstalledApps As String
- Dim unsupportedApps As String
- Dim runningApps As String
- Dim bSuccess As Boolean
-
- bSuccess = False
-
- If mWordDocCount > 0 Or mWordTemplateCount > 0 Then
- If wordAppStr = "" Then 'Word not installed
- missingInstalledApps = CAPPNAME_WORD
- ElseIf Not CheckForSupportedApp(CAPPNAME_WORD, CSUPPORTED_VERSION) Then
- unsupportedApps = CAPPNAME_WORD
- ElseIf IsOfficeAppRunning(CAPPNAME_WORD) Then
- runningApps = CAPPNAME_WORD
- End If
- End If
-
- If excelAppStr = "" Then
- If missingInstalledApps <> "" Then missingInstalledApps = missingInstalledApps & ", "
- missingInstalledApps = missingInstalledApps & CAPPNAME_EXCEL
- ElseIf Not CheckForSupportedApp(CAPPNAME_EXCEL, CSUPPORTED_VERSION) Then
- If unsupportedApps <> "" Then unsupportedApps = unsupportedApps & ", "
- unsupportedApps = unsupportedApps & CAPPNAME_EXCEL
- ElseIf IsOfficeAppRunning(CAPPNAME_EXCEL) Then
- If runningApps <> "" Then runningApps = runningApps & ", "
- runningApps = runningApps & CAPPNAME_EXCEL
- End If
-
- If mPPDocCount > 0 Or mPPTemplateCount > 0 Then
- If ppAppStr = "" Then 'PP not installed
- If missingInstalledApps <> "" Then missingInstalledApps = missingInstalledApps & ", "
- missingInstalledApps = missingInstalledApps & CAPPNAME_POWERPOINT
- ElseIf Not CheckForSupportedApp(CAPPNAME_POWERPOINT, CSUPPORTED_VERSION) Then
- If unsupportedApps <> "" Then unsupportedApps = unsupportedApps & ", "
- unsupportedApps = unsupportedApps & CAPPNAME_POWERPOINT
- ElseIf IsOfficeAppRunning(CAPPNAME_POWERPOINT) Then
- If runningApps <> "" Then runningApps = runningApps & ", "
- runningApps = runningApps & CAPPNAME_POWERPOINT
- End If
- End If
-
- If missingInstalledApps <> "" Then
- str = ReplaceTopic2Tokens(GetResString(ERR_NOT_INSTALLED), _
- TOPIC_STR, missingInstalledApps, CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
- GoTo FinalExit
- End If
-
- If unsupportedApps <> "" Then
- str = ReplaceTopic2Tokens(GetResString(ERR_SUPPORTED_VERSION), _
- TOPIC_STR, unsupportedApps, CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
- GoTo FinalExit
- End If
-
- If runningApps <> "" Then
- str = ReplaceTopic2Tokens(GetResString(ERR_APPLICATION_IN_USE), _
- TOPIC_STR, runningApps, CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
- GoTo FinalExit
- End If
-
- 'Check for Excel automation server
- If CheckForExcel Then
- str = ReplaceTopicTokens(GetResString(ERR_EXCEL_OPEN), _
- CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
- bSuccess = False
- GoTo FinalExit
- End If
-
- bSuccess = True
-
-FinalExit:
- CheckInstalledApps = bSuccess
- Exit Function
-
-HandleErrors:
- bSuccess = False
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Function
-
-Function RunPPAnalysis(resultsTemplate As String, logFile As String, fsObject As FileSystemObject) As Boolean
-'DV: do we need this? get some error handling ideas here
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "RunPPAnalysis"
- Const APP_PP = "PowerPoint"
- Dim str As String
- Dim bSuccess
- bSuccess = False
-
- If (chkPPDoc.value <> vbChecked) And (chkPPTemplate.value <> vbChecked) Then
- RunPPAnalysis = True
- Exit Function
- End If
-
- Dim sPPDriverDocPath As String
-
- sPPDriverDocPath = fsObject.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CPP_DRIVER_FILE)
- If Not fsObject.FileExists(sPPDriverDocPath) Then
- str = ReplaceTopic2Tokens(GetResString(ERR_MISSING_PP_DRIVER), _
- TOPIC_STR, sPPDriverDocPath, CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
- bSuccess = False
- GoTo FinalExit
- End If
-
- Dim pp As PowerPoint.application
- Dim po As Object
- Dim aPres As PowerPoint.Presentation
- Dim RegValue As Long
- Set po = GetObject(sPPDriverDocPath)
- Set pp = po.application
-
- If val(pp.Version) < CSUPPORTED_VERSION Then
- str = ReplaceTopic2Tokens(GetResString(ERR_SUPPORTED_VERSION), _
- TOPIC_STR, pp.Version, CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
- bSuccess = False
- GoTo FinalExit
- End If
-
- If Not CheckForAccesToPPVBProject(pp, aPres) Then
- RegValue = -1
- If Not GiveAccessToMacroProject(APP_PP, pp.Version, RegValue) Then
- Dim Style, response
- str = ReplaceTopic2Tokens(GetResString(ERR_NO_ACCESS_TO_VBPROJECT), _
- TOPIC_STR, CAPPNAME_POWERPOINT, CR_STR, Chr(13))
- WriteDebug str
- Style = vbYesNo + vbQuestion + vbDefaultButton1
-
- response = MsgBox(str, Style)
- If response <> vbYes Then
- bSuccess = False
- GoTo FinalExit
- End If
- End If
- End If
-
- Set aPres = pp.Presentations(1)
- Dim ppSlideHidden As PowerPoint.Slide
- Set ppSlideHidden = aPres.Slides(2)
-
- 'Setup Input Variables
- 'SetupInputVariables resultsTemplate, logFile, fsObject, CAPPNAME_POWERPOINT
-
- 'Run PowerPoint Analysis
- pp.Run (fsObject.GetFileName(CBASE_RESOURCE_DIR & "\" & CPP_DRIVER_FILE) & "!AnalysisDriver.AnalyseDirectory")
-
- bSuccess = True
-
-FinalExit:
- 'Cannot seem to close it down from VB
- 'Workaround is to close it in macro
- '
- 'If Not aPres Is Nothing Then
- ' aPres.Saved = msoTrue
- 'End If
- 'If Not pp Is Nothing Then pp.Quit
-
- 'Swallow error as we are closing down PP from macro
- 'Does not seem to be possible to close it down from VB
- On Error Resume Next
- If RegValue <> -1 Then
- SetDefaultRegValue APP_PP, pp.Version, RegValue
- End If
- If RegValue = 0 Then
- DeleteRegValue APP_PP, pp.Version
- End If
-
- If Not pp Is Nothing Then
- pp.Run (fsObject.GetFileName(CBASE_RESOURCE_DIR & "\" & CPP_DRIVER_FILE) & "!ApplicationSpecific.QuitPowerPoint")
- End If
-
-
- Set aPres = Nothing
- Set pp = Nothing
- Set po = Nothing
-
- RunPPAnalysis = bSuccess
- Exit Function
-
-HandleErrors:
- bSuccess = False
- Set pp = Nothing
- Dim failedDoc As String
-
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
-
- failedDoc = GetDebug(CAPPNAME_POWERPOINT, CANALYZING)
- If failedDoc = "" Or failedDoc = CSTR_ANALYSIS_LOG_DONE Then
- str = ReplaceTopic2Tokens(GetResString(ERR_AUTOMATION_FAILURE), _
- TOPIC_STR, CAPPNAME_POWERPOINT, CR_STR, Chr(13))
- Else
- str = ReplaceTopic2Tokens(GetResString(ERR_PP_DRIVER_CRASH), _
- TOPIC_STR, failedDoc, CR_STR, Chr(13))
- End If
-
- WriteDebug str
- MsgBox str, vbCritical
-
- Resume FinalExit
-End Function
-
-Sub SetupInputVariables(logFile As String, fso As FileSystemObject)
- Dim bNewResultsFile As Boolean
-
- bNewResultsFile = CheckCreateNewResultsFile(fso)
-
- WriteToLog CNEW_RESULTS_FILE, IIf(bNewResultsFile, "True", "False"), mIniFilePath
- WriteToLog CNEW_RESULTS_FILE, IIf(bNewResultsFile, "True", "False"), logFile
-End Sub
-
-
-
-Function RunExcelAnalysis(resultsTemplate As String, logFile As String, fsObject As FileSystemObject) As Boolean
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "RunExcelAnalysis"
- Const APP_EXCEL = "Excel"
- Dim str As String
- Dim bSuccess
- bSuccess = False
-
- If (chkExcelDoc.value <> vbChecked) And (chkExcelTemplate.value <> vbChecked) Then
- RunExcelAnalysis = True
- Exit Function
- End If
-
- Dim xl As Excel.application
- Dim aWb As Excel.Workbook
- Dim sExcelDriverDocPath As String
- Dim RegValue As Long
-
- sExcelDriverDocPath = fsObject.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CEXCEL_DRIVER_FILE)
- If Not fsObject.FileExists(sExcelDriverDocPath) Then
- str = ReplaceTopic2Tokens(GetResString(ERR_MISSING_EXCEL_DRIVER), _
- TOPIC_STR, sExcelDriverDocPath, CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
- bSuccess = False
- GoTo FinalExit
- End If
-
- Set xl = GetExcelInstance
- If val(xl.Version) < CSUPPORTED_VERSION Then
- str = ReplaceTopic2Tokens(GetResString(ERR_SUPPORTED_VERSION), _
- TOPIC_STR, xl.Version, CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
- bSuccess = False
- GoTo FinalExit
- End If
-
- If Not CheckForAccesToExcelVBProject(xl) Then
- RegValue = -1
- If Not GiveAccessToMacroProject(APP_EXCEL, xl.Version, RegValue) Then
- Dim Style, response
- str = ReplaceTopic2Tokens(GetResString(ERR_NO_ACCESS_TO_VBPROJECT), _
- TOPIC_STR, CAPPNAME_EXCEL, CR_STR, Chr(13))
- WriteDebug str
- Style = vbYesNo + vbQuestion + vbDefaultButton1
-
- response = MsgBox(str, Style)
- If response <> vbYes Then
- bSuccess = False
- GoTo FinalExit
- End If
- End If
- End If
-
- Set aWb = xl.Workbooks.Open(fileName:=sExcelDriverDocPath)
- 'Setup Input Variables
- 'SetupInputVariables resultsTemplate, logFile, fsObject, CAPPNAME_EXCEL
-
- 'Run Excel Analysis
- xl.Run ("AnalysisTool.AnalysisDriver.AnalyseDirectory")
-
- bSuccess = True
-FinalExit:
- If RegValue <> -1 Then
- SetDefaultRegValue APP_EXCEL, xl.Version, RegValue
- End If
- If RegValue = 0 Then
- DeleteRegValue APP_EXCEL, xl.Version
- End If
-
- If Not aWb Is Nothing Then
- If xl.Workbooks.count = 1 Then
- xl.Visible = False
- End If
- aWb.Close (False)
- End If
- Set aWb = Nothing
-
- If Not xl Is Nothing Then
- If xl.Workbooks.count = 0 Then
- xl.Quit
- End If
- End If
-
- Set xl = Nothing
-
- RunExcelAnalysis = bSuccess
- Exit Function
-
-HandleErrors:
- bSuccess = False
- Set aWb = Nothing
- Set xl = Nothing
- Dim failedDoc As String
-
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
-
- failedDoc = GetDebug(CAPPNAME_EXCEL, CANALYZING)
- If failedDoc = "" Or failedDoc = CSTR_ANALYSIS_LOG_DONE Then
- str = ReplaceTopic2Tokens(GetResString(ERR_AUTOMATION_FAILURE), _
- TOPIC_STR, CAPPNAME_EXCEL, CR_STR, Chr(13))
- Else
- str = ReplaceTopic2Tokens(GetResString(ERR_EXCEL_DRIVER_CRASH), _
- TOPIC_STR, failedDoc, CR_STR, Chr(13))
- End If
-
- WriteDebug str
- MsgBox str, vbCritical
-
- On Error Resume Next
- Resume FinalExit
-End Function
-
-Sub WriteWizardSettingsToLog(path As String)
- '### DO NOT USE Boolean True/ False it is loaclised by the OS - use "True"/ "False"
- WriteToLog CINPUT_DIR, getInputDir, path
- WriteToLog CINCLUDE_SUBDIRS, IIf(chkIncludeSubdirs.value, "True", "False"), path
- WriteToLog COUTPUT_DIR, getOutputDir, path
- WriteToLog CRESULTS_FILE, txtResultsName.Text, path
-
- WriteToLog CTYPE_WORDDOC, IIf(chkWordDoc.value, "True", "False"), path
- WriteToLog CTYPE_WORDDOT, IIf(chkWordTemplate.value, "True", "False"), path
- WriteToLog CTYPE_EXCELDOC, IIf(chkExcelDoc.value, "True", "False"), path
- WriteToLog CTYPE_EXCELDOT, IIf(chkExcelTemplate.value, "True", "False"), path
- WriteToLog CTYPE_PPDOC, IIf(chkPPDoc.value, "True", "False"), path
- WriteToLog CTYPE_PPDOT, IIf(chkPPTemplate.value, "True", "False"), path
-
- Dim resultsSetting As String
- If rdbResultsPrompt.value Then
- resultsSetting = CPROMPT_FILE
- ElseIf rdbResultsAppend.value Then
- resultsSetting = CAPPEND_FILE
- Else
- resultsSetting = COVERWRITE_FILE
- End If
- WriteToLog CRESULTS_EXIST, resultsSetting, path
-
- WriteToLog CIGNORE_OLD_DOCS, IIf(chkIgnoreOld.value, "True", "False"), path
- WriteToLog CISSUE_LIMIT, CStr(mIssueLimit), path
-
- 'WriteToLog CVERSION, Version, path
-End Sub
-
-Sub WriteCommonParamsToLog(resultsTemplate As String, logFile As String, path As String, fso As Scripting.FileSystemObject)
- WriteToLog CLOG_FILE, logFile, path
- WriteToLog CRESULTS_TEMPLATE, resultsTemplate, path
- WriteToLog CDEBUG_LEVEL, CLng(mDebugLevel), path
- WriteToLog CDOPREPARE, IIf(mbDoPrepare, "True", "False"), path
- WriteToLog CTITLE, frmWizard.Caption, path
- WriteToLog CLAST_CHECKPOINT, ""
- WriteToLog CNEXT_FILE, ""
- WriteToLog C_ABORT_ANALYSIS, ""
-End Sub
-
-Function GetNumberOfDocsToAnalyze() As Long
- Dim count As Long
-
- count = 0
-
- If CheckWordDocsToAnalyze Then
- count = mWordDocCount + mWordTemplateCount
- End If
- If CheckExcelDocsToAnalyze Then
- count = count + mExcelDocCount + mExcelTemplateCount
- End If
- If CheckPPDocsToAnalyze Then
- count = count + mPPDocCount + mPPTemplateCount
- End If
-
- GetNumberOfDocsToAnalyze = count
-End Function
-
-Function CheckWordDocsToAnalyze() As Boolean
-
- CheckWordDocsToAnalyze = mbDocCountCurrent And (chkWordDoc.value = vbChecked And mWordDocCount > 0) Or _
- (chkWordTemplate.value = vbChecked And mWordTemplateCount > 0)
-End Function
-
-Function CheckExcelDocsToAnalyze() As Boolean
- CheckExcelDocsToAnalyze = mbDocCountCurrent And (chkExcelDoc.value = vbChecked And mExcelDocCount > 0) Or _
- (chkExcelTemplate.value = vbChecked And mExcelTemplateCount > 0)
-End Function
-
-Function CheckPPDocsToAnalyze() As Boolean
- CheckPPDocsToAnalyze = mbDocCountCurrent And (chkPPDoc.value = vbChecked And mPPDocCount > 0) Or _
- (chkPPTemplate.value = vbChecked And mPPTemplateCount > 0)
-End Function
-
-Function CheckNumberDocsToAnalyze() As Boolean
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "CheckNumberDocsToAnalyze"
-
- Set mDocFiles = New CollectedFiles
-
- Dim docSearchTypes As Collection
- Set docSearchTypes = New Collection
-
- mbDocCountCurrent = False
-
- SetupDocSearchTypes docSearchTypes
-
- If (cbIgnoreOld.ListIndex = 0) Then
- mIssueLimit = 3
- ElseIf (cbIgnoreOld.ListIndex = 1) Then
- mIssueLimit = 6
- Else
- mIssueLimit = 12
- End If
-
- If Not mDocFiles.Search(rootDir:=getInputDir, FileSpecs:=docSearchTypes, _
- IncludeSubdirs:=IIf(chkIncludeSubdirs.value, mbTrue, mbFalse), _
- ignoreOld:=IIf(chkIgnoreOld.value, mbTrue, mbFalse), Months:=mIssueLimit) Then
- CheckNumberDocsToAnalyze = False
- GoTo FinalExit
- End If
-
- SetDocCountsFromFileSearch mDocFiles
- WriteFileDateCountsToLog mDocFiles
-
- 'WriteDocsToAnalyzeToLog mDocFiles 'UNCOMMENT Recovery - want to list out files to analyze
-
- mbDocCountCurrent = True
-
- lblNumDocs.Caption = ReplaceTopicTokens(GetResString(ANALYZE_DOCUMENTS_ID), TOPIC_STR, _
- CStr(mWordDocCount))
- lblNumTemplates.Caption = ReplaceTopicTokens(GetResString(ANALYZE_TEMPLATES_ID), TOPIC_STR, _
- CStr(mWordTemplateCount))
-
- lblNumXLS.Caption = ReplaceTopicTokens(GetResString(ANALYZE_DOCUMENTS_XLS_ID), TOPIC_STR, _
- CStr(mExcelDocCount))
- lblNumXLT.Caption = ReplaceTopicTokens(GetResString(ANALYZE_TEMPLATES_ID), TOPIC_STR, _
- CStr(mExcelTemplateCount))
-
- lblNumPPT.Caption = ReplaceTopicTokens(GetResString(ANALYZE_DOCUMENTS_PPT_ID), TOPIC_STR, _
- CStr(mPPDocCount))
- lblNumPOT.Caption = ReplaceTopicTokens(GetResString(ANALYZE_TEMPLATES_ID), TOPIC_STR, _
- CStr(mPPTemplateCount))
-
- lblTotalNumDocs.Caption = ReplaceTopicTokens(GetResString(ANALYZE_TOTAL_NUM_DOCS_ID), TOPIC_STR, _
- CStr(mTotalDocCount))
-
- If (mIgnoredDocCount > 0) Then
- lblSkippedOld.Caption = ReplaceTopicTokens(GetResString(RID_STR_ENG_ANALYZE_IGNORED_DOCS_ID), _
- TOPIC_STR, CStr(mIgnoredDocCount))
- lblSkippedOld.Visible = True
- Else
- lblSkippedOld.Visible = False
- End If
-
- CheckNumberDocsToAnalyze = True
-
-FinalExit:
- Set docSearchTypes = Nothing
- Exit Function
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Function
-
-Sub SetDocCountsFromFileSearch(myDocFiles As CollectedFiles)
- 'No Error handling required
- mWordDocCount = myDocFiles.DocCount
- mWordTemplateCount = myDocFiles.DotCount
- mExcelDocCount = myDocFiles.XlsCount
- mExcelTemplateCount = myDocFiles.XltCount
- mPPDocCount = myDocFiles.PptCount
- mPPTemplateCount = myDocFiles.PotCount
- mTotalDocCount = mWordDocCount + mWordTemplateCount + mExcelDocCount + mExcelTemplateCount + _
- mPPDocCount + mPPTemplateCount
- mIgnoredDocCount = myDocFiles.IgnoredDocCount
-End Sub
-
-Sub SetupDocSearchTypes(docSearchTypes As Collection)
- 'No Error handling required
- If chkWordDoc.value Then docSearchTypes.add ("*.doc")
- If chkWordTemplate.value Then docSearchTypes.add ("*.dot")
- If chkExcelDoc.value Then docSearchTypes.add ("*.xls")
- If chkExcelTemplate.value Then docSearchTypes.add ("*.xlt")
- If chkPPDoc.value Then docSearchTypes.add ("*.ppt")
- If chkPPTemplate.value Then docSearchTypes.add ("*.pot")
-End Sub
-
-Sub WriteDocsToAnalyzeToLog(myDocFiles As CollectedFiles)
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "WriteDocsToAnalyzeToLog"
-
- Dim vFileName As Variant
- Dim Index As Long
- Dim limit As Long
- limit = myDocFiles.WordFiles.count
- For Index = 1 To limit
- vFileName = myDocFiles.WordFiles(Index)
- WriteToLog "Doc" & Index, CStr(vFileName), section:=(WIZARD_NAME & "ListFor" & CAPPNAME_WORD)
- Next
- limit = myDocFiles.ExcelFiles.count
- For Index = 1 To limit
- vFileName = myDocFiles.ExcelFiles(Index)
- WriteToLog "Doc" & Index, CStr(vFileName), section:=(WIZARD_NAME & "ListFor" & CAPPNAME_EXCEL)
- Next
- limit = myDocFiles.PowerPointFiles.count
- For Index = 1 To limit
- vFileName = myDocFiles.PowerPointFiles(Index)
- WriteToLog "Doc" & Index, CStr(vFileName), section:=(WIZARD_NAME & "ListFor" & CAPPNAME_POWERPOINT)
- Next
-
-FinalExit:
- Exit Sub
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Sub
-
-Sub WriteFileDateCountsToLog(myDocFiles As CollectedFiles)
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "WriteFileDateCountsToLog"
-
- WriteToLog C_DOCS_LESS_3_MONTH, CStr(myDocFiles.DocsLessThan3Months), mIniFilePath
- WriteToLog C_DOCS_LESS_6_MONTH, CStr(myDocFiles.DocsLessThan6Months), mIniFilePath
- WriteToLog C_DOCS_LESS_12_MONTH, CStr(myDocFiles.DocsLessThan12Months), mIniFilePath
- WriteToLog C_DOCS_MORE_12_MONTH, CStr(myDocFiles.DocsMoreThan12Months), mIniFilePath
-
-FinalExit:
- Exit Sub
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Sub
-
-
-Function RunWordAnalysis(resultsTemplate As String, logFile As String, fsObject As FileSystemObject) As Boolean
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "RunWordAnalysis"
- Const APP_WORD = "Word"
- Dim str As String
- Dim bSuccess
- bSuccess = False
-
- Dim wrd As Word.application
- Dim aDoc As Word.Document
- Dim sWordDriverDocPath As String
- Dim RegValue As Long
-
- If (chkWordDoc.value <> vbChecked) And (chkWordTemplate.value <> vbChecked) Then
- 'No Word doc filters selected
- RunWordAnalysis = True
- Exit Function
- End If
-
- sWordDriverDocPath = fsObject.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CWORD_DRIVER_FILE)
- If Not fsObject.FileExists(sWordDriverDocPath) Then
- str = ReplaceTopic2Tokens(GetResString(ERR_MISSING_WORD_DRIVER), _
- TOPIC_STR, sWordDriverDocPath, CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
- bSuccess = False
- GoTo FinalExit
- End If
-
- Set wrd = New Word.application
- If val(wrd.Version) < CSUPPORTED_VERSION Then
- str = ReplaceTopic2Tokens(GetResString(ERR_SUPPORTED_VERSION), _
- TOPIC_STR, wrd.Version, CR_STR, Chr(13))
- WriteDebug str
- MsgBox str, vbCritical
- bSuccess = False
- GoTo FinalExit
- End If
-
- If Not CheckForAccesToWordVBProject(wrd) Then
- RegValue = -1
- If Not GiveAccessToMacroProject(APP_WORD, wrd.Version, RegValue) Then
- Dim Style, response
- str = ReplaceTopic2Tokens(GetResString(ERR_NO_ACCESS_TO_VBPROJECT), _
- TOPIC_STR, CAPPNAME_WORD, CR_STR, Chr(13))
- WriteDebug str
- Style = vbYesNo + vbQuestion + vbDefaultButton1
-
- response = MsgBox(str, Style)
- If response <> vbYes Then
- bSuccess = False
- GoTo FinalExit
- End If
- End If
- End If
-
- Set aDoc = wrd.Documents.Open(fileName:=sWordDriverDocPath)
- 'Clear out any doc vars
- Dim MyObj As Variable
- For Each MyObj In aDoc.Variables
- MyObj.Delete
- Next
-
- 'Setup Input Variables
- 'SetupInputVariables resultsTemplate, logFile, fsObject, CAPPNAME_WORD
-
- wrd.Run ("AnalysisTool.AnalysisDriver.AnalyseDirectory")
-
- wrd.Visible = False
- bSuccess = True
-
-FinalExit:
- If RegValue <> -1 Then
- SetDefaultRegValue APP_WORD, wrd.Version, RegValue
- End If
- If RegValue = 0 Then
- DeleteRegValue APP_WORD, wrd.Version
- End If
- If Not aDoc Is Nothing Then aDoc.Close (False)
- Set aDoc = Nothing
-
- If Not wrd Is Nothing Then wrd.Quit (False)
- Set wrd = Nothing
-
- RunWordAnalysis = bSuccess
- Exit Function
-
-HandleErrors:
- On Error Resume Next
-
- bSuccess = False
- Set aDoc = Nothing
- Set wrd = Nothing
-
- Dim failedDoc As String
-
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
-
- failedDoc = GetDebug(CAPPNAME_WORD, CANALYZING)
- If failedDoc = "" Or failedDoc = CSTR_ANALYSIS_LOG_DONE Then
- str = ReplaceTopic2Tokens(GetResString(ERR_AUTOMATION_FAILURE), _
- TOPIC_STR, CAPPNAME_WORD, CR_STR, Chr(13))
- Else
- str = ReplaceTopic2Tokens(GetResString(ERR_WORD_DRIVER_CRASH), _
- TOPIC_STR, failedDoc, CR_STR, Chr(13))
- End If
-
- WriteDebug str
- MsgBox str, vbCritical
-
- Resume FinalExit
-End Function
-
-Function stripLastBackslash(inputStr As String) As String
- Const MIN_DIR_SIZE = 3
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "stripLastBackslash"
-
- If Len(inputStr) > MIN_DIR_SIZE Then
- Dim lastStrChar As String
- lastStrChar = Right(inputStr, 1)
- If lastStrChar = "\" Then
- inputStr = Left(inputStr, Len(inputStr) - 1)
- End If
- End If
- stripLastBackslash = inputStr
-
- Exit Function
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- stripLastBackslash = inputStr
-End Function
-
-Function getInputDir() As String
- getInputDir = stripLastBackslash(txtInputDir.Text)
-End Function
-
-Function getOutputDir() As String
- Dim tmpStr As String
-
- tmpStr = stripLastBackslash(txtOutputDir.Text)
-
- 'Bug when specifying C:\
- If tmpStr <> "" Then
- If Right(tmpStr, 1) = "\" Then
- tmpStr = Left(tmpStr, Len(tmpStr) - 1)
- End If
- End If
- getOutputDir = tmpStr
-End Function
-
-Function CheckCreateNewResultsFile(fsObject As FileSystemObject) As Boolean
- If Not fsObject.FileExists(getOutputDir & "\" & txtResultsName.Text) Then
- 'No Results File - Create it
- CheckCreateNewResultsFile = True
- ElseIf rdbResultsAppend.value Then
- 'Results File exists and user wants to append to it
- CheckCreateNewResultsFile = False
- Else
- 'Results File exists and user has elected not to append
- CheckCreateNewResultsFile = True
- End If
-End Function
-
-Sub DeleteFile(file As String)
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "DeleteFile"
- Dim fso As Scripting.FileSystemObject
- Set fso = New Scripting.FileSystemObject
- Dim filePath As String
-
- filePath = fso.GetAbsolutePathName(file)
- If fso.FileExists(filePath) Then
- fso.DeleteFile filePath, True
- End If
-
-FinalExit:
- Set fso = Nothing
- Exit Sub
-
-HandleErrors:
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Sub
-
-Public Property Get Version() As String
- Version = app.Major & "." & app.Minor & "." & app.Revision
-End Property
-
-Function GetExcelInstance() As Excel.application
- Dim xl As Excel.application
- On Error Resume Next
- 'Try and get an existing instance
- Set xl = GetObject(, "Excel.Application")
- If Err.Number = 429 Then
- Set xl = CreateObject("Excel.Application")
- ElseIf Err.Number <> 0 Then
- Set xl = Nothing
- MsgBox "Error: " & Err.Description
- Exit Function
- End If
- Set GetExcelInstance = xl
- Set xl = Nothing
-End Function
-
-Function CheckForAnalysisResultsWorkbook(analysisResultsName As String) As Boolean
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "CheckForAnalysisResultsWorkbook"
-
- CheckForAnalysisResultsWorkbook = False
-
- Dim xl As Excel.application
- Set xl = GetExcelInstance
-
- Dim aWb As Excel.Workbook
- For Each aWb In xl.Workbooks
-
- If aWb.Name = analysisResultsName Then
- CheckForAnalysisResultsWorkbook = True
- Exit For
- End If
- Next aWb
-
-FinalExit:
- If Not xl Is Nothing Then
- If xl.Workbooks.count = 0 Then
- xl.Quit
- End If
- End If
-
- Set xl = Nothing
-
- Exit Function
-
-HandleErrors:
- Set xl = Nothing
-
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Function
-
-Function CheckForExcel() As Boolean
- On Error GoTo HandleErrors
- Dim currentFunctionName As String
- currentFunctionName = "CheckForExcel"
-
- CheckForExcel = False
-
- Dim xl As Excel.application
- Set xl = GetExcelInstance
-
-
- If xl.Workbooks.count > 0 Then
- CheckForExcel = True
- End If
-
-FinalExit:
- If Not xl Is Nothing Then
- If xl.Workbooks.count = 0 Then
- xl.Quit
- End If
- End If
-
- Set xl = Nothing
-
- Exit Function
-
-HandleErrors:
- Set xl = Nothing
-
- WriteDebug currentFunctionName & " : " & Err.Number & " " & Err.Description & " " & Err.Source
- Resume FinalExit
-End Function
-
-Public Function GetIniSetting(key As String) As String
-
- If mIniFilePath = "" Or key = "" Then Exit Function
-
- GetIniSetting = ProfileGetItem(WIZARD_NAME, key, "", mIniFilePath)
-End Function
-
-Sub WriteIniSetting(key As String, value As String)
-
- If mIniFilePath = "" Or key = "" Then Exit Sub
-
- Call WritePrivateProfileString(WIZARD_NAME, key, value, mIniFilePath)
-End Sub
-
-Private Sub lblSetupComplete_Click(Index As Integer)
-
-End Sub
-
-Private Function CheckNeededFiles(missingFile As String) As Boolean
-
- Dim fso As New FileSystemObject
- Dim filePath As String
-
- CheckNeededFiles = False
- filePath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CWORD_DRIVER_FILE)
- If Not fso.FileExists(filePath) Then
- missingFile = filePath
- Exit Function
- End If
-
- filePath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CEXCEL_DRIVER_FILE)
- If Not fso.FileExists(filePath) Then
- missingFile = filePath
- Exit Function
- End If
-
- filePath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CPP_DRIVER_FILE)
- If Not fso.FileExists(filePath) Then
- missingFile = filePath
- Exit Function
- End If
-
- filePath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CLAUNCH_DRIVERS_EXE)
- If Not fso.FileExists(filePath) Then
- missingFile = filePath
- Exit Function
- End If
-
- filePath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CMSO_KILL_EXE)
- If Not fso.FileExists(filePath) Then
- missingFile = filePath
- Exit Function
- End If
-
- filePath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CRESULTS_TEMPLATE_FILE)
- If Not fso.FileExists(filePath) Then
- missingFile = filePath
- Exit Function
- End If
-
- filePath = fso.GetAbsolutePathName(CBASE_RESOURCE_DIR & "\" & CRESOURCE_DLL)
- If Not fso.FileExists(filePath) Then
- missingFile = filePath
- Exit Function
- End If
-
- CheckNeededFiles = True
-End Function
diff --git a/migrationanalysis/src/wizard/makefile.mk b/migrationanalysis/src/wizard/makefile.mk
deleted file mode 100644
index bcb211288933..000000000000
--- a/migrationanalysis/src/wizard/makefile.mk
+++ /dev/null
@@ -1,107 +0,0 @@
-#
-# This file is part of the LibreOffice project.
-#
-# This Source Code Form is subject to the terms of the Mozilla Public
-# License, v. 2.0. If a copy of the MPL was not distributed with this
-# file, You can obtain one at http://mozilla.org/MPL/2.0/.
-#
-# This file incorporates work covered by the following license notice:
-#
-# Licensed to the Apache Software Foundation (ASF) under one or more
-# contributor license agreements. See the NOTICE file distributed
-# with this work for additional information regarding copyright
-# ownership. The ASF licenses this file to you under the Apache
-# License, Version 2.0 (the "License"); you may not use this file
-# except in compliance with the License. You may obtain a copy of
-# the License at http://www.apache.org/licenses/LICENSE-2.0 .
-#
-
-PRJ=..$/..
-
-PRJNAME=migrationanalysis
-TARGET=wizard
-
-# --- Settings -----------------------------------------------------
-
-.INCLUDE : settings.mk
-
-# --- Files --------------------------------------------------------
-
-PAW_APPSDEST:=$(BIN)$/ProAnalysisWizard
-ALTERNATE_SRC:=..$/exe
-
-PAW_DATDEST:=$(PAW_APPSDEST)$/Resources
-
-PROJECTDEST:=$(BIN)$/ProAnalysisWizard
-RCFILES:=$(RES)$/$(TARGET).rc
-RESFILE:=$(RES)$/$(TARGET).res
-ULFFILES:=$(TARGET).ulf
-.IF "$(WITH_LANG)"!=""
-ULFDIR:=$(COMMONMISC)$/$(TARGET)
-.ELSE # "$(WITH_LANG)"!=""
-ULFDIR:=.
-.ENDIF # "$(WITH_LANG)"!=""
-MANIFEST:=$(RES)$/DocAnalysisWizard.exe.manifest
-
-LAUNCHER_APP:= $(BIN)$/LaunchDrivers.exe
-
-BASIC_APPS:= \
- $(LAUNCHER_APP) \
- $(PAW_APPSDEST)$/ProAnalysisWizard.exe
-
-BASIC_VBP:= \
- $(BIN)$/LaunchDrivers.vbp \
- $(PAW_APPSDEST)$/ProAnalysisWizard.vbp
-
-PAW_RES_DLLS:=$(PAW_DATDEST)$/Resources.dll
-PAW_LAUNCHER:=$(PAW_DATDEST)$/LaunchDrivers.exe
-
-# --- Targets ------------------------------------------------------
-
-.INCLUDE : target.mk
-
-ALLTAR : $(BASIC_APPS) $(PAW_RES_DLLS) $(PAW_LAUNCHER)
-
-$(MANIFEST) : $$(@:f)
- -$(MKDIRHIER) $(@:d)
- $(COPY) $< $@
-
-.IF "$(VB6_LOCATION)" != ""
-
-$(BASIC_VBP) : $$(@:b).vbp
- -$(MKDIRHIER) $(@:d)
- $(COPY) $(@:f) $@
-
-$(BASIC_APPS) : $(BASIC_VBP)
- -$(MKDIRHIER) $(@:d)
- cd $(@:d) && "$(VB6_LOCATION)$/vb6.exe" /m $(@:b).vbp
-
-$(PAW_LAUNCHER) : $(LAUNCHER_APP)
- -$(MKDIRHIER) $(@:d)
- $(COPY) $(LAUNCHER_APP) $@
-
-.ELSE # "$(VB6_LOCATION)" != ""
-
-$(BASIC_APPS) : $(ALTERNATE_SRC)$/$$(@:f)
- @echo "------------------------------------"
- @echo "No VB6 found: using prebuild wizards"
- @echo "------------------------------------"
- -$(MKDIRHIER) $(@:d)
- $(COPY) $(ALTERNATE_SRC)$/$(@:f) $@
-
-$(PAW_LAUNCHER) : $(ALTERNATE_SRC)$/$$(@:f)
- -$(MKDIRHIER) $(@:d)
- $(COPY) $(ALTERNATE_SRC)$/$(@:f) $@
-
-.ENDIF # "$(VB6_LOCATION)" != ""
-
-# Generate the native Windows resource file
-# using lngconvex.exe
-
-$(RCFILES) : $(MANIFEST) $(ULFDIR)$/$(TARGET).ulf makefile.mk rcfooter.txt rcheader.txt rctmpl.txt
- $(LNGCONVEX) -ulf $(ULFDIR)$/$(TARGET).ulf -rc $(RES)$/$(TARGET).rc -rct rctmpl.txt -rch rcheader.txt -rcf rcfooter.txt
-
-$(PAW_RES_DLLS) : $(RCFILES)
- -$(MKDIRHIER) $(@:d)
- link /NOENTRY /DLL /MACHINE:X86 /OUT:$@ $(RESFILE)
-
diff --git a/migrationanalysis/src/wizard/rcfooter.txt b/migrationanalysis/src/wizard/rcfooter.txt
deleted file mode 100644
index d3f5a12faa99..000000000000
--- a/migrationanalysis/src/wizard/rcfooter.txt
+++ /dev/null
@@ -1 +0,0 @@
-
diff --git a/migrationanalysis/src/wizard/rcheader.txt b/migrationanalysis/src/wizard/rcheader.txt
deleted file mode 100644
index ad35c23356b9..000000000000
--- a/migrationanalysis/src/wizard/rcheader.txt
+++ /dev/null
@@ -1,34 +0,0 @@
-//
-// This file is part of the LibreOffice project.
-//
-// This Source Code Form is subject to the terms of the Mozilla Public
-// License, v. 2.0. If a copy of the MPL was not distributed with this
-// file, You can obtain one at http://mozilla.org/MPL/2.0/.
-//
-// This file incorporates work covered by the following license notice:
-//
-// Licensed to the Apache Software Foundation (ASF) under one or more
-// contributor license agreements. See the NOTICE file distributed
-// with this work for additional information regarding copyright
-// ownership. The ASF licenses this file to you under the Apache
-// License, Version 2.0 (the "License"); you may not use this file
-// except in compliance with the License. You may obtain a copy of
-// the License at http://www.apache.org/licenses/LICENSE-2.0 .
-//
-//_START_OF_HEADER
-/////////////////////////////////////////////////////////////////////////////
-//
-// Document Analysis Wizard - Resources
-//
-
-#include "res_defines.h"
-
-/////////////////////////////////////////////////////////////////////////////
-//
-// Required for Windows XP look and feel support
-//
-#define RT_MANIFEST 24
-
-1 RT_MANIFEST "DocAnalysisWizard.exe.manifest"
-
-
diff --git a/migrationanalysis/src/wizard/rctmpl.txt b/migrationanalysis/src/wizard/rctmpl.txt
deleted file mode 100644
index b451f3ea1fdc..000000000000
--- a/migrationanalysis/src/wizard/rctmpl.txt
+++ /dev/null
@@ -1,143 +0,0 @@
-//
-// This file is part of the LibreOffice project.
-//
-// This Source Code Form is subject to the terms of the Mozilla Public
-// License, v. 2.0. If a copy of the MPL was not distributed with this
-// file, You can obtain one at http://mozilla.org/MPL/2.0/.
-//
-// This file incorporates work covered by the following license notice:
-//
-// Licensed to the Apache Software Foundation (ASF) under one or more
-// contributor license agreements. See the NOTICE file distributed
-// with this work for additional information regarding copyright
-// ownership. The ASF licenses this file to you under the Apache
-// License, Version 2.0 (the "License"); you may not use this file
-// except in compliance with the License. You may obtain a copy of
-// the License at http://www.apache.org/licenses/LICENSE-2.0 .
-//
-// String Table
-
-STRINGTABLE DISCARDABLE
-BEGIN
- RID_STR_ANALYZE_NUM_DOCS %ANALYZE_NUM_DOCS%
- RID_STR_ANALYZE_RUN_TOOL %ANALYZE_RUN_TOOL%
- RID_STR_ANALYZE_SETUP_COMPLETE %ANALYZE_SETUP_COMPLETE%
- RID_STR_ANALYZE_VIEW_RESULTS %ANALYZE_VIEW_RESULTS%
- RID_STR_ANALYZE_PREPARE_DOCS %ANALYZE_PREPARE_DOCS%
- RID_STR_ANALYZE_START %ANALYZE_START%
- RID_STR_ANALYZE_COMPLETED %ANALYZE_COMPLETED%
- RID_STR_ANALYZE_VIEW_NOW %ANALYZE_VIEW_NOW%
- RID_STR_ANALYZE_VIEW_LATER %ANALYZE_VIEW_LATER%
- RID_STR_ANALYSE_NOT_RUN %ANALYSE_NOT_RUN%
- RID_STR_ANALYZE_DOCUMENTS %ANALYZE_DOCUMENTS%
- RID_STR_ANALYZE_TEMPLATES %ANALYZE_TEMPLATES%
- RID_STR_ANALYZE_DOCUMENTS_XLS %ANALYZE_DOCUMENTS_XLS%
- RID_STR_ANALYZE_DOCUMENTS_PPT %ANALYZE_DOCUMENTS_PPT%
- RID_STR_ERROR_AUTOMATION_SERVER_FAILED %ERROR_AUTOMATION_SERVER_FAILED%
- RID_STR_ERROR_CANNOT_CREATE_RESULTS_DIRECTORY %ERROR_CANNOT_CREATE_RESULTS_DIRECTORY%
- RID_STR_ERROR_CHOOSE_DOCUMENT_TYPE %ERROR_CHOOSE_DOCUMENT_TYPE%
- RID_STR_ERROR_CREATE_FILE %ERROR_CREATE_FILE%
- RID_STR_ERROR_EXCEL_ANALYSIS_FAILED %ERROR_EXCEL_ANALYSIS_FAILED%
- RID_STR_ERROR_EXCEL_OPEN %ERROR_EXCEL_OPEN%
- RID_STR_ERROR_MACRO_SECURITY_SET %ERROR_MACRO_SECURITY_SET%
- RID_STR_ERROR_MISSING_DOCUMENTS_DIRECTORY %ERROR_MISSING_DOCUMENTS_DIRECTORY%
- RID_STR_ERROR_MISSING_EXCEL_DRIVER %ERROR_MISSING_EXCEL_DRIVER%
- RID_STR_ERROR_MISSING_ISSUES_LIST %ERROR_MISSING_ISSUES_LIST%
- RID_STR_ERROR_MISSING_MIGRATION_RESULTS %ERROR_MISSING_MIGRATION_RESULTS%
- RID_STR_ERROR_MISSING_POWERPOINT_DRIVER %ERROR_MISSING_POWERPOINT_DRIVER%
- RID_STR_ERROR_MISSING_README %ERROR_MISSING_README%
- RID_STR_ERROR_MISSING_RESULTS_TEMPLATE %ERROR_MISSING_RESULTS_TEMPLATE%
- RID_STR_ERROR_MISSING_WORD_DRIVER %ERROR_MISSING_WORD_DRIVER%
- RID_STR_ERROR_MSOFFICE_9_REQUIRED %ERROR_MSOFFICE_9_REQUIRED%
- RID_STR_ERROR_NO_RESULTS_DIRECTORY %ERROR_NO_RESULTS_DIRECTORY%
- RID_STR_ERROR_POWERPOINT_ANALYSIS_FAILED %ERROR_POWERPOINT_ANALYSIS_FAILED%
- RID_STR_ERROR_RESULTS_DIRECTORY_DOES_NOT_EXIST %ERROR_RESULTS_DIRECTORY_DOES_NOT_EXIST%
- RID_STR_ERROR_RESULTS_SPREADSHEET_OPEN %ERROR_RESULTS_SPREADSHEET_OPEN%
- RID_STR_ERROR_VERSION_MISMATCH %ERROR_VERSION_MISMATCH%
- RID_STR_ERROR_WIN2000_REQUIRED %ERROR_WIN2000_REQUIRED%
- RID_STR_ERROR_WORD_ANALYSIS_FAILED %ERROR_WORD_ANALYSIS_FAILED%
- RID_STR_ERROR_APP_NOT_INSTALLED %ERROR_APP_NOT_INSTALLED%
- RID_STR_ERROR_CDROM_NOT_ALLOWED %ERROR_CDROM_NOT_ALLOWED%
- RID_STR_ERROR_CDROM_NOT_READY %ERROR_CDROM_NOT_READY%
- RID_STR_ERROR_NO_WRITE_TO_READ_ONLY_FOLDER %ERROR_NO_WRITE_TO_READ_ONLY_FOLDER%
- RID_STR_ERROR_APPLICATION_STILL_RUNNING %ERROR_APPLICATION_STILL_RUNNING%
- RID_STR_ERROR_MISSING_IMPORTANT_FILE %ERROR_MISSING_IMPORTANT_FILE%
- RID_STR_INTRODUCTION %INTRODUCTION%
- RID_STR_INTRODUCTION_INTRO1 %INTRODUCTION_INTRO1%
- RID_STR_INTRODUCTION_INTRO2 %INTRODUCTION_INTRO2%
- RID_STR_INTRODUCTION_INTRO3 %INTRODUCTION_INTRO3%
- RID_STR_NAVBAR_BACK_BTN %NAVBAR_BACK_BTN%
- RID_STR_NAVBAR_EXIT_BTN %NAVBAR_EXIT_BTN%
- RID_STR_NAVBAR_FINISH_BTN %NAVBAR_FINISH_BTN%
- RID_STR_NAVBAR_HELP_BTN %NAVBAR_HELP_BTN%
- RID_STR_NAVBAR_NEXT_BTN %NAVBAR_NEXT_BTN%
- RID_STR_OTHER_APPLICATON_LOG_PATH %OTHER_APPLICATON_LOG_PATH%
- RID_STR_OTHER_README_PATH %OTHER_README_PATH%
- RID_STR_OTHER_RUNNING %OTHER_RUNNING%
- RID_STR_OTHER_SELECT_ANALYZE_DIRECTORY %OTHER_SELECT_ANALYZE_DIRECTORY%
- RID_STR_OTHER_SELECT_RESULTS_DIRECTORY %OTHER_SELECT_RESULTS_DIRECTORY%
- RID_STR_OTHER_XML_RESULTS %OTHER_XML_RESULTS%
- RID_STR_DOCUMENTS_CHOOSE_DOCUMENTS %DOCUMENTS_CHOOSE_DOCUMENTS%
- RID_STR_DOCUMENTS_DOCUMENTS_DIRECTORY %DOCUMENTS_DOCUMENTS_DIRECTORY%
- RID_STR_DOCUMENTS_INCLUDE_SUBDIRECTORIES %DOCUMENTS_INCLUDE_SUBDIRECTORIES%
- RID_STR_DOCUMENTS_ROOT_C %DOCUMENTS_ROOT_C%
- RID_STR_DOCUMENTS_CHOOSE_DOC_TYPES %DOCUMENTS_CHOOSE_DOC_TYPES%
- RID_STR_DOCUMENTS_CHOOSE_DOC %DOCUMENTS_CHOOSE_DOC%
- RID_STR_DOCUMENTS_CHOOSE_DOT %DOCUMENTS_CHOOSE_DOT%
- RID_STR_DOCUMENTS_CHOOSE_EXCEL %DOCUMENTS_CHOOSE_EXCEL%
- RID_STR_DOCUMENTS_CHOOSE_POT %DOCUMENTS_CHOOSE_POT%
- RID_STR_DOCUMENTS_CHOOSE_POWERPOINT %DOCUMENTS_CHOOSE_POWERPOINT%
- RID_STR_DOCUMENTS_CHOOSE_PPT %DOCUMENTS_CHOOSE_PPT%
- RID_STR_DOCUMENTS_CHOOSE_WORD %DOCUMENTS_CHOOSE_WORD%
- RID_STR_DOCUMENTS_CHOOSE_XLS %DOCUMENTS_CHOOSE_XLS%
- RID_STR_DOCUMENTS_CHOOSE_XLT %DOCUMENTS_CHOOSE_XLT%
- RID_STR_RESULTS_CHOOSE_OPTIONS %RESULTS_CHOOSE_OPTIONS%
- RID_STR_RESULTS_RESULTS_SPREADSHEET %RESULTS_RESULTS_SPREADSHEET%
- RID_STR_RESULTS_ANALYSIS_XLS %RESULTS_ANALYSIS_XLS%
- RID_STR_RESULTS_RESULTS_DIRECTORY %RESULTS_RESULTS_DIRECTORY%
- RID_STR_RESULTS_CHOOSE_SAVE_OPTIONS %RESULTS_CHOOSE_SAVE_OPTIONS%
- RID_STR_RESULTS_CHOOSE_PROMPT %RESULTS_CHOOSE_PROMPT%
- RID_STR_RESULTS_CHOOSE_OVERWRITE %RESULTS_CHOOSE_OVERWRITE%
- RID_STR_RESULTS_CHOOSE_APPEND %RESULTS_CHOOSE_APPEND%
- RID_STR_SIDEBAR_INTRODUCTION %SIDEBAR_INTRODUCTION%
- RID_STR_SIDEBAR_DOCUMENTS %SIDEBAR_DOCUMENTS%
- RID_STR_SIDEBAR_RESULTS %SIDEBAR_RESULTS%
- RID_STR_SIDEBAR_ANALYZE %SIDEBAR_ANALYZE%
- RID_STR_SIDEBAR_STEPS %SIDEBAR_STEPS%
- RID_STR_TITLE %TITLE%
- RID_STR_PRODUCTNAME %PRODUCTNAME%
- RID_STR_TITLE_PREP %TITLE_PREP%
- RID_STR_SIDEBAR_ANALYZE_PREP %SIDEBAR_ANALYZE_PREP%
- RID_STR_INTRODUCTION_INTRO1_PREP %INTRODUCTION_INTRO1_PREP%
- RID_STR_INTRODUCTION_INTRO2_PREP %INTRODUCTION_INTRO2_PREP%
- RID_STR_INTRODUCTION_INTRO3_PREP %INTRODUCTION_INTRO3_PREP%
- RID_STR_DOCUMENTS_CHOOSE_DOCUMENTS_PREP %DOCUMENTS_CHOOSE_DOCUMENTS_PREP%
- RID_STR_DOCUMENTS_CHOOSE_DOC_TYPES_PREP %DOCUMENTS_CHOOSE_DOC_TYPES_PREP%
- RID_STR_DOCUMENTS_INCLUDE_SUBDIRECTORIES_PREP %DOCUMENTS_INCLUDE_SUBDIRECTORIES_PREP%
- RID_STR_IGNORE_OLDER_CB_ID %IGNORE_OLDER_CB_LABEL%
- RID_STR_IGNORE_OLDER_3_MONTHS_ID %IGNORE_OLDER_3_MONTHS_TEXT%
- RID_STR_IGNORE_OLDER_6_MONTHS_ID %IGNORE_OLDER_6_MONTHS_TEXT%
- RID_STR_IGNORE_OLDER_12_MONTHS_ID %IGNORE_OLDER_12_MONTHS_TEXT%
- RID_STR_RESULTS_CHOOSE_OPTIONS_PREP %RESULTS_CHOOSE_OPTIONS_PREP%
- RID_STR_RESULTS_ANALYSIS_XLS_PREP %RESULTS_ANALYSIS_XLS_PREP%
- RID_STR_ANALYZE_IGNORED_DOCS %ANALYZE_IGNORED_DOCS%
- RID_STR_ANALYZE_NUM_DOCS_PREP %ANALYZE_NUM_DOCS_PREP%
- RID_STR_ANALYZE_SETUP_COMPLETE_PREP %ANALYZE_SETUP_COMPLETE_PREP%
- RID_STR_OTHER_PLEASE_REFER_TO_README_PREP %OTHER_PLEASE_REFER_TO_README_PREP%
- RID_STR_OTHER_XML_RESULTS_PREP %OTHER_XML_RESULTS_PREP%
- RID_STR_OTHER_PREPARE_PROMPT_PREP %OTHER_PREPARE_PROMPT_PREP%
- RID_STR_OTHER_PREPARE_COMPLETED_PREP %OTHER_PREPARE_COMPLETED_PREP%
- RID_STR_PROGRESS_CAPTION %PROGRESS_CAPTION%
- RID_STR_PROGRESS_ABORTING %PROGRESS_ABORTING%
- RID_STR_PROGRESS_PATH_LABEL %PROGRESS_PATH_LABEL%
- RID_STR_PROGRESS_FILE_LABEL %PROGRESS_FILE_LABEL%
- RID_STR_PROGRESS_INFO_LABEL %PROGRESS_INFO_LABEL%
- RID_STR_PROGRESS_WAIT_LABEL %PROGRESS_WAIT_LABEL%
- RID_STR_SEARCH_CAPTION %SEARCH_CAPTION%
- RID_STR_SEARCH_INFO_LABEL %SEARCH_INFO_LABEL%
- RID_STR_SEARCH_FOUND_LABEL %SEARCH_FOUND_LABEL%
- RID_STR_TERMINATE_CAPTION %TERMINATE_CAPTION%
- RID_STR_TERMINATE_INFO %TERMINATE_INFO%
- RID_STR_TERMINATE_YES %TERMINATE_YES%
- RID_STR_TERMINATE_NO %TERMINATE_NO%
-END
diff --git a/migrationanalysis/src/wizard/res_defines.h b/migrationanalysis/src/wizard/res_defines.h
deleted file mode 100644
index b318bc73ad41..000000000000
--- a/migrationanalysis/src/wizard/res_defines.h
+++ /dev/null
@@ -1,153 +0,0 @@
-/* -*- Mode: C++; tab-width: 4; indent-tabs-mode: nil; c-basic-offset: 4 -*- */
-#ifndef RES_DEFINES_H_INCLUDED
-#define RES_DEFINES_H_INCLUDED
-
-#define RID_STR_ANALYZE_SETUP_COMPLETE 1400
-#define RID_STR_ANALYZE_NUM_DOCS 1401
-#define RID_STR_ANALYZE_RUN_TOOL 1404
-#define RID_STR_ANALYZE_VIEW_RESULTS 1406
-#define RID_STR_ANALYZE_COMPLETED 1412
-#define RID_STR_ANALYZE_START 1413
-#define RID_STR_ANALYZE_VIEW_NOW 1414
-#define RID_STR_ANALYZE_VIEW_LATER 1415
-#define RID_STR_ANALYSE_NOT_RUN 1416
-
-#define RID_STR_ANALYZE_PREPARE_DOCS 1411
-
-#define RID_STR_ANALYZE_DOCUMENTS 1402
-#define RID_STR_ANALYZE_TEMPLATES 1403
-#define RID_STR_ANALYZE_DOCUMENTS_XLS 1408
-#define RID_STR_ANALYZE_DOCUMENTS_PPT 1409
-
-#define RID_STR_ERROR_AUTOMATION_SERVER_FAILED 1920
-#define RID_STR_ERROR_CANNOT_CREATE_RESULTS_DIRECTORY 1904
-#define RID_STR_ERROR_CHOOSE_DOCUMENT_TYPE 1902
-#define RID_STR_ERROR_CREATE_FILE 1922
-#define RID_STR_ERROR_EXCEL_ANALYSIS_FAILED 1907
-#define RID_STR_ERROR_EXCEL_OPEN 1918
-#define RID_STR_ERROR_MACRO_SECURITY_SET 1919
-#define RID_STR_ERROR_MISSING_DOCUMENTS_DIRECTORY 1901
-#define RID_STR_ERROR_MISSING_EXCEL_DRIVER 1906
-#define RID_STR_ERROR_MISSING_ISSUES_LIST 1915
-#define RID_STR_ERROR_MISSING_MIGRATION_RESULTS 1900
-#define RID_STR_ERROR_MISSING_POWERPOINT_DRIVER 1911
-#define RID_STR_ERROR_MISSING_README 1910
-#define RID_STR_ERROR_MISSING_RESULTS_TEMPLATE 1905
-#define RID_STR_ERROR_MISSING_WORD_DRIVER 1908
-#define RID_STR_ERROR_MSOFFICE_9_REQUIRED 1913
-#define RID_STR_ERROR_NO_RESULTS_DIRECTORY 1921
-#define RID_STR_ERROR_POWERPOINT_ANALYSIS_FAILED 1912
-#define RID_STR_ERROR_RESULTS_DIRECTORY_DOES_NOT_EXIST 1903
-#define RID_STR_ERROR_RESULTS_SPREADSHEET_OPEN 1917
-#define RID_STR_ERROR_VERSION_MISMATCH 1914
-#define RID_STR_ERROR_WIN2000_REQUIRED 1916
-#define RID_STR_ERROR_WORD_ANALYSIS_FAILED 1909
-#define RID_STR_ERROR_APP_NOT_INSTALLED 1924
-#define RID_STR_ERROR_CDROM_NOT_ALLOWED 1925
-#define RID_STR_ERROR_CDROM_NOT_READY 1926
-#define RID_STR_ERROR_NO_WRITE_TO_READ_ONLY_FOLDER 1927
-#define RID_STR_ERROR_APPLICATION_STILL_RUNNING 1928
-#define RID_STR_ERROR_MISSING_IMPORTANT_FILE 1929
-
-
-#define RID_STR_INTRODUCTION 1100
-#define RID_STR_INTRODUCTION_INTRO1 1101
-#define RID_STR_INTRODUCTION_INTRO2 1102
-#define RID_STR_INTRODUCTION_INTRO3 1104
-
-#define RID_STR_NAVBAR_BACK_BTN 1021
-#define RID_STR_NAVBAR_EXIT_BTN 1024
-#define RID_STR_NAVBAR_FINISH_BTN 1023
-#define RID_STR_NAVBAR_HELP_BTN 1020
-#define RID_STR_NAVBAR_NEXT_BTN 1022
-
-
-#define RID_STR_RESULTS_CHOOSE_OPTIONS 1300
-#define RID_STR_RESULTS_RESULTS_SPREADSHEET 1301
-#define RID_STR_RESULTS_ANALYSIS_XLS 1302
-#define RID_STR_RESULTS_RESULTS_DIRECTORY 1304
-#define RID_STR_RESULTS_CHOOSE_SAVE_OPTIONS 1311
-#define RID_STR_RESULTS_CHOOSE_PROMPT 1312
-#define RID_STR_RESULTS_CHOOSE_OVERWRITE 1313
-#define RID_STR_RESULTS_CHOOSE_APPEND 1314
-
-#define RID_STR_OTHER_APPLICATON_LOG_PATH 1812
-#define RID_STR_OTHER_RUNNING 1810
-#define RID_STR_OTHER_SELECT_ANALYZE_DIRECTORY 1806
-#define RID_STR_OTHER_SELECT_RESULTS_DIRECTORY 1807
-#define RID_STR_OTHER_XML_RESULTS 1815
-#define RID_STR_OTHER_README_PATH 1805
-
-#define RID_STR_DOCUMENTS_CHOOSE_DOCUMENTS 1200
-#define RID_STR_DOCUMENTS_DOCUMENTS_DIRECTORY 1201
-#define RID_STR_DOCUMENTS_INCLUDE_SUBDIRECTORIES 1202
-#define RID_STR_DOCUMENTS_ROOT_C 1205
-#define RID_STR_DOCUMENTS_CHOOSE_DOC_TYPES 1206
-#define RID_STR_DOCUMENTS_CHOOSE_WORD 1207
-#define RID_STR_DOCUMENTS_CHOOSE_DOC 1208
-#define RID_STR_DOCUMENTS_CHOOSE_DOT 1209
-#define RID_STR_DOCUMENTS_CHOOSE_EXCEL 1210
-#define RID_STR_DOCUMENTS_CHOOSE_XLS 1211
-#define RID_STR_DOCUMENTS_CHOOSE_XLT 1212
-#define RID_STR_DOCUMENTS_CHOOSE_POWERPOINT 1213
-#define RID_STR_DOCUMENTS_CHOOSE_PPT 1214
-#define RID_STR_DOCUMENTS_CHOOSE_POT 1215
-
-#define RID_STR_SIDEBAR_STEPS 1040
-#define RID_STR_SIDEBAR_INTRODUCTION 1041
-#define RID_STR_SIDEBAR_DOCUMENTS 1042
-#define RID_STR_SIDEBAR_RESULTS 1043
-#define RID_STR_SIDEBAR_ANALYZE 1044
-
-#define RID_STR_TITLE 1000
-#define RID_STR_PRODUCTNAME 1001
-
-
-// Preparation
-#define RID_STR_SIDEBAR_ANALYZE_PREP 1074
-#define RID_STR_TITLE_PREP 1030
-
-#define RID_STR_INTRODUCTION_INTRO1_PREP 1131
-#define RID_STR_INTRODUCTION_INTRO2_PREP 1132
-#define RID_STR_INTRODUCTION_INTRO3_PREP 1134
-
-#define RID_STR_DOCUMENTS_CHOOSE_DOCUMENTS_PREP 1230
-#define RID_STR_DOCUMENTS_INCLUDE_SUBDIRECTORIES_PREP 1232
-#define RID_STR_DOCUMENTS_CHOOSE_DOC_TYPES_PREP 1236
-
-#define RID_STR_IGNORE_OLDER_CB_ID 1231
-#define RID_STR_IGNORE_OLDER_3_MONTHS_ID 1233
-#define RID_STR_IGNORE_OLDER_6_MONTHS_ID 1234
-#define RID_STR_IGNORE_OLDER_12_MONTHS_ID 1235
-
-#define RID_STR_RESULTS_CHOOSE_OPTIONS_PREP 1330
-#define RID_STR_RESULTS_ANALYSIS_XLS_PREP 1332
-
-#define RID_STR_ANALYZE_NUM_DOCS_PREP 1431
-#define RID_STR_ANALYZE_SETUP_COMPLETE_PREP 1430
-#define RID_STR_ANALYZE_IGNORED_DOCS 1435
-
-#define RID_STR_OTHER_PLEASE_REFER_TO_README_PREP 1838
-#define RID_STR_OTHER_XML_RESULTS_PREP 1845
-#define RID_STR_OTHER_PREPARE_PROMPT_PREP 1846
-#define RID_STR_OTHER_PREPARE_COMPLETED_PREP 1847
-
-// Progress
-#define RID_STR_PROGRESS_CAPTION 1820
-#define RID_STR_PROGRESS_ABORTING 1821
-#define RID_STR_PROGRESS_PATH_LABEL 1822
-#define RID_STR_PROGRESS_FILE_LABEL 1823
-#define RID_STR_PROGRESS_INFO_LABEL 1824
-#define RID_STR_PROGRESS_WAIT_LABEL 1825
-
-#define RID_STR_SEARCH_CAPTION 1826
-#define RID_STR_SEARCH_INFO_LABEL 1827
-#define RID_STR_SEARCH_FOUND_LABEL 1828
-
-#define RID_STR_TERMINATE_CAPTION 1830
-#define RID_STR_TERMINATE_INFO 1831
-#define RID_STR_TERMINATE_YES 1832
-#define RID_STR_TERMINATE_NO 1833
-#endif
-
-/* vim:set shiftwidth=4 softtabstop=4 expandtab: */
diff --git a/migrationanalysis/src/wizard/wizard.ulf b/migrationanalysis/src/wizard/wizard.ulf
deleted file mode 100644
index 5d345fa0ad5e..000000000000
--- a/migrationanalysis/src/wizard/wizard.ulf
+++ /dev/null
@@ -1,370 +0,0 @@
-/*
- * This file is part of the LibreOffice project.
- *
- * This Source Code Form is subject to the terms of the Mozilla Public
- * License, v. 2.0. If a copy of the MPL was not distributed with this
- * file, You can obtain one at http://mozilla.org/MPL/2.0/.
- *
- * This file incorporates work covered by the following license notice:
- *
- * Licensed to the Apache Software Foundation (ASF) under one or more
- * contributor license agreements. See the NOTICE file distributed
- * with this work for additional information regarding copyright
- * ownership. The ASF licenses this file to you under the Apache
- * License, Version 2.0 (the "License"); you may not use this file
- * except in compliance with the License. You may obtain a copy of
- * the License at http://www.apache.org/licenses/LICENSE-2.0 .
- */
-
-[%ANALYZE_NUM_DOCS%]
-en-US = "A total of <TOPIC> documents will be analyzed:"
-
-[%ANALYZE_RUN_TOOL%]
-en-US = "Run analysis"
-
-[%ANALYZE_SETUP_COMPLETE%]
-en-US = "Run the analysis and view the results"
-
-[%ANALYZE_VIEW_RESULTS%]
-en-US = "View results"
-
-[%ANALYZE_PREPARE_DOCS%]
-en-US = "Prepare Documents for Migration"
-
-[%ANALYZE_START%]
-en-US = "The analysis will now be carried out on <TOPIC> documents.<CR><CR>Please note this may take some time as each document must be opened<CR>in order to analyze it.<CR><CR>A message will appear when the analysis is complete."
-
-[%ANALYZE_COMPLETED%]
-en-US = "The analysis has been completed successfully.<CR><CR>Click on OK to see the results now."
-
-[%ANALYZE_VIEW_NOW%]
-en-US = "View Now"
-
-[%ANALYZE_VIEW_LATER%]
-en-US = "View Later"
-
-[%ANALYSE_NOT_RUN%]
-en-US = "The document analysis has not been run yet.<CR><CR>Click on OK to leave wizard now.<CR>Press 'Cancel' button to return to the Wizard. Then press 'Run Analysis' button to start the analysis."
-
-[%ANALYZE_DOCUMENTS%]
-en-US = "<TOPIC> Documents"
-
-[%ANALYZE_TEMPLATES%]
-en-US = "<TOPIC> Templates"
-
-[%ANALYZE_DOCUMENTS_XLS%]
-en-US = "<TOPIC> Spreadsheets"
-
-[%ANALYZE_DOCUMENTS_PPT%]
-en-US = "<TOPIC> Presentations"
-
-[%ERROR_AUTOMATION_SERVER_FAILED%]
-en-US = "<TOPIC> The analysis failed to connect to the <TOPIC> automation server.<CR><CR>Please ensure that all instances of <TOPIC> are closed before rerunning the analysis<CR>and check that the machine has sufficient free memory to run the analysis.<CR><CR>If necessary use the Task Manager to remove any frozen instances of <TOPIC>,<CR>using the Applications Tab - End Task"
-
-[%ERROR_CANNOT_CREATE_RESULTS_DIRECTORY%]
-en-US = "Can't create the directory: <CR><TOPIC><CR><CR>Check that you are creating only a single directory at the lowest level and <CR>that you can write to this disk and <CR>that it is not full."
-
-[%ERROR_CHOOSE_DOCUMENT_TYPE%]
-en-US = "Please choose at least one document type to analyze."
-
-[%ERROR_CREATE_FILE%]
-en-US = "Can't create the file: <CR><TOPIC><CR><CR>Please check that you have write permission to this directory."
-
-[%ERROR_EXCEL_ANALYSIS_FAILED%]
-en-US = "Excel Analysis Failed on document: <CR><CR><TOPIC><CR><CR>Please remove this file from the Documents Directory and ensure that all instances of Excel<CR>are closed before rerunning the analysis<CR><CR>If necessary use the Task Manager to remove any frozen instances of Excel,<CR>using the Applications Tab - End Task"
-
-[%ERROR_EXCEL_OPEN%]
-en-US = "The wizard cannot run the analysis if Excel is open. The wizard needs<CR>exclusive access to Excel in order to create the results spreadsheet.<CR><CR>Please close Excel so the analysis can be run."
-
-[%ERROR_MACRO_SECURITY_SET%]
-en-US = "Unable to detect or analyze <TOPIC> macros due to the following <TOPIC> macro security setting:<CR> <TOPIC> main menu:<CR> Tools-> Macro-> Security...<CR> Trusted Sources tab:<CR> Trust access to Visual Basic Project - unchecked<CR>To analyze macros you must check this checkbox before running the analysis.<CR><CR>Do you wish to continue the analysis without detecting and analyzing <TOPIC> macros?"
-
-[%ERROR_MISSING_DOCUMENTS_DIRECTORY%]
-en-US = "Documents Directory does not exist.<CR><CR>Please choose another directory."
-
-[%ERROR_MISSING_EXCEL_DRIVER%]
-en-US = "Missing Excel Analysis Driver Spreadsheet: <CR><TOPIC><CR><CR>Please reinstall the application."
-
-[%ERROR_MISSING_ISSUES_LIST%]
-en-US = "Missing issues list:<CR><TOPIC><CR><CR>Please reinstall the application."
-
-[%ERROR_MISSING_MIGRATION_RESULTS%]
-en-US = "Missing Analysis Results Document: <CR><TOPIC><CR><CR>Please check that you have write permissions on the <CR>results directory and rerun the analysis.<CR>"
-
-[%ERROR_MISSING_POWERPOINT_DRIVER%]
-en-US = "Missing PowerPoint Analysis Driver Document: <CR><TOPIC><CR><CR>Please reinstall the application."
-
-[%ERROR_MISSING_README%]
-en-US = "Missing Help Documentation: <CR><TOPIC><CR><CR>Please reinstall the application."
-
-[%ERROR_MISSING_RESULTS_TEMPLATE%]
-en-US = "Missing Results Template: <CR><TOPIC><CR><CR>Please reinstall the application."
-
-[%ERROR_MISSING_WORD_DRIVER%]
-en-US = "Missing Word Analysis Driver Document: <CR><TOPIC><CR><CR>Please reinstall the application."
-
-[%ERROR_MSOFFICE_9_REQUIRED%]
-en-US = "The wizard requires Microsoft Office version 9.0 or above to be installed.<CR><CR>The currently installed version <TOPIC> is not supported."
-
-[%ERROR_NO_RESULTS_DIRECTORY%]
-en-US = "Results Directory has not been specified.<CR><CR>Please enter a results directory."
-
-[%ERROR_POWERPOINT_ANALYSIS_FAILED%]
-en-US = "PowerPoint Analysis Failed on document: <CR><CR><TOPIC><CR><CR>Please remove this file from the Documents Directory and ensure that all instances of PowerPoint<CR>are closed before rerunning the analysis<CR><CR>If necessary use the Task Manager to remove any frozen instances of PowerPoint,<CR>using the Applications Tab - End Task"
-
-[%ERROR_RESULTS_DIRECTORY_DOES_NOT_EXIST%]
-en-US = "Results Directory does not exist.<CR><CR>Do you want to create the directory?"
-
-[%ERROR_RESULTS_SPREADSHEET_OPEN%]
-en-US = "The wizard needs to write to the results spreadsheet:<CR><TOPIC><CR><CR>Excel currently has this spreadsheet open. It must be closed before the analysis can be run.<CR><CR>If Excel does not appear to be running please check the Task Manager and remove any Excel.exe processes."
-
-[%ERROR_VERSION_MISMATCH%]
-en-US = "There is a version mismatch between the Wizard [<TOPIC>] and the Issues list [<TOPIC2>]<CR>used to cutomize the reporting of minor issues.<CR><CR>Please contact support."
-
-[%ERROR_WIN2000_REQUIRED%]
-en-US = "To run this wizard, Windows 2000 or newer is required.<CR><CR>The current operating system <TOPIC> is not supported."
-
-[%ERROR_WORD_ANALYSIS_FAILED%]
-en-US = "Word Analysis Failed on document: <CR><CR><TOPIC><CR><CR>Please remove this file from the Documents Directory and ensure that all instances of Word<CR>are closed before rerunning the analysis<CR><CR>If necessary use the Task Manager to remove any frozen instances of Word,<CR>using the Applications Tab - End Task"
-
-[%ERROR_APP_NOT_INSTALLED%]
-en-US = "The wizard requires Microsoft <TOPIC> version 9.0 or above to be installed.<CR><CR>Please install and rerun the analysis."
-
-[%ERROR_APPLICATION_STILL_RUNNING%]
-en-US = "The following applications are still running: <TOPIC>.<CR><CR>Please ensure that all instances of <TOPIC> are closed before rerunning the analysis.<CR><CR>If necessary use the Task Manager to remove any frozen instances of <TOPIC>,<CR>using the Applications Tab - End Task"
-
-[%ERROR_MISSING_IMPORTANT_FILE%]
-en-US = "A file needed for analyzing is missing: <CR><TOPIC><CR><CR>Please reinstall the application."
-
-[%INTRODUCTION%]
-en-US = "Introduction"
-
-[%INTRODUCTION_INTRO1%]
-en-US = "The <PRODUCTNAME> Document Analysis Wizard is for you to use to automatically analyze a collection of Microsoft Office documents for issues relevant to a migration to <PRODUCTNAME>."
-
-[%INTRODUCTION_INTRO2%]
-en-US = "You will be able to select which documents you want to analyze as well as where you want the results of the analysis to be saved."
-
-[%INTRODUCTION_INTRO3%]
-en-US = "The wizard will remain on screen while the analysis is carried out."
-
-[%NAVBAR_BACK_BTN%]
-en-US = "<< Back"
-
-[%NAVBAR_EXIT_BTN%]
-en-US = "Cancel"
-
-[%NAVBAR_FINISH_BTN%]
-en-US = "Finish"
-
-[%NAVBAR_HELP_BTN%]
-en-US = "Help"
-
-[%NAVBAR_NEXT_BTN%]
-en-US = "Next >>"
-
-[%OTHER_README_PATH%]
-en-US = "UserGuide_en-US.pdf"
-
-[%OTHER_RUNNING%]
-en-US = "Running ..."
-
-[%OTHER_SELECT_ANALYZE_DIRECTORY%]
-en-US = "Select a Directory to Analyze"
-
-[%OTHER_SELECT_RESULTS_DIRECTORY%]
-en-US = "Select a Directory for Analysis Results"
-
-[%OTHER_XML_RESULTS%]
-en-US = "Analysis Results have been output in XML format to: <CR><TOPIC>"
-
-[%DOCUMENTS_CHOOSE_DOCUMENTS%]
-en-US = "Choose the documents you want to analyze"
-
-[%DOCUMENTS_DOCUMENTS_DIRECTORY%]
-en-US = "Location of Microsoft Office documents"
-
-[%DOCUMENTS_INCLUDE_SUBDIRECTORIES%]
-en-US = "Include subdirectories in the analysis"
-
-[%DOCUMENTS_ROOT_C%]
-en-US = "C:\\"
-
-[%DOCUMENTS_CHOOSE_DOC_TYPES%]
-en-US = "Document types to analyze:"
-
-[%DOCUMENTS_CHOOSE_DOC%]
-en-US = "Documents (*.doc)"
-
-[%DOCUMENTS_CHOOSE_DOT%]
-en-US = "Templates (*.dot)"
-
-[%DOCUMENTS_CHOOSE_EXCEL%]
-en-US = "Excel"
-
-[%DOCUMENTS_CHOOSE_POT%]
-en-US = "Templates (*.pot)"
-
-[%DOCUMENTS_CHOOSE_POWERPOINT%]
-en-US = "PowerPoint"
-
-[%DOCUMENTS_CHOOSE_PPT%]
-en-US = "Presentations (*.ppt)"
-
-[%DOCUMENTS_CHOOSE_WORD%]
-en-US = "Word"
-
-[%DOCUMENTS_CHOOSE_XLS%]
-en-US = "Spreadsheets (*.xls)"
-
-[%DOCUMENTS_CHOOSE_XLT%]
-en-US = "Templates (*.xlt)"
-
-[%RESULTS_CHOOSE_OPTIONS%]
-en-US = "Choose where and how to save the results"
-
-[%RESULTS_RESULTS_SPREADSHEET%]
-en-US = "File name for the results spreadsheet"
-
-[%RESULTS_ANALYSIS_XLS%]
-en-US = "Analysis Results.xls"
-
-[%RESULTS_RESULTS_DIRECTORY%]
-en-US = "Location"
-
-[%RESULTS_CHOOSE_SAVE_OPTIONS%]
-en-US = "If results already exist under the same name and location:"
-
-[%RESULTS_CHOOSE_PROMPT%]
-en-US = "Ask me before overwriting"
-
-[%RESULTS_CHOOSE_OVERWRITE%]
-en-US = "Overwrite without asking me"
-
-[%RESULTS_CHOOSE_APPEND%]
-en-US = "Append the new results to the existing results"
-
-[%SIDEBAR_INTRODUCTION%]
-en-US = "1. Introduction"
-
-[%SIDEBAR_DOCUMENTS%]
-en-US = "2. Documents"
-
-[%SIDEBAR_RESULTS%]
-en-US = "3. Results"
-
-[%SIDEBAR_ANALYZE%]
-en-US = "4. Analysis"
-
-[%SIDEBAR_STEPS%]
-en-US = "Steps"
-
-[%TITLE%]
-en-US = "<PRODUCTNAME> Document Analysis Wizard"
-
-[%PRODUCTNAME%]
-en-US = "OpenOffice.org"
-
-[%TITLE_PREP%]
-en-US = "<PRODUCTNAME> Professional Analysis Wizard"
-
-[%SIDEBAR_ANALYZE_PREP%]
-en-US = "4. Analysis"
-
-[%INTRODUCTION_INTRO1_PREP%]
-en-US = "The <PRODUCTNAME> Professional Analysis Wizard is for you to use to automatically analyze a collection of Microsoft Office documents for issues relevant to a migration to <PRODUCTNAME>."
-
-[%INTRODUCTION_INTRO2_PREP%]
-en-US = "You will be able to select which documents you want to analyze as well as where you want the results of the analysis to be saved."
-
-[%INTRODUCTION_INTRO3_PREP%]
-en-US = "Where a workaround is available for a migration issue, the wizard will enable you to prepare a modified copy of the original document in which the migration issue has been resolved."
-
-[%DOCUMENTS_CHOOSE_DOCUMENTS_PREP%]
-en-US = "Choose the documents you want to analyze"
-
-[%DOCUMENTS_CHOOSE_DOC_TYPES_PREP%]
-en-US = "Document types to analyze:"
-
-[%IGNORE_OLDER_CB_LABEL%]
-en-US = "Ignore documents older than:"
-
-[%IGNORE_OLDER_3_MONTHS_TEXT%]
-en-US = "3 months"
-
-[%IGNORE_OLDER_6_MONTHS_TEXT%]
-en-US = "6 months"
-
-[%IGNORE_OLDER_12_MONTHS_TEXT%]
-en-US = "12 months"
-
-[%DOCUMENTS_INCLUDE_SUBDIRECTORIES_PREP%]
-en-US = "Include subdirectories in the analysis"
-
-[%RESULTS_CHOOSE_OPTIONS_PREP%]
-en-US = "Choose where and how to save the results"
-
-[%RESULTS_ANALYSIS_XLS_PREP%]
-en-US = "Analysis Results.xls"
-
-[%ANALYZE_NUM_DOCS_PREP%]
-en-US = "A total of <TOPIC> documents will be analyzed:"
-
-[%ANALYZE_IGNORED_DOCS%]
-en-US = "Skipped <TOPIC> documents because they were to old."
-
-[%ANALYZE_SETUP_COMPLETE_PREP%]
-en-US = "Run the analysis and view the results"
-
-[%OTHER_PLEASE_REFER_TO_README_PREP%]
-en-US = "<PRODUCTNAME> Professional Analysis Wizard <TOPIC><CR><CR>For help please refer to the User Guide in<CR>the install directory."
-
-[%OTHER_XML_RESULTS_PREP%]
-en-US = "Analysis Results have been output in XML format to: <CR><TOPIC>"
-
-[%OTHER_PREPARE_PROMPT_PREP%]
-en-US = "Prepare any documents that have Preparable Document Issues, listed in the results spreadsheet:<CR> <TOPIC><CR><CR>Prepared documents will be saved under:<CR> <TOPIC2>\prepared<CR><CR>Source documents will not be modified."
-
-[%OTHER_PREPARE_COMPLETED_PREP%]
-en-US = "Preparation completed successfully.<CR><CR>Prepared documents have been saved under:<CR><TOPIC>\prepared"
-
-[%PROGRESS_CAPTION%]
-en-US = "Analysing Microsoft Office Documents"
-
-[%PROGRESS_ABORTING%]
-en-US = "Aborting"
-
-[%PROGRESS_PATH_LABEL%]
-en-US = "Path:"
-
-[%PROGRESS_FILE_LABEL%]
-en-US = "File:"
-
-[%PROGRESS_INFO_LABEL%]
-en-US = "Please wait while wizard is analysing Microsoft Office documents."
-
-[%PROGRESS_WAIT_LABEL%]
-en-US = "Please wait while wizard is aborting the analysis."
-
-[%SEARCH_CAPTION%]
-en-US = "Scanning for Microsoft Office Documents"
-
-[%SEARCH_INFO_LABEL%]
-en-US = "Please wait while wizard is scanning for Microsoft Office documents."
-
-[%SEARCH_FOUND_LABEL%]
-en-US = "Documents found:"
-
-[%TERMINATE_CAPTION%]
-en-US = "Application not Responding"
-
-[%TERMINATE_INFO%]
-en-US = "The Microsoft Office application, used for the analysis, is currently not responding and could not be closed. Microsoft Office needs to be closed before the Wizard could start a new analysis.<CR><CR>Do you want to abort this application?<CR><CR>Please note that unsaved data of this application will be lost."
-
-[%TERMINATE_YES%]
-en-US = "Yes"
-
-[%TERMINATE_NO%]
-en-US = "No"
-
-