Results 1 to 1 of 1

Thread: VBA Import Table From MS Word Included Format

  1. #1
    Member
    Join Date
    Sep 2013
    Posts
    37
    Rep Power
    0

    VBA Import Table From MS Word Included Format

    hi all.
    the code work properly to import tabel from ms word to excel
    Code:
    Sub ImportWordTable()
    On Error GoTo errHandler
    Dim wordDoc As Object
    Dim wdFileName As Variant
    Dim noTble As Integer
    Dim rowNb As Long
    Dim colNb As Integer
    Dim x As Long, y As Long
    x = 1: y = 1
    wdFileName = Application.GetOpenFilename("Word files (*.docx),*.docx", , _
    "Browse for file containing table to be imported") 'adjust this to the document type you are after
    If wdFileName = False Then Exit Sub
    Set wordDoc = GetObject(wdFileName)
    With wordDoc
    noTble = wordDoc.tables.Count
    If noTble = 0 Then
    MsgBox "No Tables in this document", vbExclamation, "No Tables to Import"
    Exit Sub
    End If
    For k = 1 To noTble
    With .tables(k)
    For rowNb = 1 To .Rows.Count
    For colNb = 1 To .Columns.Count
    Cells(x, y) = WorksheetFunction.Clean(.cell(rowNb, colNb).Range.Text)
    y = y + 1
    Next colNb
    y = 1
    x = x + 1
    Next rowNb
    End With
    x = x + 2
    Next
    End With
    Set wordDoc = Nothing
    Exit Sub
    errHandler:
    MsgBox "Error in generating tables - " & Err.Number & " - " & Err.Description
    End Sub
    i want to modified how to make code can import tabel with included format like border, shading, color.
    this my attachment file
    any help me out thank in advance

    note:
    i'm using Ms Office 2013
    .susanto
    Attached Files Attached Files
    Last edited by DocAElstein; 02-16-2022 at 10:10 PM. Reason: Code tags

Similar Threads

  1. Export data (text) Excel to Ms Word Format
    By muhammad susanto in forum Excel Help
    Replies: 0
    Last Post: 10-06-2017, 09:36 AM
  2. Replies: 3
    Last Post: 06-01-2013, 11:31 AM
  3. Replies: 2
    Last Post: 04-17-2013, 11:53 PM
  4. Replies: 1
    Last Post: 10-16-2012, 01:53 PM
  5. Embed ms project in a table in ms word
    By hometech in forum Word Help
    Replies: 6
    Last Post: 09-27-2012, 12:57 PM

Posting Permissions

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