MySQL to Excel Table - Ex. 1

This example retrieves data from an online SQL database, and sends the records to the relevant tab, depending on the month of the field called ‘Tax Date’.

Screenshots

Front Sheet
Monthly Table

Click to view large-sized image

VBA Module Code

VBA
Sub Oval2_Click()
    frmData.Show
End Sub
Sub Clear_DataSheet()
    Dim this_sheet As Worksheet
    Set this_sheet = ActiveSheet
    
    With this_sheet.ListObjects(1)
        If Not .DataBodyRange Is Nothing Then
            .DataBodyRange.Delete
        End If
    End With
End Sub
Sub GetDataFromADO()

    'Declare variables'
    'Dim objMyConn As Object: Set objMyConn = CreateObject("New ADODB.Connection")
    'Dim objMyCmd As Object: Set objMyCmd = CreateObject("ADODB.Command")
    'Dim objMyRecordset As Object: Set objMyRecordset = CreateObject("ADODB.Recordset")
        
        Dim objMyConn As ADODB.Connection
        Dim objMyCmd As ADODB.Command
        Dim objMyRecordset As ADODB.Recordset

        Set objMyConn = New ADODB.Connection
        Set objMyCmd = New ADODB.Command
        Set objMyRecordset = New ADODB.Recordset
        
        Dim SQL As String
        Dim QT As Excel.QueryTable
        Dim ConnectionString
        
    'DECLARE SHEET, TABLE, and ROW variables
        Dim this_sheet As Worksheet
        Dim table_list_object As ListObject
        Dim table_object_row As ListRow
        
    'OPEN CONNECTION
    ' Open a connection by referencing the ODBC driver.
    'objMyConn.ConnectionString = "driver={sql server};" & _
    '"Server=sql2.freesqldatabase.com; Database=sql2208694; Uid=sql2208694;Pwd=kG3!iA3%;"
    
    objMyConn.Open "DRIVER={MySQL ODBC 5.3 ANSI Driver};" & _
    "SERVER=sql2.freesqldatabase.com;" & _
    "DATABASE=sql2208694;" & _
    "USER=sql2208694;" & _
    "PASSWORD=kG3!iA3%;" & _
    "Option=3"
    
    
        Set objMyCmd.ActiveConnection = objMyConn
                         
'****************************************************************************************************
'****************************************************************************************************
                         
    'QUERY RECORDS FROM JANUARY
    
        SQL = "SELECT * FROM `sql2208694`.`Transactions` WHERE MONTH(STR_TO_DATE(Tax_date, '%m/%d/%Y')) = 1"
        objMyRecordset.Open SQL, objMyConn, adOpenStatic, adLockReadOnly
    
    'SET SHEET to JANUARY
      Set this_sheet = Sheets("Mth 1")
      Set table_list_object = this_sheet.ListObjects(1)
      Set table_object_row = table_list_object.ListRows.Add
    
    'ADD JANUARY RECORD
      With this_sheet.ListObjects(1)
        Call table_object_row.Range(1, 1).CopyFromRecordset(objMyRecordset)
      'Call table_object_row.Resize(this_sheet.UsedRange)
      End With
        
    'Close Objects and Variables
        objMyRecordset.Close
    
'*****************************************************************************************************
'****************************************************************************************************
                         
    'QUERY RECORDS FROM FEBUARY
    
        SQL = "SELECT * FROM `sql2208694`.`Transactions` WHERE MONTH(STR_TO_DATE(Tax_date, '%m/%d/%Y')) = 2"
        objMyRecordset.Open SQL, objMyConn, adOpenStatic, adLockReadOnly
    
    'SET SHEET to FEBUARY
      Set this_sheet = Sheets("Mth 2")
      Set table_list_object = this_sheet.ListObjects(1)
      Set table_object_row = table_list_object.ListRows.Add
    
    'ADD FEBURARY RECORD
      With this_sheet.ListObjects(1)
        Call table_object_row.Range(1, 1).CopyFromRecordset(objMyRecordset)
      'Call table_object_row.Resize(this_sheet.UsedRange)
      End With
        
    'Close Objects and Variables
        objMyRecordset.Close
    
