Consulting

Results 1 to 13 of 13

Thread: Inserting Text via VBA into a Text Form Field in a Protected Word Document

  1. #1

    Inserting Text via VBA into a Text Form Field in a Protected Word Document

    Hello everyone.

    I have a Protected Form(that I don't have the password to) with Text Form Fields and have been struggling to get text to be inserted via VBA into the Text Form Field. Here's the code:

    Sub TypeTextMethod()
    Selection.TypeText Text:="Hello" 
    End Sub
    It's nothing fancy, but after i click on the Text Form Field and run it, I get:
    Run-time Error '4065': This method or property is not available because the object refers to a protected area of the document.

    Pasting text seems to work but that would mean me manually highlighting the text (from a different source), manually clicking the text field, then pasting it.
    Is there no other way to Insert text into a Text Form Field?

    Thanks in advance everyone.

    -Steve

  2. #2
    If you are not going to unlock the form then use the following code to write to the selected text form field.

    Option Explicit
    
    Sub WriteToTextFF()
        With GetCurrentFF
            If .Type = wdFieldFormTextInput Then
                .Result = "This is the text to enter into the field"
            End If
        End With
    lbl_Exit:
        Exit Sub
    End Sub
    
    Private Function GetCurrentFF() As Word.FormField
        Set rngFF = Selection.Range
        rngFF.Expand wdParagraph
        For Each fldFF In rngFF.FormFields
            Set GetCurrentFF = fldFF
            Exit For
        Next fldFF
    lbl_Exit:
        Exit Function
    End Function
    Graham Mayor - MS MVP (Word) 2002-2019
    Visit my web site for more programming tips and ready made processes
    http://www.gmayor.com

  3. #3

    Thumbs up

    Quote Originally Posted by gmayor View Post
    If you are not going to unlock the form then use the following code to write to the selected text form field.

    Option Explicit
    
    Sub WriteToTextFF()
        With GetCurrentFF
            If .Type = wdFieldFormTextInput Then
                .Result = "This is the text to enter into the field"
            End If
        End With
    lbl_Exit:
        Exit Sub
    End Sub
    
    Private Function GetCurrentFF() As Word.FormField
        Set rngFF = Selection.Range
        rngFF.Expand wdParagraph
        For Each fldFF In rngFF.FormFields
            Set GetCurrentFF = fldFF
            Exit For
        Next fldFF
    lbl_Exit:
        Exit Function
    End Function
    This solved my problem!!!

    Thanks so much gmayor!

    -Steve

  4. #4
    Quote Originally Posted by Steve Hale View Post
    This solved my problem!!!

    Thanks so much gmayor!

    -Steve
    Hello again.

    While the code gmayor posted is absolute brilliance and is currently working well on several assigned Command Buttons, there was one string of text that was way too long as it gave out the 4609 Error: String too long.

    I've done some digging around and most of the workarounds are having the Document Unprotected. This poses a problem as I am not in possession of this form's password. I also tested this protected field by typing in the text that the system was considering to be "too long", and IT ACCEPTED IT! Looks like this field was set to UNLIMITED.

    Any recommendations?

    Always, thank you so much!

    -Steve
    Last edited by Steve Hale; 09-16-2016 at 11:12 AM.

  5. #5
    Microsoft Word MVP 2003-2009 VBAX Guru gmaxey's Avatar
    Joined
    Sep 2005
    Posts
    3,336
    Location
    Create a copy of the document that is unprotected and your can then define your own password or leave it without a password:

    Sub ScratchMacro()
    'A basic Word macro coded by Greg Maxey
    Dim oRng As Range
    Dim oDoc As Document
      Set oRng = ActiveDocument.Range
        oRng.End = oRng.End - 1
        oRng.Copy
        Set oDoc = Documents.Add
        oDoc.Range.Paste
    lbl_Exit:
      Exit Sub
    End Sub
    Greg

    Visit my website: http://gregmaxey.com

  6. #6
    Quote Originally Posted by gmaxey View Post
    Create a copy of the document that is unprotected and your can then define your own password or leave it without a password:

    Sub ScratchMacro()
    'A basic Word macro coded by Greg Maxey
    Dim oRng As Range
    Dim oDoc As Document
      Set oRng = ActiveDocument.Range
        oRng.End = oRng.End - 1
        oRng.Copy
        Set oDoc = Documents.Add
        oDoc.Range.Paste
    lbl_Exit:
      Exit Sub
    End Sub
    Thanks for this gmaxey. This worked on a different document of ours.

  7. #7
    Quote Originally Posted by gmayor View Post
    If you are not going to unlock the form then use the following code to write to the selected text form field.

    Option Explicit
    
    Sub WriteToTextFF()
        With GetCurrentFF
            If .Type = wdFieldFormTextInput Then
                .Result = "This is the text to enter into the field"
            End If
        End With
    lbl_Exit:
        Exit Sub
    End Sub
    
    Private Function GetCurrentFF() As Word.FormField
        Set rngFF = Selection.Range
        rngFF.Expand wdParagraph
        For Each fldFF In rngFF.FormFields
            Set GetCurrentFF = fldFF
            Exit For
        Next fldFF
    lbl_Exit:
        Exit Function
    End Function
    Hi again.

    While working on this, a similar form that has multiple fields was in need of the same code.

    I was trying to make it so that when I ran this, it would JUMP / GOTO onto the next field and insert the new text that is specific for the field.

    What I have tried:
    1. Used Sendkeys TAB
    2. Used Sendkeys DOWN
    3. Replicated the same procedure and renamed variables in a different Module and Called for it in the Original Module
    Result on all 3 instances: It put in the FIRST TEXT i wanted and then overwriting it with the new text in the SAME text field and then it TABBED OVER / WENT TO THE to the next field I was aiming for.

    I am unable to use SETFOCUS as this is the form that is protected and is generated by the application we are using.

    Thanks a bunch for the helping hand!

    -Steve

  8. #8
    Don't even think of using SendKeys!

    You need to get the form field names. You can do that with the GetCurrentFF function (GetName macro). Then you can set the values for each text field by name and write to them all with a single macro.

    Sub GetName()
        MsgBox GetCurrentFF.name
    lbl_Exit:
        Exit Sub
    End Sub
    
    Sub FillFields()
    Dim oFF As FormField
        For Each oFF In ActiveDocument.FormFields
            oFF.Select
            WriteToTextFF
        Next oFF
    lbl_Exit:
        Set oFF = Nothing
        Exit Sub
    End Sub
    
    
    Sub WriteToTextFF()
        With GetCurrentFF
            If .Type = wdFieldFormTextInput Then
                Select Case .name
                    Case "Text1"
                        .Result = "This is the text to enter into the Text1 field"
                    Case "Text2"
                        .Result = "This is the text to enter into the Text2 field"
                    Case "Text3"
                        .Result = "This is the text to enter into the Text3 field"
                    'etc
                End Select
            End If
        End With
    lbl_Exit:
        Exit Sub
    End Sub
     
    Private Function GetCurrentFF() As Word.FormField
        Set rngFF = Selection.Range
        rngFF.Expand wdParagraph
        For Each fldFF In rngFF.FormFields
            Set GetCurrentFF = fldFF
            Exit For
        Next fldFF
    lbl_Exit:
        Exit Function
    End Function
    Graham Mayor - MS MVP (Word) 2002-2019
    Visit my web site for more programming tips and ready made processes
    http://www.gmayor.com

  9. #9
    Microsoft Word MVP 2003-2009 VBAX Guru gmaxey's Avatar
    Joined
    Sep 2005
    Posts
    3,336
    Location
    Graham,

    Headed off to class but can you look at this:

    Private Function GetCurrentFF() As Word.FormField
    Dim fldFF As FormField
        Set rngFF = Selection.Range
        rngFF.Expand wdParagraph
        For Each fldFF In rngFF.FormFields
            Set GetCurrentFF = fldFF
            Exit For
        Next fldFF
    lbl_Exit:
        Exit Function
    End Function
    If I have two or more FFs in a paragraph and run this code the FF returned is always the first in the paragraph not the the one the cursor might be in.
    Greg

    Visit my website: http://gregmaxey.com

  10. #10
    That was what that particular code was supposed to do, however for more than one field in the paragraph, the following will work in the context of the thread, but not if your cursor is simply in the field. The field must be selected.

    Private Function GetCurrentFF() As Word.FormField
    Dim rngff As Range
        Set rngff = Selection.Range
        Set GetCurrentFF = rngff.FormFields(1)
    lbl_Exit:
        Exit Function
    End Function
    Graham Mayor - MS MVP (Word) 2002-2019
    Visit my web site for more programming tips and ready made processes
    http://www.gmayor.com

  11. #11
    Quote Originally Posted by gmayor View Post
    Don't even think of using SendKeys!

    You need to get the form field names. You can do that with the GetCurrentFF function (GetName macro). Then you can set the values for each text field by name and write to them all with a single macro.

    Sub GetName()
        MsgBox GetCurrentFF.name
    lbl_Exit:
        Exit Sub
    End Sub
    
    Sub FillFields()
    Dim oFF As FormField
        For Each oFF In ActiveDocument.FormFields
            oFF.Select
            WriteToTextFF
        Next oFF
    lbl_Exit:
        Set oFF = Nothing
        Exit Sub
    End Sub
    
    
    Sub WriteToTextFF()
        With GetCurrentFF
            If .Type = wdFieldFormTextInput Then
                Select Case .name
                    Case "Text1"
                        .Result = "This is the text to enter into the Text1 field"
                    Case "Text2"
                        .Result = "This is the text to enter into the Text2 field"
                    Case "Text3"
                        .Result = "This is the text to enter into the Text3 field"
                    'etc
                End Select
            End If
        End With
    lbl_Exit:
        Exit Sub
    End Sub
     
    Private Function GetCurrentFF() As Word.FormField
        Set rngFF = Selection.Range
        rngFF.Expand wdParagraph
        For Each fldFF In rngFF.FormFields
            Set GetCurrentFF = fldFF
            Exit For
        Next fldFF
    lbl_Exit:
        Exit Function
    End Function
    HOLY SCHNEIKE! This works beautifully!

    This definitely solved my Word Problem!

    It's not a major issue but would be a nice addition... CHECKBOXES. I tried giving it a .Result of the following:
    " "
    " "
    "x"
    "X"
    x
    1
    -1
    "1"
    True
    "True"... none seem to work.

    THANKS GMAYOR AND GMAXEY!

    -Steve
    Last edited by Steve Hale; 09-21-2016 at 10:15 AM.

  12. #12
    Microsoft Word MVP 2003-2009 VBAX Guru gmaxey's Avatar
    Joined
    Sep 2005
    Posts
    3,336
    Location
        With GetCurrentFF
            'If .Type = wdFieldFormTextInput Then
                Select Case .Name
                Case "Check1"
                  .CheckBox.Value = True
                Case "Text1"
                    .Result = "This is the text to enter into the Text1 field"
                Case "Text2"
                    .Result = "This is the text to enter into the Text2 field"
                Case "Text3"
                    .Result = "This is the text to enter into the Text3 field"
                     'etc
                End Select
            'End If
        End With
    Greg

    Visit my website: http://gregmaxey.com

  13. #13
    Quote Originally Posted by gmaxey View Post
        With GetCurrentFF
            'If .Type = wdFieldFormTextInput Then
                Select Case .Name
                Case "Check1"
                  .CheckBox.Value = True
                Case "Text1"
                    .Result = "This is the text to enter into the Text1 field"
                Case "Text2"
                    .Result = "This is the text to enter into the Text2 field"
                Case "Text3"
                    .Result = "This is the text to enter into the Text3 field"
                     'etc
                End Select
            'End If
        End With
    Hi gmaxey.

    It works!

    Thanks so much for your time.

    -Steve

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •