From: Jay Freedman on
Hi Dimitri,

The following code works in your template to display the names of the
documents in the hyperlinks. I'll leave it to you to replace the
MsgBox statement with the code that actually opens and prints those
documents.

Private Sub PrintButton_Click()
Dim oDoc As Document
Dim FrmFld As FormField
Dim Rg As Range
Dim HLink As Hyperlink
Dim docName As String

Set oDoc = ActiveDocument
For Each FrmFld In oDoc.FormFields
If FrmFld.Type = wdFieldFormCheckBox Then
If FrmFld.CheckBox.Value = True Then
Set Rg = FrmFld.Range.Cells(1).Range
Set HLink = Rg.Hyperlinks(1)
docName = HLink.Address
MsgBox docName
End If
End If
Next
End Sub

The code is more verbose than it really needs to be, but I left it
that way so you can follow more easily what it's doing.

The For Each statement is a more efficient way of looking at each
formfield in the document. If the number of formfields was large, the
macro would slow perceptibly as the counter x increases, although the
effect is slight for less than 20 or 30 of them.

Each time a checked box is found, the range Rg is set to the table
cell that contains the checkbox, and the HLink variable then is set to
the single hyperlink in that range. (There might be a simpler way to
get the hyperlink from the formfield, but this is reliable and
independent of whether the hyperlink contains the formfield or vice
versa.) Finally, the text of the hyperlink's address is the name of
the document to work on.

--
Regards,
Jay Freedman
Microsoft Word MVP FAQ: http://word.mvps.org
Email cannot be acknowledged; please post all follow-ups to the
newsgroup so all may benefit.


On Tue, 2 Mar 2010 03:08:11 -0800, Dimitri Backaert
<DimitriBackaert(a)discussions.microsoft.com> wrote:

>Hi Jay, Hi Fumei2,
>
>I'm sorry for my lack of information.
>Let me try to clear things out.
>
>I've uploaded a demo file which will surely answer your questions.
>It can be dowloaded at this location:
>http://www.dss-bvba.be/Checklist.dot
>
>Thanks in advance
>
>"Fumei2 via OfficeKB.com" wrote:
>
>> I too am unclear as to what the situation is. Are these checkboxes
>> themselves tagged as hyperlinks. This is possible, although a checkbox
>> formfield selected and hyperlinked will NOT activate the hyperlink by
>> checking the checkbox. Although you CAN activate the hyperlink by right-
>> clicking. (Assuming the document is indeed protected for forms.)
>>
>> What does "Get the attached Hyperlink" actually mean?
>>
>> Dimitri Backaert wrote:
>> >Hi,
>> >
>> >I have a question on how to capture a hyperlink that is inserted behind a
>> >checked FormField (type Checkbox).
>> >
>> >The idea is to create some sort of index page with checkboxes, which will
>> >summarize a number of hyperlinks (which point towards several files on the
>> >company network).
>> >A button will print out all of the CHECKED checkboxes.
>> >
>> >I'm not able to achieve this.
>> >This is my code so far:
>> >
>> >Private Sub PrintButton_Click()
>> >
>> > For x = 1 To ActiveDocument.FormFields.Count
>> > If ActiveDocument.FormFields(x).Type = wdFieldFormCheckBox Then
>> > If ActiveDocument.FormFields(x).CheckBox.Value = True Then
>> >
>> > 'Get the attached Hyperlink and print this document
>> > MsgBox x
>> >
>> > End If
>> > End If
>> > Next x
>> >
>> >End Sub
>> >
>> >Can anyone help me out?
>> >
>> >Thanks in advance.
>>
>> --
>> Message posted via http://www.officekb.com
>>
>> .
>>
From: Dimitri Backaert on
Hi Jay,

Thanks for your help.
It's really clear to me.

I've encountered another problem.
The file types which need to be printed, can be various.
It can be .doc, .pdf, .ppt,or .xls

