How to enable the spellchecker in a protected document

Article contributed Dave Rado, Bill Coan Bill Coan, Astrid Zeelenberg, Dan Monk and Geoff Whitfield

Unfortunately, Word's protection feature disables a huge number of  important functions, even if you only protect a single section of a document.  As well as the spellchecker, many of the items on the View, Insert, Format, Tools and Table menus are disabled, as well as most items on the Drawing, Database, Visual Basic and Picture toolbars.

The most important of these is probably the  spellchecker, which you can re-enable as follows.  In your Forms template, (which you should leave unprotected for now):

1.

Create a macro, and paste the following code in, first deleting anything in the code module that Microsoft inserted automatically.

Note: you may want to modify the line which says Selection.LanguageID = wdEnglishUS to your own language).

Option Explicit

Dim Cancelled As Boolean, MyRange As Range, _
        CorrectedError As String, oDoc As Document

Sub RunSpellcheck()

Dim oSection As Section, OriginalRange As Range

'If no documents open, quit macro
If Documents.Count = 0 Thenn
    Exit Sub
End If


Set oDoc = ActiveDocument

'Check what type of protection - if any - has been applied
Select Case oDoc.ProtectionType

    'If not protected, or if protected for tracked changes,
    'run spellchecker and quit
    '-------------
    Case wdNoProtection, wdAllowOnlyRevisions
        If Options.CheckGrammarWithSpelling Then
            oDoc.CheckGrammar
        Else
            oDoc.CheckSpellingg
        End If
        Application.ScreenUpdating = True
        Application.ScreenRefresh
        If oDoc.SpellingErrors.Count = 0 Then
            If Options.CheckGrammarWithSpelling Then
                MsgBox "The spelling and grammar check is complete", _
                        vbInformation
            Else
                MsgBox "The spelling check is complete", vbInformation
            End If
        End If
        System.Cursor = wdCursorNormal
        Exit Sub
    '-------------
    Case wdAllowOnlyComments
        'Don't want to run spellchecker if protected for comments
         Exit Sub
End Select


Set OriginalRange = Selection.Range
System.Cursor = wdCursorWait

'-------------
'-------------
'If we've got this far, it's protected for forms
'Now unprotect the document
oDoc.Unprotect
oDoc.SpellingChecked = False

'Check each section for its protection property -
'which you can get even after unprotecting the document.
'If the section was protected, call a subroutine to spellcheck the formfields.
'if it wasn't, spellcheck the section
StatusBar = "Spellchecking document ..."
For Each oSection In oDoc.Sections
    If oSection.ProtectedForForms Then
        Call CheckProtectedSection(oSection)
        If Cancelled Then
            'Boolean variable returned by CheckProtectedSection
            'procedure if user pressed Cancel button
            Exit For
        End If
    Else

        If oSection.Range.SpellingErrors.Count > 0 Then
            Application.ScreenUpdating = True
            oSection.Range.CheckSpelling
            If oSection.Range.SpellingErrors.Count > 0 Then
                'User pressed Cancel button
                '(Pressing Ignore reduces the count, pressing Cancel doesn't)
                Exit For
            End If
        End If

    End If
Next oSection

'Re-protect the document
oDoc.Protect Type:=wdAllowOnlyFormFields, NoReset:=True
OriginalRange.Select
Application.ScreenUpdating = True
Application.ScreenRefresh
If oDoc.Range.SpellingErrors.Count = 0 Then
    If Options.CheckGrammarWithSpelling Then
        MsgBox "The spelling and grammar check is complete", _
                vbInformation
    Else
        MsgBox "The spelling check is complete", vbInformation
    End If
End If


'Release variables from memory
System.Cursor = wdCursorNormal
Cancelled = False
CorrectedError = vbNullString
Set MyRange = Nothing

End Sub


Private Sub CheckProtectedSection(oSection As Section)

Dim FmFld As FormField, FmFldCount As Long, Pos As Long

