can't attach doc. to a protected template

W

William

hi,

g'd morning. i made changes to a word template. i detached the old template
from word. when i attached to the new one, i got "can't attach doc. to a
protected template" error. i am working on windows xp and xp for word. does
anyone has any idea? thank you. -william.

--
 
W

Word Heretic

G'day "William" <[email protected]>,

Create a new document from the template, copy and paste the content
in.

Steve Hudson - Word Heretic

steve from wordheretic.com (Email replies require payment)
Without prejudice


William reckoned:
 
W

William

hi,

hum....the orginial doc. stored some of the doc. info. in doc. properties
for which i want to retain. your suggestion might not work in this case. any
other ideas? thanks. -will
 
W

Word Heretic

G'day "William" <[email protected]>,

a preview of an article for the MVP site:


The Auto Maggie
By Steve Hudson
Version 0.5 - TESTED DRAFT
You may reproduce any or all of the text, code and methods for
non-commercial purposes so long as you explicitly acknowledge this
article. This allows legal internal distributions of up to 500
different users in a single year. For commercial purposes, please
contact the author (e-mail address removed) for explicit permission and
pricing.
You use the information in this article at your own risk. Following
the advice in this article substantially reduces the risk of Word's
document corruption.


Introduction
Synopsis
The Maggie is a time-honoured technique for reducing corruption in
Word documents. The solution in this article allows for instant,
simple document cleaning. It has not been pre-packaged as a ready to
go tool because you would then not read this document and therefore
would only ever use 10% of this tool's power.
If you require pre-packaged solutions, they are commercial so please
feel free to contact the author with your list of controlled templates
and other requirements.

Target Audience
Any Word user.

Related Reading
Learning VBA: http://word.mvps.org/FAQs/MacrosVBA.htm
Word PC List archives: http://listserv.liv.ac.uk/archives/word-pc.html


The Automated Maggie

What is a Maggie?

The Maggie is a well-proven technique for removing a LOT of garbage
and undocumented functionality from your documents. You copy and paste
everything except the last paragraph mark in each section to a new
document and start work again.

Why is it called a Maggie?

The Word PC-L mailing list
(mailto:[email protected] to join), no subject
or command text required), around the turn of the Millennium had two
frequent posters, amongst others; the author and Margaret Secara,
known as Maggie to the residents of the list.

There was a well-known technique of copy-and-pasting the last
paragraph mark in each section of a bad document to a new clean
document when their text, styles or lists went really haywire. The
author kept frantically chanting long and complicated VBA spells to
try to cure other stranger and evil omens that were sporadically
appearing in users' documents.

Maggie persisted in her private notion that the above technique would
solve a LOT more problems than anyone else to that date had given it
credit for. Indeed, she rapidly demonstrated its cure-all powers.
Since then, to abbreviate the long-winded "copy-and-pasting the last
paragraph mark in each section of a bad document to a new clean
document", we call it a Maggie in her honour. It is the first line
defence against Word Happening for serious writers.

The Maggie is finally in the MS hall of fame, err Knowledge Base -
well, the technique at least, that was a good start. It is also taught
at the beginning of writing courses at many tertiary institutions
across the globe, name intact. There are also many tens of thousands
of users that know it as the Maggie. The term and the technique are
here to stay, start using them.

Why is this the best solution?
It is quick, it is easy to customise and it solves many strange
problems with your documents. It is faster than either of the more
advanced solutions. It solves most common problems. It is used in many
Quality processes.

About the code
Batch Auto-Maggies
The code has been optimised for batch performance, just look at those
modes! It is so powerful that there is good call for calling the
Auto-Maggie down twice in your batch process. Once before you process
documents so you don't get hung up on weirdness beyond your control,
and then once after to house them in a nice new document with no bad
list styles or list templates and all is lovely.

The # stuff
The # statements are compiler directives. Essentially, I love
enumerations used in this way, as it is SO API friendly:
For the vast majority of us with auto complete on in the VBE options,
when you are typing in the command, you not only get a syntax guide
for the command, but when you get to this parameter you get the whole
list of options. Zero brainwork and a lot less keying, you bewdy!
The BIG problem is, not everyone's platform supports Enums. Macintosh
users, already tortured by their new GUIs and eye-breaking,
colour-casting cases, are without not only this command, but also the
InStrRev in use further on down. Don't panic, it all works, we've
allowed for you.