I've modified your code as follows:

Private Sub PrintButton_Click()

Dim oDoc As Document
Dim FrmFld As FormField
Dim Rg As Range
Dim HLink As Hyperlink
Dim docName As String

Set oDoc = ActiveDocument

For Each FrmFld In oDoc.FormFields
If FrmFld.Type = wdFieldFormCheckBox Then
If FrmFld.CheckBox.Value = True Then
Set Rg = FrmFld.Range.Cells(1).Range
Set HLink = Rg.Hyperlinks(1)
docName = HLink.Address
MsgBox docName

Application.PrintOut , , , , , , , , , , , , docName

End If
End If
Next
End Sub

This does work for .doc files, but when I'm printing a PDF file, i get some
kind of code which is printed to the default printer.
It isn't clear text.

Is there some way of handling this?

Thanks.

"Jay Freedman" wrote:

> Hi Dimitri,
>
> The following code works in your template to display the names of the
> documents in the hyperlinks. I'll leave it to you to replace the
> MsgBox statement with the code that actually opens and prints those
> documents.
>
> Private Sub PrintButton_Click()
> Dim oDoc As Document
> Dim FrmFld As FormField
> Dim Rg As Range
> Dim HLink As Hyperlink
> Dim docName As String
>
> Set oDoc = ActiveDocument
> For Each FrmFld In oDoc.FormFields
> If FrmFld.Type = wdFieldFormCheckBox Then
> If FrmFld.CheckBox.Value = True Then
> Set Rg = FrmFld.Range.Cells(1).Range
> Set HLink = Rg.Hyperlinks(1)
> docName = HLink.Address
> MsgBox docName
> End If
> End If
> Next
> End Sub
>
> The code is more verbose than it really needs to be, but I left it
> that way so you can follow more easily what it's doing.
>
> The For Each statement is a more efficient way of looking at each
> formfield in the document. If the number of formfields was large, the
> macro would slow perceptibly as the counter x increases, although the
> effect is slight for less than 20 or 30 of them.
>
> Each time a checked box is found, the range Rg is set to the table
> cell that contains the checkbox, and the HLink variable then is set to
> the single hyperlink in that range. (There might be a simpler way to
> get the hyperlink from the formfield, but this is reliable and
> independent of whether the hyperlink contains the formfield or vice
> versa.) Finally, the text of the hyperlink's address is the name of
> the document to work on.
>
> --
> Regards,
> Jay Freedman
> Microsoft Word MVP FAQ: http://word.mvps.org
> Email cannot be acknowledged; please post all follow-ups to the
> newsgroup so all may benefit.
>
>
> On Tue, 2 Mar 2010 03:08:11 -0800, Dimitri Backaert
> <DimitriBackaert(a)discussions.microsoft.com> wrote:
>
> >Hi Jay, Hi Fumei2,
> >
> >I'm sorry for my lack of information.
> >Let me try to clear things out.
> >
> >I've uploaded a demo file which will surely answer your questions.
> >It can be dowloaded at this location:
> >http://www.dss-bvba.be/Checklist.dot
> >
> >Thanks in advance
> >
> >"Fumei2 via OfficeKB.com" wrote:
> >
> >> I too am unclear as to what the situation is. Are these checkboxes
> >> themselves tagged as hyperlinks. This is possible, although a checkbox
> >> formfield selected and hyperlinked will NOT activate the hyperlink by
> >> checking the checkbox. Although you CAN activate the hyperlink by right-
> >> clicking. (Assuming the document is indeed protected for forms.)
> >>
> >> What does "Get the attached Hyperlink" actually mean?
> >>
> >> Dimitri Backaert wrote:
> >> >Hi,
> >> >
> >> >I have a question on how to capture a hyperlink that is inserted behind a
> >> >checked FormField (type Checkbox).
> >> >
> >> >The idea is to create some sort of index page with checkboxes, which will
> >> >summarize a number of hyperlinks (which point towards several files on the
> >> >company network).
> >> >A button will print out all of the CHECKED checkboxes.
> >> >
> >> >I'm not able to achieve this.
> >> >This is my code so far:
> >> >
> >> >Private Sub PrintButton_Click()
> >> >
> >> > For x = 1 To ActiveDocument.FormFields.Count
> >> > If ActiveDocument.FormFields(x).Type = wdFieldFormCheckBox Then
> >> > If ActiveDocument.FormFields(x).CheckBox.Value = True Then
> >> >
> >> > 'Get the attached Hyperlink and print this document
> >> > MsgBox x
> >> >
> >> > End If
> >> > End If
> >> > Next x
> >> >
> >> >End Sub
> >> >
> >> >Can anyone help me out?
> >> >
> >> >Thanks in advance.
> >>
> >> --
> >> Message posted via http://www.officekb.com
> >>
> >> .
> >>
> .
>
From: Jay Freedman on
You'll need to expand your macro to look at the extension in the
filename and then take the appropriate action.

