1cdf0e10cSrcweirAttribute VB_Name = "RunServer"
2*e76eebc6SAndrew Rist'*************************************************************************
3*e76eebc6SAndrew Rist'
4*e76eebc6SAndrew Rist'  Licensed to the Apache Software Foundation (ASF) under one
5*e76eebc6SAndrew Rist'  or more contributor license agreements.  See the NOTICE file
6*e76eebc6SAndrew Rist'  distributed with this work for additional information
7*e76eebc6SAndrew Rist'  regarding copyright ownership.  The ASF licenses this file
8*e76eebc6SAndrew Rist'  to you under the Apache License, Version 2.0 (the
9*e76eebc6SAndrew Rist'  "License"); you may not use this file except in compliance
10*e76eebc6SAndrew Rist'  with the License.  You may obtain a copy of the License at
11*e76eebc6SAndrew Rist'
12*e76eebc6SAndrew Rist'    http://www.apache.org/licenses/LICENSE-2.0
13*e76eebc6SAndrew Rist'
14*e76eebc6SAndrew Rist'  Unless required by applicable law or agreed to in writing,
15*e76eebc6SAndrew Rist'  software distributed under the License is distributed on an
16*e76eebc6SAndrew Rist'  "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
17*e76eebc6SAndrew Rist'  KIND, either express or implied.  See the License for the
18*e76eebc6SAndrew Rist'  specific language governing permissions and limitations
19*e76eebc6SAndrew Rist'  under the License.
20*e76eebc6SAndrew Rist'
21*e76eebc6SAndrew Rist'*************************************************************************
22cdf0e10cSrcweirOption Explicit
23cdf0e10cSrcweir
24cdf0e10cSrcweirPrivate Declare Function WritePrivateProfileString Lib "kernel32" _
25cdf0e10cSrcweir   Alias "WritePrivateProfileStringA" _
26cdf0e10cSrcweir  (ByVal lpSectionName As String, _
27cdf0e10cSrcweir   ByVal lpKeyName As Any, _
28cdf0e10cSrcweir   ByVal lpString As Any, _
29cdf0e10cSrcweir   ByVal lpFileName As String) As Long
30cdf0e10cSrcweir
31cdf0e10cSrcweirConst CWORD_DRIVER = "_OOoDocAnalysisWordDriver.doc"
32cdf0e10cSrcweirConst CEXCEL_DRIVER = "_OOoDocAnalysisExcelDriver.xls"
33cdf0e10cSrcweirConst CPP_DRIVER = "_OOoDocAnalysisPPTDriver.ppt"
34cdf0e10cSrcweir
35cdf0e10cSrcweirConst CWORD_APP = "word"
36cdf0e10cSrcweirConst CEXCEL_APP = "excel"
37cdf0e10cSrcweirConst CPP_APP = "pp"
38cdf0e10cSrcweir
39cdf0e10cSrcweirConst CSTART_FILE = "PAW_Start_Analysis"
40cdf0e10cSrcweirConst CSTOP_FILE = "PAW_Stop_Analysis"
41cdf0e10cSrcweir
42cdf0e10cSrcweirSub Main()
43cdf0e10cSrcweir
44cdf0e10cSrcweir    Dim serverType As String
45cdf0e10cSrcweir    serverType = LCase(Command$)
46cdf0e10cSrcweir    If (serverType <> CWORD_APP) And (serverType <> CEXCEL_APP) And (serverType <> CPP_APP) Then
47cdf0e10cSrcweir        MsgBox "Unknown server type: " & serverType
48cdf0e10cSrcweir        GoTo FinalExit
49cdf0e10cSrcweir    End If
50cdf0e10cSrcweir
51cdf0e10cSrcweir    Dim fso As New FileSystemObject
52cdf0e10cSrcweir    Dim driverName As String
53cdf0e10cSrcweir
54cdf0e10cSrcweir    If (serverType = CWORD_APP) Then
55cdf0e10cSrcweir        driverName = fso.GetAbsolutePathName(".\" & CWORD_DRIVER)
56cdf0e10cSrcweir    ElseIf (serverType = CEXCEL_APP) Then
57cdf0e10cSrcweir        driverName = fso.GetAbsolutePathName(".\" & CEXCEL_DRIVER)
58cdf0e10cSrcweir    ElseIf (serverType = CPP_APP) Then
59cdf0e10cSrcweir        driverName = fso.GetAbsolutePathName(".\" & CPP_DRIVER)
60cdf0e10cSrcweir    End If
61cdf0e10cSrcweir
62cdf0e10cSrcweir    If Not fso.FileExists(driverName) Then
63cdf0e10cSrcweir        If (serverType = CWORD_APP) Then
64cdf0e10cSrcweir            driverName = fso.GetAbsolutePathName(".\Resources\" & CWORD_DRIVER)
65cdf0e10cSrcweir        ElseIf (serverType = CEXCEL_APP) Then
66cdf0e10cSrcweir            driverName = fso.GetAbsolutePathName(".\Resources\" & CEXCEL_DRIVER)
67cdf0e10cSrcweir        ElseIf (serverType = CPP_APP) Then
68cdf0e10cSrcweir            driverName = fso.GetAbsolutePathName(".\Resources\" & CPP_DRIVER)
69cdf0e10cSrcweir        End If
70cdf0e10cSrcweir    End If
71cdf0e10cSrcweir
72cdf0e10cSrcweir    If Not fso.FileExists(driverName) Then
73cdf0e10cSrcweir        WriteToLog fso, "ALL", "LaunchDrivers: Could not find: " & driverName
74cdf0e10cSrcweir        GoTo FinalExit
75cdf0e10cSrcweir    End If
76cdf0e10cSrcweir
77cdf0e10cSrcweir    If (serverType = CWORD_APP) Then
78cdf0e10cSrcweir        OpenWordDriverDoc fso, driverName
79cdf0e10cSrcweir    ElseIf (serverType = CEXCEL_APP) Then
80cdf0e10cSrcweir        OpenExcelDriverDoc fso, driverName
81cdf0e10cSrcweir    ElseIf (serverType = CPP_APP) Then
82cdf0e10cSrcweir        OpenPPDriverDoc fso, driverName
83cdf0e10cSrcweir    End If
84cdf0e10cSrcweir
85cdf0e10cSrcweirFinalExit:
86cdf0e10cSrcweir
87cdf0e10cSrcweir    Set fso = Nothing
88cdf0e10cSrcweirEnd Sub
89cdf0e10cSrcweir
90cdf0e10cSrcweirSub OpenWordDriverDoc(fso As FileSystemObject, driverName As String)
91cdf0e10cSrcweir
92cdf0e10cSrcweir    Dim wrdApp As Word.Application
93cdf0e10cSrcweir    Dim wrdDriverDoc As Word.Document
94cdf0e10cSrcweir
95cdf0e10cSrcweir    On Error GoTo HandleErrors
96cdf0e10cSrcweir
97cdf0e10cSrcweir    Set wrdApp = New Word.Application
98cdf0e10cSrcweir    Set wrdDriverDoc = wrdApp.Documents.Open(driverName)
99cdf0e10cSrcweir
100cdf0e10cSrcweir    wrdApp.Run ("AnalysisTool.AnalysisDriver.AnalyseDirectory")
101cdf0e10cSrcweir    If Err.Number <> 0 Then
102cdf0e10cSrcweir        WriteToLog fso, CWORD_APP, "OpenWordDriverDoc: " & Err.Number & " " & Err.Description & " " & Err.Source
103cdf0e10cSrcweir    End If
104cdf0e10cSrcweir
105cdf0e10cSrcweir    wrdDriverDoc.Close wdDoNotSaveChanges
106cdf0e10cSrcweir    wrdApp.Quit False
107cdf0e10cSrcweir
108cdf0e10cSrcweirFinalExit:
109cdf0e10cSrcweir    Set wrdDriverDoc = Nothing
110cdf0e10cSrcweir    Set wrdApp = Nothing
111cdf0e10cSrcweir    Exit Sub
112cdf0e10cSrcweir
113cdf0e10cSrcweirHandleErrors:
114cdf0e10cSrcweir    WriteToLog fso, CWORD_APP, "OpenWordDriverDoc: " & Err.Number & " " & Err.Description & " " & Err.Source
115cdf0e10cSrcweir    Resume FinalExit
116cdf0e10cSrcweirEnd Sub
117cdf0e10cSrcweir
118cdf0e10cSrcweirSub OpenExcelDriverDoc(fso As FileSystemObject, driverName As String)
119cdf0e10cSrcweir
120cdf0e10cSrcweir    Dim excelApp As Excel.Application
121cdf0e10cSrcweir    Dim excelDriverDoc As Excel.Workbook
122cdf0e10cSrcweir
123cdf0e10cSrcweir    On Error GoTo HandleErrors
124cdf0e10cSrcweir
125cdf0e10cSrcweir    Set excelApp = New Excel.Application
126cdf0e10cSrcweir    Set excelDriverDoc = Excel.Workbooks.Open(driverName)
127cdf0e10cSrcweir    excelApp.Run ("AnalysisTool.AnalysisDriver.AnalyseDirectory")
128cdf0e10cSrcweir
129cdf0e10cSrcweir    If Err.Number <> 0 Then
130cdf0e10cSrcweir        WriteToLog fso, CEXCEL_APP, "OpenExcelDriverDoc: " & Err.Number & " " & Err.Description & " " & Err.Source
131cdf0e10cSrcweir    End If
132cdf0e10cSrcweir
133cdf0e10cSrcweir    excelDriverDoc.Close False
134cdf0e10cSrcweir    excelApp.Quit
135cdf0e10cSrcweir
136cdf0e10cSrcweirFinalExit:
137cdf0e10cSrcweir    Set excelDriverDoc = Nothing
138cdf0e10cSrcweir    Set excelApp = Nothing
139cdf0e10cSrcweir    Exit Sub
140cdf0e10cSrcweir
141cdf0e10cSrcweirHandleErrors:
142cdf0e10cSrcweir    WriteToLog fso, CEXCEL_APP, "OpenExcelDriverDoc: " & Err.Number & " " & Err.Description & " " & Err.Source
143cdf0e10cSrcweir    Resume FinalExit
144cdf0e10cSrcweirEnd Sub
145cdf0e10cSrcweir
146cdf0e10cSrcweirSub OpenPPDriverDoc(fso As FileSystemObject, driverName As String)
147cdf0e10cSrcweir
148cdf0e10cSrcweir    Dim ppApp As PowerPoint.Application
149cdf0e10cSrcweir    Dim ppDriverDoc As PowerPoint.Presentation
150cdf0e10cSrcweir    Dim ppDummy(0) As Variant
151cdf0e10cSrcweir
152cdf0e10cSrcweir    On Error GoTo HandleErrors
153cdf0e10cSrcweir
154cdf0e10cSrcweir    Set ppApp = New PowerPoint.Application
155cdf0e10cSrcweir    ppApp.Visible = msoTrue
156cdf0e10cSrcweir    Set ppDriverDoc = ppApp.Presentations.Open(driverName) ', msoTrue, msoFalse, msoFalse)
157cdf0e10cSrcweir    ppApp.Run ("AnalysisDriver.AnalyseDirectory")
158cdf0e10cSrcweir
159cdf0e10cSrcweir    If Err.Number <> 0 Then
160cdf0e10cSrcweir        WriteToLog fso, CPP_APP, "OpenPPDriverDoc: " & Err.Number & " " & Err.Description & " " & Err.Source
161cdf0e10cSrcweir    End If
162cdf0e10cSrcweir
163cdf0e10cSrcweir    ppDriverDoc.Close
164cdf0e10cSrcweir    ppApp.Quit
165cdf0e10cSrcweir
166cdf0e10cSrcweirFinalExit:
167cdf0e10cSrcweir    Set ppDriverDoc = Nothing
168cdf0e10cSrcweir    Set ppApp = Nothing
169cdf0e10cSrcweir    Exit Sub
170cdf0e10cSrcweir
171cdf0e10cSrcweirHandleErrors:
172cdf0e10cSrcweir    WriteToLog fso, CPP_APP, "OpenPPDriverDoc: " & Err.Number & " " & Err.Description & " " & Err.Source
173cdf0e10cSrcweir    Resume FinalExit
174cdf0e10cSrcweirEnd Sub
175cdf0e10cSrcweir
176cdf0e10cSrcweirSub WriteToLog(fso As FileSystemObject, currApp As String, errMsg As String)
177cdf0e10cSrcweir
178cdf0e10cSrcweir    On Error Resume Next
179cdf0e10cSrcweir
180cdf0e10cSrcweir    Static ErrCount As Long
181cdf0e10cSrcweir    Dim logFileName As String
182cdf0e10cSrcweir    Dim tempPath As String
183cdf0e10cSrcweir
184cdf0e10cSrcweir    tempPath = fso.GetSpecialFolder(TemporaryFolder).Path
185cdf0e10cSrcweir    If (tempPath = "") Then tempPath = "."
186cdf0e10cSrcweir    logFileName = fso.GetAbsolutePathName(tempPath & "\LauchDrivers.log")
187cdf0e10cSrcweir    ErrCount = ErrCount + 1
188cdf0e10cSrcweir
189cdf0e10cSrcweir    Call WritePrivateProfileString("ERRORS", currApp & "_log" & ErrCount, _
190cdf0e10cSrcweir                                   errMsg, logFileName)
191cdf0e10cSrcweirEnd Sub
192cdf0e10cSrcweir
193