1*a893be29SPedro GiffuniVERSION 1.0 CLASS
2*a893be29SPedro GiffuniBEGIN
3*a893be29SPedro Giffuni  MultiUse = -1  'True
4*a893be29SPedro GiffuniEND
5*a893be29SPedro GiffuniAttribute VB_Name = "MigrationAnalyser"
6*a893be29SPedro GiffuniAttribute VB_GlobalNameSpace = False
7*a893be29SPedro GiffuniAttribute VB_Creatable = False
8*a893be29SPedro GiffuniAttribute VB_PredeclaredId = False
9*a893be29SPedro GiffuniAttribute VB_Exposed = False
10*a893be29SPedro Giffuni'*************************************************************************
11*a893be29SPedro Giffuni'
12*a893be29SPedro Giffuni'  Licensed to the Apache Software Foundation (ASF) under one
13*a893be29SPedro Giffuni'  or more contributor license agreements.  See the NOTICE file
14*a893be29SPedro Giffuni'  distributed with this work for additional information
15*a893be29SPedro Giffuni'  regarding copyright ownership.  The ASF licenses this file
16*a893be29SPedro Giffuni'  to you under the Apache License, Version 2.0 (the
17*a893be29SPedro Giffuni'  "License"); you may not use this file except in compliance
18*a893be29SPedro Giffuni'  with the License.  You may obtain a copy of the License at
19*a893be29SPedro Giffuni'
20*a893be29SPedro Giffuni'    http://www.apache.org/licenses/LICENSE-2.0
21*a893be29SPedro Giffuni'
22*a893be29SPedro Giffuni'  Unless required by applicable law or agreed to in writing,
23*a893be29SPedro Giffuni'  software distributed under the License is distributed on an
24*a893be29SPedro Giffuni'  "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
25*a893be29SPedro Giffuni'  KIND, either express or implied.  See the License for the
26*a893be29SPedro Giffuni'  specific language governing permissions and limitations
27*a893be29SPedro Giffuni'  under the License.
28*a893be29SPedro Giffuni'
29*a893be29SPedro Giffuni'*************************************************************************
30*a893be29SPedro Giffuni
31*a893be29SPedro GiffuniOption Explicit
32*a893be29SPedro Giffuni
33*a893be29SPedro Giffuni'Class variables
34*a893be29SPedro GiffuniPrivate Enum HFIssueType
35*a893be29SPedro Giffuni    hfInline
36*a893be29SPedro Giffuni    hfShape
37*a893be29SPedro Giffuni    hfFrame
38*a893be29SPedro GiffuniEnd Enum
39*a893be29SPedro Giffuni
40*a893be29SPedro GiffuniPrivate Enum HFIssueLocation
41*a893be29SPedro Giffuni    hfHeader
42*a893be29SPedro Giffuni    hffooter
43*a893be29SPedro GiffuniEnd Enum
44*a893be29SPedro Giffuni
45*a893be29SPedro Giffuni
46*a893be29SPedro GiffuniPrivate Type ShapeInfo
47*a893be29SPedro Giffuni        top As Single
48*a893be29SPedro Giffuni        Height As Single
49*a893be29SPedro GiffuniEnd Type
50*a893be29SPedro Giffuni
51*a893be29SPedro GiffuniPrivate Type FrameInfo
52*a893be29SPedro Giffuni        Height As Single
53*a893be29SPedro Giffuni        VerticalPosition As Single
54*a893be29SPedro GiffuniEnd Type
55*a893be29SPedro Giffuni
56*a893be29SPedro GiffuniPrivate mAnalysis As DocumentAnalysis
57*a893be29SPedro GiffuniPrivate mOdd As Boolean
58*a893be29SPedro GiffuniPrivate mbFormFieldErrorLogged As Boolean
59*a893be29SPedro GiffuniPrivate mbRefFormFieldErrorLogged As Boolean
60*a893be29SPedro Giffuni
61*a893be29SPedro Giffuni'***ADDING-ISSUE: Use Following Skeleton as Guideline for Adding Issue
62*a893be29SPedro Giffuni' For complete list of all RID_STR_... for Issues (IssueType), SubIssues (SubType) and Attributes refer to:
63*a893be29SPedro Giffuni'   word_res.bas and common_res.bas
64*a893be29SPedro Giffuni'
65*a893be29SPedro Giffuni' For complete list of all CID_... for Issue Categories(IssueID) and
66*a893be29SPedro Giffuni' CSTR_... for XML Issues (IssueTypeXML) and XML SubIssues (SubTypeXML) refer to:
67*a893be29SPedro Giffuni'   ApplicationSpecific.bas and CommonMigrationAnalyser.bas
68*a893be29SPedro Giffuni'
69*a893be29SPedro Giffuni' You should not have to add any new Issue Categories or matching IssueTypes, only new SubIssues
70*a893be29SPedro GiffuniSub Analyze_SKELETON()
71*a893be29SPedro Giffuni    On Error GoTo HandleErrors
72*a893be29SPedro Giffuni    Dim currentFunctionName As String
73*a893be29SPedro Giffuni    currentFunctionName = "Analyze_SKELETON"
74*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
75*a893be29SPedro Giffuni    Set myIssue = New IssueInfo
76*a893be29SPedro Giffuni
77*a893be29SPedro Giffuni    With myIssue
78*a893be29SPedro Giffuni        .IssueID = CID_VBA_MACROS 'Issue Category
79*a893be29SPedro Giffuni        .IssueType = RID_STR_COMMON_ISSUE_VBA_MACROS 'Issue String
80*a893be29SPedro Giffuni        .SubType = RID_STR_COMMON_SUBISSUE_PROPERTIES 'SubIssue String
81*a893be29SPedro Giffuni        .Location = .CLocationDocument 'Location string
82*a893be29SPedro Giffuni
83*a893be29SPedro Giffuni        .IssueTypeXML = CSTR_ISSUE_VBA_MACROS 'Non localised XML Issue String
84*a893be29SPedro Giffuni        .SubTypeXML = CSTR_SUBISSUE_PROPERTIES 'Non localised XML SubIssue String
85*a893be29SPedro Giffuni        .locationXML = .CXMLLocationDocument 'Non localised XML location
86*a893be29SPedro Giffuni
87*a893be29SPedro Giffuni        .SubLocation = 0 'if not set will default to RID_STR_NOT_AVAILABLE_SHORTHAND
88*a893be29SPedro Giffuni        .Line = 0 'if not set will default to RID_STR_NOT_AVAILABLE_SHORTHAND
89*a893be29SPedro Giffuni        .column = 0 'if not set will default to RID_STR_NOT_AVAILABLE_SHORTHAND
90*a893be29SPedro Giffuni
91*a893be29SPedro Giffuni        ' Add as many Attribute Value pairs as needed
92*a893be29SPedro Giffuni        ' Note: following must always be true - Attributes.Count = Values.Count
93*a893be29SPedro Giffuni        .Attributes.Add "AAA"
94*a893be29SPedro Giffuni        .Values.Add "foobar"
95*a893be29SPedro Giffuni
96*a893be29SPedro Giffuni        ' Use AddIssueDetailsNote to add notes to the Issue Details if required
97*a893be29SPedro Giffuni        ' Public Sub AddIssueDetailsNote(myIssue As IssueInfo, noteNum As Long, noteStr As String, _
98*a893be29SPedro Giffuni        '   Optional preStr As String = RID_STR_COMMON_NOTE_PRE)
99*a893be29SPedro Giffuni        ' Where preStr is prepended to the output, with "Note" as the default
100*a893be29SPedro Giffuni         AddIssueDetailsNote myIssue, 0, RID_STR_COMMON_NOTE_DOCUMENT_PROPERTIES_LOST
101*a893be29SPedro Giffuni
102*a893be29SPedro Giffuni         'Only put this in if you have a preparation function added for this issue in CommonPreparation
103*a893be29SPedro Giffuni         'or Preparation - NUll can be replaced with any variant if you want to pass info to the Prepare fnc
104*a893be29SPedro Giffuni         Call DoPreparation(mAnalysis, myIssue, "", Null, Null)
105*a893be29SPedro Giffuni
106*a893be29SPedro Giffuni         mAnalysis.IssuesCountArray(CID_VBA_MACROS) = _
107*a893be29SPedro Giffuni                mAnalysis.IssuesCountArray(CID_VBA_MACROS) + 1
108*a893be29SPedro Giffuni    End With
109*a893be29SPedro Giffuni
110*a893be29SPedro Giffuni    mAnalysis.Issues.Add myIssue
111*a893be29SPedro Giffuni
112*a893be29SPedro GiffuniFinalExit:
113*a893be29SPedro Giffuni    Set myIssue = Nothing
114*a893be29SPedro Giffuni    Exit Sub
115*a893be29SPedro Giffuni
116*a893be29SPedro GiffuniHandleErrors:
117*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
118*a893be29SPedro Giffuni    Resume FinalExit
119*a893be29SPedro GiffuniEnd Sub
120*a893be29SPedro Giffuni
121*a893be29SPedro GiffuniSub DoAnalyse(fileName As String, userFormTypesDict As Scripting.Dictionary, _
122*a893be29SPedro Giffuni    startDir As String, storeToDir As String, fso As FileSystemObject)
123*a893be29SPedro Giffuni    On Error GoTo HandleErrors
124*a893be29SPedro Giffuni    Dim currentFunctionName As String
125*a893be29SPedro Giffuni    currentFunctionName = "DoAnalyse"
126*a893be29SPedro Giffuni    mAnalysis.name = fileName
127*a893be29SPedro Giffuni    Dim aDoc As Document
128*a893be29SPedro Giffuni    Dim bUnprotectError As Boolean
129*a893be29SPedro Giffuni    mAnalysis.TotalIssueTypes = CTOTAL_CATEGORIES
130*a893be29SPedro Giffuni    mbFormFieldErrorLogged = False
131*a893be29SPedro Giffuni    mbRefFormFieldErrorLogged = False
132*a893be29SPedro Giffuni
133*a893be29SPedro Giffuni    'Turn off any AutoExce macros before loading the Word doc
134*a893be29SPedro Giffuni    On Error Resume Next ' Ignore errors on setting
135*a893be29SPedro Giffuni    WordBasic.DisableAutoMacros 1
136*a893be29SPedro Giffuni    On Error GoTo HandleErrors
137*a893be29SPedro Giffuni
138*a893be29SPedro Giffuni    Dim myPassword As String
139*a893be29SPedro Giffuni    myPassword = GetDefaultPassword
140*a893be29SPedro Giffuni
141*a893be29SPedro Giffuni    'Always skip password protected documents
142*a893be29SPedro Giffuni    'If IsSkipPasswordDocs() Then
143*a893be29SPedro Giffuni    Dim aPass As String
144*a893be29SPedro Giffuni    If myPassword <> "" Then
145*a893be29SPedro Giffuni        aPass = myPassword
146*a893be29SPedro Giffuni    Else
147*a893be29SPedro Giffuni        aPass = "xoxoxoxoxo"
148*a893be29SPedro Giffuni    End If
149*a893be29SPedro Giffuni
150*a893be29SPedro Giffuni    On Error Resume Next
151*a893be29SPedro Giffuni    Set aDoc = Documents.Open(fileName, False, False, False, _
152*a893be29SPedro Giffuni                            aPass, aPass, False, aPass, aPass, wdOpenFormatAuto, _
153*a893be29SPedro Giffuni                            msoEncodingAutoDetect, False)
154*a893be29SPedro Giffuni    If Err.Number = 5408 Then
155*a893be29SPedro Giffuni        ' if password protected, try open readonly next
156*a893be29SPedro Giffuni        Set aDoc = Documents.Open(fileName, False, True, False, _
157*a893be29SPedro Giffuni                    aPass, aPass, False, aPass, aPass, wdOpenFormatAuto, _
158*a893be29SPedro Giffuni                    msoEncodingAutoDetect, False)
159*a893be29SPedro Giffuni    End If
160*a893be29SPedro Giffuni    If Err.Number = 5408 Then
161*a893be29SPedro Giffuni        HandleProtectedDocInvalidPassword mAnalysis, _
162*a893be29SPedro Giffuni            "User entered Invalid Document Password, further analysis not possible", fso
163*a893be29SPedro Giffuni        Analyze_Password_Protection True, False
164*a893be29SPedro Giffuni        GoTo FinalExit
165*a893be29SPedro Giffuni    ElseIf (Err.Number <> 0) Then
166*a893be29SPedro Giffuni        GoTo HandleErrors
167*a893be29SPedro Giffuni    End If
168*a893be29SPedro Giffuni
169*a893be29SPedro Giffuni    On Error GoTo HandleErrors
170*a893be29SPedro Giffuni
171*a893be29SPedro Giffuni    If aDoc Is Nothing Then GoTo FinalExit
172*a893be29SPedro Giffuni
173*a893be29SPedro Giffuni    'Do Analysis
174*a893be29SPedro Giffuni    Analyze_Password_Protection aDoc.HasPassword, aDoc.WriteReserved
175*a893be29SPedro Giffuni    Analyze_Document_Protection aDoc
176*a893be29SPedro Giffuni
177*a893be29SPedro Giffuni    If aDoc.ProtectionType <> wdNoProtection Then
178*a893be29SPedro Giffuni        If myPassword <> "" Then
179*a893be29SPedro Giffuni            aDoc.Unprotect (myPassword)
180*a893be29SPedro Giffuni        Else
181*a893be29SPedro Giffuni            aDoc.Unprotect
182*a893be29SPedro Giffuni        End If
183*a893be29SPedro Giffuni    End If
184*a893be29SPedro Giffuni
185*a893be29SPedro Giffuni    'Set Doc Properties
186*a893be29SPedro Giffuni    SetDocProperties mAnalysis, aDoc, fso
187*a893be29SPedro Giffuni
188*a893be29SPedro GiffuniContinueFromUnprotectError:
189*a893be29SPedro Giffuni
190*a893be29SPedro Giffuni    Analyze_Tables_TablesInTables aDoc
191*a893be29SPedro Giffuni    Analyze_Tables_Borders aDoc
192*a893be29SPedro Giffuni    Analyze_TOA aDoc
193*a893be29SPedro Giffuni    If Not bUnprotectError Then
194*a893be29SPedro Giffuni        Analyze_FieldAndFormFieldIssues aDoc
195*a893be29SPedro Giffuni    End If
196*a893be29SPedro Giffuni    Analyze_OLEEmbedded aDoc
197*a893be29SPedro Giffuni    Analyze_MailMerge_DataSource aDoc
198*a893be29SPedro Giffuni    Analyze_Macros mAnalysis, userFormTypesDict, aDoc
199*a893be29SPedro Giffuni    'Analyze_Numbering aDoc, mAnalysis
200*a893be29SPedro Giffuni    'Analyze_NumberingTabs aDoc, mAnalysis
201*a893be29SPedro Giffuni
202*a893be29SPedro Giffuni    ' Doc Preparation only
203*a893be29SPedro Giffuni    ' Save document with any prepared issues under <storeToDir>\prepared\<source doc name>
204*a893be29SPedro Giffuni    If mAnalysis.PreparableIssuesCount > 0 And CheckDoPrepare Then
205*a893be29SPedro Giffuni        Dim preparedFullPath As String
206*a893be29SPedro Giffuni        preparedFullPath = GetPreparedFullPath(mAnalysis.name, startDir, storeToDir, fso)
207*a893be29SPedro Giffuni        If preparedFullPath <> "" Then
208*a893be29SPedro Giffuni            If fso.FileExists(preparedFullPath) Then
209*a893be29SPedro Giffuni                fso.DeleteFile preparedFullPath, True
210*a893be29SPedro Giffuni            End If
211*a893be29SPedro Giffuni            If fso.FolderExists(fso.GetParentFolderName(preparedFullPath)) Then
212*a893be29SPedro Giffuni                    aDoc.SaveAs preparedFullPath
213*a893be29SPedro Giffuni            End If
214*a893be29SPedro Giffuni        End If
215*a893be29SPedro Giffuni    End If
216*a893be29SPedro Giffuni
217*a893be29SPedro Giffuni    'DebugMacroInfo
218*a893be29SPedro Giffuni
219*a893be29SPedro GiffuniFinalExit:
220*a893be29SPedro Giffuni
221*a893be29SPedro Giffuni
222*a893be29SPedro Giffuni    If Not aDoc Is Nothing Then 'If Not IsEmpty(aDoc) Then
223*a893be29SPedro Giffuni        aDoc.Close (False)
224*a893be29SPedro Giffuni    End If
225*a893be29SPedro Giffuni    Set aDoc = Nothing
226*a893be29SPedro Giffuni
227*a893be29SPedro Giffuni    Exit Sub
228*a893be29SPedro Giffuni
229*a893be29SPedro GiffuniHandleErrors:
230*a893be29SPedro Giffuni    ' MsgBox currentFunctionName & " : " & fileName & ": " & Err.Number & " " & Err.Description & " " & Err.Source
231*a893be29SPedro Giffuni    ' Handle Password error on Doc Open, Modify and Cancel
232*a893be29SPedro Giffuni    If Err.Number = 5408 Or Err.Number = 4198 Then
233*a893be29SPedro Giffuni        WriteDebug currentFunctionName & " : " & fileName & ": " & _
234*a893be29SPedro Giffuni            "User entered Invalid Document Password - " & Err.Number & " " & Err.Description & " " & Err.Source
235*a893be29SPedro Giffuni        HandleProtectedDocInvalidPassword mAnalysis, _
236*a893be29SPedro Giffuni            "User entered Invalid Document Password, further analysis not possible", fso
237*a893be29SPedro Giffuni        Resume FinalExit
238*a893be29SPedro Giffuni    ElseIf Err.Number = 5485 Then
239*a893be29SPedro Giffuni        ' Handle Password error on Unprotect Doc
240*a893be29SPedro Giffuni        WriteDebug currentFunctionName & " : " & fileName & ": " & _
241*a893be29SPedro Giffuni            "User entered Invalid Document Part Password, Analysis of doc will continue but will skip analysis of:" & _
242*a893be29SPedro Giffuni            "Forms, Comments, Headers & Footers and Table cell spanning issues - " & Err.Number & " " & Err.Description & " " & Err.Source
243*a893be29SPedro Giffuni        HandleProtectedDocInvalidPassword mAnalysis, _
244*a893be29SPedro Giffuni            "User entered Invalid Document Part Password, Analysis of doc will continue but will skip analysis of:" & vbLf & _
245*a893be29SPedro Giffuni            "Forms, Comments, Headers & Footers and Table cell spanning issues", fso
246*a893be29SPedro Giffuni        bUnprotectError = True
247*a893be29SPedro Giffuni        'wdAllowOnlyComments, wdAllowOnlyFormFields, wdAllowOnlyRevisions
248*a893be29SPedro Giffuni        Resume ContinueFromUnprotectError
249*a893be29SPedro Giffuni    End If
250*a893be29SPedro Giffuni    mAnalysis.Application = RID_STR_COMMON_CANNOT_OPEN
251*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & fileName & ": " & Err.Number & " " & Err.Description & " " & Err.Source
252*a893be29SPedro Giffuni    Resume FinalExit
253*a893be29SPedro GiffuniEnd Sub
254*a893be29SPedro Giffuni
255*a893be29SPedro GiffuniSub DebugMacroInfo()
256*a893be29SPedro Giffuni    MsgBox "TotalNumLines: " & mAnalysis.MacroTotalNumLines & vbLf & _
257*a893be29SPedro Giffuni    "NumUserForms: " & mAnalysis.MacroNumUserForms & vbLf & _
258*a893be29SPedro Giffuni    "NumUserFormControls: " & mAnalysis.MacroNumUserFormControls & vbLf & _
259*a893be29SPedro Giffuni    "NumUserFormControlTypes: " & mAnalysis.MacroNumUserFormControlTypes & vbLf & _
260*a893be29SPedro Giffuni    "NumExternalRefs: " & mAnalysis.MacroNumExternalRefs & vbLf & _
261*a893be29SPedro Giffuni    "MacroNumFieldsUsingMacros: " & mAnalysis.MacroNumFieldsUsingMacros & vbLf & _
262*a893be29SPedro Giffuni    "NumOLEControls: " & mAnalysis.MacroNumOLEControls & vbLf & _
263*a893be29SPedro Giffuni    "MacroOverallClass: " & getDocOverallMacroClassAsString(mAnalysis.MacroOverallClass)
264*a893be29SPedro GiffuniEnd Sub
265*a893be29SPedro Giffuni
266*a893be29SPedro GiffuniSub SetDocProperties(docAnalysis As DocumentAnalysis, doc As Document, fso As FileSystemObject)
267*a893be29SPedro Giffuni    On Error GoTo HandleErrors
268*a893be29SPedro Giffuni    Dim currentFunctionName As String
269*a893be29SPedro Giffuni    currentFunctionName = "SetProperties"
270*a893be29SPedro Giffuni    Dim f As File
271*a893be29SPedro Giffuni    Set f = fso.GetFile(docAnalysis.name)
272*a893be29SPedro Giffuni
273*a893be29SPedro Giffuni    docAnalysis.PageCount = doc.ComputeStatistics(wdStatisticPages)
274*a893be29SPedro Giffuni    docAnalysis.Accessed = f.DateLastAccessed
275*a893be29SPedro Giffuni
276*a893be29SPedro Giffuni    On Error Resume Next 'Some apps may not support all props
277*a893be29SPedro Giffuni    docAnalysis.Application = getAppSpecificApplicationName & " " & Application.Version
278*a893be29SPedro Giffuni    'docAnalysis.Application = doc.BuiltinDocumentProperties(wdPropertyAppName)
279*a893be29SPedro Giffuni    'If InStr(docAnalysis.Application, "Microsoft") = 1 Then
280*a893be29SPedro Giffuni    '    docAnalysis.Application = Mid(docAnalysis.Application, Len("Microsoft") + 2)
281*a893be29SPedro Giffuni    'End If
282*a893be29SPedro Giffuni    'If InStr(Len(docAnalysis.Application) - 2, docAnalysis.Application, ".") = 0 Then
283*a893be29SPedro Giffuni    '    docAnalysis.Application = docAnalysis.Application & " " & Application.Version
284*a893be29SPedro Giffuni    'End If
285*a893be29SPedro Giffuni
286*a893be29SPedro Giffuni    docAnalysis.Created = _
287*a893be29SPedro Giffuni        doc.BuiltInDocumentProperties(wdPropertyTimeCreated)
288*a893be29SPedro Giffuni    docAnalysis.Modified = _
289*a893be29SPedro Giffuni        doc.BuiltInDocumentProperties(wdPropertyTimeLastSaved)
290*a893be29SPedro Giffuni    docAnalysis.Printed = _
291*a893be29SPedro Giffuni        doc.BuiltInDocumentProperties(wdPropertyTimeLastPrinted)
292*a893be29SPedro Giffuni    docAnalysis.SavedBy = _
293*a893be29SPedro Giffuni        doc.BuiltInDocumentProperties(wdPropertyLastAuthor)
294*a893be29SPedro Giffuni    docAnalysis.Revision = _
295*a893be29SPedro Giffuni        val(doc.BuiltInDocumentProperties(wdPropertyRevision))
296*a893be29SPedro Giffuni    docAnalysis.Template = _
297*a893be29SPedro Giffuni        fso.GetFileName(doc.BuiltInDocumentProperties(wdPropertyTemplate))
298*a893be29SPedro Giffuni
299*a893be29SPedro GiffuniFinalExit:
300*a893be29SPedro Giffuni    Set f = Nothing
301*a893be29SPedro Giffuni    Exit Sub
302*a893be29SPedro Giffuni
303*a893be29SPedro GiffuniHandleErrors:
304*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
305*a893be29SPedro Giffuni    Resume FinalExit
306*a893be29SPedro GiffuniEnd Sub
307*a893be29SPedro Giffuni
308*a893be29SPedro Giffuni'Limitation: Detect first level table in tables, does not detect further nesting
309*a893be29SPedro Giffuni'Can do so if required
310*a893be29SPedro GiffuniSub Analyze_Tables_TablesInTables(currDoc As Document)
311*a893be29SPedro Giffuni    On Error GoTo HandleErrors
312*a893be29SPedro Giffuni    Dim currentFunctionName As String
313*a893be29SPedro Giffuni    currentFunctionName = "Analyze_Tables_TablesInTables"
314*a893be29SPedro Giffuni    Dim myTopTable As Table
315*a893be29SPedro Giffuni    Dim myInnerTable As Table
316*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
317*a893be29SPedro Giffuni
318*a893be29SPedro Giffuni    For Each myTopTable In currDoc.Tables
319*a893be29SPedro Giffuni        For Each myInnerTable In myTopTable.Tables
320*a893be29SPedro Giffuni            Dim logString As String
321*a893be29SPedro Giffuni            Dim myRng As Range
322*a893be29SPedro Giffuni            Dim startpage As Long
323*a893be29SPedro Giffuni            Dim startRow As Long
324*a893be29SPedro Giffuni            Dim StartColumn As Long
325*a893be29SPedro Giffuni            Dim details As String
326*a893be29SPedro Giffuni
327*a893be29SPedro Giffuni            Set myIssue = New IssueInfo
328*a893be29SPedro Giffuni            Set myRng = myInnerTable.Range
329*a893be29SPedro Giffuni            myRng.start = myRng.End
330*a893be29SPedro Giffuni            startpage = myRng.Information(wdActiveEndPageNumber)
331*a893be29SPedro Giffuni            startRow = myRng.Information(wdStartOfRangeRowNumber)
332*a893be29SPedro Giffuni            StartColumn = myRng.Information(wdStartOfRangeColumnNumber)
333*a893be29SPedro Giffuni
334*a893be29SPedro Giffuni            With myIssue
335*a893be29SPedro Giffuni                .IssueID = CID_TABLES
336*a893be29SPedro Giffuni                .IssueType = RID_STR_WORD_ISSUE_TABLES
337*a893be29SPedro Giffuni                .SubType = RID_STR_WORD_SUBISSUE_NESTED_TABLES
338*a893be29SPedro Giffuni                .Location = .CLocationPage
339*a893be29SPedro Giffuni                .SubLocation = startpage
340*a893be29SPedro Giffuni
341*a893be29SPedro Giffuni                .IssueTypeXML = CSTR_ISSUE_TABLES
342*a893be29SPedro Giffuni                .SubTypeXML = CSTR_SUBISSUE_NESTED_TABLES
343*a893be29SPedro Giffuni                .locationXML = .CXMLLocationPage
344*a893be29SPedro Giffuni
345*a893be29SPedro Giffuni                .Attributes.Add RID_STR_WORD_ATTRIBUTE_OUTER_TABLE
346*a893be29SPedro Giffuni                .Values.Add myTopTable.Rows.count & "x" & myTopTable.Columns.count
347*a893be29SPedro Giffuni                .Attributes.Add RID_STR_WORD_ATTRIBUTE_INNER_TABLE
348*a893be29SPedro Giffuni                .Values.Add myInnerTable.Rows.count & "x" & myInnerTable.Columns.count
349*a893be29SPedro Giffuni                .Attributes.Add RID_STR_WORD_ATTRIBUTE_START_ROW
350*a893be29SPedro Giffuni                .Values.Add startRow
351*a893be29SPedro Giffuni                .Attributes.Add RID_STR_WORD_ATTRIBUTE_START_COL
352*a893be29SPedro Giffuni                .Values.Add StartColumn
353*a893be29SPedro Giffuni                AddIssueDetailsNote myIssue, 0, RID_STR_WORD_NOTE_NESTED_TABLE_WILL_BE_LOST
354*a893be29SPedro Giffuni
355*a893be29SPedro Giffuni                mAnalysis.IssuesCountArray(CID_TABLES) = _
356*a893be29SPedro Giffuni                    mAnalysis.IssuesCountArray(CID_TABLES) + 1
357*a893be29SPedro Giffuni            End With
358*a893be29SPedro Giffuni
359*a893be29SPedro Giffuni            mAnalysis.Issues.Add myIssue
360*a893be29SPedro Giffuni            Set myIssue = Nothing
361*a893be29SPedro Giffuni            Set myRng = Nothing
362*a893be29SPedro Giffuni        Next
363*a893be29SPedro Giffuni    Next
364*a893be29SPedro Giffuni    Exit Sub
365*a893be29SPedro GiffuniHandleErrors:
366*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
367*a893be29SPedro GiffuniEnd Sub
368*a893be29SPedro Giffuni
369*a893be29SPedro GiffuniSub Analyze_Document_Protection(currDoc As Document)
370*a893be29SPedro Giffuni    On Error GoTo HandleErrors
371*a893be29SPedro Giffuni    Dim currentFunctionName As String
372*a893be29SPedro Giffuni    currentFunctionName = "Analyze_Document_Protection"
373*a893be29SPedro Giffuni    If currDoc.ProtectionType = wdNoProtection Then
374*a893be29SPedro Giffuni        Exit Sub
375*a893be29SPedro Giffuni    End If
376*a893be29SPedro Giffuni
377*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
378*a893be29SPedro Giffuni    Set myIssue = New IssueInfo
379*a893be29SPedro Giffuni
380*a893be29SPedro Giffuni    With myIssue
381*a893be29SPedro Giffuni        .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
382*a893be29SPedro Giffuni        .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
383*a893be29SPedro Giffuni        .SubType = RID_STR_COMMON_SUBISSUE_DOCUMENT_PARTS_PROTECTION
384*a893be29SPedro Giffuni        .Location = .CLocationDocument
385*a893be29SPedro Giffuni
386*a893be29SPedro Giffuni        .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
387*a893be29SPedro Giffuni        .SubTypeXML = CSTR_SUBISSUE_DOCUMENT_PARTS_PROTECTION
388*a893be29SPedro Giffuni        .locationXML = .CXMLLocationDocument
389*a893be29SPedro Giffuni
390*a893be29SPedro Giffuni        .Attributes.Add RID_STR_WORD_ATTRIBUTE_PROTECTION
391*a893be29SPedro Giffuni        Select Case currDoc.ProtectionType
392*a893be29SPedro Giffuni            Case wdAllowOnlyComments
393*a893be29SPedro Giffuni                .Values.Add RID_STR_WORD_ATTRIBUTE_ALLOW_ONLY_COMMENTS
394*a893be29SPedro Giffuni            Case wdAllowOnlyFormFields
395*a893be29SPedro Giffuni                .Values.Add RID_STR_WORD_ATTRIBUTE_ALLOW_ONLY_FORM_FIELDS
396*a893be29SPedro Giffuni            Case wdAllowOnlyRevisions
397*a893be29SPedro Giffuni                .Values.Add RID_STR_WORD_ATTRIBUTE_ALLOW_ONLY_REVISIONS
398*a893be29SPedro Giffuni            Case Else
399*a893be29SPedro Giffuni                .Values.Add RID_STR_COMMON_ATTRIBUTE_UNKNOWN
400*a893be29SPedro Giffuni        End Select
401*a893be29SPedro Giffuni
402*a893be29SPedro Giffuni         mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
403*a893be29SPedro Giffuni                mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
404*a893be29SPedro Giffuni    End With
405*a893be29SPedro Giffuni
406*a893be29SPedro Giffuni    mAnalysis.Issues.Add myIssue
407*a893be29SPedro GiffuniFinalExit:
408*a893be29SPedro Giffuni    Set myIssue = Nothing
409*a893be29SPedro Giffuni    Exit Sub
410*a893be29SPedro Giffuni
411*a893be29SPedro GiffuniHandleErrors:
412*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
413*a893be29SPedro Giffuni    Resume FinalExit
414*a893be29SPedro GiffuniEnd Sub
415*a893be29SPedro Giffuni
416*a893be29SPedro GiffuniSub Analyze_Password_Protection(bHasPassword As Boolean, bWriteReserved As Boolean)
417*a893be29SPedro Giffuni    On Error GoTo HandleErrors
418*a893be29SPedro Giffuni    Dim currentFunctionName As String
419*a893be29SPedro Giffuni    currentFunctionName = "Analyze_Password_Protection"
420*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
421*a893be29SPedro Giffuni
422*a893be29SPedro Giffuni    If bHasPassword Or bWriteReserved Then
423*a893be29SPedro Giffuni        Set myIssue = New IssueInfo
424*a893be29SPedro Giffuni
425*a893be29SPedro Giffuni        With myIssue
426*a893be29SPedro Giffuni            .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
427*a893be29SPedro Giffuni            .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
428*a893be29SPedro Giffuni            .SubType = RID_STR_COMMON_SUBISSUE_PASSWORDS_PROTECTION
429*a893be29SPedro Giffuni            .Location = .CLocationDocument
430*a893be29SPedro Giffuni
431*a893be29SPedro Giffuni            .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
432*a893be29SPedro Giffuni            .SubTypeXML = CSTR_SUBISSUE_PASSWORDS_PROTECTION
433*a893be29SPedro Giffuni            .locationXML = .CXMLLocationDocument
434*a893be29SPedro Giffuni
435*a893be29SPedro Giffuni            If bHasPassword Then
436*a893be29SPedro Giffuni                .Attributes.Add RID_STR_WORD_ATTRIBUTE_PASSWORD_TO_OPEN
437*a893be29SPedro Giffuni                .Values.Add RID_STR_WORD_ATTRIBUTE_SET
438*a893be29SPedro Giffuni            End If
439*a893be29SPedro Giffuni            If bWriteReserved Then
440*a893be29SPedro Giffuni                .Attributes.Add RID_STR_WORD_ATTRIBUTE_PASSWORD_TO_MODIFY
441*a893be29SPedro Giffuni                .Values.Add RID_STR_WORD_ATTRIBUTE_SET
442*a893be29SPedro Giffuni            End If
443*a893be29SPedro Giffuni
444*a893be29SPedro Giffuni            mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
445*a893be29SPedro Giffuni                    mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
446*a893be29SPedro Giffuni        End With
447*a893be29SPedro Giffuni
448*a893be29SPedro Giffuni        mAnalysis.Issues.Add myIssue
449*a893be29SPedro Giffuni    End If
450*a893be29SPedro GiffuniFinalExit:
451*a893be29SPedro Giffuni    Set myIssue = Nothing
452*a893be29SPedro Giffuni    Exit Sub
453*a893be29SPedro Giffuni
454*a893be29SPedro GiffuniHandleErrors:
455*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
456*a893be29SPedro Giffuni    Resume FinalExit
457*a893be29SPedro GiffuniEnd Sub
458*a893be29SPedro Giffuni
459*a893be29SPedro GiffuniSub Analyze_OLEEmbedded(currDoc As Document)
460*a893be29SPedro Giffuni    On Error GoTo HandleErrors
461*a893be29SPedro Giffuni    Dim currentFunctionName As String
462*a893be29SPedro Giffuni    currentFunctionName = "Analyze_OLEEmbedded"
463*a893be29SPedro Giffuni
464*a893be29SPedro Giffuni    ' Handle Inline Shapes
465*a893be29SPedro Giffuni    Dim aILShape As InlineShape
466*a893be29SPedro Giffuni    For Each aILShape In currDoc.InlineShapes
467*a893be29SPedro Giffuni        Analyze_OLEEmbeddedSingleInlineShape aILShape
468*a893be29SPedro Giffuni    Next aILShape
469*a893be29SPedro Giffuni
470*a893be29SPedro Giffuni    ' Handle Shapes
471*a893be29SPedro Giffuni    Dim aShape As Shape
472*a893be29SPedro Giffuni    For Each aShape In currDoc.Shapes
473*a893be29SPedro Giffuni        Analyze_OLEEmbeddedSingleShape mAnalysis, aShape, _
474*a893be29SPedro Giffuni            Selection.Information(wdActiveEndPageNumber)
475*a893be29SPedro Giffuni        Analyze_Lines mAnalysis, aShape, _
476*a893be29SPedro Giffuni            Selection.Information(wdActiveEndPageNumber)
477*a893be29SPedro Giffuni        Analyze_Transparency mAnalysis, aShape, _
478*a893be29SPedro Giffuni            Selection.Information(wdActiveEndPageNumber)
479*a893be29SPedro Giffuni        Analyze_Gradients mAnalysis, aShape, _
480*a893be29SPedro Giffuni            Selection.Information(wdActiveEndPageNumber)
481*a893be29SPedro Giffuni    Next aShape
482*a893be29SPedro Giffuni
483*a893be29SPedro Giffuni    Exit Sub
484*a893be29SPedro Giffuni
485*a893be29SPedro GiffuniHandleErrors:
486*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
487*a893be29SPedro GiffuniEnd Sub
488*a893be29SPedro Giffuni
489*a893be29SPedro Giffuni
490*a893be29SPedro Giffuni'WdInlineShapeType constants:
491*a893be29SPedro Giffuni'wdInlineShapeEmbeddedOLEObject, wdInlineShapeHorizontalLine, wdInlineShapeLinkedOLEObject,
492*a893be29SPedro Giffuni'wdInlineShapeLinkedPicture, wdInlineShapeLinkedPictureHorizontalLine, wdInlineShapeOLEControlObject,
493*a893be29SPedro Giffuni'wdInlineShapeOWSAnchor, wdInlineShapePicture, wdInlineShapePictureBullet,
494*a893be29SPedro Giffuni'wdInlineShapePictureHorizontalLine, wdInlineShapeScriptAnchor
495*a893be29SPedro Giffuni
496*a893be29SPedro GiffuniSub Analyze_OLEEmbeddedSingleInlineShape(aILShape As InlineShape)
497*a893be29SPedro Giffuni    On Error GoTo HandleErrors
498*a893be29SPedro Giffuni    Dim currentFunctionName As String
499*a893be29SPedro Giffuni    currentFunctionName = "Analyze_OLEEmbeddedSingleInlineShape"
500*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
501*a893be29SPedro Giffuni    Dim bOleObject As Boolean
502*a893be29SPedro Giffuni    Dim TypeAsString As String
503*a893be29SPedro Giffuni    Dim XMLTypeAsString As String
504*a893be29SPedro Giffuni    Dim objName As String
505*a893be29SPedro Giffuni
506*a893be29SPedro Giffuni    bOleObject = (aILShape.Type = wdInlineShapeEmbeddedOLEObject) Or _
507*a893be29SPedro Giffuni                    (aILShape.Type = wdInlineShapeLinkedOLEObject) Or _
508*a893be29SPedro Giffuni                    (aILShape.Type = wdInlineShapeOLEControlObject)
509*a893be29SPedro Giffuni
510*a893be29SPedro Giffuni    If Not bOleObject Then Exit Sub
511*a893be29SPedro Giffuni
512*a893be29SPedro Giffuni    aILShape.Select
513*a893be29SPedro Giffuni    Select Case aILShape.Type
514*a893be29SPedro Giffuni        Case wdInlineShapeOLEControlObject
515*a893be29SPedro Giffuni            TypeAsString = RID_STR_COMMON_OLE_CONTROL
516*a893be29SPedro Giffuni            XMLTypeAsString = CSTR_SUBISSUE_OLE_CONTROL
517*a893be29SPedro Giffuni        Case wdInlineShapeEmbeddedOLEObject
518*a893be29SPedro Giffuni            TypeAsString = RID_STR_COMMON_OLE_EMBEDDED
519*a893be29SPedro Giffuni            XMLTypeAsString = CSTR_SUBISSUE_OLE_EMBEDDED
520*a893be29SPedro Giffuni        Case wdInlineShapeLinkedOLEObject
521*a893be29SPedro Giffuni            TypeAsString = RID_STR_COMMON_OLE_LINKED
522*a893be29SPedro Giffuni            XMLTypeAsString = CSTR_SUBISSUE_OLE_LINKED
523*a893be29SPedro Giffuni        Case Else
524*a893be29SPedro Giffuni            TypeAsString = RID_STR_COMMON_OLE_UNKNOWN
525*a893be29SPedro Giffuni            XMLTypeAsString = CSTR_SUBISSUE_OLE_UNKNOWN
526*a893be29SPedro Giffuni    End Select
527*a893be29SPedro Giffuni
528*a893be29SPedro Giffuni    Set myIssue = New IssueInfo
529*a893be29SPedro Giffuni    With myIssue
530*a893be29SPedro Giffuni        .IssueID = CID_PORTABILITY
531*a893be29SPedro Giffuni        .IssueType = RID_STR_COMMON_ISSUE_PORTABILITY
532*a893be29SPedro Giffuni        .SubType = TypeAsString
533*a893be29SPedro Giffuni        .Location = .CLocationPage
534*a893be29SPedro Giffuni        .SubLocation = Selection.Information(wdActiveEndPageNumber)
535*a893be29SPedro Giffuni
536*a893be29SPedro Giffuni        .IssueTypeXML = CSTR_ISSUE_PORTABILITY
537*a893be29SPedro Giffuni        .SubTypeXML = XMLTypeAsString
538*a893be29SPedro Giffuni        .locationXML = .CXMLLocationPage
539*a893be29SPedro Giffuni
540*a893be29SPedro Giffuni        .Line = Selection.Information(wdFirstCharacterLineNumber)
541*a893be29SPedro Giffuni        .column = Selection.Information(wdFirstCharacterColumnNumber)
542*a893be29SPedro Giffuni
543*a893be29SPedro Giffuni        DoEvents
544*a893be29SPedro Giffuni        If aILShape.Type = wdInlineShapeEmbeddedOLEObject Or _
545*a893be29SPedro Giffuni           aILShape.Type = wdInlineShapeOLEControlObject Then
546*a893be29SPedro Giffuni
547*a893be29SPedro Giffuni            'If Object is invalid can get automation server hanging
548*a893be29SPedro Giffuni            Dim tmpStr As String
549*a893be29SPedro Giffuni            On Error Resume Next
550*a893be29SPedro Giffuni            tmpStr = aILShape.OLEFormat.Object
551*a893be29SPedro Giffuni            If Err.Number = 0 Then
552*a893be29SPedro Giffuni                .Attributes.Add RID_STR_COMMON_ATTRIBUTE_OBJECT_TYPE
553*a893be29SPedro Giffuni                .Values.Add aILShape.OLEFormat.ProgID
554*a893be29SPedro Giffuni            Else
555*a893be29SPedro Giffuni                Err.Clear
556*a893be29SPedro Giffuni                tmpStr = aILShape.OLEFormat.ClassType
557*a893be29SPedro Giffuni                If Err.Number = 0 Then
558*a893be29SPedro Giffuni                    .Attributes.Add RID_STR_COMMON_ATTRIBUTE_OBJECT_TYPE
559*a893be29SPedro Giffuni                    .Values.Add aILShape.OLEFormat.ClassType
560*a893be29SPedro Giffuni                Else
561*a893be29SPedro Giffuni                    .Attributes.Add RID_STR_COMMON_ATTRIBUTE_OBJECT_TYPE
562*a893be29SPedro Giffuni                    .Values.Add RID_STR_COMMON_NA
563*a893be29SPedro Giffuni                End If
564*a893be29SPedro Giffuni            End If
565*a893be29SPedro Giffuni
566*a893be29SPedro Giffuni            If aILShape.Type = wdInlineShapeOLEControlObject Then
567*a893be29SPedro Giffuni                mAnalysis.MacroNumOLEControls = 1 + mAnalysis.MacroNumOLEControls
568*a893be29SPedro Giffuni            End If
569*a893be29SPedro Giffuni
570*a893be29SPedro Giffuni            objName = aILShape.OLEFormat.Object.name
571*a893be29SPedro Giffuni            If Err.Number = 0 Then
572*a893be29SPedro Giffuni                .Attributes.Add RID_STR_COMMON_ATTRIBUTE_OBJECT_NAME
573*a893be29SPedro Giffuni                .Values.Add objName
574*a893be29SPedro Giffuni            End If
575*a893be29SPedro Giffuni            On Error GoTo HandleErrors
576*a893be29SPedro Giffuni        End If
577*a893be29SPedro Giffuni        If aILShape.Type = wdInlineShapeLinkedOLEObject Then
578*a893be29SPedro Giffuni            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_SOURCE
579*a893be29SPedro Giffuni            .Values.Add aILShape.LinkFormat.SourceFullName
580*a893be29SPedro Giffuni        End If
581*a893be29SPedro Giffuni
582*a893be29SPedro Giffuni        mAnalysis.IssuesCountArray(CID_PORTABILITY) = _
583*a893be29SPedro Giffuni            mAnalysis.IssuesCountArray(CID_PORTABILITY) + 1
584*a893be29SPedro Giffuni    End With
585*a893be29SPedro Giffuni
586*a893be29SPedro Giffuni    mAnalysis.Issues.Add myIssue
587*a893be29SPedro Giffuni
588*a893be29SPedro GiffuniFinalExit:
589*a893be29SPedro Giffuni    Set myIssue = Nothing
590*a893be29SPedro Giffuni    Exit Sub
591*a893be29SPedro Giffuni
592*a893be29SPedro GiffuniHandleErrors:
593*a893be29SPedro Giffuni    WriteDebugLevelTwo currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
594*a893be29SPedro Giffuni    Resume FinalExit
595*a893be29SPedro GiffuniEnd Sub
596*a893be29SPedro Giffuni
597*a893be29SPedro Giffuni'Appears to be picked up by other OLE analysis code - the Shapes are actually field codes
598*a893be29SPedro Giffuni'So I get double reporting if I use this as well.
599*a893be29SPedro GiffuniSub Analyze_OLEFields(myField As Field)
600*a893be29SPedro Giffuni    On Error GoTo HandleErrors
601*a893be29SPedro Giffuni    Dim currentFunctionName As String
602*a893be29SPedro Giffuni    currentFunctionName = "Analyze_OLEFields"
603*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
604*a893be29SPedro Giffuni    Dim bOleObject As Boolean
605*a893be29SPedro Giffuni    Dim TypeAsString As String
606*a893be29SPedro Giffuni    Dim XMLTypeAsString As String
607*a893be29SPedro Giffuni
608*a893be29SPedro Giffuni    bOleObject = (myField.Type = wdFieldOCX)
609*a893be29SPedro Giffuni
610*a893be29SPedro Giffuni    If Not bOleObject Then Exit Sub
611*a893be29SPedro Giffuni
612*a893be29SPedro Giffuni    myField.Select
613*a893be29SPedro Giffuni    Select Case myField.Type
614*a893be29SPedro Giffuni        Case wdFieldLink
615*a893be29SPedro Giffuni            TypeAsString = RID_STR_COMMON_OLE_FIELD_LINK
616*a893be29SPedro Giffuni            XMLTypeAsString = CSTR_SUBISSUE_OLE_FIELD_LINK
617*a893be29SPedro Giffuni        Case Else
618*a893be29SPedro Giffuni            TypeAsString = RID_STR_COMMON_OLE_UNKNOWN
619*a893be29SPedro Giffuni            XMLTypeAsString = CSTR_SUBISSUE_OLE_UNKNOWN
620*a893be29SPedro Giffuni    End Select
621*a893be29SPedro Giffuni    Set myIssue = New IssueInfo
622*a893be29SPedro Giffuni    With myIssue
623*a893be29SPedro Giffuni        .IssueID = CID_PORTABILITY
624*a893be29SPedro Giffuni        .IssueType = RID_STR_COMMON_ISSUE_PORTABILITY
625*a893be29SPedro Giffuni        .SubType = TypeAsString
626*a893be29SPedro Giffuni        .Location = .CLocationPage
627*a893be29SPedro Giffuni        .SubLocation = Selection.Information(wdActiveEndPageNumber)
628*a893be29SPedro Giffuni
629*a893be29SPedro Giffuni        .IssueTypeXML = CSTR_ISSUE_PORTABILITY
630*a893be29SPedro Giffuni        .SubTypeXML = XMLTypeAsString
631*a893be29SPedro Giffuni        .locationXML = .CXMLLocationPage
632*a893be29SPedro Giffuni
633*a893be29SPedro Giffuni        .Line = Selection.Information(wdFirstCharacterLineNumber)
634*a893be29SPedro Giffuni        .column = Selection.Information(wdFirstCharacterColumnNumber)
635*a893be29SPedro Giffuni        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_OBJECT_TYPE
636*a893be29SPedro Giffuni        .Values.Add myField.OLEFormat.ClassType
637*a893be29SPedro Giffuni
638*a893be29SPedro Giffuni        If myField.Type = wdFieldLink Then
639*a893be29SPedro Giffuni            .Attributes.Add RID_STR_WORD_ATTRIBUTE_LINK
640*a893be29SPedro Giffuni            .Values.Add myField.LinkFormat.SourceFullName
641*a893be29SPedro Giffuni        End If
642*a893be29SPedro Giffuni        mAnalysis.IssuesCountArray(CID_PORTABILITY) = _
643*a893be29SPedro Giffuni            mAnalysis.IssuesCountArray(CID_PORTABILITY) + 1
644*a893be29SPedro Giffuni    End With
645*a893be29SPedro Giffuni    mAnalysis.Issues.Add myIssue
646*a893be29SPedro Giffuni
647*a893be29SPedro Giffuni    Set myIssue = Nothing
648*a893be29SPedro Giffuni
649*a893be29SPedro Giffuni    Exit Sub
650*a893be29SPedro Giffuni
651*a893be29SPedro GiffuniHandleErrors:
652*a893be29SPedro Giffuni    Set myIssue = Nothing
653*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
654*a893be29SPedro GiffuniEnd Sub
655*a893be29SPedro Giffuni
656*a893be29SPedro GiffuniSub Analyze_MailMergeField(myField As Field)
657*a893be29SPedro Giffuni    On Error GoTo HandleErrors
658*a893be29SPedro Giffuni    Dim currentFunctionName As String
659*a893be29SPedro Giffuni    currentFunctionName = "Analyze_MailMergeField"
660*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
661*a893be29SPedro Giffuni    Dim TypeAsString As String
662*a893be29SPedro Giffuni    Dim bProblemMailMergeField As Boolean
663*a893be29SPedro Giffuni
664*a893be29SPedro Giffuni    bProblemMailMergeField = _
665*a893be29SPedro Giffuni        (myField.Type = wdFieldFillIn) Or _
666*a893be29SPedro Giffuni        (myField.Type = wdFieldAsk) Or _
667*a893be29SPedro Giffuni        (myField.Type = wdFieldMergeRec) Or _
668*a893be29SPedro Giffuni        (myField.Type = wdFieldMergeField) Or _
669*a893be29SPedro Giffuni        (myField.Type = wdFieldNext) Or _
670*a893be29SPedro Giffuni        (myField.Type = wdFieldRevisionNum) Or _
671*a893be29SPedro Giffuni        (myField.Type = wdFieldSequence) Or _
672*a893be29SPedro Giffuni        (myField.Type = wdFieldAutoNum) Or _
673*a893be29SPedro Giffuni        (myField.Type = wdFieldAutoNumOutline) Or _
674*a893be29SPedro Giffuni        (myField.Type = wdFieldAutoNumLegal)
675*a893be29SPedro Giffuni
676*a893be29SPedro Giffuni    If bProblemMailMergeField Then
677*a893be29SPedro Giffuni    'Some of the following are numbering fields and need to be broken out into a separate function. See migration guide.
678*a893be29SPedro Giffuni
679*a893be29SPedro Giffuni        Select Case myField.Type
680*a893be29SPedro Giffuni        Case wdFieldFillIn
681*a893be29SPedro Giffuni            TypeAsString = RID_STR_WORD_ENUMERATION_MAILMERGE_FILL_IN
682*a893be29SPedro Giffuni        Case wdFieldAsk
683*a893be29SPedro Giffuni            TypeAsString = RID_STR_WORD_ENUMERATION_MAILMERGE_ASK
684*a893be29SPedro Giffuni        Case wdFieldMergeRec
685*a893be29SPedro Giffuni            TypeAsString = RID_STR_WORD_ENUMERATION_MAILMERGE_MERGE_RECORDS
686*a893be29SPedro Giffuni        Case wdFieldMergeField
687*a893be29SPedro Giffuni            TypeAsString = RID_STR_WORD_ENUMERATION_MAILMERGE_MERGE_FIELDS
688*a893be29SPedro Giffuni        Case wdFieldNext
689*a893be29SPedro Giffuni            TypeAsString = RID_STR_WORD_ENUMERATION_MAILMERGE_NEXT
690*a893be29SPedro Giffuni        Case wdFieldRevisionNum
691*a893be29SPedro Giffuni            TypeAsString = RID_STR_WORD_ENUMERATION_MAILMERGE_REVISION_NUMBER
692*a893be29SPedro Giffuni        Case wdFieldSequence
693*a893be29SPedro Giffuni            TypeAsString = RID_STR_WORD_ENUMERATION_MAILMERGE_SEQUENCE
694*a893be29SPedro Giffuni        Case wdFieldAutoNum
695*a893be29SPedro Giffuni            TypeAsString = RID_STR_WORD_ENUMERATION_MAILMERGE_AUTO_NUMBER
696*a893be29SPedro Giffuni        Case wdFieldAutoNumOutline
697*a893be29SPedro Giffuni            TypeAsString = RID_STR_WORD_ENUMERATION_MAILMERGE_AUTO_NUMBER_OUTLINE
698*a893be29SPedro Giffuni        Case wdFieldAutoNumLegal
699*a893be29SPedro Giffuni            TypeAsString = RID_STR_WORD_ENUMERATION_MAILMERGE_AUTO_NUMBER_LEGAL
700*a893be29SPedro Giffuni        Case Else
701*a893be29SPedro Giffuni            TypeAsString = RID_STR_WORD_ENUMERATION_MAILMERGE_FIELD_NAME_NOT_KNOWN
702*a893be29SPedro Giffuni        End Select
703*a893be29SPedro Giffuni
704*a893be29SPedro Giffuni        Set myIssue = New IssueInfo
705*a893be29SPedro Giffuni        myField.Select
706*a893be29SPedro Giffuni        With myIssue
707*a893be29SPedro Giffuni            .IssueID = CID_FIELDS
708*a893be29SPedro Giffuni            .IssueType = RID_STR_WORD_ISSUE_FIELDS
709*a893be29SPedro Giffuni            .SubType = RID_STR_WORD_SUBISSUE_MAILMERGE_FIELD
710*a893be29SPedro Giffuni            .Location = .CLocationPage
711*a893be29SPedro Giffuni
712*a893be29SPedro Giffuni            .IssueTypeXML = CSTR_ISSUE_FIELDS
713*a893be29SPedro Giffuni            .SubTypeXML = CSTR_SUBISSUE_MAILMERGE_FIELD
714*a893be29SPedro Giffuni            .locationXML = .CXMLLocationPage
715*a893be29SPedro Giffuni
716*a893be29SPedro Giffuni            .SubLocation = Selection.Information(wdActiveEndPageNumber)
717*a893be29SPedro Giffuni            .Line = Selection.Information(wdFirstCharacterLineNumber)
718*a893be29SPedro Giffuni            .column = Selection.Information(wdFirstCharacterColumnNumber)
719*a893be29SPedro Giffuni
720*a893be29SPedro Giffuni            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
721*a893be29SPedro Giffuni            .Values.Add TypeAsString
722*a893be29SPedro Giffuni            If myField.Code.Text <> "" Then
723*a893be29SPedro Giffuni                .Attributes.Add RID_STR_WORD_ATTRIBUTE_TEXT
724*a893be29SPedro Giffuni                .Values.Add myField.Code.Text
725*a893be29SPedro Giffuni            End If
726*a893be29SPedro Giffuni
727*a893be29SPedro Giffuni            mAnalysis.IssuesCountArray(CID_FIELDS) = _
728*a893be29SPedro Giffuni                mAnalysis.IssuesCountArray(CID_FIELDS) + 1
729*a893be29SPedro Giffuni        End With
730*a893be29SPedro Giffuni        mAnalysis.Issues.Add myIssue
731*a893be29SPedro Giffuni        Set myIssue = Nothing
732*a893be29SPedro Giffuni    End If
733*a893be29SPedro Giffuni    Exit Sub
734*a893be29SPedro Giffuni
735*a893be29SPedro GiffuniHandleErrors:
736*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
737*a893be29SPedro GiffuniEnd Sub
738*a893be29SPedro Giffuni
739*a893be29SPedro Giffuni'Get field DS Info
740*a893be29SPedro GiffuniSub Analyze_MailMerge_DataSource(currDoc As Document)
741*a893be29SPedro Giffuni    On Error GoTo HandleErrors
742*a893be29SPedro Giffuni    Dim currentFunctionName As String
743*a893be29SPedro Giffuni    currentFunctionName = "Analyze_MailMerge_DataSource"
744*a893be29SPedro Giffuni    ' There may be no mail merge in the document
745*a893be29SPedro Giffuni    If (currDoc.MailMerge.DataSource.Type = wdNoMergeInfo) Then
746*a893be29SPedro Giffuni        Exit Sub
747*a893be29SPedro Giffuni    End If
748*a893be29SPedro Giffuni
749*a893be29SPedro Giffuni    'Dim issue As SimpleAnalysisInfo
750*a893be29SPedro Giffuni    If (currDoc.MailMerge.DataSource.Type <> wdNoMergeInfo) Then
751*a893be29SPedro Giffuni        Dim myIssue As IssueInfo
752*a893be29SPedro Giffuni        Set myIssue = New IssueInfo
753*a893be29SPedro Giffuni        With myIssue
754*a893be29SPedro Giffuni            .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
755*a893be29SPedro Giffuni            .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
756*a893be29SPedro Giffuni            .SubType = RID_STR_WORD_SUBISSUE_MAILMERGE_DATASOURCE
757*a893be29SPedro Giffuni            .Location = .CLocationDocument
758*a893be29SPedro Giffuni
759*a893be29SPedro Giffuni            .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
760*a893be29SPedro Giffuni            .SubTypeXML = CSTR_SUBISSUE_MAILMERGE_DATASOURCE
761*a893be29SPedro Giffuni            .locationXML = .CXMLLocationDocument
762*a893be29SPedro Giffuni
763*a893be29SPedro Giffuni            .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
764*a893be29SPedro Giffuni            .Values.Add currDoc.MailMerge.DataSource.name
765*a893be29SPedro Giffuni            .Attributes.Add RID_STR_WORD_ATTRIBUTE_DATASOURCE
766*a893be29SPedro Giffuni            .Values.Add currDoc.MailMerge.DataSource.Type
767*a893be29SPedro Giffuni
768*a893be29SPedro Giffuni            mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
769*a893be29SPedro Giffuni                mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
770*a893be29SPedro Giffuni        End With
771*a893be29SPedro Giffuni
772*a893be29SPedro Giffuni        mAnalysis.Issues.Add myIssue
773*a893be29SPedro Giffuni        Set myIssue = Nothing
774*a893be29SPedro Giffuni   End If
775*a893be29SPedro Giffuni   Exit Sub
776*a893be29SPedro Giffuni
777*a893be29SPedro GiffuniHandleErrors:
778*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
779*a893be29SPedro GiffuniEnd Sub
780*a893be29SPedro Giffuni
781*a893be29SPedro GiffuniFunction getFormFieldTypeAsString(fieldType As WdFieldType)
782*a893be29SPedro Giffuni    Dim Str As String
783*a893be29SPedro Giffuni
784*a893be29SPedro Giffuni    Select Case fieldType
785*a893be29SPedro Giffuni    Case wdFieldFormCheckBox
786*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_CHECK_BOX
787*a893be29SPedro Giffuni    Case wdFieldFormDropDown
788*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_DROP_DOWN
789*a893be29SPedro Giffuni    Case wdFieldFormTextInput
790*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_TEXT
791*a893be29SPedro Giffuni    Case Else
792*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_UNKNOWN
793*a893be29SPedro Giffuni    End Select
794*a893be29SPedro Giffuni
795*a893be29SPedro Giffuni    getFormFieldTypeAsString = Str
796*a893be29SPedro GiffuniEnd Function
797*a893be29SPedro GiffuniFunction getTextFormFieldTypeAsString(fieldType As WdTextFormFieldType)
798*a893be29SPedro Giffuni    Dim Str As String
799*a893be29SPedro Giffuni
800*a893be29SPedro Giffuni    Select Case fieldType
801*a893be29SPedro Giffuni    Case wdCalculationText
802*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_CALCULATION
803*a893be29SPedro Giffuni    Case wdCurrentDateText
804*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_CURRENT_DATE
805*a893be29SPedro Giffuni    Case wdCurrentTimeText
806*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_CURRENT_TIME
807*a893be29SPedro Giffuni    Case wdDateText
808*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_DATE
809*a893be29SPedro Giffuni    Case wdNumberText
810*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_NUMBER
811*a893be29SPedro Giffuni    Case wdRegularText
812*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_REGULAR
813*a893be29SPedro Giffuni    Case Else
814*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_UNKNOWN
815*a893be29SPedro Giffuni    End Select
816*a893be29SPedro Giffuni
817*a893be29SPedro Giffuni    getTextFormFieldTypeAsString = Str
818*a893be29SPedro GiffuniEnd Function
819*a893be29SPedro GiffuniFunction getTextFormFieldDefaultAsString(fieldType As WdTextFormFieldType)
820*a893be29SPedro Giffuni    Dim Str As String
821*a893be29SPedro Giffuni
822*a893be29SPedro Giffuni    Select Case fieldType
823*a893be29SPedro Giffuni    Case wdCalculationText
824*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_DEFAULT_EXPRESSION
825*a893be29SPedro Giffuni    Case wdCurrentDateText
826*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_DEFAULT_DATE
827*a893be29SPedro Giffuni    Case wdCurrentTimeText
828*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_DEFAULT_TIME
829*a893be29SPedro Giffuni    Case wdDateText
830*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_DEFAULT_DATE
831*a893be29SPedro Giffuni    Case wdNumberText
832*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_DEFAULT_NUMBER
833*a893be29SPedro Giffuni    Case wdRegularText
834*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_DEFAULT_TEXT
835*a893be29SPedro Giffuni    Case Else
836*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_UNKNOWN
837*a893be29SPedro Giffuni    End Select
838*a893be29SPedro Giffuni
839*a893be29SPedro Giffuni    getTextFormFieldDefaultAsString = Str
840*a893be29SPedro GiffuniEnd Function
841*a893be29SPedro GiffuniFunction getTextFormFieldFormatAsString(fieldType As WdTextFormFieldType)
842*a893be29SPedro Giffuni    Dim Str As String
843*a893be29SPedro Giffuni
844*a893be29SPedro Giffuni    Select Case fieldType
845*a893be29SPedro Giffuni    Case wdCalculationText
846*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_FORMAT_NUMBER
847*a893be29SPedro Giffuni    Case wdCurrentDateText
848*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_FORMAT_DATE
849*a893be29SPedro Giffuni    Case wdCurrentTimeText
850*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_FORMAT_TIME
851*a893be29SPedro Giffuni    Case wdDateText
852*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_FORMAT_DATE
853*a893be29SPedro Giffuni    Case wdNumberText
854*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_FORMAT_NUMBER
855*a893be29SPedro Giffuni    Case wdRegularText
856*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_FORM_FIELD_FORMAT_TEXT
857*a893be29SPedro Giffuni    Case Else
858*a893be29SPedro Giffuni        Str = RID_STR_WORD_ENUMERATION_UNKNOWN
859*a893be29SPedro Giffuni    End Select
860*a893be29SPedro Giffuni
861*a893be29SPedro Giffuni    getTextFormFieldFormatAsString = Str
862*a893be29SPedro GiffuniEnd Function
863*a893be29SPedro Giffuni
864*a893be29SPedro GiffuniSub Analyze_FieldAndFormFieldIssues(currDoc As Document)
865*a893be29SPedro Giffuni    On Error GoTo HandleErrors
866*a893be29SPedro Giffuni    Dim currentFunctionName As String
867*a893be29SPedro Giffuni    currentFunctionName = "Analyze_FormFields"
868*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
869*a893be29SPedro Giffuni
870*a893be29SPedro Giffuni    'Analysze all Fields in doc
871*a893be29SPedro Giffuni    Dim myField As Field
872*a893be29SPedro Giffuni
873*a893be29SPedro Giffuni    For Each myField In currDoc.Fields
874*a893be29SPedro Giffuni        'Analyze Mail Merge Fields
875*a893be29SPedro Giffuni        Analyze_MailMergeField myField
876*a893be29SPedro Giffuni
877*a893be29SPedro Giffuni        'Analyze TOA Fields
878*a893be29SPedro Giffuni        Analyze_TOAField myField
879*a893be29SPedro Giffuni    Next myField
880*a893be29SPedro Giffuni
881*a893be29SPedro Giffuni    'Analyze FormField doc issues
882*a893be29SPedro Giffuni    If currDoc.FormFields.count = 0 Then GoTo FinalExit
883*a893be29SPedro Giffuni
884*a893be29SPedro Giffuni    If (currDoc.FormFields.Shaded) Then
885*a893be29SPedro Giffuni        Set myIssue = New IssueInfo
886*a893be29SPedro Giffuni        With myIssue
887*a893be29SPedro Giffuni            .IssueID = CID_FIELDS
888*a893be29SPedro Giffuni            .IssueType = RID_STR_WORD_ISSUE_FIELDS
889*a893be29SPedro Giffuni            .SubType = RID_STR_WORD_SUBISSUE_APPEARANCE
890*a893be29SPedro Giffuni            .Location = .CLocationDocument
891*a893be29SPedro Giffuni
892*a893be29SPedro Giffuni            .IssueTypeXML = CSTR_ISSUE_FIELDS
893*a893be29SPedro Giffuni            .SubTypeXML = CSTR_SUBISSUE_APPEARANCE
894*a893be29SPedro Giffuni            .locationXML = .CXMLLocationDocument
895*a893be29SPedro Giffuni
896*a893be29SPedro Giffuni            .Attributes.Add RID_STR_WORD_ATTRIBUTE_FORM_FIELD_GREYED
897*a893be29SPedro Giffuni            .Values.Add RID_STR_WORD_TRUE
898*a893be29SPedro Giffuni            mAnalysis.IssuesCountArray(CID_FIELDS) = _
899*a893be29SPedro Giffuni                mAnalysis.IssuesCountArray(CID_FIELDS) + 1
900*a893be29SPedro Giffuni        End With
901*a893be29SPedro Giffuni        mAnalysis.Issues.Add myIssue
902*a893be29SPedro Giffuni        Set myIssue = Nothing
903*a893be29SPedro Giffuni    End If
904*a893be29SPedro Giffuni
905*a893be29SPedro Giffuni    'Analyse all FormFields in doc
906*a893be29SPedro Giffuni    Dim myFormField As FormField
907*a893be29SPedro Giffuni
908*a893be29SPedro Giffuni    For Each myFormField In currDoc.FormFields
909*a893be29SPedro Giffuni        Analyze_FormFieldIssue myFormField
910*a893be29SPedro Giffuni    Next myFormField
911*a893be29SPedro Giffuni
912*a893be29SPedro GiffuniFinalExit:
913*a893be29SPedro Giffuni    Set myIssue = Nothing
914*a893be29SPedro Giffuni    Set myFormField = Nothing
915*a893be29SPedro Giffuni    Exit Sub
916*a893be29SPedro Giffuni
917*a893be29SPedro GiffuniHandleErrors:
918*a893be29SPedro Giffuni
919*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
920*a893be29SPedro Giffuni    Resume FinalExit
921*a893be29SPedro GiffuniEnd Sub
922*a893be29SPedro Giffuni
923*a893be29SPedro GiffuniSub Analyze_FormFieldIssue(myFormField As FormField)
924*a893be29SPedro Giffuni    On Error GoTo HandleErrors
925*a893be29SPedro Giffuni    Dim currentFunctionName As String
926*a893be29SPedro Giffuni    currentFunctionName = "Analyze_FormFieldIssue"
927*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
928*a893be29SPedro Giffuni    Dim bCheckBoxIssues As Boolean
929*a893be29SPedro Giffuni    Dim bFormFieldIssues As Boolean
930*a893be29SPedro Giffuni
931*a893be29SPedro Giffuni    bCheckBoxIssues = False
932*a893be29SPedro Giffuni    If (myFormField.Type = wdFieldFormCheckBox) Then
933*a893be29SPedro Giffuni        If myFormField.CheckBox.AutoSize Then
934*a893be29SPedro Giffuni            bCheckBoxIssues = True
935*a893be29SPedro Giffuni        End If
936*a893be29SPedro Giffuni    End If
937*a893be29SPedro Giffuni
938*a893be29SPedro Giffuni    bFormFieldIssues = bCheckBoxIssues
939*a893be29SPedro Giffuni
940*a893be29SPedro Giffuni    If Not bFormFieldIssues Then GoTo FinalExit
941*a893be29SPedro Giffuni
942*a893be29SPedro Giffuni    myFormField.Select
943*a893be29SPedro Giffuni    Set myIssue = New IssueInfo
944*a893be29SPedro Giffuni    With myIssue
945*a893be29SPedro Giffuni        .IssueID = CID_FIELDS
946*a893be29SPedro Giffuni        .IssueType = RID_STR_WORD_ISSUE_FIELDS
947*a893be29SPedro Giffuni        .SubType = RID_STR_WORD_SUBISSUE_FORM_FIELD
948*a893be29SPedro Giffuni        .Location = .CLocationPage
949*a893be29SPedro Giffuni
950*a893be29SPedro Giffuni        .IssueTypeXML = CSTR_ISSUE_FIELDS
951*a893be29SPedro Giffuni        .SubTypeXML = CSTR_SUBISSUE_FORM_FIELD
952*a893be29SPedro Giffuni        .locationXML = .CXMLLocationPage
953*a893be29SPedro Giffuni
954*a893be29SPedro Giffuni        .SubLocation = Selection.Information(wdActiveEndPageNumber)
955*a893be29SPedro Giffuni        .Line = Selection.Information(wdFirstCharacterLineNumber)
956*a893be29SPedro Giffuni        .column = Selection.Information(wdFirstCharacterColumnNumber)
957*a893be29SPedro Giffuni        myIssue.Attributes.Add RID_STR_COMMON_ATTRIBUTE_TYPE
958*a893be29SPedro Giffuni        myIssue.Values.Add getFormFieldTypeAsString(myFormField.Type)
959*a893be29SPedro Giffuni    End With
960*a893be29SPedro Giffuni
961*a893be29SPedro Giffuni    'Checkbox Issues
962*a893be29SPedro Giffuni    If (myFormField.Type = wdFieldFormCheckBox) Then
963*a893be29SPedro Giffuni       'AutoSize CheckBoxes
964*a893be29SPedro Giffuni        If myFormField.CheckBox.AutoSize Then
965*a893be29SPedro Giffuni            myIssue.Attributes.Add RID_STR_WORD_ATTRIBUTE_FORM_FIELD_AUTOSIZE
966*a893be29SPedro Giffuni            myIssue.Values.Add RID_STR_WORD_TRUE
967*a893be29SPedro Giffuni        End If
968*a893be29SPedro Giffuni    End If
969*a893be29SPedro Giffuni
970*a893be29SPedro Giffuni    'TextInput Issues
971*a893be29SPedro Giffuni    If myFormField.Type = wdFieldFormTextInput Then
972*a893be29SPedro Giffuni        myIssue.Attributes.Add RID_STR_WORD_ATTRIBUTE_FORM_FIELD_TEXT_FORM_FIELD_TYPE
973*a893be29SPedro Giffuni        myIssue.Values.Add getTextFormFieldTypeAsString(myFormField.TextInput.Type)
974*a893be29SPedro Giffuni        Dim bLostType As Boolean
975*a893be29SPedro Giffuni        bLostType = False
976*a893be29SPedro Giffuni        If (myFormField.TextInput.Type = wdCalculationText) Or _
977*a893be29SPedro Giffuni            (myFormField.TextInput.Type = wdCurrentDateText) Or _
978*a893be29SPedro Giffuni            (myFormField.TextInput.Type = wdCurrentTimeText) Then
979*a893be29SPedro Giffuni            AddIssueDetailsNote myIssue, 0, getTextFormFieldTypeAsString(myFormField.TextInput.Type) & _
980*a893be29SPedro Giffuni            " " & RID_STR_WORD_NOTE_FORM_FIELD_TYPE_LOST
981*a893be29SPedro Giffuni            bLostType = True
982*a893be29SPedro Giffuni        End If
983*a893be29SPedro Giffuni
984*a893be29SPedro Giffuni        If (myFormField.TextInput.Format <> "") Then
985*a893be29SPedro Giffuni            myIssue.Attributes.Add getTextFormFieldFormatAsString(myFormField.TextInput.Type)
986*a893be29SPedro Giffuni            myIssue.Values.Add myFormField.TextInput.Format
987*a893be29SPedro Giffuni        End If
988*a893be29SPedro Giffuni
989*a893be29SPedro Giffuni       'Default text
990*a893be29SPedro Giffuni        If (myFormField.TextInput.Default <> "") Then
991*a893be29SPedro Giffuni            myIssue.Attributes.Add getTextFormFieldDefaultAsString(myFormField.TextInput.Type)
992*a893be29SPedro Giffuni            myIssue.Values.Add myFormField.TextInput.Default
993*a893be29SPedro Giffuni        End If
994*a893be29SPedro Giffuni
995*a893be29SPedro Giffuni       'Maximum text
996*a893be29SPedro Giffuni        If (myFormField.TextInput.Width <> 0) Then
997*a893be29SPedro Giffuni            myIssue.Attributes.Add RID_STR_WORD_ATTRIBUTE_FORM_FIELD_MAX_LENGTH
998*a893be29SPedro Giffuni            myIssue.Values.Add myFormField.TextInput.Width
999*a893be29SPedro Giffuni        End If
1000*a893be29SPedro Giffuni
1001*a893be29SPedro Giffuni        'Fill-in disabled
1002*a893be29SPedro Giffuni        If (myFormField.Enabled = False) And (Not bLostType) Then
1003*a893be29SPedro Giffuni            myIssue.Attributes.Add RID_STR_WORD_ATTRIBUTE_FORM_FIELD_FILLIN_ENABLED
1004*a893be29SPedro Giffuni            myIssue.Values.Add RID_STR_WORD_FALSE
1005*a893be29SPedro Giffuni        End If
1006*a893be29SPedro Giffuni    End If
1007*a893be29SPedro Giffuni
1008*a893be29SPedro Giffuni    'Help Key(F1)
1009*a893be29SPedro Giffuni    If (myFormField.OwnHelp And myFormField.HelpText <> "") Then
1010*a893be29SPedro Giffuni        myIssue.Attributes.Add RID_STR_WORD_ATTRIBUTE_FORM_FIELD_HELP_KEY_F1_OWN_TEXT
1011*a893be29SPedro Giffuni        myIssue.Values.Add myFormField.HelpText
1012*a893be29SPedro Giffuni    ElseIf ((Not myFormField.OwnHelp) And myFormField.HelpText <> "") Then
1013*a893be29SPedro Giffuni        myIssue.Attributes.Add RID_STR_WORD_ATTRIBUTE_FORM_FIELD_HELP_KEY_F1_AUTO_TEXT
1014*a893be29SPedro Giffuni        myIssue.Values.Add myFormField.HelpText
1015*a893be29SPedro Giffuni    End If
1016*a893be29SPedro Giffuni
1017*a893be29SPedro Giffuni    'StatusHelp
1018*a893be29SPedro Giffuni    If (myFormField.OwnStatus And myFormField.StatusText <> "") Then
1019*a893be29SPedro Giffuni        myIssue.Attributes.Add RID_STR_WORD_ATTRIBUTE_FORM_FIELD_STATUS_BAR_HELP_OWN_TEXT
1020*a893be29SPedro Giffuni        myIssue.Values.Add myFormField.StatusText
1021*a893be29SPedro Giffuni    ElseIf ((Not myFormField.OwnStatus) And myFormField.StatusText <> "") Then
1022*a893be29SPedro Giffuni        myIssue.Attributes.Add RID_STR_WORD_ATTRIBUTE_FORM_FIELD_STATUS_BAR_HELP_AUTO_TEXT
1023*a893be29SPedro Giffuni        myIssue.Values.Add myFormField.StatusText
1024*a893be29SPedro Giffuni    End If
1025*a893be29SPedro Giffuni
1026*a893be29SPedro Giffuni    'Macros
1027*a893be29SPedro Giffuni    If (myFormField.EntryMacro <> "") Then
1028*a893be29SPedro Giffuni        myIssue.Attributes.Add RID_STR_WORD_ATTRIBUTE_FORM_FIELD_ENTRY_MACRO
1029*a893be29SPedro Giffuni        myIssue.Values.Add myFormField.EntryMacro
1030*a893be29SPedro Giffuni    End If
1031*a893be29SPedro Giffuni    If (myFormField.ExitMacro <> "") Then
1032*a893be29SPedro Giffuni        myIssue.Attributes.Add RID_STR_WORD_ATTRIBUTE_FORM_FIELD_EXIT_MACRO
1033*a893be29SPedro Giffuni        myIssue.Values.Add myFormField.ExitMacro
1034*a893be29SPedro Giffuni    End If
1035*a893be29SPedro Giffuni    If (myFormField.EntryMacro <> "") Or (myFormField.ExitMacro <> "") Then
1036*a893be29SPedro Giffuni        mAnalysis.MacroNumFieldsUsingMacros = 1 + mAnalysis.MacroNumFieldsUsingMacros
1037*a893be29SPedro Giffuni    End If
1038*a893be29SPedro Giffuni
1039*a893be29SPedro Giffuni    'LockedField
1040*a893be29SPedro Giffuni    If (myFormField.Enabled = False) And (myFormField.Type <> wdFieldFormTextInput) Then
1041*a893be29SPedro Giffuni        myIssue.Attributes.Add RID_STR_WORD_ATTRIBUTE_FORM_FIELD_LOCKED
1042*a893be29SPedro Giffuni        myIssue.Values.Add RID_STR_WORD_TRUE
1043*a893be29SPedro Giffuni    End If
1044*a893be29SPedro Giffuni
1045*a893be29SPedro Giffuni    mAnalysis.IssuesCountArray(CID_FIELDS) = _
1046*a893be29SPedro Giffuni        mAnalysis.IssuesCountArray(CID_FIELDS) + 1
1047*a893be29SPedro Giffuni
1048*a893be29SPedro Giffuni    mAnalysis.Issues.Add myIssue
1049*a893be29SPedro Giffuni
1050*a893be29SPedro GiffuniFinalExit:
1051*a893be29SPedro Giffuni    Set myIssue = Nothing
1052*a893be29SPedro Giffuni    Exit Sub
1053*a893be29SPedro Giffuni
1054*a893be29SPedro GiffuniHandleErrors:
1055*a893be29SPedro Giffuni    'Log first occurrence for this doc
1056*a893be29SPedro Giffuni    If Not mbFormFieldErrorLogged Then
1057*a893be29SPedro Giffuni        WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
1058*a893be29SPedro Giffuni        mbFormFieldErrorLogged = True
1059*a893be29SPedro Giffuni    End If
1060*a893be29SPedro Giffuni    Resume FinalExit
1061*a893be29SPedro GiffuniEnd Sub
1062*a893be29SPedro Giffuni
1063*a893be29SPedro Giffuni
1064*a893be29SPedro GiffuniSub Analyze_TOA(currDoc As Document)
1065*a893be29SPedro Giffuni    On Error GoTo HandleErrors
1066*a893be29SPedro Giffuni    Dim currentFunctionName As String
1067*a893be29SPedro Giffuni    currentFunctionName = "Analyze_TOA"
1068*a893be29SPedro Giffuni
1069*a893be29SPedro Giffuni    Dim toa As TableOfAuthorities
1070*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
1071*a893be29SPedro Giffuni    Dim myRng As Range
1072*a893be29SPedro Giffuni
1073*a893be29SPedro Giffuni    For Each toa In currDoc.TablesOfAuthorities
1074*a893be29SPedro Giffuni        Set myRng = toa.Range
1075*a893be29SPedro Giffuni        myRng.start = myRng.End
1076*a893be29SPedro Giffuni        Set myIssue = New IssueInfo
1077*a893be29SPedro Giffuni        myRng.Select
1078*a893be29SPedro Giffuni
1079*a893be29SPedro Giffuni        Dim TabLeaderAsString As String
1080*a893be29SPedro Giffuni        Select Case toa.TabLeader
1081*a893be29SPedro Giffuni            Case wdTabLeaderDashes
1082*a893be29SPedro Giffuni                TabLeaderAsString = RID_STR_WORD_ENUMERATION_INDEX_LEADER_DASHES
1083*a893be29SPedro Giffuni            Case wdTabLeaderDots
1084*a893be29SPedro Giffuni                TabLeaderAsString = RID_STR_WORD_ENUMERATION_INDEX_LEADER_DOTS
1085*a893be29SPedro Giffuni            Case wdTabLeaderHeavy
1086*a893be29SPedro Giffuni                TabLeaderAsString = RID_STR_WORD_ENUMERATION_INDEX_LEADER_HEAVY
1087*a893be29SPedro Giffuni            Case wdTabLeaderLines
1088*a893be29SPedro Giffuni                TabLeaderAsString = RID_STR_WORD_ENUMERATION_INDEX_LEADER_LINES
1089*a893be29SPedro Giffuni            Case wdTabLeaderMiddleDot
1090*a893be29SPedro Giffuni                TabLeaderAsString = RID_STR_WORD_ENUMERATION_INDEX_LEADER_MIDDLEDOT
1091*a893be29SPedro Giffuni            Case wdTabLeaderSpaces
1092*a893be29SPedro Giffuni                TabLeaderAsString = RID_STR_WORD_ENUMERATION_INDEX_LEADER_SPACES
1093*a893be29SPedro Giffuni            Case Else
1094*a893be29SPedro Giffuni                TabLeaderAsString = RID_STR_WORD_ENUMERATION_UNKNOWN
1095*a893be29SPedro Giffuni        End Select
1096*a893be29SPedro Giffuni
1097*a893be29SPedro Giffuni        Dim FormatAsString As String
1098*a893be29SPedro Giffuni        Select Case currDoc.TablesOfAuthorities.Format
1099*a893be29SPedro Giffuni            Case wdTOAClassic
1100*a893be29SPedro Giffuni                FormatAsString = RID_STR_WORD_ENUMERATION_INDEX_TABLES_CLASSIC
1101*a893be29SPedro Giffuni            Case wdTOADistinctive
1102*a893be29SPedro Giffuni                FormatAsString = RID_STR_WORD_ENUMERATION_INDEX_TABLES_DISTINCTIVE
1103*a893be29SPedro Giffuni            Case wdTOAFormal
1104*a893be29SPedro Giffuni                FormatAsString = RID_STR_WORD_ENUMERATION_INDEX_TABLES_FORMAL
1105*a893be29SPedro Giffuni            Case wdTOASimple
1106*a893be29SPedro Giffuni                FormatAsString = RID_STR_WORD_ENUMERATION_INDEX_TABLES_SIMPLE
1107*a893be29SPedro Giffuni            Case wdTOATemplate
1108*a893be29SPedro Giffuni                FormatAsString = RID_STR_WORD_ENUMERATION_INDEX_TABLES_FROM_TEMPLATE
1109*a893be29SPedro Giffuni            Case Else
1110*a893be29SPedro Giffuni                FormatAsString = RID_STR_WORD_ENUMERATION_UNKNOWN
1111*a893be29SPedro Giffuni        End Select
1112*a893be29SPedro Giffuni
1113*a893be29SPedro Giffuni        With myIssue
1114*a893be29SPedro Giffuni            .IssueID = CID_INDEX_AND_REFERENCES
1115*a893be29SPedro Giffuni            .IssueType = RID_STR_WORD_ISSUE_INDEX_AND_REFERENCES
1116*a893be29SPedro Giffuni            .SubType = RID_STR_WORD_SUBISSUE_TABLE_OF_AUTHORITIES
1117*a893be29SPedro Giffuni            .Location = .CLocationPage
1118*a893be29SPedro Giffuni
1119*a893be29SPedro Giffuni            .IssueTypeXML = CSTR_ISSUE_INDEX_AND_REFERENCES
1120*a893be29SPedro Giffuni            .SubTypeXML = CSTR_SUBISSUE_TABLE_OF_AUTHORITIES
1121*a893be29SPedro Giffuni            .locationXML = .CXMLLocationPage
1122*a893be29SPedro Giffuni
1123*a893be29SPedro Giffuni            .SubLocation = myRng.Information(wdActiveEndPageNumber)
1124*a893be29SPedro Giffuni            .Attributes.Add RID_STR_WORD_ATTRIBUTE_LEADER
1125*a893be29SPedro Giffuni            .Values.Add TabLeaderAsString
1126*a893be29SPedro Giffuni
1127*a893be29SPedro Giffuni            AddIssueDetailsNote myIssue, 0, RID_STR_WORD_NOTE_TOA_MIGRATE_AS_PLAIN_TEXT
1128*a893be29SPedro Giffuni
1129*a893be29SPedro Giffuni            mAnalysis.IssuesCountArray(CID_INDEX_AND_REFERENCES) = _
1130*a893be29SPedro Giffuni                mAnalysis.IssuesCountArray(CID_INDEX_AND_REFERENCES) + 1
1131*a893be29SPedro Giffuni        End With
1132*a893be29SPedro Giffuni
1133*a893be29SPedro Giffuni        mAnalysis.Issues.Add myIssue
1134*a893be29SPedro Giffuni        Set myIssue = Nothing
1135*a893be29SPedro Giffuni        Set myRng = Nothing
1136*a893be29SPedro Giffuni    Next
1137*a893be29SPedro GiffuniFinalExit:
1138*a893be29SPedro Giffuni    Set myIssue = Nothing
1139*a893be29SPedro Giffuni    Set myRng = Nothing
1140*a893be29SPedro Giffuni    Exit Sub
1141*a893be29SPedro Giffuni
1142*a893be29SPedro GiffuniHandleErrors:
1143*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
1144*a893be29SPedro Giffuni    Resume FinalExit
1145*a893be29SPedro GiffuniEnd Sub
1146*a893be29SPedro Giffuni
1147*a893be29SPedro GiffuniSub Analyze_TOAField(myField As Field)
1148*a893be29SPedro Giffuni    On Error GoTo HandleErrors
1149*a893be29SPedro Giffuni    Dim currentFunctionName As String
1150*a893be29SPedro Giffuni    currentFunctionName = "Analyze_TOAField"
1151*a893be29SPedro Giffuni
1152*a893be29SPedro Giffuni    Dim toa As TableOfAuthorities
1153*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
1154*a893be29SPedro Giffuni
1155*a893be29SPedro Giffuni    If myField.Type = wdFieldTOAEntry Then
1156*a893be29SPedro Giffuni        Set myIssue = New IssueInfo
1157*a893be29SPedro Giffuni        myField.Select
1158*a893be29SPedro Giffuni
1159*a893be29SPedro Giffuni        With myIssue
1160*a893be29SPedro Giffuni            .IssueID = CID_FIELDS
1161*a893be29SPedro Giffuni            .IssueType = RID_STR_WORD_ISSUE_FIELDS
1162*a893be29SPedro Giffuni            .SubType = RID_STR_WORD_SUBISSUE_TABLE_OF_AUTHORITIES_FIELD
1163*a893be29SPedro Giffuni            .Location = .CLocationPage
1164*a893be29SPedro Giffuni
1165*a893be29SPedro Giffuni            .IssueTypeXML = CSTR_ISSUE_FIELDS
1166*a893be29SPedro Giffuni            .SubTypeXML = CSTR_SUBISSUE_TABLE_OF_AUTHORITIES_FIELD
1167*a893be29SPedro Giffuni            .locationXML = .CXMLLocationPage
1168*a893be29SPedro Giffuni
1169*a893be29SPedro Giffuni            .SubLocation = Selection.Information(wdActiveEndPageNumber)
1170*a893be29SPedro Giffuni            .Line = Selection.Information(wdFirstCharacterLineNumber)
1171*a893be29SPedro Giffuni            .column = Selection.Information(wdFirstCharacterColumnNumber)
1172*a893be29SPedro Giffuni
1173*a893be29SPedro Giffuni            .Attributes.Add RID_STR_WORD_ATTRIBUTE_FIELD_TEXT
1174*a893be29SPedro Giffuni            .Values.Add myField.Code.Text
1175*a893be29SPedro Giffuni
1176*a893be29SPedro Giffuni            AddIssueDetailsNote myIssue, 0, RID_STR_WORD_NOTE_TOA_FIELD_LOST_ON_ROUNDTRIP
1177*a893be29SPedro Giffuni
1178*a893be29SPedro Giffuni            mAnalysis.IssuesCountArray(CID_FIELDS) = _
1179*a893be29SPedro Giffuni                mAnalysis.IssuesCountArray(CID_FIELDS) + 1
1180*a893be29SPedro Giffuni        End With
1181*a893be29SPedro Giffuni
1182*a893be29SPedro Giffuni        mAnalysis.Issues.Add myIssue
1183*a893be29SPedro Giffuni        Set myIssue = Nothing
1184*a893be29SPedro Giffuni    End If
1185*a893be29SPedro Giffuni
1186*a893be29SPedro GiffuniFinalExit:
1187*a893be29SPedro Giffuni    Set myIssue = Nothing
1188*a893be29SPedro Giffuni    Exit Sub
1189*a893be29SPedro Giffuni
1190*a893be29SPedro GiffuniHandleErrors:
1191*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
1192*a893be29SPedro Giffuni    Resume FinalExit
1193*a893be29SPedro GiffuniEnd Sub
1194*a893be29SPedro Giffuni
1195*a893be29SPedro GiffuniSub Analyze_Tables_Borders(currDoc As Document)
1196*a893be29SPedro Giffuni    On Error GoTo HandleErrors
1197*a893be29SPedro Giffuni    Dim currentFunctionName As String
1198*a893be29SPedro Giffuni    currentFunctionName = "Analyze_Tables_Borders"
1199*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
1200*a893be29SPedro Giffuni    Set myIssue = New IssueInfo
1201*a893be29SPedro Giffuni    Dim aTable As Table
1202*a893be29SPedro Giffuni    Dim invalidBorders As String
1203*a893be29SPedro Giffuni
1204*a893be29SPedro Giffuni    For Each aTable In currDoc.Tables
1205*a893be29SPedro Giffuni        invalidBorders = GetInvalidBorder(aTable)
1206*a893be29SPedro Giffuni        If invalidBorders <> "" Then
1207*a893be29SPedro Giffuni            aTable.Range.Select
1208*a893be29SPedro Giffuni            Set myIssue = New IssueInfo
1209*a893be29SPedro Giffuni            With myIssue
1210*a893be29SPedro Giffuni                .IssueID = CID_TABLES
1211*a893be29SPedro Giffuni                .IssueType = RID_STR_WORD_ISSUE_TABLES
1212*a893be29SPedro Giffuni                .SubType = RID_STR_WORD_SUBISSUE_BORDER_STYLES
1213*a893be29SPedro Giffuni                .Location = .CLocationPage
1214*a893be29SPedro Giffuni
1215*a893be29SPedro Giffuni                .IssueTypeXML = CSTR_ISSUE_TABLES
1216*a893be29SPedro Giffuni                .SubTypeXML = CSTR_SUBISSUE_BORDER_STYLES
1217*a893be29SPedro Giffuni                .locationXML = .CXMLLocationPage
1218*a893be29SPedro Giffuni
1219*a893be29SPedro Giffuni                .SubLocation = Selection.Information(wdActiveEndPageNumber)
1220*a893be29SPedro Giffuni                .Line = Selection.Information(wdFirstCharacterLineNumber)
1221*a893be29SPedro Giffuni                .column = Selection.Information(wdFirstCharacterColumnNumber)
1222*a893be29SPedro Giffuni
1223*a893be29SPedro Giffuni                .Attributes.Add RID_STR_WORD_ATTRIBUTE_BORDERS_NOT_DISPLAYING
1224*a893be29SPedro Giffuni                .Values.Add invalidBorders
1225*a893be29SPedro Giffuni
1226*a893be29SPedro Giffuni                AddIssueDetailsNote myIssue, 0, RID_STR_WORD_NOTE_TABLE_BORDER
1227*a893be29SPedro Giffuni
1228*a893be29SPedro Giffuni                mAnalysis.IssuesCountArray(CID_TABLES) = mAnalysis.IssuesCountArray(CID_TABLES) + 1
1229*a893be29SPedro Giffuni            End With
1230*a893be29SPedro Giffuni
1231*a893be29SPedro Giffuni            mAnalysis.Issues.Add myIssue
1232*a893be29SPedro Giffuni            Set myIssue = Nothing
1233*a893be29SPedro Giffuni        End If
1234*a893be29SPedro Giffuni    Next aTable
1235*a893be29SPedro GiffuniFinalExit:
1236*a893be29SPedro Giffuni    Set myIssue = Nothing
1237*a893be29SPedro Giffuni    Exit Sub
1238*a893be29SPedro Giffuni
1239*a893be29SPedro GiffuniHandleErrors:
1240*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
1241*a893be29SPedro Giffuni    Resume FinalExit
1242*a893be29SPedro GiffuniEnd Sub
1243*a893be29SPedro GiffuniFunction GetInvalidBorder(aTable As Table) As String
1244*a893be29SPedro Giffuni
1245*a893be29SPedro Giffuni    Dim theResult As String
1246*a893be29SPedro Giffuni    theResult = ""
1247*a893be29SPedro Giffuni
1248*a893be29SPedro Giffuni    If IsInvalidBorderStyle(aTable.Borders(wdBorderTop).LineStyle) Then
1249*a893be29SPedro Giffuni        theResult = theResult + "Top, "
1250*a893be29SPedro Giffuni    End If
1251*a893be29SPedro Giffuni    If IsInvalidBorderStyle(aTable.Borders(wdBorderBottom).LineStyle) Then
1252*a893be29SPedro Giffuni            theResult = theResult + "Bottom, "
1253*a893be29SPedro Giffuni    End If
1254*a893be29SPedro Giffuni    If IsInvalidBorderStyle(aTable.Borders(wdBorderDiagonalDown).LineStyle) Then
1255*a893be29SPedro Giffuni            theResult = theResult + "Down Diagonal, "
1256*a893be29SPedro Giffuni    End If
1257*a893be29SPedro Giffuni    If IsInvalidBorderStyle(aTable.Borders(wdBorderDiagonalUp).LineStyle) Then
1258*a893be29SPedro Giffuni            theResult = theResult + "Up Diagonal, "
1259*a893be29SPedro Giffuni
1260*a893be29SPedro Giffuni    End If
1261*a893be29SPedro Giffuni    If IsInvalidBorderStyle(aTable.Borders(wdBorderHorizontal).LineStyle) Then
1262*a893be29SPedro Giffuni            theResult = theResult + "Horizontal, "
1263*a893be29SPedro Giffuni    End If
1264*a893be29SPedro Giffuni    If IsInvalidBorderStyle(aTable.Borders(wdBorderLeft).LineStyle) Then
1265*a893be29SPedro Giffuni            theResult = theResult + "Left, "
1266*a893be29SPedro Giffuni    End If
1267*a893be29SPedro Giffuni    If IsInvalidBorderStyle(aTable.Borders(wdBorderRight).LineStyle) Then
1268*a893be29SPedro Giffuni            theResult = theResult + "Right, "
1269*a893be29SPedro Giffuni    End If
1270*a893be29SPedro Giffuni    If IsInvalidBorderStyle(aTable.Borders(wdBorderVertical).LineStyle) Then
1271*a893be29SPedro Giffuni            theResult = theResult + "Vertical, "
1272*a893be29SPedro Giffuni    End If
1273*a893be29SPedro Giffuni
1274*a893be29SPedro Giffuni    If theResult <> "" Then
1275*a893be29SPedro Giffuni        theResult = Left(theResult, (Len(theResult) - 2)) + "."
1276*a893be29SPedro Giffuni    End If
1277*a893be29SPedro Giffuni
1278*a893be29SPedro Giffuni    GetInvalidBorder = theResult
1279*a893be29SPedro GiffuniEnd Function
1280*a893be29SPedro Giffuni
1281*a893be29SPedro GiffuniFunction IsInvalidBorderStyle(aStyle As WdLineStyle) As Boolean
1282*a893be29SPedro Giffuni
1283*a893be29SPedro Giffuni    Dim IsInvalid As Boolean
1284*a893be29SPedro Giffuni
1285*a893be29SPedro Giffuni    Select Case aStyle
1286*a893be29SPedro Giffuni    Case wdLineStyleDot, wdLineStyleDashSmallGap, wdLineStyleDashLargeGap, wdLineStyleDashDot, _
1287*a893be29SPedro Giffuni        wdLineStyleDashDotDot, wdLineStyleTriple, wdLineStyleThinThickThinSmallGap, wdLineStyleThinThickMedGap, _
1288*a893be29SPedro Giffuni        wdLineStyleThickThinMedGap, wdLineStyleThinThickThinMedGap, wdLineStyleThinThickLargeGap, _
1289*a893be29SPedro Giffuni        wdLineStyleThickThinLargeGap, wdLineStyleThinThickThinLargeGap, wdLineStyleSingleWavy, _
1290*a893be29SPedro Giffuni        wdLineStyleDoubleWavy, wdLineStyleDashDotStroked, wdLineStyleEmboss3D, wdLineStyleEngrave3D
1291*a893be29SPedro Giffuni        IsInvalid = True
1292*a893be29SPedro Giffuni    Case Else
1293*a893be29SPedro Giffuni        IsInvalid = False
1294*a893be29SPedro Giffuni    End Select
1295*a893be29SPedro Giffuni
1296*a893be29SPedro Giffuni    IsInvalidBorderStyle = IsInvalid
1297*a893be29SPedro Giffuni
1298*a893be29SPedro GiffuniEnd Function
1299*a893be29SPedro Giffuni
1300*a893be29SPedro GiffuniPrivate Sub Class_Initialize()
1301*a893be29SPedro Giffuni    Set mAnalysis = New DocumentAnalysis
1302*a893be29SPedro GiffuniEnd Sub
1303*a893be29SPedro GiffuniPrivate Sub Class_Terminate()
1304*a893be29SPedro Giffuni    Set mAnalysis = Nothing
1305*a893be29SPedro GiffuniEnd Sub
1306*a893be29SPedro Giffuni
1307*a893be29SPedro GiffuniPublic Property Get Results() As DocumentAnalysis
1308*a893be29SPedro Giffuni    Set Results = mAnalysis
1309*a893be29SPedro GiffuniEnd Property
1310*a893be29SPedro Giffuni
1311*a893be29SPedro GiffuniSub Analyze_NumberingTabs(currDoc As Document, docAnalysis As DocumentAnalysis)
1312*a893be29SPedro Giffuni    On Error GoTo HandleErrors
1313*a893be29SPedro Giffuni    Dim currentFunctionName As String
1314*a893be29SPedro Giffuni    currentFunctionName = "Analyze_NumberingTabs"
1315*a893be29SPedro Giffuni
1316*a893be29SPedro Giffuni    Dim tb As TabStop
1317*a893be29SPedro Giffuni    Dim customTabPos As Single
1318*a893be29SPedro Giffuni    Dim tabs As Integer
1319*a893be29SPedro Giffuni    Dim listLvl As Long
1320*a893be29SPedro Giffuni    Dim tp As Single
1321*a893be29SPedro Giffuni    Dim bHasAlignmentProblem As Boolean
1322*a893be29SPedro Giffuni    Dim bHasTooManyTabs As Boolean
1323*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
1324*a893be29SPedro Giffuni    Dim p As Object
1325*a893be29SPedro Giffuni
1326*a893be29SPedro Giffuni    bHasAlignmentProblem = False
1327*a893be29SPedro Giffuni    bHasTooManyTabs = False
1328*a893be29SPedro Giffuni
1329*a893be29SPedro Giffuni    For Each p In currDoc.ListParagraphs
1330*a893be29SPedro Giffuni        tabs = 0
1331*a893be29SPedro Giffuni        For Each tb In p.TabStops
1332*a893be29SPedro Giffuni            If tb.customTab Then
1333*a893be29SPedro Giffuni                tabs = tabs + 1
1334*a893be29SPedro Giffuni                customTabPos = tb.Position
1335*a893be29SPedro Giffuni            End If
1336*a893be29SPedro Giffuni        Next
1337*a893be29SPedro Giffuni
1338*a893be29SPedro Giffuni        If tabs = 1 Then
1339*a893be29SPedro Giffuni            listLvl = p.Range.ListFormat.ListLevelNumber
1340*a893be29SPedro Giffuni            tp = p.Range.ListFormat.ListTemplate.ListLevels.item(listLvl).TabPosition
1341*a893be29SPedro Giffuni            If (p.Range.ListFormat.ListTemplate.ListLevels.item(listLvl).Alignment <> _
1342*a893be29SPedro Giffuni                wdListLevelAlignLeft) Then
1343*a893be29SPedro Giffuni                ' ERROR: alignment problem
1344*a893be29SPedro Giffuni                bHasAlignmentProblem = True
1345*a893be29SPedro Giffuni            End If
1346*a893be29SPedro Giffuni
1347*a893be29SPedro Giffuni            If tp <> customTabPos Then
1348*a893be29SPedro Giffuni                p.Range.InsertBefore ("XXXXX")
1349*a893be29SPedro Giffuni            End If
1350*a893be29SPedro Giffuni            'OK - at least heuristically
1351*a893be29SPedro Giffuni        Else
1352*a893be29SPedro Giffuni            'ERROR: too many tabs
1353*a893be29SPedro Giffuni            bHasTooManyTabs = True
1354*a893be29SPedro Giffuni        End If
1355*a893be29SPedro Giffuni    Next
1356*a893be29SPedro Giffuni
1357*a893be29SPedro Giffuni    If (bHasAlignmentProblem) Then
1358*a893be29SPedro Giffuni        Set myIssue = New IssueInfo
1359*a893be29SPedro Giffuni
1360*a893be29SPedro Giffuni        With myIssue
1361*a893be29SPedro Giffuni            .IssueID = CID_INDEX_AND_REFERENCES
1362*a893be29SPedro Giffuni            .IssueType = RID_STR_WORD_ISSUE_INDEX_AND_REFERENCES
1363*a893be29SPedro Giffuni            .SubType = RID_STR_WORD_SUBISSUE_NUMBERING_TAB_ALIGNMENT
1364*a893be29SPedro Giffuni            .Location = .CLocationDocument 'Location string
1365*a893be29SPedro Giffuni
1366*a893be29SPedro Giffuni            .IssueTypeXML = CSTR_ISSUE_INDEX_AND_REFERENCES
1367*a893be29SPedro Giffuni            .SubTypeXML = CSTR_SUBISSUE_NUMBERING_TAB_ALIGNMENT
1368*a893be29SPedro Giffuni            .locationXML = .CXMLLocationDocument
1369*a893be29SPedro Giffuni
1370*a893be29SPedro Giffuni            AddIssueDetailsNote myIssue, 0, RID_STR_WORD_NOTE_NUMBERING_TAB_ALIGNMENT
1371*a893be29SPedro Giffuni
1372*a893be29SPedro Giffuni            docAnalysis.IssuesCountArray(CID_INDEX_AND_REFERENCES) = _
1373*a893be29SPedro Giffuni                    docAnalysis.IssuesCountArray(CID_INDEX_AND_REFERENCES) + 1
1374*a893be29SPedro Giffuni        End With
1375*a893be29SPedro Giffuni        docAnalysis.Issues.Add myIssue
1376*a893be29SPedro Giffuni        Set myIssue = Nothing
1377*a893be29SPedro Giffuni    End If
1378*a893be29SPedro Giffuni
1379*a893be29SPedro Giffuni    If (bHasTooManyTabs) Then
1380*a893be29SPedro Giffuni        Set myIssue = New IssueInfo
1381*a893be29SPedro Giffuni
1382*a893be29SPedro Giffuni        With myIssue
1383*a893be29SPedro Giffuni            .IssueID = CID_INDEX_AND_REFERENCES
1384*a893be29SPedro Giffuni            .IssueType = RID_STR_WORD_ISSUE_INDEX_AND_REFERENCES
1385*a893be29SPedro Giffuni            .SubType = RID_STR_WORD_SUBISSUE_NUMBERING_TAB_OVERFLOW
1386*a893be29SPedro Giffuni            .Location = .CLocationDocument 'Location string
1387*a893be29SPedro Giffuni
1388*a893be29SPedro Giffuni            .IssueTypeXML = CSTR_ISSUE_INDEX_AND_REFERENCES
1389*a893be29SPedro Giffuni            .SubTypeXML = CSTR_SUBISSUE_NUMBERING_TAB_OVERFLOW
1390*a893be29SPedro Giffuni            .locationXML = .CXMLLocationDocument
1391*a893be29SPedro Giffuni
1392*a893be29SPedro Giffuni            AddIssueDetailsNote myIssue, 0, RID_STR_WORD_NOTE_NUMBERING_TAB_OVERFLOW
1393*a893be29SPedro Giffuni
1394*a893be29SPedro Giffuni            docAnalysis.IssuesCountArray(CID_INDEX_AND_REFERENCES) = _
1395*a893be29SPedro Giffuni                    docAnalysis.IssuesCountArray(CID_INDEX_AND_REFERENCES) + 1
1396*a893be29SPedro Giffuni        End With
1397*a893be29SPedro Giffuni        docAnalysis.Issues.Add myIssue
1398*a893be29SPedro Giffuni        Set myIssue = Nothing
1399*a893be29SPedro Giffuni    End If
1400*a893be29SPedro Giffuni
1401*a893be29SPedro GiffuniFinalExit:
1402*a893be29SPedro Giffuni    Exit Sub
1403*a893be29SPedro Giffuni
1404*a893be29SPedro GiffuniHandleErrors:
1405*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
1406*a893be29SPedro Giffuni    Set myIssue = Nothing
1407*a893be29SPedro Giffuni    Resume FinalExit
1408*a893be29SPedro GiffuniEnd Sub
1409*a893be29SPedro Giffuni
1410*a893be29SPedro GiffuniSub Analyze_Numbering(currDoc As Document, docAnalysis As DocumentAnalysis)
1411*a893be29SPedro Giffuni    On Error GoTo HandleErrors
1412*a893be29SPedro Giffuni    Dim currentFunctionName As String
1413*a893be29SPedro Giffuni    currentFunctionName = "Analyze_Numbering"
1414*a893be29SPedro Giffuni
1415*a893be29SPedro Giffuni    Dim myIssue As IssueInfo
1416*a893be29SPedro Giffuni    Dim nFormatProblems As Integer
1417*a893be29SPedro Giffuni    Dim nAlignmentProblems As Integer
1418*a893be29SPedro Giffuni    nFormatProblems = 0
1419*a893be29SPedro Giffuni    nAlignmentProblems = 0
1420*a893be29SPedro Giffuni
1421*a893be29SPedro Giffuni    Dim lt As ListTemplate
1422*a893be29SPedro Giffuni    Dim lvl As ListLevel
1423*a893be29SPedro Giffuni    Dim I, l_, p1, p2, v1, v2 As Integer
1424*a893be29SPedro Giffuni    Dim display_levels As Integer
1425*a893be29SPedro Giffuni    Dim fmt, prefix, postfix, res As String
1426*a893be29SPedro Giffuni
1427*a893be29SPedro Giffuni    For Each lt In currDoc.ListTemplates
1428*a893be29SPedro Giffuni        l_ = 0
1429*a893be29SPedro Giffuni        For Each lvl In lt.ListLevels
1430*a893be29SPedro Giffuni            l_ = l_ + 1
1431*a893be29SPedro Giffuni            'Selection.TypeText Text:="List Number Format " + lvl.NumberFormat
1432*a893be29SPedro Giffuni            'Apply Heuristic
1433*a893be29SPedro Giffuni            fmt = lvl.NumberFormat
1434*a893be29SPedro Giffuni            p1 = InStr(fmt, "%")
1435*a893be29SPedro Giffuni            p2 = InStrRev(fmt, "%")
1436*a893be29SPedro Giffuni            v1 = val(Mid(fmt, p1 + 1, 1))
1437*a893be29SPedro Giffuni            v2 = val(Mid(fmt, p2 + 1, 1))
1438*a893be29SPedro Giffuni            display_levels = v2 - v1 + 1
1439*a893be29SPedro Giffuni            prefix = Mid(fmt, 1, p1 - 1)
1440*a893be29SPedro Giffuni            postfix = Mid(fmt, p2 + 2)
1441*a893be29SPedro Giffuni            'Check Heuristic
1442*a893be29SPedro Giffuni            res = prefix
1443*a893be29SPedro Giffuni            For I = 2 To display_levels
1444*a893be29SPedro Giffuni                res = "%" + Trim(Str(l_ - I + 1)) + "." + res
1445*a893be29SPedro Giffuni            Next
1446*a893be29SPedro Giffuni            res = res + "%" + Trim(Str(l_)) + postfix
1447*a893be29SPedro Giffuni            If (StrComp(res, fmt) <> 0) Then
1448*a893be29SPedro Giffuni                nFormatProblems = nFormatProblems + 1
1449*a893be29SPedro Giffuni                'Selection.TypeText Text:="Label Problem: NumberFormat=" + fmt + " Heuristic=" + res
1450*a893be29SPedro Giffuni            End If
1451*a893be29SPedro Giffuni
1452*a893be29SPedro Giffuni            'check alignment
1453*a893be29SPedro Giffuni            If (lvl.NumberPosition <> wdListLevelAlignLeft) Then
1454*a893be29SPedro Giffuni                nAlignmentProblems = nAlignmentProblems + 1
1455*a893be29SPedro Giffuni                'Selection.TypeText Text:="Number alignment problem"
1456*a893be29SPedro Giffuni            End If
1457*a893be29SPedro Giffuni        Next
1458*a893be29SPedro Giffuni    Next
1459*a893be29SPedro Giffuni
1460*a893be29SPedro Giffuni    If (nFormatProblems > 0) Then
1461*a893be29SPedro Giffuni        Set myIssue = New IssueInfo
1462*a893be29SPedro Giffuni
1463*a893be29SPedro Giffuni        With myIssue
1464*a893be29SPedro Giffuni            .IssueID = CID_INDEX_AND_REFERENCES
1465*a893be29SPedro Giffuni            .IssueType = RID_STR_WORD_ISSUE_INDEX_AND_REFERENCES
1466*a893be29SPedro Giffuni            .SubType = RID_STR_WORD_SUBISSUE_NUMBERING_FORMAT
1467*a893be29SPedro Giffuni            .Location = .CLocationDocument 'Location string
1468*a893be29SPedro Giffuni
1469*a893be29SPedro Giffuni            .IssueTypeXML = CSTR_ISSUE_INDEX_AND_REFERENCES
1470*a893be29SPedro Giffuni            .SubTypeXML = CSTR_SUBISSUE_NUMBERING_FORMAT
1471*a893be29SPedro Giffuni            .locationXML = .CXMLLocationDocument
1472*a893be29SPedro Giffuni
1473*a893be29SPedro Giffuni            .Attributes.Add RID_STR_WORD_ATTRIBUTE_COUNT
1474*a893be29SPedro Giffuni            .Values.Add nFormatProblems
1475*a893be29SPedro Giffuni
1476*a893be29SPedro Giffuni            AddIssueDetailsNote myIssue, 0, RID_STR_WORD_NOTE_NUMBERING_FORMAT
1477*a893be29SPedro Giffuni
1478*a893be29SPedro Giffuni            docAnalysis.IssuesCountArray(CID_INDEX_AND_REFERENCES) = _
1479*a893be29SPedro Giffuni                    docAnalysis.IssuesCountArray(CID_INDEX_AND_REFERENCES) + 1
1480*a893be29SPedro Giffuni        End With
1481*a893be29SPedro Giffuni        docAnalysis.Issues.Add myIssue
1482*a893be29SPedro Giffuni        Set myIssue = Nothing
1483*a893be29SPedro Giffuni    End If
1484*a893be29SPedro Giffuni
1485*a893be29SPedro Giffuni    If (nAlignmentProblems > 0) Then
1486*a893be29SPedro Giffuni        Set myIssue = New IssueInfo
1487*a893be29SPedro Giffuni
1488*a893be29SPedro Giffuni        With myIssue
1489*a893be29SPedro Giffuni            .IssueID = CID_INDEX_AND_REFERENCES
1490*a893be29SPedro Giffuni            .IssueType = RID_STR_WORD_ISSUE_INDEX_AND_REFERENCES
1491*a893be29SPedro Giffuni            .SubType = RID_STR_WORD_SUBISSUE_NUMBERING_ALIGNMENT
1492*a893be29SPedro Giffuni            .Location = .CLocationDocument 'Location string
1493*a893be29SPedro Giffuni
1494*a893be29SPedro Giffuni            .IssueTypeXML = CSTR_ISSUE_INDEX_AND_REFERENCES
1495*a893be29SPedro Giffuni            .SubTypeXML = CSTR_SUBISSUE_NUMBERING_ALIGNMENT
1496*a893be29SPedro Giffuni            .locationXML = .CXMLLocationDocument
1497*a893be29SPedro Giffuni
1498*a893be29SPedro Giffuni            .Attributes.Add RID_STR_WORD_ATTRIBUTE_COUNT
1499*a893be29SPedro Giffuni            .Values.Add nAlignmentProblems
1500*a893be29SPedro Giffuni
1501*a893be29SPedro Giffuni            AddIssueDetailsNote myIssue, 0, RID_STR_WORD_NOTE_NUMBERING_ALIGNMENT
1502*a893be29SPedro Giffuni
1503*a893be29SPedro Giffuni            docAnalysis.IssuesCountArray(CID_INDEX_AND_REFERENCES) = _
1504*a893be29SPedro Giffuni                    docAnalysis.IssuesCountArray(CID_INDEX_AND_REFERENCES) + 1
1505*a893be29SPedro Giffuni        End With
1506*a893be29SPedro Giffuni        docAnalysis.Issues.Add myIssue
1507*a893be29SPedro Giffuni        Set myIssue = Nothing
1508*a893be29SPedro Giffuni    End If
1509*a893be29SPedro Giffuni
1510*a893be29SPedro GiffuniFinalExit:
1511*a893be29SPedro Giffuni    Exit Sub
1512*a893be29SPedro Giffuni
1513*a893be29SPedro GiffuniHandleErrors:
1514*a893be29SPedro Giffuni    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
1515*a893be29SPedro Giffuni    Set myIssue = Nothing
1516*a893be29SPedro Giffuni    Resume FinalExit
1517*a893be29SPedro GiffuniEnd Sub
1518*a893be29SPedro Giffuni
1519