Word cannot, by itself, print anything other than .doc, .rtf, .html,
or .txt -- the kinds of files listed in the File > Open dialog. For
any other kind of file, the code should pass the file to an
application that can open and print that kind of document.

In some cases, such as Adobe Reader, you can put a switch on a command
line in the Shell statement to tell the application to print the
document (see the VBA help on "shell statement" and
http://www.robvanderwoude.com/commandlineswitches.php#Acrobat). In
other cases you'll have to use the application's VBA capability to
start it, make it open and print, and then close (see
http://word.mvps.org/FAQs/InterDev/ControlXLFromWord.htm).

To be honest, it's going to be a fair bit of work.

--
Regards,
Jay Freedman
Microsoft Word MVP FAQ: http://word.mvps.org
Email cannot be acknowledged; please post all follow-ups to the
newsgroup so all may benefit.

On Thu, 4 Mar 2010 01:22:01 -0800, Dimitri Backaert
<DimitriBackaert(a)discussions.microsoft.com> wrote:

>Hi Jay,
>
>Thanks for your help.
>It's really clear to me.
>
>I've encountered another problem.
>The file types which need to be printed, can be various.
>It can be .doc, .pdf, .ppt,or .xls
>
>I've modified your code as follows:
>
>Private Sub PrintButton_Click()
>
> Dim oDoc As Document
> Dim FrmFld As FormField
> Dim Rg As Range
> Dim HLink As Hyperlink
> Dim docName As String
>
> Set oDoc = ActiveDocument
>
> For Each FrmFld In oDoc.FormFields
> If FrmFld.Type = wdFieldFormCheckBox Then
> If FrmFld.CheckBox.Value = True Then
> Set Rg = FrmFld.Range.Cells(1).Range
> Set HLink = Rg.Hyperlinks(1)
> docName = HLink.Address
> MsgBox docName
>
> Application.PrintOut , , , , , , , , , , , , docName
>
> End If
> End If
> Next
>End Sub
>
>This does work for .doc files, but when I'm printing a PDF file, i get some
>kind of code which is printed to the default printer.
>It isn't clear text.
>
>Is there some way of handling this?
>
>Thanks.
>
>"Jay Freedman" wrote:
>
>> Hi Dimitri,
>>
>> The following code works in your template to display the names of the
>> documents in the hyperlinks. I'll leave it to you to replace the
>> MsgBox statement with the code that actually opens and prints those
>> documents.
>>
>> Private Sub PrintButton_Click()
>> Dim oDoc As Document
>> Dim FrmFld As FormField
>> Dim Rg As Range
>> Dim HLink As Hyperlink
>> Dim docName As String
>>
>> Set oDoc = ActiveDocument
>> For Each FrmFld In oDoc.FormFields
>> If FrmFld.Type = wdFieldFormCheckBox Then
>> If FrmFld.CheckBox.Value = True Then
>> Set Rg = FrmFld.Range.Cells(1).Range
>> Set HLink = Rg.Hyperlinks(1)
>> docName = HLink.Address
>> MsgBox docName
>> End If
>> End If
>> Next
>> End Sub
>>
>> The code is more verbose than it really needs to be, but I left it
>> that way so you can follow more easily what it's doing.
>>
>> The For Each statement is a more efficient way of looking at each
>> formfield in the document. If the number of formfields was large, the
>> macro would slow perceptibly as the counter x increases, although the
>> effect is slight for less than 20 or 30 of them.
>>
>> Each time a checked box is found, the range Rg is set to the table
>> cell that contains the checkbox, and the HLink variable then is set to
>> the single hyperlink in that range. (There might be a simpler way to
>> get the hyperlink from the formfield, but this is reliable and
>> independent of whether the hyperlink contains the formfield or vice
>> versa.) Finally, the text of the hyperlink's address is the name of
>> the document to work on.
>>
>> --
>> Regards,
>> Jay Freedman
>> Microsoft Word MVP FAQ: http://word.mvps.org
>> Email cannot be acknowledged; please post all follow-ups to the
>> newsgroup so all may benefit.
>>
>>
>> On Tue, 2 Mar 2010 03:08:11 -0800, Dimitri Backaert
>> <DimitriBackaert(a)discussions.microsoft.com> wrote:
>>
>> >Hi Jay, Hi Fumei2,
>> >
>> >I'm sorry for my lack of information.
>> >Let me try to clear things out.
>> >
>> >I've uploaded a demo file which will surely answer your questions.
>> >It can be dowloaded at this location:
>> >http://www.dss-bvba.be/Checklist.dot
>> >
>> >Thanks in advance
>> >
>> >"Fumei2 via OfficeKB.com" wrote:
>> >
>> >> I too am unclear as to what the situation is. Are these checkboxes
>> >> themselves tagged as hyperlinks. This is possible, although a checkbox
>> >> formfield selected and hyperlinked will NOT activate the hyperlink by
>> >> checking the checkbox. Although you CAN activate the hyperlink by right-
>> >> clicking. (Assuming the document is indeed protected for forms.)
>> >>
>> >> What does "Get the attached Hyperlink" actually mean?
>> >>
>> >> Dimitri Backaert wrote:
>> >> >Hi,
>> >> >
>> >> >I have a question on how to capture a hyperlink that is inserted behind a
>> >> >checked FormField (type Checkbox).
>> >> >
>> >> >The idea is to create some sort of index page with checkboxes, which will
>> >> >summarize a number of hyperlinks (which point towards several files on the
>> >> >company network).
>> >> >A button will print out all of the CHECKED checkboxes.
>> >> >
>> >> >I'm not able to achieve this.
>> >> >This is my code so far:
>> >> >
>> >> >Private Sub PrintButton_Click()
>> >> >
>> >> > For x = 1 To ActiveDocument.FormFields.Count
>> >> > If ActiveDocument.FormFields(x).Type = wdFieldFormCheckBox Then
>> >> > If ActiveDocument.FormFields(x).CheckBox.Value = True Then
>> >> >
>> >> > 'Get the attached Hyperlink and print this document
>> >> > MsgBox x
>> >> >
>> >> > End If
>> >> > End If
>> >> > Next x
>> >> >
>> >> >End Sub
>> >> >
>> >> >Can anyone help me out?
>> >> >
>> >> >Thanks in advance.
>> >>
>> >> --
>> >> Message posted via http://www.officekb.com
>> >>
>> >> .
>> >>
>> .
>>
From: Dimitri Backaert on
Hi Jay,

Thanks for your input.
It helped me solve my problem.

I've modified my code as below

Private Sub PrintButton_Click()

Dim oDoc As Document
Dim FrmFld As FormField
Dim Rg As Range
Dim HLink As Hyperlink
Dim docName As String
Dim docExtension As String
Dim blank As String

Shell "wscript " & Chr(34) & "C:\pauseQueue.vbs" & Chr(34)

Application.ScreenUpdating = False
Set oDoc = ActiveDocument

ActiveDocument.PrintOut

For Each FrmFld In oDoc.FormFields
If FrmFld.Type = wdFieldFormCheckBox Then
If FrmFld.CheckBox.Value = True Then
Set Rg = FrmFld.Range.Cells(1).Range
Set HLink = Rg.Hyperlinks(1)
docName = HLink.Address

docExtension = Mid(docName, InStrRev(docName, ".") + 1)

Select Case docExtension
Case "doc"
Application.PrintOut , , , , , , , , , , , , Chr(34)
& docName & Chr(34)

Case "txt"
Application.PrintOut , , , , , , , , , , , , Chr(34)
& docName & Chr(34)

Case "dot"
Application.PrintOut , , , , , , , , , , , , Chr(34)
& docName & Chr(34)

Case "rtf"
Application.PrintOut , , , , , , , , , , , , Chr(34)
& docName & Chr(34)

Case "htm"
Application.PrintOut , , , , , , , , , , , , Chr(34)
& docName & Chr(34)

Case "html"
Application.PrintOut , , , , , , , , , , , , Chr(34)
& docName & Chr(34)

Case "pdf"
''Shell "C:\Program Files\Adobe\Reader
9.0\Reader\AcroRd32.exe /t " & chr(34) & docName & chr(34)
Shell "C:\Program Files\Adobe\Acrobat
9.0\Acrobat\Acrobat.exe /n /t " & Chr(34) & docName & Chr(34)

Case "xls"
PrintWorkbook (docName)

Case "ppt"
Shell "C:\Program Files\Microsoft
Office\OFFICE11\POWERPNT.EXE /P " & Chr(34) & docName & Chr(34)

End Select


End If
End If
Next

Application.ScreenUpdating = True
Shell "wscript " & Chr(34) & "C:\resumeQueue.vbs" & Chr(34)
End Sub

Sub PrintWorkbook(ByVal docName As String)

Dim oXL As Excel.Application
Dim oWB As Excel.Workbook
Dim oSheet As Excel.Worksheet
Dim oRng As Excel.Range
Dim ExcelWasNotRunning As Boolean
Dim WorkbookToWorkOn As String

'If Excel is running, get a handle on it; otherwise start a new instance
of Excel
On Error Resume Next
Set oXL = GetObject(, "Excel.Application")

If Err Then
ExcelWasNotRunning = True
Set oXL = New Excel.Application
End If

On Error GoTo Err_Handler

'If you want Excel to be visible, you could add the line: oXL.Visible =
True here; but your code will run faster if you don't make it visible

'Open the workbook
Set oWB = oXL.Workbooks.Open(FileName:=docName)

'Process each of the spreadsheets in the workbook
For Each oSheet In oXL.ActiveWorkbook.Worksheets
'put guts of your code here
oXL.ActiveWorkbook.PrintOut
'get next sheet
Next oSheet

'close the WorkBook
oWB.Close savechanges:=False

If ExcelWasNotRunning Then
oXL.Quit
End If

'Make sure you release object references.
Set oRng = Nothing
Set oSheet = Nothing
Set oWB = Nothing
Set oXL = Nothing

'quit
Exit Sub

Err_Handler:
MsgBox docName & " caused a problem. " & Err.Description, vbCritical, _
"Error: " & Err.Number
If ExcelWasNotRunning Then
oXL.Quit
End If

End Sub

This code works fine, but I had to implement 2 VBScripts, to help me print
out the documents in the correct order. Due to the processing time of the
different document types, the print order in the queue got all messed up.
I've found out that pausing the print queue, and enabling it at the end of
the routine, solves the problem.

The code of the VBScripts below

strComputer = "."
Set objWMIService = GetObject("winmgmts:{impersonationLevel=impersonate}!\\"
& strComputer & "\root\cimv2")

Set colInstalledPrinters = objWMIService.ExecQuery("Select * from
Win32_Printer")

For Each objPrinter In colInstalledPrinters
ObjPrinter.Resume()
Next

AND the Second File:

strComputer = "."
Set objWMIService = GetObject("winmgmts:{impersonationLevel=impersonate}!\\"
& strComputer & "\root\cimv2")

Set colInstalledPrinters = objWMIService.ExecQuery("Select * from
Win32_Printer")

For Each objPrinter In colInstalledPrinters
ObjPrinter.Pause()
Next

"Jay Freedman" wrote:

> You'll need to expand your macro to look at the extension in the
> filename and then take the appropriate action.
>
> Word cannot, by itself, print anything other than .doc, .rtf, .html,
> or .txt -- the kinds of files listed in the File > Open dialog. For
> any other kind of file, the code should pass the file to an
> application that can open and print that kind of document.
>
> In some cases, such as Adobe Reader, you can put a switch on a command
> line in the Shell statement to tell the application to print the
> document (see the VBA help on "shell statement" and
> http://www.robvanderwoude.com/commandlineswitches.php#Acrobat). In
> other cases you'll have to use the application's VBA capability to
> start it, make it open and print, and then close (see
> http://word.mvps.org/FAQs/InterDev/ControlXLFromWord.htm).
>
> To be honest, it's going to be a fair bit of work.
>
> --
> Regards,
> Jay Freedman
> Microsoft Word MVP FAQ: http://word.mvps.org
> Email cannot be acknowledged; please post all follow-ups to the
> newsgroup so all may benefit.
>
> On Thu, 4 Mar 2010 01:22:01 -0800, Dimitri Backaert
> <DimitriBackaert(a)discussions.microsoft.com> wrote:
>
> >Hi Jay,
> >
> >Thanks for your help.
> >It's really clear to me.
> >
> >I've encountered another problem.
> >The file types which need to be printed, can be various.
> >It can be .doc, .pdf, .ppt,or .xls
> >
> >I've modified your code as follows:
> >
> >Private Sub PrintButton_Click()
> >
> > Dim oDoc As Document
> > Dim FrmFld As FormField
> > Dim Rg As Range
> > Dim HLink As Hyperlink
> > Dim docName As String
> >
> > Set oDoc = ActiveDocument
> >
> > For Each FrmFld In oDoc.FormFields
> > If FrmFld.Type = wdFieldFormCheckBox Then
> > If FrmFld.CheckBox.Value = True Then
> > Set Rg = FrmFld.Range.Cells(1).Range
> > Set HLink = Rg.Hyperlinks(1)
> > docName = HLink.Address
> > MsgBox docName
> >
> > Application.PrintOut , , , , , , , , , , , , docName
> >
> > End If
> > End If
> > Next
> >End Sub
> >
> >This does work for .doc files, but when I'm printing a PDF file, i get some
> >kind of code which is printed to the default printer.
> >It isn't clear text.
> >
> >Is there some way of handling this?
> >
> >Thanks.
> >
> >"Jay Freedman" wrote:
> >
> >> Hi Dimitri,
> >>
> >> The following code works in your template to display the names of the
> >> documents in the hyperlinks. I'll leave it to you to replace the
> >> MsgBox statement with the code that actually opens and prints those
> >> documents.
> >>
> >> Private Sub PrintButton_Click()
> >> Dim oDoc As Document
> >> Dim FrmFld As FormField
> >> Dim Rg As Range
> >> Dim HLink As Hyperlink
> >> Dim docName As String
> >>
> >> Set oDoc = ActiveDocument
> >> For Each FrmFld In oDoc.FormFields
> >> If FrmFld.Type = wdFieldFormCheckBox Then
> >> If FrmFld.CheckBox.Value = True Then
> >> Set Rg = FrmFld.Range.Cells(1).Range
> >> Set HLink = Rg.Hyperlinks(1)
> >> docName = HLink.Address
> >> MsgBox docName
> >> End If
> >> End If
> >> Next
> >> End Sub
> >>
> >> The code is more verbose than it really needs to be, but I left it
> >> that way so you can follow more easily what it's doing.
> >>
> >> The For Each statement is a more efficient way of looking at each
> >> formfield in the document. If the number of formfields was large, the
> >> macro would slow perceptibly as the counter x increases, although the
> >> effect is slight for less than 20 or 30 of them.
> >>
> >> Each time a checked box is found, the range Rg is set to the table
> >> cell that contains the checkbox, and the HLink variable then is set to
> >> the single hyperlink in that range. (There might be a simpler way to
> >> get the hyperlink from the formfield, but this is reliable and
> >> independent of whether the hyperlink contains the formfield or vice
> >> versa.) Finally, the text of the hyperlink's address is the name of
> >> the document to work on.
> >>
> >> --
> >> Regards,
> >> Jay Freedman
> >> Microsoft Word MVP FAQ: http://word.mvps.org
> >> Email cannot be acknowledged; please post all follow-ups to the
> >> newsgroup so all may benefit.
> >>
> >>
> >> On Tue, 2 Mar 2010 03:08:11 -0800, Dimitri Backaert
> >> <DimitriBackaert(a)discussions.microsoft.com> wrote:
> >>
> >> >Hi Jay, Hi Fumei2,
> >> >
> >> >I'm sorry for my lack of information.
> >> >Let me try to clear things out.
> >> >
> >> >I've uploaded a demo file which will surely answer your questions.
> >> >It can be dowloaded at this location:
> >> >http://www.dss-bvba.be/Checklist.dot
> >> >
> >> >Thanks in advance
> >> >
> >> >"Fumei2 via OfficeKB.com" wrote:
> >> >
> >> >> I too am unclear as to what the situation is. Are these checkboxes
> >> >> themselves tagged as hyperlinks. This is possible, although a checkbox
> >> >> formfield selected and hyperlinked will NOT activate the hyperlink by
> >> >> checking the checkbox. Although you CAN activate the hyperlink by right-
> >> >> clicking. (Assuming the document is indeed protected for forms.)
> >> >>
> >> >> What does "Get the attached Hyperlink" actually mean?
> >> >>
> >> >> Dimitri Backaert wrote:
> >> >> >Hi,
> >> >> >
> >> >> >I have a question on how to capture a hyperlink that is inserted behind a
> >> >> >checked FormField (type Checkbox).
> >> >> >
> >> >> >The idea is to create some sort of index page with checkboxes, which will
> >> >> >summarize a number of hyperlinks (which point towards several files on the
> >> >> >company network).
> >> >> >A button will print out all of the CHECKED checkboxes.
> >> >> >
> >> >> >I'm not able to achieve this.
> >> >> >This is my code so far:
> >> >> >
> >> >> >Private Sub PrintButton_Click()
> >> >> >
> >> >> > For x = 1 To ActiveDocument.FormFields.Count
> >> >> > If ActiveDocument.FormFields(x).Type = wdFieldFormCheckBox Then
> >> >> > If ActiveDocument.FormFields(x).CheckBox.Value = True Then
> >> >> >
> >> >> > 'Get the attached Hyperlink and print this document
> >> >> > MsgBox x
> >> >> >
> >> >> > End If
> >> >> > End If
> >> >> > Next x
> >> >> >
> >> >> >End Sub
> >> >> >
> >> >> >Can anyone help me out?
> >> >> >
> >> >> >Thanks in advance.
> >> >>
> >> >> --
> >> >> Message posted via http://www.officekb.com
> >> >>
> >> >> .
> >> >>
> >> .
> >>
> .
>