xref: /AOO41X/main/migrationanalysis/src/driver_docs/sources/CommonMigrationAnalyser.bas (revision e76eebc6721f1fe5236ff9f8cb1c63804c1e07a9)
1cdf0e10cSrcweirAttribute VB_Name = "CommonMigrationAnalyser"
2*e76eebc6SAndrew Rist'*************************************************************************
3cdf0e10cSrcweir'
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
11cdf0e10cSrcweir'
12*e76eebc6SAndrew Rist'    http://www.apache.org/licenses/LICENSE-2.0
13cdf0e10cSrcweir'
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.
20cdf0e10cSrcweir'
21*e76eebc6SAndrew Rist'*************************************************************************
22cdf0e10cSrcweirOption Explicit
23cdf0e10cSrcweir
24cdf0e10cSrcweir
25cdf0e10cSrcweir'***********************************************
26cdf0e10cSrcweir'**** APPLICATION COMMON ANALYSIS FUNCTIONS ****
27cdf0e10cSrcweir'***********************************************
28cdf0e10cSrcweir
29cdf0e10cSrcweir'** Common - XML Issue and SubIssue strings
30cdf0e10cSrcweir'For preparation - need access to some Word/ Excel or PP consts
31cdf0e10cSrcweirPublic Const CSTR_ISSUE_OBJECTS_GRAPHICS_AND_FRAMES = "ObjectsGraphicsAndFrames"
32cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_OBJECT_IN_HEADER_FOOTER = "ObjectInHeaderFooter"
33cdf0e10cSrcweir
34cdf0e10cSrcweirPublic Const CSTR_ISSUE_INFORMATION = "Information"
35cdf0e10cSrcweirPublic Const CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES = "ContentAndDocumentProperties"
36cdf0e10cSrcweirPublic Const CSTR_ISSUE_FORMAT = "Format"
37cdf0e10cSrcweirPublic Const CSTR_ISSUE_PORTABILITY = "Portability"
38cdf0e10cSrcweirPublic Const CSTR_ISSUE_VBA_MACROS = "VBAMacros"
39cdf0e10cSrcweir
40cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_DOCUMENT_PARTS_PROTECTION = "DocumentPartsProtection"
41cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_EXTERNAL_REFERENCES_IN_MACRO = "ExternalReferencesInMacro"
42cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_EXTERNAL_REFERENCES_IN_MACRO_COUNT = "ExternalReferencesInMacroCount"
43cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_GRADIENT = "Gradient"
44cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_INVALID_PASSWORD_ENTERED = "InvalidPasswordEntered"
45cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_LINE = "Line"
46cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_MACRO_PASSWORD_PROTECTION = "PasswordProtected"
47cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_OLD_WORKBOOK_VERSION = "OldWorkbookVersion"
48cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_OLE_EMBEDDED = "EmbeddedOLEObject"
49cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_OLE_LINKED = "LinkedOLEObject"
50cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_OLE_CONTROL = "OLEControl"
51cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_OLE_FIELD_LINK = "OLEFieldLink"
52cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_OLE_UNKNOWN = "UnknownType"
53cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_PASSWORDS_PROTECTION = "PasswordProtection"
54cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_PROPERTIES = "Properties"
55cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_REFERENCES = "References"
56cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_TRANSPARENCY = "Transparency"
57cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_VBA_MACROS_NUMLINES = "NumberOfLines"
58cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_VBA_MACROS_USERFORMS_COUNT = "UserFormsCount"
59cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_VBA_MACROS_USERFORMS_CONTROL_COUNT = "UserFormsControlCount"
60cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_VBA_MACROS_USERFORMS_CONTROLTYPE_COUNT = "UserFormsControlTypeCount"
61cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_VBA_MACROS_UNIQUE_MODULE_COUNT = "UniqueModuleCount"
62cdf0e10cSrcweirPublic Const CSTR_SUBISSUE_VBA_MACROS_UNIQUE_LINE_COUNT = "UniqueLineCount"
63cdf0e10cSrcweir'** END Common - XML Issue and SubIssue strings
64cdf0e10cSrcweir
65cdf0e10cSrcweir'Macro classification bounds
66cdf0e10cSrcweirPublic Const CMACRO_LINECOUNT_MEDIUM_LBOUND = 50
67cdf0e10cSrcweir
68cdf0e10cSrcweir'Don't localize folder name
69cdf0e10cSrcweirPublic Const CSTR_COMMON_PREPARATION_FOLDER = "prepared"
70cdf0e10cSrcweir
71cdf0e10cSrcweir
72cdf0e10cSrcweirPublic Enum EnumDocOverallMacroClass
73cdf0e10cSrcweir    enMacroNone = 0
74cdf0e10cSrcweir    enMacroSimple = 1
75cdf0e10cSrcweir    enMacroMedium = 2
76cdf0e10cSrcweir    enMacroComplex = 3
77cdf0e10cSrcweirEnd Enum
78cdf0e10cSrcweirPublic Enum EnumDocOverallIssueClass
79cdf0e10cSrcweir    enNone = 0
80cdf0e10cSrcweir    enMinor = 1
81cdf0e10cSrcweir    enComplex = 2
82cdf0e10cSrcweirEnd Enum
83cdf0e10cSrcweir
84cdf0e10cSrcweirSub EmptyCollection(docAnalysis As DocumentAnalysis, coll As Collection)
85cdf0e10cSrcweir    On Error GoTo HandleErrors
86cdf0e10cSrcweir    Dim currentFunctionName As String
87cdf0e10cSrcweir    currentFunctionName = "EmptyCollection"
88cdf0e10cSrcweir    Dim Num As Long
89cdf0e10cSrcweir    For Num = 1 To coll.count    ' Remove name from the collection.
90cdf0e10cSrcweir        coll.Remove 1    ' Default collection numeric indexes
91cdf0e10cSrcweir    Next    ' begin at 1.
92cdf0e10cSrcweir    Exit Sub
93cdf0e10cSrcweir
94cdf0e10cSrcweirHandleErrors:
95cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
96cdf0e10cSrcweirEnd Sub
97cdf0e10cSrcweir
98cdf0e10cSrcweirPublic Function Analyze_Macros(docAnalysis As DocumentAnalysis, _
99cdf0e10cSrcweir                               userFormTypesDict As Scripting.Dictionary, _
100cdf0e10cSrcweir                               currDoc As Object)
101cdf0e10cSrcweir    On Error GoTo HandleErrors
102cdf0e10cSrcweir    Dim currentFunctionName As String
103cdf0e10cSrcweir    currentFunctionName = "Analyze_Macros"
104cdf0e10cSrcweir    Dim macroDetails As String
105cdf0e10cSrcweir    Dim cmpDetails As String
106cdf0e10cSrcweir    Dim myProject As VBProject
107cdf0e10cSrcweir    Dim myComponent As VBComponent
108cdf0e10cSrcweir    Dim numLines As Long
109cdf0e10cSrcweir    Dim myIssue As IssueInfo
110cdf0e10cSrcweir    Dim wrd As Object
111cdf0e10cSrcweir    Dim bUserFormWithEmptyCodeModule As Boolean
112cdf0e10cSrcweir
113cdf0e10cSrcweir    On Error Resume Next
114cdf0e10cSrcweir    Set myProject = getAppSpecificVBProject(currDoc)
115cdf0e10cSrcweir    If Err.Number <> 0 Then
116cdf0e10cSrcweir        ' Failed to get access to VBProject
117cdf0e10cSrcweir        WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & _
118cdf0e10cSrcweir            RID_STR_COMMON_ATTRIBUTE_UNABLE_TO_ACCESS_VBPROJECT & ":" & _
119cdf0e10cSrcweir            RID_STR_COMMON_ATTRIBUTE_FURTHER_MACRO_ANALYSIS_NOT_POSSIBLE
120cdf0e10cSrcweir
121cdf0e10cSrcweir        GoTo FinalExit
122cdf0e10cSrcweir    End If
123cdf0e10cSrcweir
124cdf0e10cSrcweir    On Error GoTo HandleErrors
125cdf0e10cSrcweir    If myProject.Protection = vbext_pp_locked Then
126cdf0e10cSrcweir        Set myIssue = New IssueInfo
127cdf0e10cSrcweir        With myIssue
128cdf0e10cSrcweir            .IssueID = CID_VBA_MACROS
129cdf0e10cSrcweir            .IssueType = RID_STR_COMMON_ISSUE_VBA_MACROS
130cdf0e10cSrcweir            .SubType = RID_STR_COMMON_SUBISSUE_MACRO_PASSWORD_PROTECTION
131cdf0e10cSrcweir            .Location = .CLocationDocument
132cdf0e10cSrcweir
133cdf0e10cSrcweir            .IssueTypeXML = CSTR_ISSUE_VBA_MACROS
134cdf0e10cSrcweir            .SubTypeXML = CSTR_SUBISSUE_MACRO_PASSWORD_PROTECTION
135cdf0e10cSrcweir            .locationXML = .CXMLLocationDocument
136cdf0e10cSrcweir
137cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_VBPROJECT_PASSWORD
138cdf0e10cSrcweir            .Values.Add RID_STR_COMMON_ATTRIBUTE_FURTHER_MACRO_ANALYSIS_NOT_POSSIBLE
139cdf0e10cSrcweir        End With
140cdf0e10cSrcweir        docAnalysis.IssuesCountArray(CID_VBA_MACROS) = _
141cdf0e10cSrcweir            docAnalysis.IssuesCountArray(CID_VBA_MACROS) + 1
142cdf0e10cSrcweir        docAnalysis.Issues.Add myIssue
143cdf0e10cSrcweir        docAnalysis.MacroIssuesCount = docAnalysis.MacroIssuesCount + 1
144cdf0e10cSrcweir
145cdf0e10cSrcweir        docAnalysis.HasMacros = True
146cdf0e10cSrcweir        GoTo FinalExit
147cdf0e10cSrcweir    End If
148cdf0e10cSrcweir
149cdf0e10cSrcweir    Dim myContolDict As Scripting.Dictionary
150cdf0e10cSrcweir    For Each myComponent In myProject.VBComponents
151cdf0e10cSrcweir
152cdf0e10cSrcweir        bUserFormWithEmptyCodeModule = False
153cdf0e10cSrcweir        If CheckEmptyProject(docAnalysis, myProject, myComponent) Then
154cdf0e10cSrcweir            If myComponent.Type <> vbext_ct_MSForm Then
155cdf0e10cSrcweir                GoTo FOREACH_CONTINUE
156cdf0e10cSrcweir            Else
157cdf0e10cSrcweir                bUserFormWithEmptyCodeModule = True
158cdf0e10cSrcweir            End If
159cdf0e10cSrcweir        End If
160cdf0e10cSrcweir
161cdf0e10cSrcweir        Analyze_MacrosForPortabilityIssues docAnalysis, myProject, myComponent
162cdf0e10cSrcweir
163cdf0e10cSrcweir        Set myIssue = New IssueInfo
164cdf0e10cSrcweir        With myIssue
165cdf0e10cSrcweir            .IssueID = CID_VBA_MACROS
166cdf0e10cSrcweir            .IssueType = RID_STR_COMMON_ISSUE_VBA_MACROS
167cdf0e10cSrcweir            .SubType = RID_STR_COMMON_SUBISSUE_PROPERTIES
168cdf0e10cSrcweir            .Location = .CLocationDocument
169cdf0e10cSrcweir
170cdf0e10cSrcweir            .IssueTypeXML = CSTR_ISSUE_VBA_MACROS
171cdf0e10cSrcweir            .SubTypeXML = CSTR_SUBISSUE_PROPERTIES
172cdf0e10cSrcweir            .locationXML = .CXMLLocationDocument
173cdf0e10cSrcweir
174cdf0e10cSrcweir            .SubLocation = VBComponentType(myComponent)
175cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_PROJECT
176cdf0e10cSrcweir            .Values.Add myProject.name
177cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_COMPONENT
178cdf0e10cSrcweir            .Values.Add myComponent.name
179cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_PROCEDURES
180cdf0e10cSrcweir            .Values.Add VBNumFuncs(docAnalysis, myComponent.CodeModule), RID_STR_COMMON_ATTRIBUTE_PROCEDURES
181cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NUMBER_OF_LINES
182cdf0e10cSrcweir            numLines = VBNumLines(docAnalysis, myComponent.CodeModule)
183cdf0e10cSrcweir            .Values.Add numLines, RID_STR_COMMON_ATTRIBUTE_NUMBER_OF_LINES
184cdf0e10cSrcweir
185cdf0e10cSrcweir            If bUserFormWithEmptyCodeModule Then
186cdf0e10cSrcweir                .Attributes.Add RID_STR_COMMON_ATTRIBUTE_SIGNATURE
187cdf0e10cSrcweir                .Values.Add RID_STR_COMMON_NA, RID_STR_COMMON_ATTRIBUTE_SIGNATURE
188cdf0e10cSrcweir            Else
189cdf0e10cSrcweir                .Attributes.Add RID_STR_COMMON_ATTRIBUTE_SIGNATURE
190cdf0e10cSrcweir                .Values.Add MD5HashString( _
191cdf0e10cSrcweir                    myComponent.CodeModule.Lines(1, myComponent.CodeModule.CountOfLines)), _
192cdf0e10cSrcweir                    RID_STR_COMMON_ATTRIBUTE_SIGNATURE
193cdf0e10cSrcweir            End If
194cdf0e10cSrcweir
195cdf0e10cSrcweir            docAnalysis.MacroTotalNumLines = numLines + docAnalysis.MacroTotalNumLines
196cdf0e10cSrcweir        End With
197cdf0e10cSrcweir
198cdf0e10cSrcweir        ' User Forms - control details
199cdf0e10cSrcweir        If (myComponent.Type = vbext_ct_MSForm) And Not bUserFormWithEmptyCodeModule Then
200cdf0e10cSrcweir            myIssue.Attributes.Add RID_STR_COMMON_ATTRIBUTE_CONTROLS
201cdf0e10cSrcweir            myIssue.Values.Add myComponent.Designer.Controls.count, RID_STR_COMMON_ATTRIBUTE_CONTROLS
202cdf0e10cSrcweir            docAnalysis.MacroNumUserForms = 1 + docAnalysis.MacroNumUserForms
203cdf0e10cSrcweir            docAnalysis.MacroNumUserFormControls = myComponent.Designer.Controls.count + docAnalysis.MacroNumUserFormControls
204cdf0e10cSrcweir
205cdf0e10cSrcweir            Dim myControl As Control
206cdf0e10cSrcweir            Dim controlTypes As String
207cdf0e10cSrcweir            Dim myType As String
208cdf0e10cSrcweir
209cdf0e10cSrcweir            Set myContolDict = New Scripting.Dictionary
210cdf0e10cSrcweir
211cdf0e10cSrcweir            For Each myControl In myComponent.Designer.Controls
212cdf0e10cSrcweir                myType = TypeName(myControl)
213cdf0e10cSrcweir                If myContolDict.Exists(myType) Then
214cdf0e10cSrcweir                   myContolDict.item(myType) = myContolDict.item(myType) + 1
215cdf0e10cSrcweir                Else
216cdf0e10cSrcweir                   myContolDict.Add myType, 1
217cdf0e10cSrcweir                End If
218cdf0e10cSrcweir                If userFormTypesDict.Exists(myType) Then
219cdf0e10cSrcweir                   userFormTypesDict.item(myType) = userFormTypesDict.item(myType) + 1
220cdf0e10cSrcweir                Else
221cdf0e10cSrcweir                   userFormTypesDict.Add myType, 1
222cdf0e10cSrcweir                End If
223cdf0e10cSrcweir            Next
224cdf0e10cSrcweir
225cdf0e10cSrcweir            If myComponent.Designer.Controls.count > 0 Then
226cdf0e10cSrcweir                Dim count As Long
227cdf0e10cSrcweir                Dim vKeyArray As Variant
228cdf0e10cSrcweir                Dim vItemArray As Variant
229cdf0e10cSrcweir
230cdf0e10cSrcweir                vKeyArray = myContolDict.Keys
231cdf0e10cSrcweir                vItemArray = myContolDict.Items
232cdf0e10cSrcweir
233cdf0e10cSrcweir                controlTypes = ""
234cdf0e10cSrcweir                For count = 0 To myContolDict.count - 1
235cdf0e10cSrcweir                    controlTypes = controlTypes & vKeyArray(count) & " " & CInt(vItemArray(count)) & " "
236cdf0e10cSrcweir                Next count
237cdf0e10cSrcweir                myIssue.Attributes.Add RID_STR_COMMON_ATTRIBUTE_USERFORM_TYPE
238cdf0e10cSrcweir                myIssue.Values.Add controlTypes, RID_STR_COMMON_ATTRIBUTE_USERFORM_TYPE
239cdf0e10cSrcweir
240cdf0e10cSrcweir                myIssue.Attributes.Add RID_STR_COMMON_ATTRIBUTE_USERFORM_TYPES_COUNT
241cdf0e10cSrcweir                myIssue.Values.Add myContolDict.count, RID_STR_COMMON_ATTRIBUTE_USERFORM_TYPES_COUNT
242cdf0e10cSrcweir
243cdf0e10cSrcweir                docAnalysis.MacroNumUserFormControlTypes = myContolDict.count + docAnalysis.MacroNumUserFormControlTypes
244cdf0e10cSrcweir            End If
245cdf0e10cSrcweir            Set myContolDict = Nothing
246cdf0e10cSrcweir        End If
247cdf0e10cSrcweir
248cdf0e10cSrcweir        'Check for occurence of " Me " in Form and Class Modules
249cdf0e10cSrcweir        If myComponent.Type = vbext_ct_MSForm Or _
250cdf0e10cSrcweir            myComponent.Type = vbext_ct_ClassModule Then
251cdf0e10cSrcweir
252cdf0e10cSrcweir            Dim strFind As String
253cdf0e10cSrcweir            strFind = ""
254cdf0e10cSrcweir            count = 0
255cdf0e10cSrcweir            strFind = VBFindLines(docAnalysis, myComponent.CodeModule, "Me", count, bWholeWord:=True)
256cdf0e10cSrcweir'            If (strFind <> "") Then MsgBox strFind
257cdf0e10cSrcweir
258cdf0e10cSrcweir            If count > 0 Then
259cdf0e10cSrcweir                myIssue.Attributes.Add RID_STR_COMMON_ATTRIBUTE_CLASS_ME_COUNT
260cdf0e10cSrcweir                myIssue.Values.Add count, RID_STR_COMMON_ATTRIBUTE_CLASS_ME_COUNT
261cdf0e10cSrcweir            End If
262cdf0e10cSrcweir        End If
263cdf0e10cSrcweir
264cdf0e10cSrcweir        docAnalysis.IssuesCountArray(CID_VBA_MACROS) = _
265cdf0e10cSrcweir            docAnalysis.IssuesCountArray(CID_VBA_MACROS) + 1
266cdf0e10cSrcweir        docAnalysis.Issues.Add myIssue
267cdf0e10cSrcweir        docAnalysis.MacroIssuesCount = docAnalysis.MacroIssuesCount + 1
268cdf0e10cSrcweir
269cdf0e10cSrcweir        Set myIssue = Nothing
270cdf0e10cSrcweir
271cdf0e10cSrcweirFOREACH_CONTINUE:
272cdf0e10cSrcweir        'No equiv to C continue in VB
273cdf0e10cSrcweir    Next myComponent 'End - For Each myComponent
274cdf0e10cSrcweir
275cdf0e10cSrcweir    If docAnalysis.IssuesCountArray(CID_VBA_MACROS) > 0 Then
276cdf0e10cSrcweir        Analyze_VBEReferences docAnalysis, currDoc
277cdf0e10cSrcweir        docAnalysis.HasMacros = True
278cdf0e10cSrcweir    End If
279cdf0e10cSrcweir
280cdf0e10cSrcweirFinalExit:
281cdf0e10cSrcweir    docAnalysis.MacroOverallClass = ClassifyDocOverallMacroClass(docAnalysis)
282cdf0e10cSrcweir
283cdf0e10cSrcweir    Set myProject = Nothing
284cdf0e10cSrcweir    Set myIssue = Nothing
285cdf0e10cSrcweir    Set myContolDict = Nothing
286cdf0e10cSrcweir    Exit Function
287cdf0e10cSrcweir
288cdf0e10cSrcweirHandleErrors:
289cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
290cdf0e10cSrcweir    Resume FinalExit
291cdf0e10cSrcweirEnd Function
292cdf0e10cSrcweir
293cdf0e10cSrcweirFunction CheckOnlyEmptyProject(docAnalysis As DocumentAnalysis, currDoc As Object) As Boolean
294cdf0e10cSrcweir    On Error GoTo HandleErrors
295cdf0e10cSrcweir    Dim currentFunctionName As String
296cdf0e10cSrcweir    currentFunctionName = "CheckOnlyEmptyProject"
297cdf0e10cSrcweir    Dim myProject As VBProject
298cdf0e10cSrcweir    Set myProject = getAppSpecificVBProject(currDoc)
299cdf0e10cSrcweir    Dim myVBComponent As VBComponent
300cdf0e10cSrcweir
301cdf0e10cSrcweir    For Each myVBComponent In myProject.VBComponents
302cdf0e10cSrcweir        If Not CheckEmptyProject(docAnalysis, myProject, myVBComponent) Then
303cdf0e10cSrcweir            CheckOnlyEmptyProject = False
304cdf0e10cSrcweir            GoTo FinalExit
305cdf0e10cSrcweir        End If
306cdf0e10cSrcweir    Next myVBComponent
307cdf0e10cSrcweir
308cdf0e10cSrcweir    CheckOnlyEmptyProject = True
309cdf0e10cSrcweir
310cdf0e10cSrcweirFinalExit:
311cdf0e10cSrcweir    Set myProject = Nothing
312cdf0e10cSrcweir    Exit Function
313cdf0e10cSrcweir
314cdf0e10cSrcweirHandleErrors:
315cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
316cdf0e10cSrcweir    Resume FinalExit
317cdf0e10cSrcweirEnd Function
318cdf0e10cSrcweir
319cdf0e10cSrcweirSub Analyze_VBEReferences(docAnalysis As DocumentAnalysis, currDoc As Object)
320cdf0e10cSrcweir    On Error GoTo HandleErrors
321cdf0e10cSrcweir    Dim currentFunctionName As String
322cdf0e10cSrcweir    currentFunctionName = "Analyze_VBEReferences"
323cdf0e10cSrcweir    'References
324cdf0e10cSrcweir    Dim Ref As Reference
325cdf0e10cSrcweir    Dim fso As Scripting.FileSystemObject
326cdf0e10cSrcweir    Dim myVBProject As VBProject
327cdf0e10cSrcweir    Dim myVBComponent As VBComponent
328cdf0e10cSrcweir
329cdf0e10cSrcweir    Set fso = New Scripting.FileSystemObject
330cdf0e10cSrcweir
331cdf0e10cSrcweir    If CheckOnlyEmptyProject(docAnalysis, currDoc) Then
332cdf0e10cSrcweir        Exit Sub
333cdf0e10cSrcweir    End If
334cdf0e10cSrcweir    Set myVBProject = getAppSpecificVBProject(currDoc)
335cdf0e10cSrcweir
336cdf0e10cSrcweir    For Each Ref In myVBProject.References
337cdf0e10cSrcweir        Analyze_VBEReferenceSingle docAnalysis, Ref, fso
338cdf0e10cSrcweir    Next Ref
339cdf0e10cSrcweir
340cdf0e10cSrcweirFinalExit:
341cdf0e10cSrcweir    Set myVBProject = Nothing
342cdf0e10cSrcweir    Set fso = Nothing
343cdf0e10cSrcweir    Exit Sub
344cdf0e10cSrcweir
345cdf0e10cSrcweirHandleErrors:
346cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
347cdf0e10cSrcweir    Resume FinalExit
348cdf0e10cSrcweirEnd Sub
349cdf0e10cSrcweir
350cdf0e10cSrcweirSub Analyze_VBEReferenceSingle(docAnalysis As DocumentAnalysis, Ref As Reference, fso As Scripting.FileSystemObject)
351cdf0e10cSrcweir    On Error GoTo HandleErrors
352cdf0e10cSrcweir    Dim currentFunctionName As String
353cdf0e10cSrcweir    currentFunctionName = "Analyze_VBEReferenceSingle"
354cdf0e10cSrcweir    'References
355cdf0e10cSrcweir    Dim myIssue As IssueInfo
356cdf0e10cSrcweir    Dim bBadRef As Boolean
357cdf0e10cSrcweir
358cdf0e10cSrcweir    Set myIssue = New IssueInfo
359cdf0e10cSrcweir    With myIssue
360cdf0e10cSrcweir        .IssueID = CID_INFORMATION_REFS
361cdf0e10cSrcweir        .IssueType = RID_STR_COMMON_ISSUE_INFORMATION
362cdf0e10cSrcweir        .SubType = RID_STR_COMMON_SUBISSUE_REFERENCES
363cdf0e10cSrcweir        .Location = .CLocationDocument
364cdf0e10cSrcweir
365cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_INFORMATION
366cdf0e10cSrcweir        .SubTypeXML = CSTR_SUBISSUE_REFERENCES
367cdf0e10cSrcweir        .locationXML = .CXMLLocationDocument
368cdf0e10cSrcweir
369cdf0e10cSrcweir        If Ref.GUID = "" Then
370cdf0e10cSrcweir            bBadRef = True
371cdf0e10cSrcweir        Else
372cdf0e10cSrcweir            bBadRef = False
373cdf0e10cSrcweir        End If
374cdf0e10cSrcweir        If Not bBadRef Then
375cdf0e10cSrcweir            .SubLocation = LCase(fso.GetFileName(Ref.FullPath))
376cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
377cdf0e10cSrcweir            .Values.Add Ref.name, RID_STR_COMMON_ATTRIBUTE_NAME
378cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_DESCRIPTION
379cdf0e10cSrcweir            .Values.Add Ref.Description, RID_STR_COMMON_ATTRIBUTE_DESCRIPTION
380cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_FILE
381cdf0e10cSrcweir            .Values.Add LCase(fso.GetFileName(Ref.FullPath)), RID_STR_COMMON_ATTRIBUTE_FILE
382cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_PATH
383cdf0e10cSrcweir            .Values.Add LCase(Ref.FullPath), RID_STR_COMMON_ATTRIBUTE_PATH
384cdf0e10cSrcweir        Else
385cdf0e10cSrcweir            .SubLocation = RID_STR_COMMON_NA
386cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
387cdf0e10cSrcweir            .Values.Add RID_STR_COMMON_ATTRIBUTE_MISSING, RID_STR_COMMON_ATTRIBUTE_NAME
388cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_DESCRIPTION
389cdf0e10cSrcweir            .Values.Add RID_STR_COMMON_ATTRIBUTE_CHECK_DOCUMENT_REFERENCES, RID_STR_COMMON_ATTRIBUTE_DESCRIPTION
390cdf0e10cSrcweir        End If
391cdf0e10cSrcweir
392cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_MAJOR
393cdf0e10cSrcweir        .Values.Add IIf(Not bBadRef, Ref.Major, ""), RID_STR_COMMON_ATTRIBUTE_MAJOR
394cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_MINOR
395cdf0e10cSrcweir        .Values.Add IIf(Not bBadRef, Ref.Minor, ""), RID_STR_COMMON_ATTRIBUTE_MINOR
396cdf0e10cSrcweir
397cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_TYPE
398cdf0e10cSrcweir        .Values.Add IIf(Ref.Type = vbext_rk_Project, RID_STR_COMMON_ATTRIBUTE_PROJECT, RID_STR_COMMON_ATTRIBUTE_TYPELIB), RID_STR_COMMON_ATTRIBUTE_TYPE
399cdf0e10cSrcweir
400cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_BUILTIN
401cdf0e10cSrcweir        .Values.Add IIf(Ref.BuiltIn, RID_STR_COMMON_ATTRIBUTE_BUILTIN, RID_STR_COMMON_ATTRIBUTE_CUSTOM), RID_STR_COMMON_ATTRIBUTE_BUILTIN
402cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_ISBROKEN
403cdf0e10cSrcweir        .Values.Add IIf(bBadRef, RID_STR_COMMON_ATTRIBUTE_BROKEN, RID_STR_COMMON_ATTRIBUTE_INTACT), RID_STR_COMMON_ATTRIBUTE_ISBROKEN
404cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_GUID
405cdf0e10cSrcweir        .Values.Add IIf(Ref.Type = vbext_rk_TypeLib, Ref.GUID, ""), RID_STR_COMMON_ATTRIBUTE_GUID
406cdf0e10cSrcweir    End With
407cdf0e10cSrcweir
408cdf0e10cSrcweir    docAnalysis.References.Add myIssue
409cdf0e10cSrcweir
410cdf0e10cSrcweirFinalExit:
411cdf0e10cSrcweir    Set myIssue = Nothing
412cdf0e10cSrcweir    Exit Sub
413cdf0e10cSrcweir
414cdf0e10cSrcweirHandleErrors:
415cdf0e10cSrcweir    WriteDebugLevelTwo currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
416cdf0e10cSrcweir    Resume FinalExit
417cdf0e10cSrcweirEnd Sub
418cdf0e10cSrcweir
419cdf0e10cSrcweirSub Analyze_MacrosForPortabilityIssues(docAnalysis As DocumentAnalysis, myProject As VBProject, myComponent As VBComponent)
420cdf0e10cSrcweir    On Error GoTo HandleErrors
421cdf0e10cSrcweir    Dim currentFunctionName As String
422cdf0e10cSrcweir    currentFunctionName = "Analyze_MacrosForPortabilityIssues"
423cdf0e10cSrcweir    Dim myIssue As IssueInfo
424cdf0e10cSrcweir    Dim count As Long
425cdf0e10cSrcweir
426cdf0e10cSrcweir    ' Code Modules
427cdf0e10cSrcweir    Dim strFind As String
428cdf0e10cSrcweir    strFind = VBFindLines(docAnalysis, myComponent.CodeModule, "CreateObject", count, bWholeWord:=True) & _
429cdf0e10cSrcweir        VBFindLines(docAnalysis, myComponent.CodeModule, "GetObject", count, bWholeWord:=True) & _
430cdf0e10cSrcweir        VBFindLines(docAnalysis, myComponent.CodeModule, "ADODB.", count, True, True) & _
431cdf0e10cSrcweir        VBFindLines(docAnalysis, myComponent.CodeModule, "Word.", count, True, True) & _
432cdf0e10cSrcweir        VBFindLines(docAnalysis, myComponent.CodeModule, "Excel.", count, True, True) & _
433cdf0e10cSrcweir        VBFindLines(docAnalysis, myComponent.CodeModule, "PowerPoint.", count, True, True) & _
434cdf0e10cSrcweir        VBFindLines(docAnalysis, myComponent.CodeModule, "Access.", count, True, True) & _
435cdf0e10cSrcweir        VBFindLines(docAnalysis, myComponent.CodeModule, "Declare Function ", count, False) & _
436cdf0e10cSrcweir        VBFindLines(docAnalysis, myComponent.CodeModule, "Declare Sub ", count, False)
437cdf0e10cSrcweir
438cdf0e10cSrcweir
439cdf0e10cSrcweir    If (strFind <> "") And (myComponent.Type <> vbext_ct_Document) Then
440cdf0e10cSrcweir        Set myIssue = New IssueInfo
441cdf0e10cSrcweir        With myIssue
442cdf0e10cSrcweir            .IssueID = CID_PORTABILITY
443cdf0e10cSrcweir            .IssueType = RID_STR_COMMON_ISSUE_PORTABILITY
444cdf0e10cSrcweir            .SubType = RID_STR_COMMON_SUBISSUE_EXTERNAL_REFERENCES_IN_MACROS
445cdf0e10cSrcweir            .Location = .CLocationDocument
446cdf0e10cSrcweir
447cdf0e10cSrcweir            .IssueTypeXML = CSTR_ISSUE_PORTABILITY
448cdf0e10cSrcweir            .SubTypeXML = CSTR_SUBISSUE_EXTERNAL_REFERENCES_IN_MACRO
449cdf0e10cSrcweir            .locationXML = .CXMLLocationDocument
450cdf0e10cSrcweir
451cdf0e10cSrcweir            .SubLocation = VBComponentType(myComponent)
452cdf0e10cSrcweir
453cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_PROJECT
454cdf0e10cSrcweir            .Values.Add myProject.name
455cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_COMPONENT
456cdf0e10cSrcweir            .Values.Add myComponent.name
457cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NON_PORTABLE_EXTERNAL_REFERENCES
458cdf0e10cSrcweir            .Values.Add RID_STR_COMMON_ATTRIBUTE_INCLUDING & vbLf & Left(strFind, Len(strFind) - 1)
459cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NON_PORTABLE_EXTERNAL_REFERENCES_COUNT
460cdf0e10cSrcweir            .Values.Add count, RID_STR_COMMON_ATTRIBUTE_NON_PORTABLE_EXTERNAL_REFERENCES_COUNT
461cdf0e10cSrcweir        End With
462cdf0e10cSrcweir        docAnalysis.IssuesCountArray(CID_PORTABILITY) = _
463cdf0e10cSrcweir            docAnalysis.IssuesCountArray(CID_PORTABILITY) + 1
464cdf0e10cSrcweir        docAnalysis.Issues.Add myIssue
465cdf0e10cSrcweir        docAnalysis.MacroNumExternalRefs = count + docAnalysis.MacroNumExternalRefs
466cdf0e10cSrcweir        docAnalysis.MacroIssuesCount = docAnalysis.MacroIssuesCount + 1
467cdf0e10cSrcweir    End If
468cdf0e10cSrcweir
469cdf0e10cSrcweirFinalExit:
470cdf0e10cSrcweir    Set myIssue = Nothing
471cdf0e10cSrcweir    Exit Sub
472cdf0e10cSrcweir
473cdf0e10cSrcweir
474cdf0e10cSrcweirHandleErrors:
475cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
476cdf0e10cSrcweirResume FinalExit
477cdf0e10cSrcweirEnd Sub
478cdf0e10cSrcweir
479cdf0e10cSrcweir'Find Lines in  code module containing strFind and return list of them
480cdf0e10cSrcweirFunction VBFindLines(docAnalysis As DocumentAnalysis, vbcm As CodeModule, strFind As String, _
481cdf0e10cSrcweir    count As Long, _
482cdf0e10cSrcweir    Optional bInProcedure As Boolean = True, _
483cdf0e10cSrcweir    Optional bUsingNew As Boolean = False, _
484cdf0e10cSrcweir    Optional bWholeWord As Boolean = False, _
485cdf0e10cSrcweir    Optional bMatchCase As Boolean = False) As String
486cdf0e10cSrcweir    On Error GoTo HandleErrors
487cdf0e10cSrcweir    Dim currentFunctionName As String
488cdf0e10cSrcweir    currentFunctionName = "VBFindLines"
489cdf0e10cSrcweir    Dim lngStartLine As Long
490cdf0e10cSrcweir    Dim lngStartCol As Long
491cdf0e10cSrcweir    Dim lngEndLine As Long
492cdf0e10cSrcweir    Dim lngEndCol As Long
493cdf0e10cSrcweir    Dim strLine As String
494cdf0e10cSrcweir    lngStartLine = 1
495cdf0e10cSrcweir    lngStartCol = 1
496cdf0e10cSrcweir    lngEndLine = vbcm.CountOfLines
497cdf0e10cSrcweir    Dim tmpString As String
498cdf0e10cSrcweir    If (vbcm.CountOfLines = 0) Then
499cdf0e10cSrcweir        Exit Function
500cdf0e10cSrcweir    End If
501cdf0e10cSrcweir    tmpString = vbcm.Lines(vbcm.CountOfLines, 1)
502cdf0e10cSrcweir    lngEndCol = Len(vbcm.Lines(vbcm.CountOfLines, 1))
503cdf0e10cSrcweir    Dim lngType As Long
504cdf0e10cSrcweir    Dim strProc As String
505cdf0e10cSrcweir    Dim retStr As String
506cdf0e10cSrcweir
507cdf0e10cSrcweir    ' Search
508cdf0e10cSrcweir    Do While vbcm.Find(strFind, lngStartLine, _
509cdf0e10cSrcweir        lngStartCol, lngEndLine, lngEndCol, bWholeWord, bMatchCase)
510cdf0e10cSrcweir
511cdf0e10cSrcweir        'Ignore any lines using this func
512cdf0e10cSrcweir        If InStr(1, vbcm.Lines(lngStartLine, 1), "VBFindLines") <> 0 Then
513cdf0e10cSrcweir            GoTo CONTINUE_LOOP
514cdf0e10cSrcweir        End If
515cdf0e10cSrcweir
516cdf0e10cSrcweir        If bInProcedure Then
517cdf0e10cSrcweir            If bUsingNew Then
518cdf0e10cSrcweir                If InStr(1, vbcm.Lines(lngStartLine, 1), "New") <> 0 Then
519cdf0e10cSrcweir                    strProc = vbcm.ProcOfLine(lngStartLine, lngType)
520cdf0e10cSrcweir                Else
521cdf0e10cSrcweir                    strProc = ""
522cdf0e10cSrcweir                End If
523cdf0e10cSrcweir            Else
524cdf0e10cSrcweir                strProc = vbcm.ProcOfLine(lngStartLine, lngType)
525cdf0e10cSrcweir            End If
526cdf0e10cSrcweir            If strProc = "" Then GoTo CONTINUE_LOOP
527cdf0e10cSrcweir
528cdf0e10cSrcweir            VBFindLines = VBFindLines & "[" & strProc & " ( ) - " & lngStartLine & " ]" & _
529cdf0e10cSrcweir                vbLf & vbcm.Lines(lngStartLine, 1) & vbLf
530cdf0e10cSrcweir        Else
531cdf0e10cSrcweir            strProc = vbcm.Lines(lngStartLine, 1)
532cdf0e10cSrcweir            If strProc = "" Then GoTo CONTINUE_LOOP
533cdf0e10cSrcweir
534cdf0e10cSrcweir            'Can be External refs, Const, Type or variable declarations
535cdf0e10cSrcweir            If InStr(1, vbcm.Lines(lngStartLine, 1), "Declare Function") <> 0 Then
536cdf0e10cSrcweir            VBFindLines = VBFindLines & "[" & RID_STR_COMMON_DEC_TO_EXTERNAL_LIBRARY & " - " & lngStartLine & " ]" & _
537cdf0e10cSrcweir                vbLf & strProc & vbLf
538cdf0e10cSrcweir            Else
539cdf0e10cSrcweir                VBFindLines = VBFindLines & "[" & RID_STR_COMMON_VB_COMPONENT_MODULE & " " & strFind & _
540cdf0e10cSrcweir                    " - " & lngStartLine & " ]" & vbLf
541cdf0e10cSrcweir            End If
542cdf0e10cSrcweir        End If
543cdf0e10cSrcweir        count = count + 1
544cdf0e10cSrcweir
545cdf0e10cSrcweirCONTINUE_LOOP:
546cdf0e10cSrcweir        'Reset Params to search for next hit
547cdf0e10cSrcweir        lngStartLine = lngEndLine + 1
548cdf0e10cSrcweir        lngStartCol = 1
549cdf0e10cSrcweir        lngEndLine = vbcm.CountOfLines
550cdf0e10cSrcweir        lngEndCol = Len(vbcm.Lines(vbcm.CountOfLines, 1))
551cdf0e10cSrcweir
552cdf0e10cSrcweir        If lngStartLine >= lngEndLine Then Exit Function
553cdf0e10cSrcweir
554cdf0e10cSrcweir    Loop 'End - Do While vbcm.Find
555cdf0e10cSrcweir    VBFindLines = VBFindLines
556cdf0e10cSrcweir    Exit Function
557cdf0e10cSrcweir
558cdf0e10cSrcweirHandleErrors:
559cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
560cdf0e10cSrcweirEnd Function
561cdf0e10cSrcweirFunction VBNumLines(docAnalysis As DocumentAnalysis, vbcm As CodeModule) As Long
562cdf0e10cSrcweir    On Error GoTo HandleErrors
563cdf0e10cSrcweir    Dim currentFunctionName As String
564cdf0e10cSrcweir    currentFunctionName = "VBNumLines"
565cdf0e10cSrcweir    Dim cLines As Long
566cdf0e10cSrcweir    Dim lngType As Long
567cdf0e10cSrcweir    Dim strProc As String
568cdf0e10cSrcweir
569cdf0e10cSrcweir    'Issue: Just give line count in module to be in sync with Macro Analysis and Migration Wizard
570cdf0e10cSrcweir    VBNumLines = vbcm.CountOfLines
571cdf0e10cSrcweir
572cdf0e10cSrcweir    'For cLines = 1 To vbcm.CountOfLines
573cdf0e10cSrcweir    '    strProc = vbcm.ProcOfLine(cLines, lngType)
574cdf0e10cSrcweir    '    If strProc <> "" Then
575cdf0e10cSrcweir    '        VBNumLines = VBNumLines - _
576cdf0e10cSrcweir    '            (vbcm.ProcBodyLine(strProc, lngType) - vbcm.ProcStartLine(strProc, lngType))
577cdf0e10cSrcweir    '        cLines = cLines + vbcm.ProcCountLines(strProc, lngType) - 1
578cdf0e10cSrcweir    '    End If
579cdf0e10cSrcweir    'Next
580cdf0e10cSrcweir    Exit Function
581cdf0e10cSrcweir
582cdf0e10cSrcweirHandleErrors:
583cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
584cdf0e10cSrcweirEnd Function
585cdf0e10cSrcweirFunction VBNumFuncs(docAnalysis As DocumentAnalysis, vbcm As CodeModule) As Long
586cdf0e10cSrcweir    On Error GoTo HandleErrors
587cdf0e10cSrcweir    Dim currentFunctionName As String
588cdf0e10cSrcweir    currentFunctionName = "VBNumFuncs"
589cdf0e10cSrcweir    Dim cLines As Long
590cdf0e10cSrcweir    Dim lngType As Long
591cdf0e10cSrcweir    Dim strProc As String
592cdf0e10cSrcweir
593cdf0e10cSrcweir    For cLines = 1 To vbcm.CountOfLines
594cdf0e10cSrcweir        strProc = vbcm.ProcOfLine(cLines, lngType)
595cdf0e10cSrcweir        If strProc <> "" Then
596cdf0e10cSrcweir            VBNumFuncs = VBNumFuncs + 1
597cdf0e10cSrcweir            cLines = cLines + vbcm.ProcCountLines(strProc, lngType) - 1
598cdf0e10cSrcweir        End If
599cdf0e10cSrcweir    Next
600cdf0e10cSrcweir    Exit Function
601cdf0e10cSrcweirHandleErrors:
602cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
603cdf0e10cSrcweirEnd Function
604cdf0e10cSrcweir
605cdf0e10cSrcweirFunction VBComponentType(vbc As VBComponent) As String
606cdf0e10cSrcweir    Select Case vbc.Type
607cdf0e10cSrcweir        Case vbext_ct_StdModule
608cdf0e10cSrcweir            VBComponentType = RID_STR_COMMON_VB_COMPONENT_STANDARD
609cdf0e10cSrcweir        Case vbext_ct_ClassModule
610cdf0e10cSrcweir            VBComponentType = RID_STR_COMMON_VB_COMPONENT_CLASS
611cdf0e10cSrcweir        Case vbext_ct_MSForm
612cdf0e10cSrcweir            VBComponentType = RID_STR_COMMON_VB_COMPONENT_USER_FORM
613cdf0e10cSrcweir        Case vbext_ct_Document
614cdf0e10cSrcweir            VBComponentType = RID_STR_COMMON_VB_COMPONENT_DOCUMENT
615cdf0e10cSrcweir        Case 11 'vbext_ct_ActiveX Designer
616cdf0e10cSrcweir            VBComponentType = RID_STR_COMMON_VB_COMPONENT_ACTIVEX_DESIGNER
617cdf0e10cSrcweir        Case Else
618cdf0e10cSrcweir            VBComponentType = RID_STR_COMMON_UNKNOWN
619cdf0e10cSrcweir    End Select
620cdf0e10cSrcweirEnd Function
621cdf0e10cSrcweir
622cdf0e10cSrcweirFunction CheckEmptyProject(docAnalysis As DocumentAnalysis, myProject As VBProject, myComponent As VBComponent) As Boolean
623cdf0e10cSrcweir    On Error GoTo HandleErrors
624cdf0e10cSrcweir    Dim currentFunctionName As String
625cdf0e10cSrcweir    currentFunctionName = "CheckEmptyProject"
626cdf0e10cSrcweir    Dim bEmptyProject As Boolean
627cdf0e10cSrcweir
628cdf0e10cSrcweir    'Bug: Can have empty project with different name from default, would be picked up
629cdf0e10cSrcweir    ' as not empty.
630cdf0e10cSrcweir    'bEmptyProject = _
631cdf0e10cSrcweir    '        (StrComp(myProject.name, CTOPLEVEL_PROJECT) = 0) And _
632cdf0e10cSrcweir    '        (VBNumFuncs(docAnalysis, myComponent.CodeModule) = 0) And _
633cdf0e10cSrcweir    '        (VBNumLines(docAnalysis, myComponent.CodeModule) < 3)
634cdf0e10cSrcweir
635cdf0e10cSrcweir    ' Code Modules
636cdf0e10cSrcweir    Dim strFind As String
637cdf0e10cSrcweir    Dim count As Long
638cdf0e10cSrcweir    'Check for:
639cdf0e10cSrcweir    'Public Const myFoo ....
640cdf0e10cSrcweir    'Public Declare Function ....
641cdf0e10cSrcweir    'Public myVar As ...
642cdf0e10cSrcweir    strFind = VBFindLines(docAnalysis, myComponent.CodeModule, "Public", _
643cdf0e10cSrcweir        count, bInProcedure:=False, bWholeWord:=True, bMatchCase:=True)
644cdf0e10cSrcweir
645cdf0e10cSrcweir    bEmptyProject = _
646cdf0e10cSrcweir            (VBNumFuncs(docAnalysis, myComponent.CodeModule) = 0) And _
647cdf0e10cSrcweir            (VBNumLines(docAnalysis, myComponent.CodeModule) < 3) And _
648cdf0e10cSrcweir            (strFind = "")
649cdf0e10cSrcweir
650cdf0e10cSrcweir    CheckEmptyProject = IIf(bEmptyProject, True, False)
651cdf0e10cSrcweir    Exit Function
652cdf0e10cSrcweir
653cdf0e10cSrcweir
654cdf0e10cSrcweirHandleErrors:
655cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
656cdf0e10cSrcweirEnd Function
657cdf0e10cSrcweir
658cdf0e10cSrcweirFunction getCustomDocPropTypeAsString(propType As MsoDocProperties)
659cdf0e10cSrcweir    Dim Str As String
660cdf0e10cSrcweir
661cdf0e10cSrcweir    Select Case propType
662cdf0e10cSrcweir    Case msoPropertyTypeBoolean
663cdf0e10cSrcweir        Str = RID_STR_COMMON_YES_OR_NO
664cdf0e10cSrcweir    Case msoPropertyTypeDate
665cdf0e10cSrcweir        Str = RID_STR_COMMON_DATE
666cdf0e10cSrcweir    Case msoPropertyTypeFloat
667cdf0e10cSrcweir        Str = RID_STR_COMMON_NUMBER
668cdf0e10cSrcweir    Case msoPropertyTypeNumber
669cdf0e10cSrcweir        Str = RID_STR_COMMON_NUMBER
670cdf0e10cSrcweir    Case msoPropertyTypeString
671cdf0e10cSrcweir        Str = RID_STR_COMMON_TEXT
672cdf0e10cSrcweir    Case Else
673cdf0e10cSrcweir        Str = "Unknown"
674cdf0e10cSrcweir    End Select
675cdf0e10cSrcweir
676cdf0e10cSrcweir    getCustomDocPropTypeAsString = Str
677cdf0e10cSrcweirEnd Function
678cdf0e10cSrcweir
679cdf0e10cSrcweirSub HandleProtectedDocInvalidPassword(docAnalysis As DocumentAnalysis, strError As String, fso As FileSystemObject)
680cdf0e10cSrcweir    On Error GoTo HandleErrors
681cdf0e10cSrcweir    Dim currentFunctionName As String
682cdf0e10cSrcweir    currentFunctionName = "HandleProtectedDocInvalidPassword"
683cdf0e10cSrcweir    Dim f As File
684cdf0e10cSrcweir    Set f = fso.GetFile(docAnalysis.name)
685cdf0e10cSrcweir
686cdf0e10cSrcweir    docAnalysis.Application = RID_STR_COMMON_PASSWORD_SKIPDOC
687cdf0e10cSrcweir
688cdf0e10cSrcweir    On Error Resume Next
689cdf0e10cSrcweir    docAnalysis.PageCount = 0
690cdf0e10cSrcweir    docAnalysis.Created = f.DateCreated
691cdf0e10cSrcweir    docAnalysis.Modified = f.DateLastModified
692cdf0e10cSrcweir    docAnalysis.Accessed = f.DateLastAccessed
693cdf0e10cSrcweir    docAnalysis.Printed = DateValue("01/01/1900")
694cdf0e10cSrcweir    docAnalysis.SavedBy = RID_STR_COMMON_NA
695cdf0e10cSrcweir    docAnalysis.Revision = 0
696cdf0e10cSrcweir    docAnalysis.Template = RID_STR_COMMON_NA
697cdf0e10cSrcweir    On Error GoTo HandleErrors
698cdf0e10cSrcweir
699cdf0e10cSrcweir    Dim myIssue As IssueInfo
700cdf0e10cSrcweir    Set myIssue = New IssueInfo
701cdf0e10cSrcweir
702cdf0e10cSrcweir    With myIssue
703cdf0e10cSrcweir        .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
704cdf0e10cSrcweir        .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
705cdf0e10cSrcweir        .SubType = RID_STR_COMMON_SUBISSUE_INVALID_PASSWORD_ENTERED
706cdf0e10cSrcweir        .Location = .CLocationDocument
707cdf0e10cSrcweir
708cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
709cdf0e10cSrcweir        .SubTypeXML = CSTR_SUBISSUE_INVALID_PASSWORD_ENTERED
710cdf0e10cSrcweir        .locationXML = .CXMLLocationDocument
711cdf0e10cSrcweir
712cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_PASSWORD
713cdf0e10cSrcweir        .Values.Add strError
714cdf0e10cSrcweir
715cdf0e10cSrcweir        docAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
716cdf0e10cSrcweir                docAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
717cdf0e10cSrcweir    End With
718cdf0e10cSrcweir
719cdf0e10cSrcweir    docAnalysis.Issues.Add myIssue
720cdf0e10cSrcweir
721cdf0e10cSrcweirFinalExit:
722cdf0e10cSrcweir    Set myIssue = Nothing
723cdf0e10cSrcweir    Set f = Nothing
724cdf0e10cSrcweir    Exit Sub
725cdf0e10cSrcweir
726cdf0e10cSrcweirHandleErrors:
727cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
728cdf0e10cSrcweir    Resume FinalExit
729cdf0e10cSrcweirEnd Sub
730cdf0e10cSrcweir
731cdf0e10cSrcweirSub Analyze_OLEEmbeddedSingleShape(docAnalysis As DocumentAnalysis, aShape As Shape, mySubLocation As Variant)
732cdf0e10cSrcweir
733cdf0e10cSrcweir    On Error GoTo HandleErrors
734cdf0e10cSrcweir    Dim currentFunctionName As String
735cdf0e10cSrcweir    currentFunctionName = "Analyze_OLEEmbeddedSingleShape"
736cdf0e10cSrcweir    Dim myIssue As IssueInfo
737cdf0e10cSrcweir    Dim bOleObject As Boolean
738cdf0e10cSrcweir    Dim TypeAsString As String
739cdf0e10cSrcweir    Dim XMLTypeAsString As String
740cdf0e10cSrcweir    Dim objName As String
741cdf0e10cSrcweir
742cdf0e10cSrcweir    bOleObject = (aShape.Type = msoEmbeddedOLEObject) Or _
743cdf0e10cSrcweir                    (aShape.Type = msoLinkedOLEObject) Or _
744cdf0e10cSrcweir                    (aShape.Type = msoOLEControlObject)
745cdf0e10cSrcweir
746cdf0e10cSrcweir    If Not bOleObject Then Exit Sub
747cdf0e10cSrcweir
748cdf0e10cSrcweir    aShape.Select
749cdf0e10cSrcweir    Select Case aShape.Type
750cdf0e10cSrcweir        Case msoEmbeddedOLEObject
751cdf0e10cSrcweir            TypeAsString = RID_STR_COMMON_OLE_EMBEDDED
752cdf0e10cSrcweir            XMLTypeAsString = CSTR_SUBISSUE_OLE_EMBEDDED
753cdf0e10cSrcweir        Case msoLinkedOLEObject
754cdf0e10cSrcweir            TypeAsString = RID_STR_COMMON_OLE_LINKED
755cdf0e10cSrcweir            XMLTypeAsString = CSTR_SUBISSUE_OLE_LINKED
756cdf0e10cSrcweir        Case msoOLEControlObject
757cdf0e10cSrcweir            TypeAsString = RID_STR_COMMON_OLE_CONTROL
758cdf0e10cSrcweir            XMLTypeAsString = CSTR_SUBISSUE_OLE_CONTROL
759cdf0e10cSrcweir        Case Else
760cdf0e10cSrcweir            TypeAsString = RID_STR_COMMON_OLE_UNKNOWN
761cdf0e10cSrcweir            XMLTypeAsString = CSTR_SUBISSUE_OLE_UNKNOWN
762cdf0e10cSrcweir    End Select
763cdf0e10cSrcweir
764cdf0e10cSrcweir    Dim appStr As String
765cdf0e10cSrcweir    appStr = getAppSpecificApplicationName
766cdf0e10cSrcweir
767cdf0e10cSrcweir    Set myIssue = New IssueInfo
768cdf0e10cSrcweir    With myIssue
769cdf0e10cSrcweir        .IssueID = CID_PORTABILITY
770cdf0e10cSrcweir        .IssueType = RID_STR_COMMON_ISSUE_PORTABILITY
771cdf0e10cSrcweir        .SubType = TypeAsString
772cdf0e10cSrcweir        .Location = .CLocationPage
773cdf0e10cSrcweir        .SubLocation = mySubLocation
774cdf0e10cSrcweir
775cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_PORTABILITY
776cdf0e10cSrcweir        .SubTypeXML = XMLTypeAsString
777cdf0e10cSrcweir        .locationXML = .CXMLLocationPage
778cdf0e10cSrcweir
779cdf0e10cSrcweir        .Line = aShape.top
780cdf0e10cSrcweir        .column = aShape.Left
781cdf0e10cSrcweir
782cdf0e10cSrcweir        If aShape.name <> "" Then
783cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
784cdf0e10cSrcweir            .Values.Add aShape.name
785cdf0e10cSrcweir        End If
786cdf0e10cSrcweir
787cdf0e10cSrcweir        If aShape.Type = msoEmbeddedOLEObject Or _
788cdf0e10cSrcweir           aShape.Type = msoOLEControlObject Then
789cdf0e10cSrcweir            Dim objType As String
790cdf0e10cSrcweir            On Error Resume Next
791cdf0e10cSrcweir
792cdf0e10cSrcweir            objType = getAppSpecificOLEClassType(aShape)
793cdf0e10cSrcweir
794cdf0e10cSrcweir            If objType = "" Then GoTo FinalExit
795cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_OBJECT_TYPE
796cdf0e10cSrcweir            .Values.Add objType
797cdf0e10cSrcweir
798cdf0e10cSrcweir            If aShape.Type = msoOLEControlObject Then
799cdf0e10cSrcweir                docAnalysis.MacroNumOLEControls = 1 + docAnalysis.MacroNumOLEControls
800cdf0e10cSrcweir            End If
801cdf0e10cSrcweir
802cdf0e10cSrcweir            If appStr = CAPPNAME_POWERPOINT Then
803cdf0e10cSrcweir            '#114127: Too many open windows
804cdf0e10cSrcweir            'Checking for OLEFormat.Object is Nothing or IsEmpty still causes problem
805cdf0e10cSrcweir                If objType <> "Equation.3" Then
806cdf0e10cSrcweir                    objName = aShape.OLEFormat.Object.name
807cdf0e10cSrcweir                    If Err.Number = 0 Then
808cdf0e10cSrcweir                        If aShape.name <> objName Then
809cdf0e10cSrcweir                            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_OBJECT_NAME
810cdf0e10cSrcweir                            .Values.Add objName
811cdf0e10cSrcweir                       End If
812cdf0e10cSrcweir                    End If
813cdf0e10cSrcweir                End If
814cdf0e10cSrcweir            Else
815cdf0e10cSrcweir                If Not (aShape.OLEFormat.Object) Is Nothing Then
816cdf0e10cSrcweir                    objName = aShape.OLEFormat.Object.name
817cdf0e10cSrcweir                    If Err.Number = 0 Then
818cdf0e10cSrcweir                        If aShape.name <> objName Then
819cdf0e10cSrcweir                            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_OBJECT_NAME
820cdf0e10cSrcweir                            .Values.Add objName
821cdf0e10cSrcweir                        End If
822cdf0e10cSrcweir                    End If
823cdf0e10cSrcweir                End If
824cdf0e10cSrcweir            End If
825cdf0e10cSrcweir
826cdf0e10cSrcweir            On Error GoTo HandleErrors
827cdf0e10cSrcweir        End If
828cdf0e10cSrcweir
829cdf0e10cSrcweir        If aShape.Type = msoLinkedOLEObject Then
830cdf0e10cSrcweir            If appStr <> CAPPNAME_WORD Then
831cdf0e10cSrcweir                On Error Resume Next
832cdf0e10cSrcweir                Dim path As String
833cdf0e10cSrcweir                path = aShape.OLEFormat.Object.SourceFullName
834cdf0e10cSrcweir                If Err.Number = 0 Then
835cdf0e10cSrcweir                    .Attributes.Add RID_STR_COMMON_ATTRIBUTE_SOURCE
836cdf0e10cSrcweir                    .Values.Add path
837cdf0e10cSrcweir                End If
838cdf0e10cSrcweir                On Error GoTo HandleErrors
839cdf0e10cSrcweir            Else
840cdf0e10cSrcweir                .Attributes.Add RID_STR_COMMON_ATTRIBUTE_SOURCE
841cdf0e10cSrcweir                .Values.Add aShape.LinkFormat.SourceFullName
842cdf0e10cSrcweir            End If
843cdf0e10cSrcweir        End If
844cdf0e10cSrcweir
845cdf0e10cSrcweir        docAnalysis.IssuesCountArray(CID_PORTABILITY) = _
846cdf0e10cSrcweir            docAnalysis.IssuesCountArray(CID_PORTABILITY) + 1
847cdf0e10cSrcweir    End With
848cdf0e10cSrcweir    docAnalysis.Issues.Add myIssue
849cdf0e10cSrcweir
850cdf0e10cSrcweirFinalExit:
851cdf0e10cSrcweir    Set myIssue = Nothing
852cdf0e10cSrcweir    Exit Sub
853cdf0e10cSrcweir
854cdf0e10cSrcweirHandleErrors:
855cdf0e10cSrcweir    WriteDebugLevelTwo currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
856cdf0e10cSrcweir    Resume FinalExit
857cdf0e10cSrcweirEnd Sub
858cdf0e10cSrcweir
859cdf0e10cSrcweirSub Analyze_Lines(docAnalysis As DocumentAnalysis, myShape As Shape, mySubLocation As Variant)
860cdf0e10cSrcweir    On Error GoTo HandleErrors
861cdf0e10cSrcweir    Dim currentFunctionName As String
862cdf0e10cSrcweir    currentFunctionName = "Analyze_Lines"
863cdf0e10cSrcweir
864cdf0e10cSrcweir    If myShape.Line.Style = msoLineSingle Or _
865cdf0e10cSrcweir       myShape.Line.Style = msoLineStyleMixed Then Exit Sub
866cdf0e10cSrcweir
867cdf0e10cSrcweir    Dim myIssue As IssueInfo
868cdf0e10cSrcweir    Set myIssue = New IssueInfo
869cdf0e10cSrcweir
870cdf0e10cSrcweir    With myIssue
871cdf0e10cSrcweir        .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
872cdf0e10cSrcweir        .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
873cdf0e10cSrcweir        .SubType = RID_RESXLS_COST_LineStyle
874cdf0e10cSrcweir        .Location = .CLocationPage
875cdf0e10cSrcweir        .SubLocation = mySubLocation
876cdf0e10cSrcweir
877cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
878cdf0e10cSrcweir        .SubTypeXML = CSTR_SUBISSUE_LINE
879cdf0e10cSrcweir        .locationXML = .CXMLLocationPage
880cdf0e10cSrcweir
881cdf0e10cSrcweir        .Line = myShape.top
882cdf0e10cSrcweir        .column = myShape.Left
883cdf0e10cSrcweir
884cdf0e10cSrcweir        If myShape.name <> "" Then
885cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
886cdf0e10cSrcweir            .Values.Add myShape.name
887cdf0e10cSrcweir        End If
888cdf0e10cSrcweir
889cdf0e10cSrcweir        AddIssueDetailsNote myIssue, 0, RID_STR_COMMON_SUBISSUE_LINE_NOTE
890cdf0e10cSrcweir
891cdf0e10cSrcweir        docAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
892cdf0e10cSrcweir                docAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
893cdf0e10cSrcweir    End With
894cdf0e10cSrcweir
895cdf0e10cSrcweir    docAnalysis.Issues.Add myIssue
896cdf0e10cSrcweir
897cdf0e10cSrcweirFinalExit:
898cdf0e10cSrcweir    Set myIssue = Nothing
899cdf0e10cSrcweir    Exit Sub
900cdf0e10cSrcweir
901cdf0e10cSrcweirHandleErrors:
902cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
903cdf0e10cSrcweir    Resume FinalExit
904cdf0e10cSrcweirEnd Sub
905cdf0e10cSrcweir
906cdf0e10cSrcweirSub Analyze_Transparency(docAnalysis As DocumentAnalysis, myShape As Shape, mySubLocation As Variant)
907cdf0e10cSrcweir    On Error GoTo HandleErrors
908cdf0e10cSrcweir    Dim currentFunctionName As String
909cdf0e10cSrcweir    currentFunctionName = "Analyze_Transparency"
910cdf0e10cSrcweir
911cdf0e10cSrcweir    If Not myShape.Type = msoPicture Then Exit Sub
912cdf0e10cSrcweir
913cdf0e10cSrcweir    Dim bHasTransparentBkg
914cdf0e10cSrcweir    bHasTransparentBkg = False
915cdf0e10cSrcweir
916cdf0e10cSrcweir    On Error Resume Next
917cdf0e10cSrcweir    If myShape.PictureFormat.TransparentBackground = msoTrue Then
918cdf0e10cSrcweir        If Error.Number = 0 Then
919cdf0e10cSrcweir            bHasTransparentBkg = True
920cdf0e10cSrcweir        End If
921cdf0e10cSrcweir    End If
922cdf0e10cSrcweir
923cdf0e10cSrcweir    On Error GoTo HandleErrors
924cdf0e10cSrcweir    If Not bHasTransparentBkg Then Exit Sub
925cdf0e10cSrcweir
926cdf0e10cSrcweir    Dim myIssue As IssueInfo
927cdf0e10cSrcweir    Set myIssue = New IssueInfo
928cdf0e10cSrcweir
929cdf0e10cSrcweir    With myIssue
930cdf0e10cSrcweir        .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
931cdf0e10cSrcweir        .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
932cdf0e10cSrcweir        .SubType = RID_RESXLS_COST_Transparent
933cdf0e10cSrcweir        .Location = .CLocationSlide
934cdf0e10cSrcweir        .SubLocation = mySubLocation
935cdf0e10cSrcweir
936cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
937cdf0e10cSrcweir        .SubTypeXML = CSTR_SUBISSUE_TRANSPARENCY
938cdf0e10cSrcweir        .locationXML = .CXMLLocationPage
939cdf0e10cSrcweir
940cdf0e10cSrcweir        .Line = myShape.top
941cdf0e10cSrcweir        .column = myShape.Left
942cdf0e10cSrcweir
943cdf0e10cSrcweir        If myShape.name <> "" Then
944cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
945cdf0e10cSrcweir            .Values.Add myShape.name
946cdf0e10cSrcweir        End If
947cdf0e10cSrcweir
948cdf0e10cSrcweir        AddIssueDetailsNote myIssue, 0, RID_STR_COMMON_SUBISSUE_TRANSPARENCY_NOTE
949cdf0e10cSrcweir
950cdf0e10cSrcweir        docAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
951cdf0e10cSrcweir                docAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
952cdf0e10cSrcweir    End With
953cdf0e10cSrcweir
954cdf0e10cSrcweir    docAnalysis.Issues.Add myIssue
955cdf0e10cSrcweir
956cdf0e10cSrcweirFinalExit:
957cdf0e10cSrcweir    Set myIssue = Nothing
958cdf0e10cSrcweir    Exit Sub
959cdf0e10cSrcweir
960cdf0e10cSrcweirHandleErrors:
961cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
962cdf0e10cSrcweir    Resume FinalExit
963cdf0e10cSrcweirEnd Sub
964cdf0e10cSrcweir
965cdf0e10cSrcweirSub Analyze_Gradients(docAnalysis As DocumentAnalysis, myShape As Shape, mySubLocation As Variant)
966cdf0e10cSrcweir    On Error GoTo HandleErrors
967cdf0e10cSrcweir    Dim currentFunctionName As String
968cdf0e10cSrcweir    currentFunctionName = "Analyze_Gradients"
969cdf0e10cSrcweir
970cdf0e10cSrcweir    If myShape.Fill.Type <> msoFillGradient Then Exit Sub
971cdf0e10cSrcweir
972cdf0e10cSrcweir    Dim bUsesPresetGradient, bUsesFromCorner, bUsesFromCenter
973cdf0e10cSrcweir    bUsesPresetGradient = False
974cdf0e10cSrcweir    bUsesFromCorner = False
975cdf0e10cSrcweir    bUsesFromCenter = False
976cdf0e10cSrcweir
977cdf0e10cSrcweir    On Error Resume Next
978cdf0e10cSrcweir    If myShape.Fill.PresetGradientType <> msoPresetGradientMixed Then
979cdf0e10cSrcweir        If Error.Number = 0 Then
980cdf0e10cSrcweir            bUsesPresetGradient = True
981cdf0e10cSrcweir        End If
982cdf0e10cSrcweir    End If
983cdf0e10cSrcweir    If myShape.Fill.GradientStyle <> msoGradientFromCorner Then
984cdf0e10cSrcweir        If Error.Number = 0 Then
985cdf0e10cSrcweir            bUsesFromCorner = True
986cdf0e10cSrcweir        End If
987cdf0e10cSrcweir    End If
988cdf0e10cSrcweir    If myShape.Fill.GradientStyle <> msoGradientFromCenter Then
989cdf0e10cSrcweir        If Error.Number = 0 Then
990cdf0e10cSrcweir            bUsesFromCenter = True
991cdf0e10cSrcweir        End If
992cdf0e10cSrcweir    End If
993cdf0e10cSrcweir
994cdf0e10cSrcweir    On Error GoTo HandleErrors
995cdf0e10cSrcweir    If Not bUsesPresetGradient And Not bUsesFromCorner _
996cdf0e10cSrcweir       And Not bUsesFromCenter Then Exit Sub
997cdf0e10cSrcweir
998cdf0e10cSrcweir    Dim myIssue As IssueInfo
999cdf0e10cSrcweir    Set myIssue = New IssueInfo
1000cdf0e10cSrcweir
1001cdf0e10cSrcweir    With myIssue
1002cdf0e10cSrcweir        .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
1003cdf0e10cSrcweir        .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
1004cdf0e10cSrcweir        .SubType = RID_RESXLS_COST_GradientStyle
1005cdf0e10cSrcweir        .Location = .CLocationSlide
1006cdf0e10cSrcweir        .SubLocation = mySubLocation
1007cdf0e10cSrcweir
1008cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
1009cdf0e10cSrcweir        .SubTypeXML = CSTR_SUBISSUE_GRADIENT
1010cdf0e10cSrcweir        .locationXML = .CXMLLocationSlide
1011cdf0e10cSrcweir
1012cdf0e10cSrcweir        .Line = myShape.top
1013cdf0e10cSrcweir        .column = myShape.Left
1014cdf0e10cSrcweir
1015cdf0e10cSrcweir        If myShape.name <> "" Then
1016cdf0e10cSrcweir            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
1017cdf0e10cSrcweir            .Values.Add myShape.name
1018cdf0e10cSrcweir        End If
1019cdf0e10cSrcweir
1020cdf0e10cSrcweir        If bUsesPresetGradient Then
1021cdf0e10cSrcweir            AddIssueDetailsNote myIssue, 0, RID_STR_COMMON_SUBISSUE_GRADIENT_PRESET_NOTE
1022cdf0e10cSrcweir        ElseIf bUsesFromCorner Then
1023cdf0e10cSrcweir            AddIssueDetailsNote myIssue, 0, RID_STR_COMMON_SUBISSUE_GRADIENT_CORNER_NOTE
1024cdf0e10cSrcweir        Else
1025cdf0e10cSrcweir            AddIssueDetailsNote myIssue, 0, RID_STR_COMMON_SUBISSUE_GRADIENT_CENTER_NOTE
1026cdf0e10cSrcweir        End If
1027cdf0e10cSrcweir
1028cdf0e10cSrcweir        docAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
1029cdf0e10cSrcweir                docAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
1030cdf0e10cSrcweir    End With
1031cdf0e10cSrcweir
1032cdf0e10cSrcweir    docAnalysis.Issues.Add myIssue
1033cdf0e10cSrcweir
1034cdf0e10cSrcweirFinalExit:
1035cdf0e10cSrcweir    Set myIssue = Nothing
1036cdf0e10cSrcweir    Exit Sub
1037cdf0e10cSrcweir
1038cdf0e10cSrcweirHandleErrors:
1039cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & docAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
1040cdf0e10cSrcweir    Resume FinalExit
1041cdf0e10cSrcweirEnd Sub
1042cdf0e10cSrcweir
1043cdf0e10cSrcweirPrivate Function CreateFullPath(newPath As String, fso As FileSystemObject)
1044cdf0e10cSrcweir    'We don't want to create 'c:\'
1045cdf0e10cSrcweir    If (Len(newPath) < 4) Then
1046cdf0e10cSrcweir        Exit Function
1047cdf0e10cSrcweir    End If
1048cdf0e10cSrcweir
1049cdf0e10cSrcweir    'Create parent folder first
1050cdf0e10cSrcweir    If (Not fso.FolderExists(fso.GetParentFolderName(newPath))) Then
1051cdf0e10cSrcweir        CreateFullPath fso.GetParentFolderName(newPath), fso
1052cdf0e10cSrcweir    End If
1053cdf0e10cSrcweir
1054cdf0e10cSrcweir    If (Not fso.FolderExists(newPath)) Then
1055cdf0e10cSrcweir        fso.CreateFolder (newPath)
1056cdf0e10cSrcweir    End If
1057cdf0e10cSrcweirEnd Function
1058cdf0e10cSrcweir
1059cdf0e10cSrcweirFunction GetPreparedFullPath(sourceDocPath As String, startDir As String, storeToDir As String, _
1060cdf0e10cSrcweir    fso As FileSystemObject) As String
1061cdf0e10cSrcweir    On Error GoTo HandleErrors
1062cdf0e10cSrcweir    Dim currentFunctionName As String
1063cdf0e10cSrcweir    currentFunctionName = "GetPreparedFullPath"
1064cdf0e10cSrcweir    GetPreparedFullPath = ""
1065cdf0e10cSrcweir
1066cdf0e10cSrcweir    Dim preparedPath As String
1067cdf0e10cSrcweir
1068cdf0e10cSrcweir    preparedPath = Right(sourceDocPath, Len(sourceDocPath) - Len(startDir))
1069cdf0e10cSrcweir    If Left(preparedPath, 1) = "\" Then
1070cdf0e10cSrcweir        preparedPath = Right(preparedPath, Len(preparedPath) - 1)
1071cdf0e10cSrcweir    End If
1072cdf0e10cSrcweir
1073cdf0e10cSrcweir    'Allow for root folder C:\
1074cdf0e10cSrcweir    If Right(storeToDir, 1) <> "\" Then
1075cdf0e10cSrcweir        preparedPath = storeToDir & "\" & CSTR_COMMON_PREPARATION_FOLDER & "\" & preparedPath
1076cdf0e10cSrcweir    Else
1077cdf0e10cSrcweir        preparedPath = storeToDir & CSTR_COMMON_PREPARATION_FOLDER & "\" & preparedPath
1078cdf0e10cSrcweir    End If
1079cdf0e10cSrcweir
1080cdf0e10cSrcweir    'Debug: MsgBox "Preppath: " & preparedPath
1081cdf0e10cSrcweir    CreateFullPath fso.GetParentFolderName(preparedPath), fso
1082cdf0e10cSrcweir
1083cdf0e10cSrcweir    'Only set if folder to save to exists or has been created, otherwise return ""
1084cdf0e10cSrcweir    GetPreparedFullPath = preparedPath
1085cdf0e10cSrcweir
1086cdf0e10cSrcweirFinalExit:
1087cdf0e10cSrcweir    Exit Function
1088cdf0e10cSrcweir
1089cdf0e10cSrcweirHandleErrors:
1090cdf0e10cSrcweir    WriteDebugLevelTwo currentFunctionName & " : " & sourceDocPath & ": " & Err.Number & " " & Err.Description & " " & Err.Source
1091cdf0e10cSrcweir    Resume FinalExit
1092cdf0e10cSrcweirEnd Function
1093cdf0e10cSrcweir
1094cdf0e10cSrcweirFunction ClassifyDocOverallMacroClass(docAnalysis As DocumentAnalysis) As EnumDocOverallMacroClass
1095cdf0e10cSrcweir    ClassifyDocOverallMacroClass = enMacroNone
1096cdf0e10cSrcweir
1097cdf0e10cSrcweir    If Not docAnalysis.HasMacros Then Exit Function
1098cdf0e10cSrcweir
1099cdf0e10cSrcweir    If (docAnalysis.MacroTotalNumLines >= CMACRO_LINECOUNT_MEDIUM_LBOUND) Then
1100cdf0e10cSrcweir        If (docAnalysis.MacroNumExternalRefs > 0) Or _
1101cdf0e10cSrcweir            (docAnalysis.MacroNumOLEControls > 0 Or docAnalysis.MacroNumFieldsUsingMacros > 0) Or _
1102cdf0e10cSrcweir            docAnalysis.MacroNumUserForms > 0 Then
1103cdf0e10cSrcweir            ClassifyDocOverallMacroClass = enMacroComplex
1104cdf0e10cSrcweir        Else
1105cdf0e10cSrcweir            ClassifyDocOverallMacroClass = enMacroMedium
1106cdf0e10cSrcweir        End If
1107cdf0e10cSrcweir    Else
1108cdf0e10cSrcweir        ClassifyDocOverallMacroClass = enMacroSimple
1109cdf0e10cSrcweir    End If
1110cdf0e10cSrcweir
1111cdf0e10cSrcweirEnd Function
1112cdf0e10cSrcweir
1113