'check only the text formfields,
'don't check listboxes and checkboxes - this speeds up the code
Application.ScreenUpdating = False
For Each FmFld In oSection.Range.FormFields
    'Check to see if the field is a text formfield
    If FmFld.Type = wdFieldFormTextInput Thenn
        'Check if the field is a 'real' text field (no date, formula etc);
        'and that it is enabled for text input
        If FmFld.TextInput.Type = wdRegularText And FmFld.Enabled Then
            'The following subroutine won't be called if Word 97 is in use
            If Not Left$(Application.Version, 1) = "8" Then
                Call TurnNoProofingOff(FmFld)
            End If
            FmFld.Range.SpellingChecked = Falsee

            'Change the language constant in the following line if necessary;
            'when you type the = sign, a list of all supported language
            'constants will appear, and you can choose one from the list.
            FmFld.Range.LanguageID = wdEnglishUS  
            'Or whichever language is appropriate for you

            'If the current form field contains errors, spellcheck the text in it
 
           If FmFld.Range.SpellingErrors.Count > 0 Then
                'The following condition is to allow for a Word 97 bug, which
                'was fixed in 2000; (and in the latest Word 97 patches). If
                'the formfield is in a table and contains more than one
                'paragraph, then spellchecking it will crash Word 97
                If Left$(Application.Version, 1) = "8" _
                          And FmFld.Range.Paragraphs.Count > 1 _
                          And FmFld.Range.Tables.Count > 0 Then
                    Call Word97TableBugWorkaround(FmFld)
                    If Cancelled Then Exit Sub
                Else
                    'Set a range to the formfield's range in case the user
                    'accidentally destroys the formfield by overtyping its entire
                    'contents
                    Set MyRange = FmFld.Range
                    FmFldCount = oSection.Range.FormFields.Count
                    Application.ScreenUpdating = True

                    FmFld.Range.CheckSpelling

                    If IsObjectValid(FmFld) Then
                        If FmFld.Range.SpellingErrors.Count > 0 Then
                            'User pressed Cancel button. (Pressing Ignore
                            'reduces the count, pressing Cancel doesn't)
                            Cancelled = True
                            Exit Sub
                        End If
                    Else

                        'If formfield was destroyed because user overtyped its
                        'entire contents
                        CorrectedError = MyRange.Text
                        If Len(CorrectedError) = 0 Then
                            CorrectedError = MyRange.Words(1).Text
                        End If

                        'Formfields should really NEVER be preceded by a tab;
                        'design your forms so that each formfield is in its own
                        'table cell (removing borders as necessary). However, to
                        'cater for any legacy forms you may have, the following
                        'loop works around the possibility that it might be
                        'preceded by a tab
                        Pos = InStr(CorrectedError, vbTab)
                        Do While Pos > 0
                            CorrectedError = Mid$(CorrectedError, Pos + 1)
                            Pos = InStr(CorrectedError, vbTab)
                        Loop

                        'If formfield was destroyed when the user corrected the
                        'spelling, reinstate it, and put the user's correction into its
                        'result. Note that although Undo reinstates the Formfield
                        'itself, if the Formfield is preceded by a tab, It doesn't
                        'reinstate the FmFld object, hence the need to do a count
                        '(although, as previously stated, in a well-designed form,
                        'formfields should never be preceded by a tab, as it's
                        'better use table cells (removing borders as necessary).
                        Do While Not FmFldCount = _
                                oSection.Range.FormFields.Count
                            oDoc.Undo
                        Loop

                        'Also due to a Word bug, if the formfield is preceded by a
                        'tab, the text within the formfield may now be selected
                        'without the formfield itself being selected!
                        'Hence the following convoluted workaround
                        If Selection.FormFields.Count = 0 Then
                            Selection.MoveRight unit:=wdCharacter
                            Selection.MoveLeft unit:=wdCharacter, Extend:=True
                        End If
                        If Not IsObjectValid(FmFld) Then
                            Set FmFld =  Selection.FormFields(1)
                        End If
                        FmFld.Result = CorrectedError
                    End If
                End If

                Application.ScreenUpdating = False
            End If
        End If
    End If
Next
FmFld

End Sub


Private Sub TurnNoProofingOff(FmFld As FormField)
    'This subroutine is called only in Word 2000 and above
 
   FmFld.Range.NoProofing = False
