Consulting

Results 1 to 6 of 6

Thread: Can't populate Word VBA Combobox Value with last cell from xldown error

  1. #1

    Question Can't populate Word VBA Combobox Value with last cell from xldown error

    Hello all,

    I have Word VBA Macros for auto-fill document purposes.

    I have a Combobox named CountryBox that should populate some Content Control fields based on value selection (taken from external Excel table).

    I have it working for strict range of values (A1:A3) but every time I try to use 'xldown' to utilize all cells, VBA gives me error 438:
    Object doesn't support this property or method


    This is my code:

    Private Sub UserForm_Initialize()
    'Populate CountryBox Combobox with Countries.xlsx
    Dim appExcel As Object
        Dim ExcelBook As Object
        Dim ExcelSheet As Object
        Dim ListItems As Variant, i As Integer
        Dim LastRow As Long
    On Error Resume Next
    Set appExcel = GetObject(Class:="Excel.Application")
        On Error GoTo 0
    If appExcel Is Nothing Then
        Set appExcel = CreateObject(Class:="Excel.Application")
        appExcel.Visible = True
    End If
    With Me.CountryBox
        .Clear ' remove existing entries from the listbox
        ' turn screen updating off,
        ' prevent the user from seeing the source workbook being opened
        Application.ScreenUpdating = False
        ' open the source workbook as ReadOnly
        Set ExcelBook = appExcel.Workbooks.Open("C:\Users\plifshits\Desktop\temaplte\Countries.xlsx", False, True)
        'ListItems = ExcelBook.Worksheets(1).Range("A1:A100").Value
        LastRow = appExcel.Cells(1, appExcel.Row.Count).End(appExcel.xlDown).Row
        ' With ExcelBook.Worksheets(1)
            ' ListItems = appExcel.Range(appExcel.Cells(1, 1), appExcel.Cells(appExcel.Rows.Count, 1).End(appExcel.xlDown)).Value
        ' End With
        ' get the values you want
        ExcelBook.Close False ' close the source workbook without saving changes
        Set ExcelBook = Nothing
        ListItems = appExcel.WorksheetFunction.Transpose(ListItems)
        ' convert values to a vertical array
        For i = 1 To UBound(ListItems)
            .AddItem ListItems(i) ' populate the listbox
        Next i
        .ListIndex = -1 ' no items selected, set to 0 to select the first item
        Application.ScreenUpdating = True
        End With
    End Sub
    Please advise!
    Last edited by Aussiebear; 03-07-2024 at 05:20 AM. Reason: Added code tags to supplied code

  2. #2
    you started from the end of the Row (appExcel.Rows.Count), therefore you need to Go Up. use xlUp.

    ListItems = appExcel.Range(appExcel.Cells(1, 1), appExcel.Cells(appExcel.Rows.Count, 1).End(appExcel.xlUp)).Value


  3. #3
    Quote Originally Posted by arnelgp View Post
    you started from the end of the Row (appExcel.Rows.Count), therefore you need to Go Up. use xlUp.

    ListItems = appExcel.Range(appExcel.Cells(1, 1), appExcel.Cells(appExcel.Rows.Count, 1).End(appExcel.xlUp)).Value

    Hi arnelgp,

    Unfortunately this does not help,
    Still receiving an error.

  4. #4
    Microsoft Word MVP 2003-2009 VBAX Guru gmaxey's Avatar
    Joined
    Sep 2005
    Posts
    3,340
    Location
    The most efficient way is to use ADODB rather than physically opening the Excel file. The attached has an example and examples of using GetObject.Simple Methods Single Column.docm
    Greg

    Visit my website: http://gregmaxey.com

  5. #5
    replace all XlDown with xlUp.

  6. #6
    VBAX Regular
    Joined
    Sep 2023
    Posts
    97
    Location
    Shouldn't this line
    LastRow = appExcel.Cells(1, appExcel.Row.Count).End(appExcel.xlDown).Row
    be
    LastRow = appExcel.Cells(appExcel.Rows.Count, 1).End(appExcel.xlUp).Row
    The row count is in the column parameter, and of course xlUp should be used.
    EDIT: also Rows.Count
    Last edited by jdelano; 03-08-2024 at 03:17 AM.

Tags for this Thread

Posting Permissions

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