1*cdf0e10cSrcweirVERSION 1.0 CLASS
2*cdf0e10cSrcweirBEGIN
3*cdf0e10cSrcweir  MultiUse = -1  'True
4*cdf0e10cSrcweirEND
5*cdf0e10cSrcweirAttribute VB_Name = "MigrationAnalyser"
6*cdf0e10cSrcweirAttribute VB_GlobalNameSpace = False
7*cdf0e10cSrcweirAttribute VB_Creatable = False
8*cdf0e10cSrcweirAttribute VB_PredeclaredId = False
9*cdf0e10cSrcweirAttribute VB_Exposed = False
10*cdf0e10cSrcweir'/*************************************************************************
11*cdf0e10cSrcweir' *
12*cdf0e10cSrcweir' DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
13*cdf0e10cSrcweir'
14*cdf0e10cSrcweir' Copyright 2000, 2010 Oracle and/or its affiliates.
15*cdf0e10cSrcweir'
16*cdf0e10cSrcweir' OpenOffice.org - a multi-platform office productivity suite
17*cdf0e10cSrcweir'
18*cdf0e10cSrcweir' This file is part of OpenOffice.org.
19*cdf0e10cSrcweir'
20*cdf0e10cSrcweir' OpenOffice.org is free software: you can redistribute it and/or modify
21*cdf0e10cSrcweir' it under the terms of the GNU Lesser General Public License version 3
22*cdf0e10cSrcweir' only, as published by the Free Software Foundation.
23*cdf0e10cSrcweir'
24*cdf0e10cSrcweir' OpenOffice.org is distributed in the hope that it will be useful,
25*cdf0e10cSrcweir' but WITHOUT ANY WARRANTY; without even the implied warranty of
26*cdf0e10cSrcweir' MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
27*cdf0e10cSrcweir' GNU Lesser General Public License version 3 for more details
28*cdf0e10cSrcweir' (a copy is included in the LICENSE file that accompanied this code).
29*cdf0e10cSrcweir'
30*cdf0e10cSrcweir' You should have received a copy of the GNU Lesser General Public License
31*cdf0e10cSrcweir' version 3 along with OpenOffice.org.  If not, see
32*cdf0e10cSrcweir' <http://www.openoffice.org/license.html>
33*cdf0e10cSrcweir' for a copy of the LGPLv3 License.
34*cdf0e10cSrcweir'
35*cdf0e10cSrcweir' ************************************************************************/
36*cdf0e10cSrcweir
37*cdf0e10cSrcweirOption Explicit
38*cdf0e10cSrcweir
39*cdf0e10cSrcweir
40*cdf0e10cSrcweirPrivate mAnalysis As DocumentAnalysis
41*cdf0e10cSrcweir
42*cdf0e10cSrcweir'***ADDING-ISSUE: Use Following Skeleton as Guideline for Adding Issue
43*cdf0e10cSrcweir' For complete list of all RID_STR_... for Issues (IssueType), SubIssues (SubType) and Attributes refer to:
44*cdf0e10cSrcweir'   powerpoint_res.bas and common_res.bas
45*cdf0e10cSrcweir'
46*cdf0e10cSrcweir' For complete list of all CID_... for Issue Categories(IssueID) and
47*cdf0e10cSrcweir' CSTR_... for XML Issues (IssueTypeXML) and XML SubIssues (SubTypeXML) refer to:
48*cdf0e10cSrcweir'   ApplicationSpecific.bas and CommonMigrationAnalyser.bas
49*cdf0e10cSrcweir'
50*cdf0e10cSrcweir' You should not have to add any new Issue Categories or matching IssueTypes, only new SubIssues
51*cdf0e10cSrcweirSub Analyze_SKELETON()
52*cdf0e10cSrcweir    On Error GoTo HandleErrors
53*cdf0e10cSrcweir    Dim currentFunctionName As String
54*cdf0e10cSrcweir    currentFunctionName = "Analyze_SKELETON"
55*cdf0e10cSrcweir    Dim myIssue As IssueInfo
56*cdf0e10cSrcweir    Set myIssue = New IssueInfo
57*cdf0e10cSrcweir
58*cdf0e10cSrcweir    With myIssue
59*cdf0e10cSrcweir        .IssueID = CID_VBA_MACROS 'Issue Category
60*cdf0e10cSrcweir        .IssueType = RID_STR_COMMON_ISSUE_VBA_MACROS 'Issue String
61*cdf0e10cSrcweir        .SubType = RID_STR_COMMON_SUBISSUE_PROPERTIES 'SubIssue String
62*cdf0e10cSrcweir        .Location = .CLocationDocument 'Location string
63*cdf0e10cSrcweir
64*cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_VBA_MACROS 'Non localised XML Issue String
65*cdf0e10cSrcweir        .SubTypeXML = CSTR_SUBISSUE_PROPERTIES 'Non localised XML SubIssue String
66*cdf0e10cSrcweir        .locationXML = .CXMLLocationDocument 'Non localised XML location
67*cdf0e10cSrcweir
68*cdf0e10cSrcweir        .SubLocation = 0 'if not set will default to RID_STR_NOT_AVAILABLE_SHORTHAND
69*cdf0e10cSrcweir        .Line = 0 'if not set will default to RID_STR_NOT_AVAILABLE_SHORTHAND
70*cdf0e10cSrcweir        .column = 0 'if not set will default to RID_STR_NOT_AVAILABLE_SHORTHAND
71*cdf0e10cSrcweir
72*cdf0e10cSrcweir        ' Add as many Attribute Value pairs as needed
73*cdf0e10cSrcweir        ' Note: following must always be true - Attributes.Count = Values.Count
74*cdf0e10cSrcweir        .Attributes.Add "AAA"
75*cdf0e10cSrcweir        .Values.Add "foobar"
76*cdf0e10cSrcweir
77*cdf0e10cSrcweir        ' Use AddIssueDetailsNote to add notes to the Issue Details if required
78*cdf0e10cSrcweir        ' Public Sub AddIssueDetailsNote(myIssue As IssueInfo, noteNum As Long, noteStr As String, _
79*cdf0e10cSrcweir        '   Optional preStr As String = RID_STR_COMMON_NOTE_PRE)
80*cdf0e10cSrcweir        ' Where preStr is prepended to the output, with "Note" as the default
81*cdf0e10cSrcweir         AddIssueDetailsNote myIssue, 0, RID_STR_COMMON_NOTE_DOCUMENT_PROPERTIES_LOST
82*cdf0e10cSrcweir
83*cdf0e10cSrcweir         mAnalysis.IssuesCountArray(CID_VBA_MACROS) = _
84*cdf0e10cSrcweir                mAnalysis.IssuesCountArray(CID_VBA_MACROS) + 1
85*cdf0e10cSrcweir    End With
86*cdf0e10cSrcweir
87*cdf0e10cSrcweir    mAnalysis.Issues.Add myIssue
88*cdf0e10cSrcweir
89*cdf0e10cSrcweirFinalExit:
90*cdf0e10cSrcweir    Set myIssue = Nothing
91*cdf0e10cSrcweir    Exit Sub
92*cdf0e10cSrcweir
93*cdf0e10cSrcweirHandleErrors:
94*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
95*cdf0e10cSrcweir    Resume FinalExit
96*cdf0e10cSrcweirEnd Sub
97*cdf0e10cSrcweir
98*cdf0e10cSrcweirSub DoAnalyse(fileName As String, userFormTypesDict As Scripting.Dictionary, _
99*cdf0e10cSrcweir    startDir As String, storeToDir As String, fso As FileSystemObject)
100*cdf0e10cSrcweir    On Error GoTo HandleErrors
101*cdf0e10cSrcweir    Dim containsInvalidChar As Boolean
102*cdf0e10cSrcweir    containsInvalidChar = False
103*cdf0e10cSrcweir    Dim currentFunctionName As String
104*cdf0e10cSrcweir    currentFunctionName = "DoAnalyse"
105*cdf0e10cSrcweir    mAnalysis.name = fileName
106*cdf0e10cSrcweir    Dim aPres As Presentation
107*cdf0e10cSrcweir    mAnalysis.TotalIssueTypes = CTOTAL_CATEGORIES
108*cdf0e10cSrcweir
109*cdf0e10cSrcweir    If InStr(fileName, "[") = 0 And InStr(fileName, "]") = 0 Then 'If fileName does not contain [ AND ]
110*cdf0e10cSrcweir        containsInvalidChar = False
111*cdf0e10cSrcweir    Else
112*cdf0e10cSrcweir        containsInvalidChar = True
113*cdf0e10cSrcweir    End If
114*cdf0e10cSrcweir
115*cdf0e10cSrcweir    'Cannot Turn off any AutoExce macros before loading the Presentation
116*cdf0e10cSrcweir    'WordBasic.DisableAutoMacros 1
117*cdf0e10cSrcweir    'On Error GoTo HandleErrors
118*cdf0e10cSrcweir
119*cdf0e10cSrcweir    On Error Resume Next ' Ignore errors on setting
120*cdf0e10cSrcweir    If containsInvalidChar = True Then
121*cdf0e10cSrcweir        GoTo HandleErrors
122*cdf0e10cSrcweir    End If
123*cdf0e10cSrcweir    Set aPres = Presentations.Open(fileName:=fileName, ReadOnly:=True)
124*cdf0e10cSrcweir    If Err.Number <> 0 Then
125*cdf0e10cSrcweir        mAnalysis.Application = RID_STR_COMMON_CANNOT_OPEN
126*cdf0e10cSrcweir        GoTo HandleErrors
127*cdf0e10cSrcweir    End If
128*cdf0e10cSrcweir    On Error GoTo HandleErrors
129*cdf0e10cSrcweir
130*cdf0e10cSrcweir    'MsgBox "Window: " & PPViewType(aPres.Windows(1).viewType) & _
131*cdf0e10cSrcweir    '    " Pane: " & PPViewType(aPres.Windows(1).ActivePane.viewType)
132*cdf0e10cSrcweir
133*cdf0e10cSrcweir    'Set Doc Properties
134*cdf0e10cSrcweir    SetDocProperties mAnalysis, aPres, fso
135*cdf0e10cSrcweir
136*cdf0e10cSrcweir    Analyze_SlideIssues aPres
137*cdf0e10cSrcweir    Analyze_Macros mAnalysis, userFormTypesDict, aPres
138*cdf0e10cSrcweir
139*cdf0e10cSrcweir    ' Doc Preparation only
140*cdf0e10cSrcweir    ' Save document with any fixed issues under <storeToDir>\prepared\<source doc name>
141*cdf0e10cSrcweir    If mAnalysis.PreparableIssuesCount > 0 And CheckDoPrepare Then
142*cdf0e10cSrcweir        Dim preparedFullPath As String
143*cdf0e10cSrcweir        preparedFullPath = GetPreparedFullPath(mAnalysis.name, startDir, storeToDir, fso)
144*cdf0e10cSrcweir        If preparedFullPath <> "" Then
145*cdf0e10cSrcweir            If fso.FileExists(preparedFullPath) Then
146*cdf0e10cSrcweir                fso.DeleteFile preparedFullPath, True
147*cdf0e10cSrcweir            End If
148*cdf0e10cSrcweir            If fso.FolderExists(fso.GetParentFolderName(preparedFullPath)) Then
149*cdf0e10cSrcweir                aPres.SaveAs preparedFullPath
150*cdf0e10cSrcweir            End If
151*cdf0e10cSrcweir        End If
152*cdf0e10cSrcweir    End If
153*cdf0e10cSrcweir
154*cdf0e10cSrcweirFinalExit:
155*cdf0e10cSrcweir    If Not aPres Is Nothing Then 'If Not IsEmpty(aDoc) Then
156*cdf0e10cSrcweir        aPres.Saved = True
157*cdf0e10cSrcweir        aPres.Close
158*cdf0e10cSrcweir    End If
159*cdf0e10cSrcweir    Set aPres = Nothing
160*cdf0e10cSrcweir    Exit Sub
161*cdf0e10cSrcweir
162*cdf0e10cSrcweirHandleErrors:
163*cdf0e10cSrcweir    If containsInvalidChar = False Then
164*cdf0e10cSrcweir        WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
165*cdf0e10cSrcweir    Else
166*cdf0e10cSrcweir        WriteDebug currentFunctionName & " : " & mAnalysis.name & ": The file name contains the invalid character [ or ].  Please change the file name and run analysis again."
167*cdf0e10cSrcweir    End If
168*cdf0e10cSrcweir    Resume FinalExit
169*cdf0e10cSrcweirEnd Sub
170*cdf0e10cSrcweir
171*cdf0e10cSrcweirSub SetDocProperties(docAnalysis As DocumentAnalysis, pres As Presentation, fso As FileSystemObject)
172*cdf0e10cSrcweir    On Error GoTo HandleErrors
173*cdf0e10cSrcweir    Dim currentFunctionName As String
174*cdf0e10cSrcweir    currentFunctionName = "SetDocProperties"
175*cdf0e10cSrcweir    Dim f As File
176*cdf0e10cSrcweir    Set f = fso.GetFile(docAnalysis.name)
177*cdf0e10cSrcweir
178*cdf0e10cSrcweir    Const appPropertyAppName = 9
179*cdf0e10cSrcweir    Const appPropertyLastAuthor = 7
180*cdf0e10cSrcweir    Const appPropertyRevision = 8
181*cdf0e10cSrcweir    Const appPropertyTemplate = 6
182*cdf0e10cSrcweir    Const appPropertyTimeCreated = 11
183*cdf0e10cSrcweir    Const appPropertyTimeLastSaved = 12
184*cdf0e10cSrcweir
185*cdf0e10cSrcweir    On Error Resume Next
186*cdf0e10cSrcweir    docAnalysis.PageCount = pres.Slides.count
187*cdf0e10cSrcweir    docAnalysis.Created = f.DateCreated
188*cdf0e10cSrcweir    docAnalysis.Modified = f.DateLastModified
189*cdf0e10cSrcweir    docAnalysis.Accessed = f.DateLastAccessed
190*cdf0e10cSrcweir    docAnalysis.Printed = DateValue("01/01/1900")
191*cdf0e10cSrcweir
192*cdf0e10cSrcweir    On Error Resume Next 'Some apps may not support all props
193*cdf0e10cSrcweir    DocAnalysis.Application = getAppSpecificApplicationName & " " & Application.Version
194*cdf0e10cSrcweir
195*cdf0e10cSrcweir    'docAnalysis.Application = pres.BuiltInDocumentProperties(appPropertyAppName)
196*cdf0e10cSrcweir    'If InStr(docAnalysis.Application, "Microsoft") = 1 Then
197*cdf0e10cSrcweir    '    docAnalysis.Application = Mid(docAnalysis.Application, Len("Microsoft") + 2)
198*cdf0e10cSrcweir    'End If
199*cdf0e10cSrcweir    'If InStr(Len(docAnalysis.Application) - 2, docAnalysis.Application, ".") = 0 Then
200*cdf0e10cSrcweir    '    docAnalysis.Application = docAnalysis.Application & " " & Application.Version
201*cdf0e10cSrcweir    'End If
202*cdf0e10cSrcweir
203*cdf0e10cSrcweir    docAnalysis.SavedBy = _
204*cdf0e10cSrcweir        pres.BuiltInDocumentProperties(appPropertyLastAuthor)
205*cdf0e10cSrcweir    docAnalysis.Revision = _
206*cdf0e10cSrcweir        val(pres.BuiltInDocumentProperties(appPropertyRevision))
207*cdf0e10cSrcweir    docAnalysis.Template = _
208*cdf0e10cSrcweir        fso.GetFileName(pres.BuiltInDocumentProperties(appPropertyTemplate))
209*cdf0e10cSrcweir
210*cdf0e10cSrcweirFinalExit:
211*cdf0e10cSrcweir    Set f = Nothing
212*cdf0e10cSrcweir    Exit Sub
213*cdf0e10cSrcweir
214*cdf0e10cSrcweirHandleErrors:
215*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
216*cdf0e10cSrcweir    Resume FinalExit
217*cdf0e10cSrcweirEnd Sub
218*cdf0e10cSrcweir
219*cdf0e10cSrcweirFunction PPViewType(viewType As PPViewType) As String
220*cdf0e10cSrcweir
221*cdf0e10cSrcweir    Select Case viewType
222*cdf0e10cSrcweir        Case ppViewHandoutMaster
223*cdf0e10cSrcweir            PPViewType = RID_STR_PP_ENUMERATION_VIEW_HANDOUT_MASTER
224*cdf0e10cSrcweir        Case ppViewNormal
225*cdf0e10cSrcweir            PPViewType = RID_STR_PP_ENUMERATION_VIEW_NORMAL
226*cdf0e10cSrcweir        Case ppViewNotesMaster
227*cdf0e10cSrcweir            PPViewType = RID_STR_PP_ENUMERATION_VIEW_NOTES_MASTER
228*cdf0e10cSrcweir        Case ppViewNotesPage
229*cdf0e10cSrcweir            PPViewType = RID_STR_PP_ENUMERATION_VIEW_NOTES_PAGE
230*cdf0e10cSrcweir        Case ppViewOutline
231*cdf0e10cSrcweir            PPViewType = RID_STR_PP_ENUMERATION_VIEW_OUTLINE
232*cdf0e10cSrcweir        Case ppViewSlide
233*cdf0e10cSrcweir            PPViewType = RID_STR_PP_ENUMERATION_VIEW_SLIDE
234*cdf0e10cSrcweir        Case ppViewSlideMaster
235*cdf0e10cSrcweir            PPViewType = RID_STR_PP_ENUMERATION_VIEW_SLIDE_MASTER
236*cdf0e10cSrcweir        Case ppViewSlideSorter
237*cdf0e10cSrcweir            PPViewType = RID_STR_PP_ENUMERATION_VIEW_SLIDE_SORTER
238*cdf0e10cSrcweir        Case ppViewTitleMaster
239*cdf0e10cSrcweir            PPViewType = RID_STR_PP_ENUMERATION_VIEW_TITLE_MASTER
240*cdf0e10cSrcweir        Case Else
241*cdf0e10cSrcweir            PPViewType = RID_STR_PP_ENUMERATION_UNKNOWN
242*cdf0e10cSrcweir    End Select
243*cdf0e10cSrcweirEnd Function
244*cdf0e10cSrcweir
245*cdf0e10cSrcweirSub Analyze_SlideIssues(curPresentation As Presentation)
246*cdf0e10cSrcweir    On Error GoTo HandleErrors
247*cdf0e10cSrcweir    Dim currentFunctionName As String
248*cdf0e10cSrcweir    currentFunctionName = "Analyze_SlideIssues"
249*cdf0e10cSrcweir
250*cdf0e10cSrcweir    Dim mySlide As Slide
251*cdf0e10cSrcweir    Dim SlideNum As Integer
252*cdf0e10cSrcweir
253*cdf0e10cSrcweir    SlideNum = 1
254*cdf0e10cSrcweir    For Each mySlide In curPresentation.Slides
255*cdf0e10cSrcweir        ActiveWindow.View.GotoSlide index:=SlideNum
256*cdf0e10cSrcweir        Analyze_ShapeIssues mySlide
257*cdf0e10cSrcweir        Analyze_Hyperlinks mySlide
258*cdf0e10cSrcweir        Analyze_Templates mySlide
259*cdf0e10cSrcweir        SlideNum = SlideNum + 1
260*cdf0e10cSrcweir    Next mySlide
261*cdf0e10cSrcweir
262*cdf0e10cSrcweir    Analyze_TabStops curPresentation
263*cdf0e10cSrcweir
264*cdf0e10cSrcweir    Exit Sub
265*cdf0e10cSrcweirHandleErrors:
266*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
267*cdf0e10cSrcweirEnd Sub
268*cdf0e10cSrcweir
269*cdf0e10cSrcweirSub Analyze_TabStops(curPresentation As Presentation)
270*cdf0e10cSrcweir    On Error GoTo HandleErrors
271*cdf0e10cSrcweir    Dim currentFunctionName As String
272*cdf0e10cSrcweir    currentFunctionName = "Analyze_TabStops"
273*cdf0e10cSrcweir
274*cdf0e10cSrcweir    'Dim firstSlide As Slide
275*cdf0e10cSrcweir    'Dim firstShape As Shape
276*cdf0e10cSrcweir    Dim mySlide As Slide
277*cdf0e10cSrcweir    Dim myShape As Shape
278*cdf0e10cSrcweir    Dim bInitialized, bHasDifferentDefaults As Boolean
279*cdf0e10cSrcweir    Dim curDefault, lastDefault As Single
280*cdf0e10cSrcweir
281*cdf0e10cSrcweir    bInitialized = False
282*cdf0e10cSrcweir    bHasDifferentDefaults = False
283*cdf0e10cSrcweir
284*cdf0e10cSrcweir    For Each mySlide In curPresentation.Slides
285*cdf0e10cSrcweir        For Each myShape In mySlide.Shapes
286*cdf0e10cSrcweir            If myShape.HasTextFrame Then
287*cdf0e10cSrcweir                If myShape.TextFrame.HasText Then
288*cdf0e10cSrcweir                    curDefault = myShape.TextFrame.Ruler.TabStops.DefaultSpacing
289*cdf0e10cSrcweir                    If Not bInitialized Then
290*cdf0e10cSrcweir                        bInitialized = True
291*cdf0e10cSrcweir                        lastDefault = curDefault
292*cdf0e10cSrcweir                        'Set firstSlide = mySlide
293*cdf0e10cSrcweir                        'Set firstShape = myShape
294*cdf0e10cSrcweir                    End If
295*cdf0e10cSrcweir                    If curDefault <> lastDefault Then
296*cdf0e10cSrcweir                        bHasDifferentDefaults = True
297*cdf0e10cSrcweir                        Exit For
298*cdf0e10cSrcweir                    End If
299*cdf0e10cSrcweir                End If
300*cdf0e10cSrcweir            End If
301*cdf0e10cSrcweir        Next myShape
302*cdf0e10cSrcweir        If bHasDifferentDefaults Then Exit For
303*cdf0e10cSrcweir    Next mySlide
304*cdf0e10cSrcweir
305*cdf0e10cSrcweir    If Not bHasDifferentDefaults Then Exit Sub
306*cdf0e10cSrcweir
307*cdf0e10cSrcweir    Dim myIssue As IssueInfo
308*cdf0e10cSrcweir    Set myIssue = New IssueInfo
309*cdf0e10cSrcweir
310*cdf0e10cSrcweir    With myIssue
311*cdf0e10cSrcweir        .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
312*cdf0e10cSrcweir        .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
313*cdf0e10cSrcweir        .SubType = RID_RESXLS_COST_Tabstop
314*cdf0e10cSrcweir        .Location = .CLocationSlide
315*cdf0e10cSrcweir
316*cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
317*cdf0e10cSrcweir        .SubTypeXML = CSTR_SUBISSUE_TABSTOP
318*cdf0e10cSrcweir        .locationXML = .CXMLLocationSlide
319*cdf0e10cSrcweir
320*cdf0e10cSrcweir        .SubLocation = mySlide.name
321*cdf0e10cSrcweir        .Line = myShape.top
322*cdf0e10cSrcweir        .column = myShape.Left
323*cdf0e10cSrcweir
324*cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
325*cdf0e10cSrcweir        .Values.Add myShape.name
326*cdf0e10cSrcweir
327*cdf0e10cSrcweir        AddIssueDetailsNote myIssue, 0, RID_STR_PP_SUBISSUE_TABSTOP_NOTE
328*cdf0e10cSrcweir
329*cdf0e10cSrcweir        mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
330*cdf0e10cSrcweir                mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
331*cdf0e10cSrcweir    End With
332*cdf0e10cSrcweir
333*cdf0e10cSrcweir    mAnalysis.Issues.Add myIssue
334*cdf0e10cSrcweir
335*cdf0e10cSrcweirFinalExit:
336*cdf0e10cSrcweir    Set myIssue = Nothing
337*cdf0e10cSrcweir    Exit Sub
338*cdf0e10cSrcweir
339*cdf0e10cSrcweirHandleErrors:
340*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
341*cdf0e10cSrcweir    Resume FinalExit
342*cdf0e10cSrcweirEnd Sub
343*cdf0e10cSrcweir
344*cdf0e10cSrcweirSub Analyze_Fonts(curPresentation As Presentation)
345*cdf0e10cSrcweir    On Error GoTo HandleErrors
346*cdf0e10cSrcweir    Dim currentFunctionName As String
347*cdf0e10cSrcweir    currentFunctionName = "Analyze_Fonts"
348*cdf0e10cSrcweir
349*cdf0e10cSrcweir    Dim myFont As Font
350*cdf0e10cSrcweir    Dim bHasEmbeddedFonts As Boolean
351*cdf0e10cSrcweir
352*cdf0e10cSrcweir    bHasEmbeddedFonts = False
353*cdf0e10cSrcweir    For Each myFont In curPresentation.Fonts
354*cdf0e10cSrcweir        If myFont.Embedded Then
355*cdf0e10cSrcweir            bHasEmbeddedFonts = True
356*cdf0e10cSrcweir            Exit For
357*cdf0e10cSrcweir        End If
358*cdf0e10cSrcweir    Next
359*cdf0e10cSrcweir
360*cdf0e10cSrcweir    If Not bHasEmbeddedFonts Then Exit Sub
361*cdf0e10cSrcweir
362*cdf0e10cSrcweir    Dim myIssue As IssueInfo
363*cdf0e10cSrcweir    Set myIssue = New IssueInfo
364*cdf0e10cSrcweir
365*cdf0e10cSrcweir    With myIssue
366*cdf0e10cSrcweir        .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
367*cdf0e10cSrcweir        .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
368*cdf0e10cSrcweir        .SubType = RID_STR_PP_SUBISSUE_FONTS
369*cdf0e10cSrcweir        .Location = .CLocationSlide
370*cdf0e10cSrcweir
371*cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
372*cdf0e10cSrcweir        .SubTypeXML = CSTR_SUBISSUE_FONTS
373*cdf0e10cSrcweir        .locationXML = .CXMLLocationSlide
374*cdf0e10cSrcweir
375*cdf0e10cSrcweir        .SubLocation = mySlide.name
376*cdf0e10cSrcweir        .Line = myShape.top
377*cdf0e10cSrcweir        .column = myShape.Left
378*cdf0e10cSrcweir
379*cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
380*cdf0e10cSrcweir        .Values.Add myShape.name
381*cdf0e10cSrcweir
382*cdf0e10cSrcweir        AddIssueDetailsNote myIssue, 0, RID_STR_PP_SUBISSUE_FONTS_NOTE
383*cdf0e10cSrcweir
384*cdf0e10cSrcweir        mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
385*cdf0e10cSrcweir                mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
386*cdf0e10cSrcweir    End With
387*cdf0e10cSrcweir
388*cdf0e10cSrcweir    mAnalysis.Issues.Add myIssue
389*cdf0e10cSrcweir
390*cdf0e10cSrcweirFinalExit:
391*cdf0e10cSrcweir    Set myIssue = Nothing
392*cdf0e10cSrcweir    Exit Sub
393*cdf0e10cSrcweir
394*cdf0e10cSrcweirHandleErrors:
395*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
396*cdf0e10cSrcweir    Resume FinalExit
397*cdf0e10cSrcweirEnd Sub
398*cdf0e10cSrcweir
399*cdf0e10cSrcweirSub Analyze_Templates(mySlide As Slide)
400*cdf0e10cSrcweir    On Error GoTo HandleErrors
401*cdf0e10cSrcweir    Dim currentFunctionName As String
402*cdf0e10cSrcweir    currentFunctionName = "Analyze_Templates"
403*cdf0e10cSrcweir
404*cdf0e10cSrcweir    If mySlide.Layout <> ppLayoutTitle Then Exit Sub
405*cdf0e10cSrcweir
406*cdf0e10cSrcweir    Dim myIssue As IssueInfo
407*cdf0e10cSrcweir    Set myIssue = New IssueInfo
408*cdf0e10cSrcweir
409*cdf0e10cSrcweir    With myIssue
410*cdf0e10cSrcweir        .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
411*cdf0e10cSrcweir        .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
412*cdf0e10cSrcweir        .SubType = RID_RESXLS_COST_Template
413*cdf0e10cSrcweir        .Location = .CLocationSlide
414*cdf0e10cSrcweir
415*cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
416*cdf0e10cSrcweir        .SubTypeXML = CSTR_SUBISSUE_TEMPLATE
417*cdf0e10cSrcweir        .locationXML = .CXMLLocationSlide
418*cdf0e10cSrcweir        .SubLocation = mySlide.name
419*cdf0e10cSrcweir
420*cdf0e10cSrcweir        '.Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
421*cdf0e10cSrcweir        '.Values.Add mySlide.name
422*cdf0e10cSrcweir
423*cdf0e10cSrcweir        AddIssueDetailsNote myIssue, 0, RID_STR_PP_SUBISSUE_TEMPLATE_NOTE
424*cdf0e10cSrcweir
425*cdf0e10cSrcweir        mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
426*cdf0e10cSrcweir                mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
427*cdf0e10cSrcweir    End With
428*cdf0e10cSrcweir
429*cdf0e10cSrcweir    mAnalysis.Issues.Add myIssue
430*cdf0e10cSrcweir
431*cdf0e10cSrcweirFinalExit:
432*cdf0e10cSrcweir    Set myIssue = Nothing
433*cdf0e10cSrcweir    Exit Sub
434*cdf0e10cSrcweir
435*cdf0e10cSrcweirHandleErrors:
436*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
437*cdf0e10cSrcweir    Resume FinalExit
438*cdf0e10cSrcweirEnd Sub
439*cdf0e10cSrcweir
440*cdf0e10cSrcweirSub Analyze_Hyperlinks(mySlide As Slide)
441*cdf0e10cSrcweir    On Error GoTo HandleErrors
442*cdf0e10cSrcweir    Dim currentFunctionName As String
443*cdf0e10cSrcweir    currentFunctionName = "Analyze_Hyperlinks"
444*cdf0e10cSrcweir
445*cdf0e10cSrcweir    Dim myIssue As IssueInfo
446*cdf0e10cSrcweir    Dim hl As Hyperlink
447*cdf0e10cSrcweir    Dim bHasMultipleFonts As Boolean
448*cdf0e10cSrcweir    Dim bHasMultipleLines As Boolean
449*cdf0e10cSrcweir
450*cdf0e10cSrcweir    bHasMultipleFonts = False
451*cdf0e10cSrcweir    bHasMultipleLines = False
452*cdf0e10cSrcweir
453*cdf0e10cSrcweir    For Each hl In mySlide.Hyperlinks
454*cdf0e10cSrcweir        If TypeName(hl.Parent.Parent) = "TextRange" Then
455*cdf0e10cSrcweir            Dim myTextRange As TextRange
456*cdf0e10cSrcweir            Dim currRun As TextRange
457*cdf0e10cSrcweir            Dim currLine As TextRange
458*cdf0e10cSrcweir            Dim first, last, noteCount As Long
459*cdf0e10cSrcweir
460*cdf0e10cSrcweir            Set myTextRange = hl.Parent.Parent
461*cdf0e10cSrcweir            first = myTextRange.start
462*cdf0e10cSrcweir            last = first + myTextRange.Length - 1
463*cdf0e10cSrcweir
464*cdf0e10cSrcweir            For Each currRun In myTextRange.Runs
465*cdf0e10cSrcweir                If (currRun.start > first And currRun.start < last) Then
466*cdf0e10cSrcweir                    bHasMultipleFonts = True
467*cdf0e10cSrcweir                    Exit For
468*cdf0e10cSrcweir                End If
469*cdf0e10cSrcweir            Next
470*cdf0e10cSrcweir
471*cdf0e10cSrcweir            For Each currLine In myTextRange.Lines
472*cdf0e10cSrcweir                Dim lineEnd As Long
473*cdf0e10cSrcweir                lineEnd = currLine.start + currLine.Length - 1
474*cdf0e10cSrcweir                If (first <= lineEnd And last > lineEnd) Then
475*cdf0e10cSrcweir                    bHasMultipleLines = True
476*cdf0e10cSrcweir                    Exit For
477*cdf0e10cSrcweir                End If
478*cdf0e10cSrcweir            Next
479*cdf0e10cSrcweir        End If
480*cdf0e10cSrcweir
481*cdf0e10cSrcweir        noteCount = 0
482*cdf0e10cSrcweir
483*cdf0e10cSrcweir        If bHasMultipleFonts Then
484*cdf0e10cSrcweir            Set myIssue = New IssueInfo
485*cdf0e10cSrcweir
486*cdf0e10cSrcweir            With myIssue
487*cdf0e10cSrcweir                .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
488*cdf0e10cSrcweir                .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
489*cdf0e10cSrcweir                .SubType = RID_RESXLS_COST_Hyperlink
490*cdf0e10cSrcweir                .Location = .CLocationSlide
491*cdf0e10cSrcweir
492*cdf0e10cSrcweir                .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
493*cdf0e10cSrcweir                .SubTypeXML = CSTR_SUBISSUE_HYPERLINK
494*cdf0e10cSrcweir                .locationXML = .CXMLLocationSlide
495*cdf0e10cSrcweir                .SubLocation = mySlide.name
496*cdf0e10cSrcweir
497*cdf0e10cSrcweir                .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
498*cdf0e10cSrcweir                .Values.Add myTextRange.Text
499*cdf0e10cSrcweir
500*cdf0e10cSrcweir                AddIssueDetailsNote myIssue, 0, RID_STR_PP_SUBISSUE_HYPERLINK_NOTE
501*cdf0e10cSrcweir
502*cdf0e10cSrcweir                mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
503*cdf0e10cSrcweir                        mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
504*cdf0e10cSrcweir            End With
505*cdf0e10cSrcweir            mAnalysis.Issues.Add myIssue
506*cdf0e10cSrcweir            Set myIssue = Nothing
507*cdf0e10cSrcweir            bHasMultipleFonts = False
508*cdf0e10cSrcweir        End If
509*cdf0e10cSrcweir        If bHasMultipleLines Then
510*cdf0e10cSrcweir            Set myIssue = New IssueInfo
511*cdf0e10cSrcweir
512*cdf0e10cSrcweir            With myIssue
513*cdf0e10cSrcweir                .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
514*cdf0e10cSrcweir                .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
515*cdf0e10cSrcweir                .SubType = RID_RESXLS_COST_HyperlinkSplit
516*cdf0e10cSrcweir                .Location = .CLocationSlide
517*cdf0e10cSrcweir
518*cdf0e10cSrcweir                .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
519*cdf0e10cSrcweir                .SubTypeXML = CSTR_SUBISSUE_HYPERLINK_SPLIT
520*cdf0e10cSrcweir                .locationXML = .CXMLLocationSlide
521*cdf0e10cSrcweir                .SubLocation = mySlide.name
522*cdf0e10cSrcweir
523*cdf0e10cSrcweir                .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
524*cdf0e10cSrcweir                .Values.Add myTextRange.Text
525*cdf0e10cSrcweir
526*cdf0e10cSrcweir                AddIssueDetailsNote myIssue, 0, RID_STR_PP_SUBISSUE_HYPERLINK_SPLIT_NOTE
527*cdf0e10cSrcweir
528*cdf0e10cSrcweir                mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
529*cdf0e10cSrcweir                        mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
530*cdf0e10cSrcweir            End With
531*cdf0e10cSrcweir            mAnalysis.Issues.Add myIssue
532*cdf0e10cSrcweir            Set myIssue = Nothing
533*cdf0e10cSrcweir            bHasMultipleLines = False
534*cdf0e10cSrcweir        End If
535*cdf0e10cSrcweir    Next
536*cdf0e10cSrcweir
537*cdf0e10cSrcweirFinalExit:
538*cdf0e10cSrcweir    Set myIssue = Nothing
539*cdf0e10cSrcweir    Exit Sub
540*cdf0e10cSrcweir
541*cdf0e10cSrcweirHandleErrors:
542*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
543*cdf0e10cSrcweir    Resume FinalExit
544*cdf0e10cSrcweirEnd Sub
545*cdf0e10cSrcweir
546*cdf0e10cSrcweirSub Analyze_ShapeIssues(mySlide As Slide)
547*cdf0e10cSrcweir    On Error GoTo HandleErrors
548*cdf0e10cSrcweir    Dim currentFunctionName As String
549*cdf0e10cSrcweir    currentFunctionName = "Analyze_ShapeIssues"
550*cdf0e10cSrcweir    Dim myShape As Shape
551*cdf0e10cSrcweir
552*cdf0e10cSrcweir    For Each myShape In mySlide.Shapes
553*cdf0e10cSrcweir        'myShape.Select msoTrue
554*cdf0e10cSrcweir        Analyze_Movie mySlide, myShape
555*cdf0e10cSrcweir        Analyze_Comments mySlide, myShape
556*cdf0e10cSrcweir        Analyze_Background mySlide, myShape
557*cdf0e10cSrcweir        Analyze_Numbering mySlide, myShape
558*cdf0e10cSrcweir        'Analyze global issues
559*cdf0e10cSrcweir        Analyze_OLEEmbeddedSingleShape mAnalysis, myShape, mySlide.name
560*cdf0e10cSrcweir        Analyze_Lines mAnalysis, myShape, mySlide.name
561*cdf0e10cSrcweir        Analyze_Transparency mAnalysis, myShape, mySlide.name
562*cdf0e10cSrcweir        Analyze_Gradients mAnalysis, myShape, mySlide.name
563*cdf0e10cSrcweir    Next myShape
564*cdf0e10cSrcweir
565*cdf0e10cSrcweir    Exit Sub
566*cdf0e10cSrcweirHandleErrors:
567*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
568*cdf0e10cSrcweirEnd Sub
569*cdf0e10cSrcweir
570*cdf0e10cSrcweirSub Analyze_Numbering(mySlide As Slide, myShape As Shape)
571*cdf0e10cSrcweir    On Error GoTo HandleErrors
572*cdf0e10cSrcweir    Dim currentFunctionName As String
573*cdf0e10cSrcweir    currentFunctionName = "Analyze_Numbering"
574*cdf0e10cSrcweir
575*cdf0e10cSrcweir    If Not myShape.HasTextFrame Then Exit Sub
576*cdf0e10cSrcweir    If Not myShape.TextFrame.HasText Then Exit Sub
577*cdf0e10cSrcweir    Dim shapeText As TextRange
578*cdf0e10cSrcweir
579*cdf0e10cSrcweir    Set shapeText = myShape.TextFrame.TextRange
580*cdf0e10cSrcweir
581*cdf0e10cSrcweir    If shapeText.Paragraphs.count < 2 Then Exit Sub
582*cdf0e10cSrcweir    If Not (shapeText.ParagraphFormat.Bullet.Type = ppBulletMixed Or _
583*cdf0e10cSrcweir            shapeText.ParagraphFormat.Bullet.Type = ppBulletNumbered) Then Exit Sub
584*cdf0e10cSrcweir
585*cdf0e10cSrcweir    ' OpenOffice has Problems when the numbering does not start with the first
586*cdf0e10cSrcweir    ' paragraph or when there are empty paragraphs which do not have a number.
587*cdf0e10cSrcweir    ' Because PowerPoint does not give us the length of each paragraph ( .Length
588*cdf0e10cSrcweir    ' does not work ), we have to compute the length ourself.
589*cdf0e10cSrcweir
590*cdf0e10cSrcweir    Dim I As Long
591*cdf0e10cSrcweir    Dim lastType As PpBulletType
592*cdf0e10cSrcweir    Dim currType As PpBulletType
593*cdf0e10cSrcweir    Dim lastStart As Long
594*cdf0e10cSrcweir    Dim lastLength As Long
595*cdf0e10cSrcweir    Dim currStart As Long
596*cdf0e10cSrcweir    Dim bHasNumProblem As Boolean
597*cdf0e10cSrcweir    Dim bHasEmptyPar As Boolean
598*cdf0e10cSrcweir
599*cdf0e10cSrcweir    bHasNumProblem = False
600*cdf0e10cSrcweir    bHasEmptyPar = False
601*cdf0e10cSrcweir
602*cdf0e10cSrcweir    lastType = shapeText.Paragraphs(1, 0).ParagraphFormat.Bullet.Type
603*cdf0e10cSrcweir    lastStart = shapeText.Paragraphs(1, 0).start
604*cdf0e10cSrcweir
605*cdf0e10cSrcweir    For I = 2 To shapeText.Paragraphs.count
606*cdf0e10cSrcweir        currType = shapeText.Paragraphs(I, 0).ParagraphFormat.Bullet.Type
607*cdf0e10cSrcweir        currStart = shapeText.Paragraphs(I, 0).start
608*cdf0e10cSrcweir        lastLength = currStart - lastStart - 1
609*cdf0e10cSrcweir
610*cdf0e10cSrcweir        If currType <> lastType Then
611*cdf0e10cSrcweir            lastType = currType
612*cdf0e10cSrcweir            If currType = ppBulletNumbered Then
613*cdf0e10cSrcweir                bHasNumProblem = True
614*cdf0e10cSrcweir                Exit For
615*cdf0e10cSrcweir            End If
616*cdf0e10cSrcweir        End If
617*cdf0e10cSrcweir        If lastLength = 0 Then
618*cdf0e10cSrcweir            bHasEmptyPar = True
619*cdf0e10cSrcweir        Else
620*cdf0e10cSrcweir            If (bHasEmptyPar) Then
621*cdf0e10cSrcweir                bHasNumProblem = True
622*cdf0e10cSrcweir                Exit For
623*cdf0e10cSrcweir            End If
624*cdf0e10cSrcweir        End If
625*cdf0e10cSrcweir        lastStart = currStart
626*cdf0e10cSrcweir    Next I
627*cdf0e10cSrcweir
628*cdf0e10cSrcweir    lastLength = shapeText.Length - lastStart
629*cdf0e10cSrcweir    If (lastLength <> 0) And bHasEmptyPar Then
630*cdf0e10cSrcweir        bHasNumProblem = True
631*cdf0e10cSrcweir    End If
632*cdf0e10cSrcweir
633*cdf0e10cSrcweir    If Not bHasNumProblem Then Exit Sub
634*cdf0e10cSrcweir
635*cdf0e10cSrcweir    Dim myIssue As IssueInfo
636*cdf0e10cSrcweir    Set myIssue = New IssueInfo
637*cdf0e10cSrcweir
638*cdf0e10cSrcweir    With myIssue
639*cdf0e10cSrcweir        .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
640*cdf0e10cSrcweir        .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
641*cdf0e10cSrcweir        .SubType = RID_RESXLS_COST_Numbering
642*cdf0e10cSrcweir        .Location = .CLocationSlide
643*cdf0e10cSrcweir
644*cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
645*cdf0e10cSrcweir        .SubTypeXML = CSTR_SUBISSUE_NUMBERING
646*cdf0e10cSrcweir        .locationXML = .CXMLLocationSlide
647*cdf0e10cSrcweir
648*cdf0e10cSrcweir        .SubLocation = mySlide.name
649*cdf0e10cSrcweir        .Line = myShape.top
650*cdf0e10cSrcweir        .column = myShape.Left
651*cdf0e10cSrcweir
652*cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
653*cdf0e10cSrcweir        .Values.Add myShape.name
654*cdf0e10cSrcweir
655*cdf0e10cSrcweir        AddIssueDetailsNote myIssue, 0, RID_STR_PP_SUBISSUE_NUMBERING_NOTE
656*cdf0e10cSrcweir
657*cdf0e10cSrcweir        mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
658*cdf0e10cSrcweir                mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
659*cdf0e10cSrcweir    End With
660*cdf0e10cSrcweir
661*cdf0e10cSrcweir    mAnalysis.Issues.Add myIssue
662*cdf0e10cSrcweir
663*cdf0e10cSrcweirFinalExit:
664*cdf0e10cSrcweir    Set myIssue = Nothing
665*cdf0e10cSrcweir    Exit Sub
666*cdf0e10cSrcweir
667*cdf0e10cSrcweirHandleErrors:
668*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
669*cdf0e10cSrcweir    Resume FinalExit
670*cdf0e10cSrcweirEnd Sub
671*cdf0e10cSrcweir
672*cdf0e10cSrcweirSub Analyze_Background(mySlide As Slide, myShape As Shape)
673*cdf0e10cSrcweir    On Error GoTo HandleErrors
674*cdf0e10cSrcweir    Dim currentFunctionName As String
675*cdf0e10cSrcweir    currentFunctionName = "Analyze_Background"
676*cdf0e10cSrcweir
677*cdf0e10cSrcweir    If myShape.Fill.Type <> msoFillBackground Then Exit Sub
678*cdf0e10cSrcweir
679*cdf0e10cSrcweir    Dim myIssue As IssueInfo
680*cdf0e10cSrcweir    Set myIssue = New IssueInfo
681*cdf0e10cSrcweir    Dim strCr As String
682*cdf0e10cSrcweir    strCr = "" & vbCr
683*cdf0e10cSrcweir
684*cdf0e10cSrcweir    With myIssue
685*cdf0e10cSrcweir        .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
686*cdf0e10cSrcweir        .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
687*cdf0e10cSrcweir        .SubType = RID_RESXLS_COST_Background
688*cdf0e10cSrcweir        .Location = .CLocationSlide
689*cdf0e10cSrcweir
690*cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
691*cdf0e10cSrcweir        .SubTypeXML = CSTR_SUBISSUE_BACKGROUND
692*cdf0e10cSrcweir        .locationXML = .CXMLLocationSlide
693*cdf0e10cSrcweir
694*cdf0e10cSrcweir        .SubLocation = mySlide.name
695*cdf0e10cSrcweir        .Line = myShape.top
696*cdf0e10cSrcweir        .column = myShape.Left
697*cdf0e10cSrcweir
698*cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
699*cdf0e10cSrcweir        .Values.Add myShape.name
700*cdf0e10cSrcweir
701*cdf0e10cSrcweir        AddIssueDetailsNote myIssue, 0, RID_STR_PP_SUBISSUE_BACKGROUND_NOTE
702*cdf0e10cSrcweir
703*cdf0e10cSrcweir        mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
704*cdf0e10cSrcweir                mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
705*cdf0e10cSrcweir    End With
706*cdf0e10cSrcweir
707*cdf0e10cSrcweir    mAnalysis.Issues.Add myIssue
708*cdf0e10cSrcweir
709*cdf0e10cSrcweirFinalExit:
710*cdf0e10cSrcweir    Set myIssue = Nothing
711*cdf0e10cSrcweir    Exit Sub
712*cdf0e10cSrcweir
713*cdf0e10cSrcweirHandleErrors:
714*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
715*cdf0e10cSrcweir    Resume FinalExit
716*cdf0e10cSrcweirEnd Sub
717*cdf0e10cSrcweir
718*cdf0e10cSrcweirSub Analyze_Comments(mySlide As Slide, myShape As Shape)
719*cdf0e10cSrcweir    On Error GoTo HandleErrors
720*cdf0e10cSrcweir    Dim currentFunctionName As String
721*cdf0e10cSrcweir    currentFunctionName = "Analyze_Comments"
722*cdf0e10cSrcweir
723*cdf0e10cSrcweir    If myShape.Type <> msoComment Then Exit Sub
724*cdf0e10cSrcweir
725*cdf0e10cSrcweir    Dim myIssue As IssueInfo
726*cdf0e10cSrcweir    Set myIssue = New IssueInfo
727*cdf0e10cSrcweir    Dim strCr As String
728*cdf0e10cSrcweir    strCr = "" & vbCr
729*cdf0e10cSrcweir
730*cdf0e10cSrcweir    With myIssue
731*cdf0e10cSrcweir        .IssueID = CID_CONTENT_AND_DOCUMENT_PROPERTIES
732*cdf0e10cSrcweir        .IssueType = RID_STR_COMMON_ISSUE_CONTENT_AND_DOCUMENT_PROPERTIES
733*cdf0e10cSrcweir        .SubType = RID_STR_PP_SUBISSUE_COMMENT
734*cdf0e10cSrcweir        .Location = .CLocationSlide
735*cdf0e10cSrcweir
736*cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_CONTENT_DOCUMENT_PROPERTIES
737*cdf0e10cSrcweir        .SubTypeXML = CSTR_SUBISSUE_COMMENT
738*cdf0e10cSrcweir        .locationXML = .CXMLLocationSlide
739*cdf0e10cSrcweir
740*cdf0e10cSrcweir        .SubLocation = mySlide.name
741*cdf0e10cSrcweir        .Line = myShape.top
742*cdf0e10cSrcweir        .column = myShape.Left
743*cdf0e10cSrcweir
744*cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
745*cdf0e10cSrcweir        .Values.Add myShape.name
746*cdf0e10cSrcweir        .Attributes.Add RID_STR_PP_ATTRIBUTE_CONTENT
747*cdf0e10cSrcweir        .Values.Add Replace(myShape.TextFrame.TextRange.Text, strCr, "")
748*cdf0e10cSrcweir
749*cdf0e10cSrcweir         mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) = _
750*cdf0e10cSrcweir                mAnalysis.IssuesCountArray(CID_CONTENT_AND_DOCUMENT_PROPERTIES) + 1
751*cdf0e10cSrcweir    End With
752*cdf0e10cSrcweir
753*cdf0e10cSrcweir    mAnalysis.Issues.Add myIssue
754*cdf0e10cSrcweir
755*cdf0e10cSrcweirFinalExit:
756*cdf0e10cSrcweir    Set myIssue = Nothing
757*cdf0e10cSrcweir    Exit Sub
758*cdf0e10cSrcweir
759*cdf0e10cSrcweirHandleErrors:
760*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
761*cdf0e10cSrcweir    Resume FinalExit
762*cdf0e10cSrcweirEnd Sub
763*cdf0e10cSrcweirSub Analyze_Movie(mySlide As Slide, myShape As Shape)
764*cdf0e10cSrcweir    On Error GoTo HandleErrors
765*cdf0e10cSrcweir    Dim currentFunctionName As String
766*cdf0e10cSrcweir    currentFunctionName = "Analyze_Movie"
767*cdf0e10cSrcweir
768*cdf0e10cSrcweir    If myShape.Type <> msoMedia Then Exit Sub
769*cdf0e10cSrcweir    If myShape.MediaType <> ppMediaTypeMovie Then Exit Sub
770*cdf0e10cSrcweir
771*cdf0e10cSrcweir    Dim myIssue As IssueInfo
772*cdf0e10cSrcweir    Set myIssue = New IssueInfo
773*cdf0e10cSrcweir
774*cdf0e10cSrcweir    With myIssue
775*cdf0e10cSrcweir        .IssueID = CID_OBJECTS_GRAPHICS_TEXTBOXES
776*cdf0e10cSrcweir        .IssueType = RID_STR_PP_ISSUE_OBJECTS_GRAPHICS_AND_TEXTBOXES
777*cdf0e10cSrcweir        .SubType = RID_STR_PP_SUBISSUE_MOVIE
778*cdf0e10cSrcweir        .Location = .CLocationSlide
779*cdf0e10cSrcweir
780*cdf0e10cSrcweir        .IssueTypeXML = CSTR_ISSUE_OBJECTS_GRAPHICS_AND_TEXTBOXES
781*cdf0e10cSrcweir        .SubTypeXML = CSTR_SUBISSUE_MOVIE
782*cdf0e10cSrcweir        .locationXML = .CXMLLocationSlide
783*cdf0e10cSrcweir
784*cdf0e10cSrcweir        .SubLocation = mySlide.name
785*cdf0e10cSrcweir        .Line = myShape.top
786*cdf0e10cSrcweir        .column = myShape.Left
787*cdf0e10cSrcweir
788*cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_NAME
789*cdf0e10cSrcweir        .Values.Add myShape.name
790*cdf0e10cSrcweir        .Attributes.Add RID_STR_COMMON_ATTRIBUTE_SOURCE
791*cdf0e10cSrcweir        .Values.Add myShape.LinkFormat.SourceFullName
792*cdf0e10cSrcweir        .Attributes.Add RID_STR_PP_ATTRIBUTE_PLAYONENTRY
793*cdf0e10cSrcweir        .Values.Add IIf(myShape.AnimationSettings.PlaySettings.PlayOnEntry, RID_STR_PP_TRUE, RID_STR_PP_FALSE)
794*cdf0e10cSrcweir        .Attributes.Add RID_STR_PP_ATTRIBUTE_LOOP
795*cdf0e10cSrcweir        .Values.Add IIf(myShape.AnimationSettings.PlaySettings.LoopUntilStopped, RID_STR_PP_TRUE, RID_STR_PP_FALSE)
796*cdf0e10cSrcweir        .Attributes.Add RID_STR_PP_ATTRIBUTE_REWIND
797*cdf0e10cSrcweir        .Values.Add IIf(myShape.AnimationSettings.PlaySettings.RewindMovie, RID_STR_PP_TRUE, RID_STR_PP_FALSE)
798*cdf0e10cSrcweir
799*cdf0e10cSrcweir         mAnalysis.IssuesCountArray(CID_OBJECTS_GRAPHICS_TEXTBOXES) = _
800*cdf0e10cSrcweir                mAnalysis.IssuesCountArray(CID_OBJECTS_GRAPHICS_TEXTBOXES) + 1
801*cdf0e10cSrcweir    End With
802*cdf0e10cSrcweir
803*cdf0e10cSrcweir    mAnalysis.Issues.Add myIssue
804*cdf0e10cSrcweir
805*cdf0e10cSrcweirFinalExit:
806*cdf0e10cSrcweir    Set myIssue = Nothing
807*cdf0e10cSrcweir    Exit Sub
808*cdf0e10cSrcweir
809*cdf0e10cSrcweirHandleErrors:
810*cdf0e10cSrcweir    WriteDebug currentFunctionName & " : " & mAnalysis.name & ": " & Err.Number & " " & Err.Description & " " & Err.Source
811*cdf0e10cSrcweir    Resume FinalExit
812*cdf0e10cSrcweirEnd Sub
813*cdf0e10cSrcweir
814*cdf0e10cSrcweirPrivate Sub Class_Initialize()
815*cdf0e10cSrcweir    Set mAnalysis = New DocumentAnalysis
816*cdf0e10cSrcweirEnd Sub
817*cdf0e10cSrcweirPrivate Sub Class_Terminate()
818*cdf0e10cSrcweir    Set mAnalysis = Nothing
819*cdf0e10cSrcweirEnd Sub
820*cdf0e10cSrcweir
821*cdf0e10cSrcweirPublic Property Get Results() As DocumentAnalysis
822*cdf0e10cSrcweir    Set Results = mAnalysis
823*cdf0e10cSrcweirEnd Property
824*cdf0e10cSrcweir
825