When you go to run this, Word checks if you are using VBA 6 or not. If
not, you get the other stuff. If your platform gets tied up on it, or
it just plain makes your head hurt, by all means manually emulate the
compiler's expected behaviour. If you can use Enums on your platform
(it doesn't cause a compile error), then keep the first section in
each #If VBA6 block. Otherwise, keep the second! Get rid of all the #
statements altogether.

They also provide Mac compatibility, as Mac users do not have VBA6.


Installation recommendation

Keep it in its own module called AutoMaggie in a global template for
your authors, linked to a toolbar button with an icon like these: a
dirty document being wiped clean for the visual , and Word turned on
its head for perfect irony .

Intermediate users: ALT+F11 to get into the VBE. Right-click inside
your VBProject (Normal.dot) in the Project Explorer window and select
Insert > Module. Go down to the Properties window. If there is no
Properties window, View it. Change the name from Module2 or whatever
to AutoMaggie. There, that didn't hurt a bit and now you can easily
find your Maggie code!

Beginners: paste the code into a module in Normal.dot and drag one of
the pre-done buttons onto the standard Word toolbars with Tools >
Customize set to modify Normal.dot. Come back later as an intermediate
user and fix this up properly.


Customisation

You need to edit SafeAddNewDocument to match your local requirements.
The provided default always uses Normal as the basis for the Maggie.
If you want more complex results, use this example as a guide.

Public Function SafeAddNewDocument( _
ByRef TemplateName As String) As Document
'Validates the template name you pass in

Const DefaultTemplate As String = "Normal.dot" 'Edit this


'Edit this case logic as much as possible

Select Case TemplateName

'Leave this safety case

Case vbNullString 'Crikey, the source has no template
TemplateName = DefaultTemplate


'List all your known good templates here that we can re-use

Case "Known good template 1.dot", "Known good template 2.dot"
'No need to do anything, these are good for re-use!


'Start listing known old template attached to documents
'that either do not exist or have been replaced

Case "Known bad template 1.dot", "Known bad template 2.dot"
TemplateName = "MyGoodTemplate6.dot"

Case "Known bad template 3.dot", "Known bad template 4.dot"
TemplateName = "MyGoodTemplate5.dot"


'Delete the Else block to always try to use the provided template
first

Case Else
'Edit this to throw exception to a log
Debug.Print "Unknown template name " & TemplateName

'This example always uses the default template
'if the template name is not explicitly listed

TemplateName = DefaultTemplate

End Select


On Error GoTo NoSuchTemplate

Set SafeAddNewDocument = Documents.Add(TemplateName)

On Error GoTo 0


NoSuchTemplate:

If Err.Number > 0 Then

If Err.Number = 5151 Then 'No such template

'Edit this bit to throw exceptions to a log

Debug.Print "No such template: " & TemplateName


'Leave all this

Select Case TemplateName

Case "Normal.dot" 'Leave this as Normal.dot !!!
MsgBox "Failed to create a document from Normal.dot", _
vbCritical, "Catastrophic Word failure"
Stop

Case DefaultTemplate 'This shouldn't happen if you set the
default
TemplateName = "Normal.dot" 'Leave this as Normal.dot !!!
Debug.Print "Failed to create from default template " &
TemplateName

Case Else
TemplateName = DefaultTemplate

End Select
Resume

End If 'Err 5151
End If
End Function



The parameters in detail

As your confidence with this tool grows, you can start calling it with
some of the parameters set to other than the default.
There has been no attempt to preserve headers and footers; whatever is
in the template used for the new document will be what you get. A
Maggie transfers content; the document properties copy is a standing
requirement for all users, so that has been included as well. Other
solutions are also available, commercially, or you can write your own.

Parameter name Usage
Source A document to Maggie. This is mainly present to support
batch auto-maggies.
TemplateName If you are not using the default implementation to
always use Normal.dot, then you can override the template name for the
new document to use.
CloseMode The Enum at the start of the code provides the options,
essentially this is here to help close down the source document and
maybe save and close the new document.Default behaviour is set to
leave both documents open. When you have confidence, you can
auto-close the source document and save over the top of it by changing
the original call in ActiveDocumentMaggie.Maggie
ActiveDocument,CloseMode:= _MaggieCloseModeSaveMaggieIf you do not
save the Maggied document, relative pictures and hyperlinks will fail
until you save it in the correct directory.
KeepNewSections If you change the default and destroy the sections
in the template, whatever the settings for the template's last section
settings become the settings for the whole document.If you stay with
default, extra sections are added at the end of the document
inheriting the properties of the last section.

The code
Yes, it is a bit long, but it runs as is.

Option Explicit

'AutoMaggie
'$Author (c) Word Heretic
'$Version Dec 2004
'$Short Does a quick and simple clean on your document.
'$Tailor See SafeAddNewDocument

'Advanced: This part of the code needs to be in a standard code module

#If VBA6 Then

Public Enum MaggieCloseMode
MaggieCloseModeBothOpen = 0
MaggieCloseModeCloseSource = 1
MaggieCloseModeSaveMaggie = 2
MaggieCloseModeOverWriteSource = 3
MaggieCloseModeSaveMaggieAndClose = 4
MaggieCloseModeOverWriteSourceAndClose = 5
End Enum

#Else

Public Const MaggieCloseModeBothOpen As Long = 0
Public Const MaggieCloseModeCloseSource As Long = 1
Public Const MaggieCloseModeSaveMaggie As Long = 2
Public Const MaggieCloseModeOverWriteSource As Long = 3
Public Const MaggieCloseModeSaveMaggieAndClose As Long = 4
Public Const MaggieCloseModeOverWriteSourceAndClose As Long = 5

#End If


Public Sub ActiveDocumentMaggie()
System.Cursor = wdCursorWait
Application.ScreenUpdating = False

Maggie ActiveDocument

Application.ScreenUpdating = True
System.Cursor = wdCursorNormal
End Sub


'_____________________________________________________________________
'
'Advanced: This code can be relocated to a class if required


#If VBA6 Then 'We are using Enums

Public Function Maggie( _
ByRef Source As Document, _
Optional ByRef TemplateName As String = vbNullString, _
Optional ByRef CloseMode As MaggieCloseMode =
MaggieCloseModeBothOpen, _
Optional ByRef KeepNewSections As Boolean = True _
) As Document

#Else 'No Enums, no autocomplete

Public Function Maggie( _
ByRef Source As Document, _
Optional ByRef TemplateName As String = vbNullString, _
Optional ByRef CloseMode As Long = MaggieCloseModeBothOpen, _
Optional ByRef KeepNewSections As Boolean = True _
) As Document

#End If

'Returns the Maggied document
'For commercial deep cleaning solutions, see (e-mail address removed)


'Step 1 Template name defaults to source document's

If TemplateName = vbNullString _
Then TemplateName = Source.AttachedTemplate


'Step 2 Open a new document based on a possibly spurious name

Set Maggie = SafeAddNewDocument(TemplateName)


'Step 3 Make sure have para marks before all section breaks

SectionBreakIsolate Source


'Step 4 Cummon, Cummon,
' DO DA AUTO-MAGGIE WID ME!
' Ya got to swing those hips now
' (repeat)

MaggieContent Source, Maggie, KeepNewSections


'Step 5 Copy over other bits

'Copy over document properties

CopyDocProperties Source, Maggie


'You can add your 'copy over other document bits' code
'here if you need as you have your two DOCUMENTS.


'Step 6 Close, save: whatever the user asked for

MaggieClose Source, Maggie, CloseMode

End Function



Private Function SafeAddNewDocument( _
ByRef TemplateName As String) As Document
'Simple example to always use Normal for the Maggied document
'See the article for a better function, TemplateName provided
'for compatibility with the article's better version.

Set SafeAddNewDocument = Documents.Add("Normal.dot")
End Function



Private Sub SectionBreakIsolate(ByRef Source As Document)
'Forces all section breaks in the activedocument
'to have a paragraph mark immediately before them
'This is a prerequisite for the Maggie

Dim Sect As Section
Dim Snipper As Range

For Each Sect In Source.Sections
With Sect.Range.Paragraphs
If .Item(.Count).Range.Characters.Count > 1 Then


'Insert a paramark at end of range

Sect.Range.Select
With Selection
.MoveEnd wdCharacter, -1
.Collapse wdCollapseEnd
.InsertParagraph
End With


End If
End With
Next

Set Snipper = Nothing
Set Sect = Nothing
End Sub



Private Sub MaggieContent( _
ByRef Source As Document, _
ByRef Target As Document, _
ByRef KeepNewSections As Boolean)

Dim WholeSection As Section
Dim Insertion As Range

Dim Repeat As Boolean
Dim TargetSectionCount As Long

Set Insertion = Target.Content

For Each WholeSection In Source.StoryRanges(wdMainTextStory).Sections


'We are just about to insert a new section.
'Do we have to insert a section break or not?

If Repeat Then 'not the first section, so possibly

If Not (KeepNewSections And WholeSection.Index <= _
Target.StoryRanges(wdMainTextStory).Sections.Count) Then

'We do, because there are no sections waiting for us in
'the target. Insert a section break of the correct type.

With Insertion
.InsertBreak CPageLayout2BreakType( _
WholeSection.PageSetup.SectionStart)
.Collapse wdCollapseEnd
End With

End If

Else 'First time around
Repeat = True
End If

If KeepNewSections And _
WholeSection.Index <= Insertion.Parent.Content.Sections.Count Then

'There is a section waiting for us to replace,
'use it

Set Insertion = Target.StoryRanges( _
wdMainTextStory).Sections(WholeSection.Index).Range
Insertion.MoveEnd wdCharacter, -1

End If

WholeSection.Range.Select

With Selection
.MoveEnd wdCharacter, -1
.Copy
End With

With Insertion
.Paste
.Collapse wdCollapseEnd


'Copy section layout

With .Sections(1).PageSetup


'Match column counts

With .TextColumns
While .Count < WholeSection.PageSetup.TextColumns.Count
.Add
Wend
End With


'If you want to copy over other layout
'settings, this is where you do it

End With 'Page Setup
End With 'Insertion
Next 'Whole Section

Set Insertion = Nothing
Set WholeSection = Nothing
End Sub


Private Sub CopyDocProperties( _
ByRef Source As Document, _
ByRef Target As Document)

'Copies all the document properties from one document to the next
'For example, title, subject, custom properties

On Error Resume Next 'Copying null properties causes problems, ignore

Dim DocProp As DocumentProperty

For Each DocProp In Source.BuiltInDocumentProperties
Target.BuiltInDocumentProperties(DocProp.Name) = DocProp.Value
Next

For Each DocProp In Source.CustomDocumentProperties
With DocProp
Target.CustomDocumentProperties.Add .Name, .LinkToContent, _
.Type, .Value, .LinkSource
End With
Next

On Error GoTo 0

Set DocProp = Nothing
End Sub


Private Sub MaggieClose( _
ByRef Source As Document, _
ByRef Maggie As Document, _
ByRef Mode As Long)

Dim FileName As String
Dim DotPos As Long

'Closes the documents according to the mode
'This helps support batch maggies
'In full batch mode, you overwrite the source and close both files.
'In full interactive mode, the default, you leave both documents open.
'There are also a few options inbetween

Select Case Mode

Case MaggieCloseModeCloseSource
Source.Close SaveChanges:=False

Case MaggieCloseModeOverWriteSource, _
MaggieCloseModeOverWriteSourceAndClose
FileName = Source.FullName
Source.Close SaveChanges:=False

'Overwrite the source file

Maggie.SaveAs FileName, AddToRecentFiles:=False
If Mode = MaggieCloseModeOverWriteSourceAndClose _
Then Maggie.Close False

Case MaggieCloseModeSaveMaggie, _
MaggieCloseModeSaveMaggieAndClose
FileName = Source.FullName


'Add an extension and save. If you dont have VBA6 then
'you must ensure the documents have a 3 char extension after
'a period; .doc, .txt, .htm will all be fine.

#If VBA6 Then
DotPos = InStrRev(FileName, ".")
#Else
DotPos = Len(FileName) - 4 'MAC Attack
#End If

FileName = Left$(FileName, DotPos - 1) & "-Maggie" _
& Right$(FileName, Len(FileName) - DotPos + 1)


Source.Close SaveChanges:=False
Maggie.SaveAs FileName, AddToRecentFiles:=False
If Mode = MaggieCloseModeSaveMaggieAndClose _
Then Maggie.Close False

Case MaggieCloseModeBothOpen
Maggie.Activate

End Select
End Sub


Private Function CPageLayout2BreakType( _
ByRef SectionBreakType As Long) As Long
'We are reading a section break from a section's pagelayout
'This needs to be converted to the section break type to insert
'By using constants we help make it future proof

Select Case SectionBreakType

Case wdSectionNewColumn
CPageLayout2BreakType = wdColumnBreak

Case wdSectionNewPage
CPageLayout2BreakType = wdSectionBreakNextPage

Case wdSectionEvenPage
CPageLayout2BreakType = wdSectionBreakEvenPage

Case wdSectionOddPage
CPageLayout2BreakType = wdSectionBreakOddPage

End Select
End Function
 

Ask a Question

Want to reply to this thread or ask your own question?

You'll need to choose a username for the site, which only take a couple of moments. After that, you can post your question and our members will help you out.

Ask a Question

Top