Hyperlink.Address property (Publisher)
Returns or sets a String that represents the URL address for a hyperlink. Read/write.
Syntax
expression.Address
expression A variable that represents a Hyperlink object.
Return value
String
Example
This example displays the URL addresses for all hyperlinks in the active publication.
Sub ShowHyperlinkAddresses()
Dim pgsPage As Page
Dim shpShape As Shape
Dim hprLink As Hyperlink
Dim intCount As Integer
For Each pgsPage In ActiveDocument.Pages
For Each shpShape In pgsPage.Shapes
If shpShape.TextFrame.TextRange.Hyperlinks.Count > 0 Then
For Each hprLink In shpShape.TextFrame.TextRange.Hyperlinks
MsgBox "This hyperlink goes to " & hprLink.Address & "."
intCount = intCount + 1
Next hprLink
ElseIf shpShape.Hyperlink.Address <> "" Then
MsgBox "This hyperlink goes to " & shpShape.Hyperlink.Address & "."
intCount = intCount + 1
End If
Next shpShape
Next pgsPage
If intCount < 1 Then
MsgBox "You don't have any hyperlinks in your publication."
Else
MsgBox "You have " & intCount & " hyperlinks in " & ThisDocument.Name & "."
End If
End Sub
Support and feedback
Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.