End Sub


Private Sub Word97TableBugWorkaround(FmFld As FormField)

'Unlink formfield (convert to text)
Set MyRange = FmFld.Range
FmFld.Range.Fields(1).Unlink
Application.ScreenUpdating = True
MyRange.CheckSpelling
If MyRange.SpellingErrors.Count > 0 Then
    'User pressed Cancel button
    '(Pressing Ignore reduces the count, pressing Cancel doesn't)
    Cancelled = True
End If
CorrectedError = MyRange.Text
'Undo to reinstate the formfield
Do While Not IsObjectValid(FmFld)
    oDoc.Undo
Loop
FmFld.Range.Fields(1).Result.Text = CorrectedError
Application.ScreenUpdating = Falsee

End Sub


Notes:

The reason for the TurnNoProofingOff() subroutine is that Word 2000 treats No Proofing as a separate property. That is, you can set the No Proofing property to true or false without losing the Language setting. In Word 97, No Proofing was a language setting, so there was no way to have a selection of text marked both as No Proofing and at the same time as, say, wdEnglishUS. But in Word 2000 you can do this. It's really a great improvement but a bit of an extra pain for developers trying to meet the needs of both versions of Word.

The Word97TableBugWorkaround macro is not required if all of your users are using Word 2000 or higher, or, if they have all installed the so-called Word 97 Leap Year Fix (or later patches). In the original release of Word 97, if you spellchecked a form field within a table, and if the form field contained multiple paragraphs, Word would crash. This bug was fixed by the so-called Word 97 Leap Year Fix(a free upgrade which fixed well over 40 bugs). The Word97TableBugWorkaround subroutine (above) works by converting the form field to plain text, spellchecking the text, using Undo to reinstate the formfield, and putting the spellchecked result into the reinstated field.. The subroutine is only invoked if you are using Word 97, if the formfield is in a table, and if the formfield contains more than one paragraph, so leaving it in won't actually do any harm even if you are using a later version of Word.

The reason that, depending on the user's settings, the macro runs the spelling and grammar checker if the document is not protected, but only runs the spellchecker, even in unprotected sections, if the document is protected for forms, is because of a bug with the CheckGrammar method. The CheckGrammar method works properly with the document object, (oDoc.CheckGrammar checks both spelling and grammar), but it does not work properly with Range objects (for instance, oSection.Range.CheckGrammar checks the grammar in the section but does not check the spelling!)
  

2.

If your form is password protected, and you don't want the user to be asked for the password to reprotect it, you have to put the password in your code: 

oDoc.Unprotect Password:="Password"

And:

oDoc.Protect Type:=wdAllowOnlyFormFields, NoReset:=True, _
  Password:="Password"

If you want to ensure that users can't possibly see the password, you can also password protect your code (in the VBE, select Tools + Properties, and then select the protection tab).

It may be worth giving all centrally created protected forms the same password, for ease of maintenance.

3.

To make it seamless to the user, you could assign your macro to a toolbar button, and to a menu button on the Tools menu , replacing the existing spellchecking buttons with yours.

You could also copy the button images from the Microsoft buttons to yours, to make it completely seamless to the user.
  

4.

Because of the way in which Word's spellcheck dialog works, if any of your formfields are surrounded by (protected) text, some of this text may be displayed in the dialog alongside a spelling error – thus allowing the user to modify protected text ““through the back door.

The best way to prevent this is to design your forms such that each formfield is in its own table cell; and the problem will then never arise. In my experience, with a little ingenuity, it is always possible to design your forms in this way.

Failing that, the only ways of completely preventing this problem from arising would either be to:

a)

Have the macro put the result of each formfield, in turn, into a dummy document (or spellcheck window”), have the user spellcheck it there, and have the macro put the spellchecked text back into the formfield's result. In order for the user to see what they were spellchecking in context, your macro could tile the form document and the ““spellcheck window. But this workaround would be clunky.

b)

Write your own spellcheck dialog (using a UserForm).

Both the above solutions are beyond the scope of this site; and in any case, will not be necessary if your formfields are in their own table cells.