Consulting

Results 1 to 17 of 17

Thread: Solved: VBA Importing a sheet from a closed excel workbook

  1. #1
    VBAX Regular
    Joined
    Jan 2011
    Posts
    30
    Location

    Solved: VBA Importing a sheet from a closed excel workbook

    Hi PPL,

    I am pretty new in VBA and hence would appreciate if anyone could assist me with regards to my problem.

    I need a VBA code that will automatically copy and paste a sheet from a closed Excel workbook.

    Is it possible? Thank you and realy appreciate

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

    I am not exactly clear on what you are wanting. Are you looking to copy a worksheet from one workbook to another or just copy part of a sheet?

    Mark

  3. #3
    VBAX Regular
    Joined
    Jan 2011
    Posts
    30
    Location
    Hi GTO,

    I am sorry for posting such a ambiguous question.

    I will explain in greater details:

    I will open up a Excel workbook "UserFormApplication".

    I will then press a import button. What this button will do is that it will go to a closed Excel workbook "RawData" and copy a sheet call "RawSheet" and paste it in Excel workbook "UserFormApplication" that I am looking at now.

    While doing all this copying and pasting of sheet, I need to make sure that Excel workbook "RawData" is not open due to sensertive information contained.

    Yap. I am looking at copying 1 worksheet from a closed workbook to my current activated workbook.

    Thanks GTO!

  4. #4
    VBAX Regular
    Joined
    Aug 2010
    Posts
    19
    Location
    Not sure how useful this is but you could just add a formula in your cells like;
    ='workbookpath[workbookname.xls]RawData'!A1

    That should pick up the data.
    Otherwise you can use an ADO connection to pick up data from a closed workbook, but thats more difficult.

  5. #5
    VBAX Regular
    Joined
    Jan 2011
    Posts
    30
    Location

    Help to improve on the VBA code

    Greetings everyone,

    I have come out with a code that do almost what I want. However, this code select the entire sheets in the workbook. How do I modify this VBA to select a specific sheet to import instead of the entire sheets in the workbook?

    Thanks! Really appreciate your help

    Sub Importsheet()
    Dim Importsheet As Worksheet 'Imports worksheet from a closed workbook
    Sheets.Add Type:= _
    "C:\Users\Leo\Desktop\Testing1.xlsx"
    End Sub

  6. #6
    VBAX Expert shrivallabha's Avatar
    Joined
    Jan 2010
    Location
    Mumbai
    Posts
    750
    Location
    Hello LeoLee, assign the following code for using import. I have used a little different version for my requirements. So I'd to tweak it little. I have used a function for checking existence of a specific sheet.
    Sub ImportSheet()
    Dim sImportFile As String, sFile As String
    Dim sThisBk As Workbook
    Dim vfilename As Variant
    Application.ScreenUpdating = False
    Application.DisplayAlerts = False
    Set sThisBk = ActiveWorkbook
    sImportFile = Application.GetOpenFilename( _
    FileFilter:="Microsoft Excel Workbooks, *.xls; *.xlsx", Title:="Open Workbook")
    If sImportFile = "False" Then
       MsgBox "No File Selected!"
       Exit Sub
       Else
       vfilename = Split(sImportFile, "\")
       sFile = vfilename(UBound(vfilename))
       Application.Workbooks.Open Filename:=sImportFile
       Set wbBk = Workbooks(sFile)
       With wbBk
          If SheetExists("Raw_Data") Then
             Set wsSht = .Sheets("Raw_Data")
             wsSht.Copy before:=sThisBk.Sheets("Sheet1")
             Else
             MsgBox "There is no sheet with name :Raw_Data in:" & vbCr & .Name
          End If
          wbBk.Close SaveChanges:=False
       End With
    End If
    Application.ScreenUpdating = True
    Application.DisplayAlerts = True
    End Sub
    
    Private Function SheetExists(sWSName As String) As Boolean
    Dim ws As Worksheet
    On Error Resume Next
    Set ws = Worksheets(sWSName)
    If Not ws Is Nothing Then SheetExists = True
    End Function
    Regards,
    --------------------------------------------------------------------------------------------------------
    Shrivallabha
    --------------------------------------------------------------------------------------------------------
    Using Excel 2016 in Home / 2010 in Office
    --------------------------------------------------------------------------------------------------------

  7. #7
    VBAX Regular
    Joined
    Jan 2011
    Posts
    30
    Location
    shrivallabha,

    Thanks so much!!! This is exactly what I am looking for!

    Thank you and really appreciate your help.

    I shall mark this thread as solved

  8. #8
    Hi shrivallabha & Leo,

    How to import sheet in different files. In my case, I have consolidated model and i need to import 170 summary sheet in different file to my model and delete old summary sheet in model before importing. Appreciate if u could help me on this
    Last edited by halimi1306; 03-31-2011 at 03:06 AM.

  9. #9

    Variable not defined!

    when I run your code, it shows error when executing macro: "Compile Error Variable not defined", I get the "Variable not defined" error on wbBk here
    Set wbBk = Workbooks(sFile) , can you help me to fix it? Thank you very much!

  10. #10
    VBAX Expert shrivallabha's Avatar
    Joined
    Jan 2010
    Location
    Mumbai
    Posts
    750
    Location
    Quote Originally Posted by mytheresa
    when I run your code, it shows error when executing macro: "Compile Error Variable not defined", I get the "Variable not defined" error on wbBk here
    Set wbBk = Workbooks(sFile) , can you help me to fix it? Thank you very much!
    You are using Option Explicit that is why you are getting this error. The error will go away if you comment it out

    Keep option explicit as it is is

    You need to modify this block [Variable dimensioning is changed]:
    Sub ImportSheet()
        Dim sImportFile As String, sFile As String
        Dim sThisBk As Workbook
        Dim vfilename As Variant
        Application.ScreenUpdating = False
    with:
    Sub ImportSheet()
        Dim sImportFile As String, sFile As String
        Dim sThisBk As Workbook, wbBk As Workbook
        Dim vfilename As Variant
        Dim wsSht As Worksheet
        Application.ScreenUpdating = False
    Regards,
    --------------------------------------------------------------------------------------------------------
    Shrivallabha
    --------------------------------------------------------------------------------------------------------
    Using Excel 2016 in Home / 2010 in Office
    --------------------------------------------------------------------------------------------------------

  11. #11

    Thank you very much!

    Thank you for your modification. It is a great help for my school project. I have small question that if I want to import the sheet which is by monthly, like Jan, Feb or March, how can I import it automatically without changing the sheet name? I'd appreciate for your enlightened ideas!

  12. #12
    VBAX Expert shrivallabha's Avatar
    Joined
    Jan 2010
    Location
    Mumbai
    Posts
    750
    Location
    Quote Originally Posted by mytheresa
    Thank you for your modification. It is a great help for my school project. I have small question that if I want to import the sheet which is by monthly, like Jan, Feb or March, how can I import it automatically without changing the sheet name? I'd appreciate for your enlightened ideas!
    You can change the Sheet Name in the code like below. Change:
                If SheetExists("Raw_Data") Then
                    Set wsSht = .Sheets("Raw_Data")
                    wsSht.Copy before:=sThisBk.Sheets("Sheet1")
                Else
                    MsgBox "There is no sheet with name :Raw_Data in:" & vbCr & .Name
                End If
                wbBk.Close SaveChanges:=False[/vba] to lets say "Jan":
    [vba]            If SheetExists("Jan") Then
                    Set wsSht = .Sheets("Jan")
                    wsSht.Copy before:=sThisBk.Sheets("Sheet1")
                Else
                    MsgBox "There is no sheet with name :Jan in:" & vbCr & .Name
                End If
                wbBk.Close SaveChanges:=False
    If this isn't what you're after then please explain your setup by uploading a sample workbook(s).
    Regards,
    --------------------------------------------------------------------------------------------------------
    Shrivallabha
    --------------------------------------------------------------------------------------------------------
    Using Excel 2016 in Home / 2010 in Office
    --------------------------------------------------------------------------------------------------------

  13. #13
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,638
    instead of:
    vfilename = Split(sImportFile, "\") 
    sFile = vfilename(UBound(vfilename))
    use
    sFile=dir(sImportfile)
    instead of
     
    Private Function SheetExists(sWSName As String) As Boolean 
        Dim ws As Worksheet 
        On Error Resume Next 
        Set ws = Worksheets(sWSName) 
        If Not ws Is Nothing Then SheetExists = True 
    End Function
    use

     
    if [ISREF(jan!A1)] then

  14. #14
    VBAX Newbie
    Joined
    Nov 2014
    Posts
    1
    Location

    Change source to a location specified in Cell A1

    Quote Originally Posted by shrivallabha View Post
    Hello LeoLee, assign the following code for using import. I have used a little different version for my requirements. So I'd to tweak it little. I have used a function for checking existence of a specific sheet.
    Sub ImportSheet()
    Dim sImportFile As String, sFile As String
    Dim sThisBk As Workbook
    Dim vfilename As Variant
    Application.ScreenUpdating = False
    Application.DisplayAlerts = False
    Set sThisBk = ActiveWorkbook
    sImportFile = Application.GetOpenFilename( _
    FileFilter:="Microsoft Excel Workbooks, *.xls; *.xlsx", Title:="Open Workbook")
    If sImportFile = "False" Then
       MsgBox "No File Selected!"
       Exit Sub
       Else
       vfilename = Split(sImportFile, "\")
       sFile = vfilename(UBound(vfilename))
       Application.Workbooks.Open Filename:=sImportFile
       Set wbBk = Workbooks(sFile)
       With wbBk
          If SheetExists("Raw_Data") Then
             Set wsSht = .Sheets("Raw_Data")
             wsSht.Copy before:=sThisBk.Sheets("Sheet1")
             Else
             MsgBox "There is no sheet with name :Raw_Data in:" & vbCr & .Name
          End If
          wbBk.Close SaveChanges:=False
       End With
    End If
    Application.ScreenUpdating = True
    Application.DisplayAlerts = True
    End Sub
    
    Private Function SheetExists(sWSName As String) As Boolean
    Dim ws As Worksheet
    On Error Resume Next
    Set ws = Worksheets(sWSName)
    If Not ws Is Nothing Then SheetExists = True
    End Function
    Hi shrivallabha,

    Your code is almost perfect for me. I would just like to know how do I make the macro select a file path that is generated on the active worksheet, for example in cell A1, instead of selecting it manually. My Workbooks all have similar names, except for month changes in the name. I can find and replace this easily enough, but I want the macro to select the file path that is generated in the active worksheet.

    Thanks in advance!
    Last edited by Chris_DP; 11-18-2014 at 06:17 AM. Reason: Better clarification

  15. #15

    Copy multiple workbooks to specific sheets

    Hi all,

    I am having the same problem. I want to copy sheet1 from 20 closed workbooks.
    I have the path in column A.

    The sheets (of closed workbooks) need to be copied to this file in a specific sheet name that is already created.
    The Sheet name is in Column B.

    Is thiss possible?
    It contains 20+ files with only ±20 rows of text.

    Thank you

  16. #16
    VBAX Newbie
    Joined
    May 2019
    Posts
    1
    Location
    Hi all,
    Sorry for resurrecting an old thread... I'm trying to perform the same activity: Copy the entire sheet from a single closed xls file. I have it running to the point that it calls Private Function SheetExists(sWSName As String) As Boolean and the file name is handed into the sub BUT it fails at:
    Set ws = Worksheets(sWSName). I've confirmed the path, file name/location but cannot figure out why it can't set the ws variable even though sWSName is correct. I've tried to incorporate the suggested changes from SNB but I still get the same results so I backed those out.

    Any suggestions?

  17. #17
    VBAX Mentor 大灰狼1976's Avatar
    Joined
    Dec 2018
    Location
    SuZhou China
    Posts
    479
    Location
    Hi anderma8!
    It's not easy to judge without attachments. Maybe the type of sheet is incorrect.
    Try changing:
    Private Function SheetExists(sWSName As String) As Boolean
    Dim ws As Worksheet
    On Error Resume Next
    Set ws = Worksheets(sWSName)
    If Not ws Is Nothing Then SheetExists = True
    End Function
    to
    Private Function SheetExists(sWSName As String) As Boolean
    Dim ws As Object
    On Error Resume Next
    Set ws = Sheets(sWSName)
    If Not ws Is Nothing Then SheetExists = True
    End Function

Posting Permissions

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