'*****************************************************************************************************
'****************************************************************************************************
                         
    'QUERY RECORDS FROM MARCH
    
        SQL = "SELECT * FROM `sql2208694`.`Transactions` WHERE MONTH(STR_TO_DATE(Tax_date, '%m/%d/%Y')) = 3"
        objMyRecordset.Open SQL, objMyConn, adOpenStatic, adLockReadOnly
    
    'SET SHEET to MARCH
      Set this_sheet = Sheets("Mth 3")
      Set table_list_object = this_sheet.ListObjects(1)
      Set table_object_row = table_list_object.ListRows.Add
    
    'ADD MARCH RECORD
      With this_sheet.ListObjects(1)
        Call table_object_row.Range(1, 1).CopyFromRecordset(objMyRecordset)
      'Call table_object_row.Resize(this_sheet.UsedRange)
      End With
        
    'Close Objects and Variables
        objMyRecordset.Close
    
'*****************************************************************************************************

'****************************************************************************************************
                         
    'QUERY RECORDS FROM APRIL
    
        SQL = "SELECT * FROM `sql2208694`.`Transactions` WHERE MONTH(STR_TO_DATE(Tax_date, '%m/%d/%Y')) = 4"
        objMyRecordset.Open SQL, objMyConn, adOpenStatic, adLockReadOnly
    
    'SET SHEET to APRIL
      Set this_sheet = Sheets("Mth 4")
      Set table_list_object = this_sheet.ListObjects(1)
      Set table_object_row = table_list_object.ListRows.Add
    
    'ADD APRIL RECORD
      With this_sheet.ListObjects(1)
        Call table_object_row.Range(1, 1).CopyFromRecordset(objMyRecordset)
      'Call table_object_row.Resize(this_sheet.UsedRange)
      End With
        
    'Close Objects and Variables
        objMyRecordset.Close
    
'*****************************************************************************************************

'****************************************************************************************************
                         
    'QUERY RECORDS FROM MAY
    SQL = "SELECT * FROM `sql2208694`.`Transactions` WHERE MONTH(STR_TO_DATE(Tax_date, '%m/%d/%Y')) = 5"
        objMyRecordset.Open SQL, objMyConn, adOpenStatic, adLockReadOnly
    
    'SET SHEET to MAY
      Set this_sheet = Sheets("Mth 5")
      Set table_list_object = this_sheet.ListObjects(1)
      Set table_object_row = table_list_object.ListRows.Add
    
    'ADD MAY RECORD
      With this_sheet.ListObjects(1)
        Call table_object_row.Range(1, 1).CopyFromRecordset(objMyRecordset)
      'Call table_object_row.Resize(this_sheet.UsedRange)
      End With
        
    'Close Objects and Variables
        objMyRecordset.Close
      
'*****************************************************************************************************
        
'****************************************************************************************************
                         
    'QUERY RECORDS FROM JUNE
    SQL = "SELECT * FROM `sql2208694`.`Transactions` WHERE MONTH(STR_TO_DATE(Tax_date, '%m/%d/%Y')) = 6"
        objMyRecordset.Open SQL, objMyConn, adOpenStatic, adLockReadOnly
    
    'SET SHEET to JUNE
      Set this_sheet = Sheets("Mth 6")
      Set table_list_object = this_sheet.ListObjects(1)
      Set table_object_row = table_list_object.ListRows.Add
    
    'ADD JUNE RECORD
      With this_sheet.ListObjects(1)
        Call table_object_row.Range(1, 1).CopyFromRecordset(objMyRecordset)
      'Call table_object_row.Resize(this_sheet.UsedRange)
      End With

    'Close Objects and Variables
        objMyRecordset.Close
    
'*****************************************************************************************************
              
'****************************************************************************************************
                         
    'QUERY RECORDS FROM JULY
    SQL = "SELECT * FROM `sql2208694`.`Transactions` WHERE MONTH(STR_TO_DATE(Tax_date, '%m/%d/%Y')) = 7"
        objMyRecordset.Open SQL, objMyConn, adOpenStatic, adLockReadOnly
    
    'SET SHEET to JULY
      Set this_sheet = Sheets("Mth 7")
      Set table_list_object = this_sheet.ListObjects(1)
      Set table_object_row = table_list_object.ListRows.Add
    
    'ADD JULY RECORD
      With this_sheet.ListObjects(1)
        Call table_object_row.Range(1, 1).CopyFromRecordset(objMyRecordset)
      'Call table_object_row.Resize(this_sheet.UsedRange)
      End With

    'Close Objects and Variables
        objMyRecordset.Close
    
'*****************************************************************************************************
              
