Consulting

Results 1 to 11 of 11

Thread: Find Missing VBA Project References Code

  1. #1
    VBAX Regular
    Joined
    Dec 2013
    Posts
    11
    Location

    Find Missing VBA Project References Code

    Workbook developed in Excel 11. Has worked great everywhere, literally globally, until I ran into Win8 with Office 2013.

    What I need is code that will display in a message box, the library references that are missing when the workbook is opened on the W8 Off2013 box.

    I have code from a solution I found on this board that did not work. I would live to link to that but the system WILL NOT LET ME.

    The solution was a workbook [book1] that you ran on your system, then sent to the user with the higher version of office. They were to open it, save it and send it back. It was supposed to list the library reference differences. It locked up Excel 2013 instead.... arrrgh... and it looks so promising.

    I could modify the code below to tell me there is a reference problem but it won't identify what libraries are causing it. Could someone help me modify this code to actually list the missing references or perhaps make the code work as it was designed to but work on Win8 with Off2013?

    Sub References_RemoveMissing()
         'Macro purpose:  To remove missing references from the VBE
         
        Dim theRef As Variant, i As Long
         
        On Error Resume Next
         
        For i = ThisWorkbook.VBProject.References.Count To 1 Step -1
            Set theRef = ThisWorkbook.VBProject.References.Item(i)
            If theRef.isbroken = True Then
                'ThisWorkbook.VBProject.References.Remove theRef
            End If
        Next i
         
        If Err <> 0 Then
            MsgBox "A missing reference has been encountered!" _
            & "You will need to email this workbook to "". In the subject line enter Broken Refs", _
            vbCritical, "Unable To Remove Missing Reference"
        End If
         
        On Error GoTo 0
    End Sub
    Incidentally, it did not pop up a message box...it just froze the workbook.
    Last edited by SamT; 12-11-2013 at 08:18 AM. Reason: Formatted code with # icon

  2. #2
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    I'm not familiar with Office 13, and, my office computer is down, but...

    Sub References_RecordMissing() 
         '''''''''''''''''Macro purpose:  To remove missing references from the VBE
         'Macro purpose:  To Record missing references in the Project
         
        Dim theRef As Variant, i As Long, j As long
        Dim WkSht As Worksheet
        Dim MyFlag As Boolean 'Personal preference. Clearing all Errors as soon as possible.
        
        'YOU insert WkSht into workbook as New Worksheet here.
         
        On Error Resume Next 
         
        For i = ThisWorkbook.VBProject.References.Count To 1 Step -1 
            Set theRef = ThisWorkbook.VBProject.References.Item(i) 
            If theRef.isbroken = True Then 
               MyFlag = True 
               j = j + 1
               WkSht.Range("A" & CStr(j)) = TheRef.Name
                 'ThisWorkbook.VBProject.References.Remove theRef
            End If 
            Err = 0
        Next i 
         
        'If Err <> 0 Then 
        If MyFlag Then
            Me.Save
            MsgBox "A missing reference has been encountered!" _ 
            & "You will need to email this workbook to "". In the subject line enter Broken Refs", _ 
            vbCritical, "Unable To Remove Missing Reference" 
        End If 
         
        On Error Goto 0 
    End Sub
    I expect the student to do their homework and find all the errrors I leeve in.


    Please take the time to read the Forum FAQ

  3. #3
    VBAX Regular
    Joined
    Dec 2013
    Posts
    11
    Location
    Thank You!

    So I'm clear on this process. I need to insert a new worksheet into the workbook. Do I need to name that worksheet something specific? I ask because I don't see a pointer to dump output to a specific worksheet and the workbook contains about 10 worksheets now.

  4. #4
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,646
    I'd suggest to make an inventory of all the necessary references before sending the workbook, storing those reference data in the workbook.
    On opening the workbook by the receiving party, the references on that system can be compared to the stored ones.
    If any reference is lackig the user can be alerted.

  5. #5
    VBAX Regular
    Joined
    Dec 2013
    Posts
    11
    Location
    Quote Originally Posted by snb View Post
    I'd suggest to make an inventory of all the necessary references before sending the workbook, storing those reference data in the workbook.
    On opening the workbook by the receiving party, the references on that system can be compared to the stored ones.
    If any reference is lackig the user can be alerted.
    Yes, that was what the other workbook was supposed to do as well. I set the 5 basic library references that have always worked, then send the workbook to the other user. When they opened it, it was supposed to check the references on their system and list them. I didn't work.

    So with regard to this new code.... It looks as if I'm supposed to add a new worksheet to the workbook. The code function will output library differences to that worksheet. But what I don't see in the code is a specific reference to a specific worksheet. So, how does the code know to output to the new worksheet I add to the workbook?

    Don't I need to give the worksheet a specific name and address that name in the new code?

    Also, do I put that code in the start up routine for the work book or can I just put the code in new module and put a command button on the new worksheet to run the code?

  6. #6
    VBAX Regular
    Joined
    Dec 2013
    Posts
    11
    Location
    I inserted a new worksheet in the workbook and named it "libs"

    I modified the code as shown:

    Sub References_RecordMissing()
         '''''''''''''''''Macro purpose:  To record missing references from the VBE
         'Macro purpose:  To Record missing references in the Project
         
        Dim theRef As Variant, i As Long, j As Long
        Dim WkSht As Worksheet
        Dim MyFlag As Boolean 'Personal preference. Clearing all Errors as soon as possible.
         
        WkSht = ("libs")
         'YOU insert WkSht into workbook as New Worksheet here.
         
        On Error Resume Next
         
        For i = ThisWorkbook.VBProject.References.Count To 1 Step -1
            Set theRef = ThisWorkbook.VBProject.References.Item(i)
            If theRef.isbroken = True Then
                MyFlag = True
                j = j + 1
                WkSht.Range("A" & CStr(j)) = theRef.Name
                 'ThisWorkbook.VBProject.References.Remove theRef
            End If
            Err = 0
        Next i
         
         'If Err <> 0 Then
        If MyFlag Then
            Me.Save [this line is highlighted]
            MsgBox "A missing reference has been encountered!" _
            & "You will need to email this workbook to "". In the subject line enter Broken Refs", _
            vbCritical, "Unable To Remove Missing Reference"
        End If
         
        On Error GoTo 0
    End Sub
    When I compile I get [ "Invalid Use of Keyword Me"] error

    Since I'm outputting to the new worksheet can I eliminate this section and just end the sub at that point?

     Err = 0
        Next i
    
         'If Err <> 0 Then
        If MyFlag Then
            Me.Save [this line is highlighted]
            MsgBox "A missing reference has been encountered!" _
            & "You will need to email this workbook to "". In the subject line enter Broken Refs", _
            vbCritical, "Unable To Remove Missing Reference"
    
    There by ending up with this:

    Sub References_RecordMissing()
         '''''''''''''''''Macro purpose:  To record missing references from the VBE
    
        Dim theRef As Variant, i As Long, j As Long
        Dim WkSht As Worksheet
        Dim MyFlag As Boolean 'Personal preference. Clearing all Errors as soon as possible.
    
        WkSht = ("libs")
         'YOU insert WkSht into workbook as New Worksheet here.
    
        On Error Resume Next
    
        For i = ThisWorkbook.VBProject.References.Count To 1 Step -1
            Set theRef = ThisWorkbook.VBProject.References.Item(i)
            If theRef.isbroken = True Then
                MyFlag = True
                j = j + 1
                WkSht.Range("A" & CStr(j)) = theRef.Name
    
            End If
    
    End Sub
    Last edited by SamT; 12-11-2013 at 10:48 AM.

  7. #7
    VBAX Regular
    Joined
    Dec 2013
    Posts
    11
    Location
    Here's what I did. I created a new worksheet [name doesn't matter because I put a command button on the worksheet itself to run the code]. I tested it and it doesn't return any data on my machine [expected] but also doesn't error out either. Will send it off to Finland and post back results. Hopefully it will help someone else down the road.

    Here's the code at this point.

    Sub References_RecordMissing()
         '''''''''''''''''Macro purpose:  To record missing references from the VBE
         'Macro purpose:  To Record missing references in the Project
         
        Dim theRef As Variant, i As Long, j As Long
        Dim WkSht As Worksheet
        Dim MyFlag As Boolean 'Personal preference. Clearing all Errors as soon as possible.
         
        'WkSht = ("libs")
         'YOU insert WkSht into workbook as New Worksheet here.
         
        On Error Resume Next
         
        For i = ThisWorkbook.VBProject.References.Count To 1 Step -1
            Set theRef = ThisWorkbook.VBProject.References.Item(i)
            If theRef.isbroken = True Then
                MyFlag = True
                j = j + 1
                WkSht.Range("A" & CStr(j)) = theRef.Name
                 'ThisWorkbook.VBProject.References.Remove theRef
            End If
           Next
             
        On Error GoTo 0
    End Sub
    Last edited by SamT; 12-11-2013 at 10:48 AM.

  8. #8
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    Sub References_RecordMissing() 
        'Macro purpose:  To record missing references from the VBE
         
        Dim theRef As Variant, i As Long, j As Long 
        Dim WkSht As Worksheet 
         
        Set WkSht = Worksheets("libs") 'Here we set a reference to a specific Worksheet
         
        On Error Resume Next 
         
        For i = ThisWorkbook.VBProject.References.Count To 1 Step -1 
            Set theRef = ThisWorkbook.VBProject.References.Item(i) 
            If theRef.isbroken = True Then ' Question: Does the function isBroken work?
                j = j + 1 
                WkSht.Range("A" & CStr(j)) = theRef.Name 
            End If 
        Next 
         
        On Error Goto 0 
    End Sub
    I expect the student to do their homework and find all the errrors I leeve in.


    Please take the time to read the Forum FAQ

  9. #9
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    Found them.

    I think this is the KB Article you used: http://www.vbaexpress.com/kb/getarticle.php?kb_id=272

    Did you also see this one, also by Ken Puls? http://www.vbaexpress.com/kb/getarticle.php?kb_id=267
    I expect the student to do their homework and find all the errrors I leeve in.


    Please take the time to read the Forum FAQ

  10. #10
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,646
    Sub M_snb()
        On error resume next
    
        For Each rf In ThisWorkbook.VBProject.References
            c00 = c00 & vbCr & rf.Name & "_" & rf.Description & "_" & rf.fullpath & "_" & rf.GUID
        Next
        
        With Sheets.Add
            .Cells(1).Resize(UBound(Split(c00, vbCr))) = Application.Transpose(Split(Mid(c00, 2), vbCr))
            .Columns(1).TextToColumns , , , , 0, 0, 0, 0, -1, "_"
            .Columns(1).Resize(, 4).AutoFit
        End With
    End Sub

  11. #11
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    snb's code adds a sheet on the fly and puts all the used references in it by name, description, path and GUID.
    I expect the student to do their homework and find all the errrors I leeve in.


    Please take the time to read the Forum FAQ

Posting Permissions

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