Consulting

Results 1 to 5 of 5

Thread: VBA to Open Workbook

  1. #1

    VBA to Open Workbook

    Hi all,

    Can someone assist with a code to do the following:

    1. Open 4 different spreadsheets ( file path to be inserted)
    2. If any one of the spreadsheets is already open, default no for the prompt would you like to reopen this workbook.
    3. Close all 4 spreadsheets again

    ( Opening and closing is simply to update values for another linked model)

    The opening is pretty straight forward, but i can't get round the reopen file prompt & i cant't seem to be able to force all 4 spreadsheets to close.

    Thank u

    Herbiec09

  2. #2
    Mac Moderator VBAX Guru mikerickson's Avatar
    Joined
    May 2007
    Location
    Davis CA
    Posts
    2,778
    Perhaps something like this will work for you.
    Sub test()
        Dim myWorkbooks(1 To 4) As Workbook
        Dim FilePaths(1 To 4) As String
        Dim NameToClose(1 To 4) As String
        Dim fileParts As Variant, fileName As String
        Dim i As Long
        
        Rem get file paths from somewhere
        FilePaths(1) = "Macintosh HD:Users:merickson:Desktop:Workbook1.xlsm"
        FilePaths(2) = "Macintosh HD:Users:merickson:Desktop:Workbook2.xlsm"
        FilePaths(3) = "Macintosh HD:Users:merickson:Desktop:Workbook3.xlsm"
        FilePaths(4) = "Macintosh HD:Users:merickson:Desktop:Workbook4.xlsm"
        
        Rem open any unopened files
        For i = 1 To 4
            fileParts = Split(FilePaths(i), Application.PathSeparator)
            NameToClose(i) = Trim(fileParts(UBound(fileParts)))
            
            If WorkbookIsOpen(NameToClose(i)) Then
                Set myWorkbooks(i) = Workbooks(NameToClose(i))
                NameToClose(i) = vbNullString
            Else
                Set myWorkbooks(i) = Workbooks.Open(FilePaths(i))
            End If
        Next i
            
        Rem do stuff to the open workbooks
        MsgBox Application.Workbooks.Count
        
        Rem close the previously closed workbooks
        For i = 1 To 4
            If NameToClose(i) <> vbNullString Then
                Workbooks(NameToClose(i)).Close savechanges:=True
            End If
        
        Next i
    End Sub
    
    Function WorkbookIsOpen(WorkbookName As String) As Boolean
        On Error Resume Next
        WorkbookIsOpen = (Workbooks(WorkbookName).Name = WorkbookName)
        On Error GoTo 0
    End Function

  3. #3
    Quote Originally Posted by mikerickson View Post
    Perhaps something like this will work for you.
    Sub test()
        Dim myWorkbooks(1 To 4) As Workbook
        Dim FilePaths(1 To 4) As String
        Dim NameToClose(1 To 4) As String
        Dim fileParts As Variant, fileName As String
        Dim i As Long
        
        Rem get file paths from somewhere
        FilePaths(1) = "Macintosh HD:Users:merickson:Desktop:Workbook1.xlsm"
        FilePaths(2) = "Macintosh HD:Users:merickson:Desktop:Workbook2.xlsm"
        FilePaths(3) = "Macintosh HD:Users:merickson:Desktop:Workbook3.xlsm"
        FilePaths(4) = "Macintosh HD:Users:merickson:Desktop:Workbook4.xlsm"
        
        Rem open any unopened files
        For i = 1 To 4
            fileParts = Split(FilePaths(i), Application.PathSeparator)
            NameToClose(i) = Trim(fileParts(UBound(fileParts)))
            
            If WorkbookIsOpen(NameToClose(i)) Then
                Set myWorkbooks(i) = Workbooks(NameToClose(i))
                NameToClose(i) = vbNullString
            Else
                Set myWorkbooks(i) = Workbooks.Open(FilePaths(i))
            End If
        Next i
            
        Rem do stuff to the open workbooks
        MsgBox Application.Workbooks.Count
        
        Rem close the previously closed workbooks
        For i = 1 To 4
            If NameToClose(i) <> vbNullString Then
                Workbooks(NameToClose(i)).Close savechanges:=True
            End If
        
        Next i
    End Sub
    
    Function WorkbookIsOpen(WorkbookName As String) As Boolean
        On Error Resume Next
        WorkbookIsOpen = (Workbooks(WorkbookName).Name = WorkbookName)
        On Error GoTo 0
    End Function
    Thanks Mike,

    This works very very well. One question, how would I set update links to false, so that when each spreadsheet pops up, the user is not asked if they wan't to update.

    Thank you

  4. #4
    Mac Moderator VBAX Guru mikerickson's Avatar
    Joined
    May 2007
    Location
    Davis CA
    Posts
    2,778
    The Workbooks.Open method has an UpdateLinks argument

    Set myWorkbooks(i) = Workbooks.Open(FilePaths(i), UpdateLinks:= False)

  5. #5
    Quote Originally Posted by mikerickson View Post
    The Workbooks.Open method has an UpdateLinks argument

    Set myWorkbooks(i) = Workbooks.Open(FilePaths(i), UpdateLinks:= False)
    What can I say Mike? you are a true genius and a life saver. Thanks you very much!!!!

Posting Permissions

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