Consulting

Results 1 to 6 of 6

Thread: Activating Excel VBA References programatically

  1. #1

    Activating Excel VBA References programatically

    Hi,

    I have sent an Excel sheet that needs the VBA Reference "Microsoft PowerPoint 11.0 Object Library".As nobody has it active. I have to go to each computer and activate it...

    Any idea how to check if it's active, and in case it's not, activate it? I have seen on the Net an example for another reference something like:

    [VBA]
    Dim ID As Object

    On Error Resume Next

    Set ID = ThisWorkbook.VBProject.References

    ID.AddFromGuid "{2DF8D04C-5BFA-101B-BDE5-00AA0044DE52}", 1, 5

    End Sub
    [/VBA]


    Thanks!!!

  2. #2
    Knowledge Base Approver VBAX Guru GTO's Avatar
    Joined
    Sep 2008
    Posts
    3,368
    Location
    Check out:

    http://www.vbaexpress.com/kb/getarticle.php?kb_id=267

    Mr. Puhls' post handles this nicely, as to adding a reference, though the 'deleting reference' didn't work for me (switching 2000/2003 aned back)

  3. #3
    Thanks! His both articles are very helpful and clear. But when I copied& pasted, and then run the first macro to find out the PPT reference GUID, it doesn't give me any error but I get nothing besides the Strings names!


    [VBA]Sub ListReferencePaths()
    'Macro purpose: To determine full path and Globally Unique Identifier (GUID)
    'to each referenced library. Select the reference in the Tools\References
    'window, then run this code to get the information on the reference's library

    On Error Resume Next
    Dim i As Long
    With ThisWorkbook.Sheets(1)
    .Cells.Clear
    .Range("A1") = "Reference name"
    .Range("B1") = "Full path to reference"
    .Range("C1") = "Reference GUID"
    End With
    For i = 1 To ThisWorkbook.VBProject.References.Count
    With ThisWorkbook.VBProject.References(i)
    k = i + 1
    ThisWorkbook.Sheets(1).Range("A" & k) = .Name
    ThisWorkbook.Sheets(1).Range("B" & k) = .FullPath
    ThisWorkbook.Sheets(1).Range("C" & k) = .GUID
    End With
    Next i
    On Error GoTo 0
    End Sub[/VBA]

  4. #4
    Knowledge Base Approver VBAX Guru GTO's Avatar
    Joined
    Sep 2008
    Posts
    3,368
    Location
    I am logging out, as it is 0604 hrs here; so not tested,,, but believe below basic code should help:

    [VBA]Sub AddReference()
    'Macro purpose: To add a reference to the project using the GUID for the
    'reference library

    Dim strGUID As String

    'Update the GUID you need below.
    strGUID = "{2DF8D04C-5BFA-101B-BDE5-00AA0044DE52}"
    'Set to continue in case of error
    On Error Resume Next

    'Add the reference
    ThisWorkbook.VBProject.References.AddFromGuid _
    GUID:=strGUID, Major:=1, Minor:=0

    'If an error was encountered, inform the user
    Select Case Err.Number
    Case Is = 32813
    'Reference already in use. No action necessary
    Case Is = vbNullString
    'Reference added without issue
    Case Else
    'An unknown error was encountered, so alert the user
    MsgBox "A problem was encountered trying to" & vbNewLine _
    & "add or remove a reference in this file" & vbNewLine & "Please check the " _
    & "references in your VBA project!", vbCritical + vbOKOnly, "Error!"
    End Select
    On Error GoTo 0
    End Sub
    [/VBA]

  5. #5
    I need to add multiple reference libraries to a spreadsheet not just one. Would it be better to include that within Addreference() or just create an Addreference2()?

  6. #6
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    Maybe like so

    [vba]

    Public Sub AddReferences()
    Call AddReference("{2DF8D04C-5BFA-101B-BDE5-00AA0044DE52}")
    'etc.
    End Sub

    Private Sub AddReference(ByVal strGuid)
    Dim strGuid As String

    On Error Resume Next

    ThisWorkbook.VBProject.References.AddFromGuid _
    GUID:=strGuid, Major:=1, Minor:=0

    Select Case Err.Number
    Case Is = 32813: 'do nothing
    Case Is = vbNullString: 'Reference added without issue
    Case Else
    MsgBox "A problem was encountered trying to" & vbNewLine _
    & "add or remove a reference in this file" & vbNewLine & "Please check the " _
    & "references in your VBA project!", vbCritical + vbOKOnly, "Error!"
    End Select
    On Error GoTo 0
    End Sub
    [/vba]
    ____________________________________________
    Nihil simul inventum est et perfectum

    Abusus non tollit usum

    Last night I dreamed of a small consolation enjoyed only by the blind: Nobody knows the trouble I've not seen!
    James Thurber

Posting Permissions

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