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