Hyperlink.Address property (Word)

Returns or sets the address (for example, a file name or URL) of the specified hyperlink. Read/write String.

Syntax

expression.Address

expression Required. A variable that represents a 'Hyperlink' object.

Remarks

If there is no hyperlink associated with an object, setting the Address property returns an error occurs. In this case, use the Add method for the Hyperlinks collection to add a hyperlink. The following example shows how to do this.

ActiveDocument.Hyperlinks.Add Selection.Range, "https://www.microsoft.com"

Example

This example adds a hyperlink to the selection in the active document, sets the address, and then displays the address in a message box.

Set aHLink = ActiveDocument.Hyperlinks.Add( _ 
 Anchor:=Selection.Range, _ 
 Address:="https://forms") 
MsgBox "The hyperlink goes to " & aHLink.Address

If the active document includes hyperlinks, this example inserts a list of the hyperlink destinations at the end of the document.

Set myRange = ActiveDocument _ 
 .Range(Start:=ActiveDocument.Content.End - 1) 
Count = 0 
For Each aHyperlink In ActiveDocument.Hyperlinks 
 Count = Count + 1 
 With myRange 
 .InsertAfter "Hyperlink #" & Count & vbTab 
 .InsertAfter aHyperlink.Address 
 .InsertParagraphAfter 
 End With 
Next aHyperlink

See also

Hyperlink Object

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.