'****************************************************************************************************
                         
    'QUERY RECORDS FROM AUGUST
    SQL = "SELECT * FROM `sql2208694`.`Transactions` WHERE MONTH(STR_TO_DATE(Tax_date, '%m/%d/%Y')) = 8"
        objMyRecordset.Open SQL, objMyConn, adOpenStatic, adLockReadOnly
    
    'SET SHEET to AUGUST
      Set this_sheet = Sheets("Mth 8")
      Set table_list_object = this_sheet.ListObjects(1)
      Set table_object_row = table_list_object.ListRows.Add
    
    'ADD AUGUST RECORD
      With this_sheet.ListObjects(1)
        Call table_object_row.Range(1, 1).CopyFromRecordset(objMyRecordset)
      'Call table_object_row.Resize(this_sheet.UsedRange)
      End With

    'Close Objects and Variables
        objMyRecordset.Close
    
'*****************************************************************************************************

'****************************************************************************************************
                         
    'QUERY RECORDS FROM SEPTEMBER
      SQL = "SELECT * FROM `sql2208694`.`Transactions` WHERE MONTH(STR_TO_DATE(Tax_date, '%m/%d/%Y')) = 9"
        objMyRecordset.Open SQL, objMyConn, adOpenStatic, adLockReadOnly
    
    'SET SHEET to SEPTEMEBER
      Set this_sheet = Sheets("Mth 9")
      Set table_list_object = this_sheet.ListObjects(1)
      Set table_object_row = table_list_object.ListRows.Add
    
    'ADD SEPTEMBER RECORD
      With this_sheet.ListObjects(1)
        Call table_object_row.Range(1, 1).CopyFromRecordset(objMyRecordset)
      'Call table_object_row.Resize(this_sheet.UsedRange)
      End With

    'Close Objects and Variables
        objMyRecordset.Close
    
'*****************************************************************************************************
              
'****************************************************************************************************
                         
    'QUERY RECORDS FROM OCTOBER
    SQL = "SELECT * FROM `sql2208694`.`Transactions` WHERE MONTH(STR_TO_DATE(Tax_date, '%m/%d/%Y')) = 10"
        objMyRecordset.Open SQL, objMyConn, adOpenStatic, adLockReadOnly
    
    'SET SHEET to OCTOBER
      Set this_sheet = Sheets("Mth 10")
      Set table_list_object = this_sheet.ListObjects(1)
      Set table_object_row = table_list_object.ListRows.Add
    
    'ADD OCTOBER RECORD
      With this_sheet.ListObjects(1)
        Call table_object_row.Range(1, 1).CopyFromRecordset(objMyRecordset)
      'Call table_object_row.Resize(this_sheet.UsedRange)
      End With

    'Close Objects and Variables
        objMyRecordset.Close
    
'*****************************************************************************************************
              
'****************************************************************************************************
                         
    'QUERY RECORDS FROM NOVEMBER
    SQL = "SELECT * FROM `sql2208694`.`Transactions` WHERE MONTH(STR_TO_DATE(Tax_date, '%m/%d/%Y')) = 11"
        objMyRecordset.Open SQL, objMyConn, adOpenStatic, adLockReadOnly
    
    'SET SHEET to NOVEMBER
      Set this_sheet = Sheets("Mth 11")
      Set table_list_object = this_sheet.ListObjects(1)
      Set table_object_row = table_list_object.ListRows.Add
    
    'ADD NOVEMBER RECORD
      With this_sheet.ListObjects(1)
        Call table_object_row.Range(1, 1).CopyFromRecordset(objMyRecordset)
      'Call table_object_row.Resize(this_sheet.UsedRange)
      End With

    'Close Objects and Variables
        objMyRecordset.Close
    
'*****************************************************************************************************
              
'****************************************************************************************************
                         
    'QUERY RECORDS FROM DECEMBER
    SQL = "SELECT * FROM `sql2208694`.`Transactions` WHERE MONTH(STR_TO_DATE(Tax_date, '%m/%d/%Y')) = 12"
        objMyRecordset.Open SQL, objMyConn, adOpenStatic, adLockReadOnly
    
    'SET SHEET to DECEMBER
      Set this_sheet = Sheets("Mth 12")
      Set table_list_object = this_sheet.ListObjects(1)
      Set table_object_row = table_list_object.ListRows.Add
    
    'ADD DECEMBER RECORD
      With this_sheet.ListObjects(1)
        Call table_object_row.Range(1, 1).CopyFromRecordset(objMyRecordset)
      'Call table_object_row.Resize(this_sheet.UsedRange)
      End With

    'Close Objects and Variables
        objMyRecordset.Close
    
'*****************************************************************************************************
              
    'Close Objects and Variables
        objMyConn.Close
        
   MsgBox "Records added from SQL Database!"
    
End Sub

Download

The full file can be downloaded here:

VBA - MySQL to Excel Table - 1 (xlsm)