Sunteți pe pagina 1din 4

VBA interaction between MS Excel and MySQL 

Posted by: Nathan Maycher ()  

Date: July 03, 2006 10:21AM  

Well after spending more time than I wish to admit I thought I would post some code that I 
adapted/created (thanks to Carlmack for core sections of the code). This code provides simple 
functionality using VBA to allow for the creation/deletion of MySQL tables and removing/adding 
records to tables.  
 
I haven't found anything like this on this site or any other so if this duplicates previous posts my 
apologies. Hope it saves others as much time as it would have saved me!  
 
Nathan  
 
‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐  
Option Explicit  
Option Base 1  
 
Sub excelmysql()  
' VBA to perform various actions on MySQL tables using VBA  
' Majority of the original code adapted from Carlmack 
http://www.ozgrid.com/forum/showthread.php?t=46893  
 
' PLEASE DO THE FOLLOWING BEFORE EXECUTING CODE:  
' 1)In VBE you need to go Tools/References and check Microsoft Active X Data Objects 2.x library  
' 2)Install MySQL ODBC 3.51 Driver. See dev.mysql.com/downloads/connector/odbc/3.51.html or 
google "MySQL ODBC 3.51 Driver"  
 
'‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐  
' Connection variables  
Dim conn As New ADODB.Connection  
Dim server_name As String  
Dim database_name As String  
Dim user_id As String  
Dim password As String  
 
' Table action variables  
Dim i As Long ' counter  
Dim sqlstr As String ' SQL to perform various actions  
Dim table1 As String, table2 As String  
Dim field1 As String, field2 As String  
Dim rs As ADODB.Recordset  
Dim vtype As Variant  
 
'‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐  
' Establish connection to the database  
server_name = "127.0.0.1" ' Enter your server name here ‐ if running from a local computer use 
127.0.0.1  
database_name = "dbname" ' Enter your database name here  
user_id = "userid" ' enter your user ID here  
password = "userpassword" ' Enter your password here  
 
Set conn = New ADODB.Connection  
conn.Open "DRIVER={MySQL ODBC 3.51 Driver}" _  
& ";SERVER=" & server_name _  
& ";DATABASE=" & database_name _  
& ";UID=" & user_id _  
& ";PWD=" & password _  
& ";OPTION=16427" ' Option 16427 = Convert LongLong to Int: This just helps makes sure that 
large numeric results get properly interpreted  
 
'‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐  
' Various Actions  
 
' Define variables (not all of the variables will be required for each action)  
vtype = Array("Text", "LongText", "Int(10)", "Float", "Double", "Date", "Time") ' array of commonly 
used MySQL variable types  
table1 = "firsttable"  
table2 = "secondtable"  
field1 = "fieldtitle1"  
field2 = "fieldtitle2"  
 
'‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐  
' Create or remove tables  
 
' Remove table from database  
GoTo skipremove  
sqlstr = "DROP TABLE " & table1  
conn.Execute sqlstr  
skipremove:  
 
' Create a new blank table with the specified fields  
GoTo skipcreate  
sqlstr = "CREATE TABLE " & table1 & "(" _  
& field1 & " " & vtype(1) & "," _  
& field2 & " " & vtype(2) _  
& ")"  
conn.Execute sqlstr  
skipcreate:  
 
'‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐  
' Add, remove or extract records from an existing table  
 
' Erase entire table contents but do not remove the table  
GoTo skiperase  
sqlstr = "DELETE FROM " & table1  
conn.Execute sqlstr  
skiperase:  
 
' Extract MySQL table data to first worksheet in the workbook  
GoTo skipextract  
Set rs = New ADODB.Recordset  
sqlstr = "SELECT * FROM " & table1 ' extracts all data  
rs.Open sqlstr, conn, adOpenStatic  
With Worksheets(1).Cells ' Enter your sheet name and range here  
.ClearContents  
.CopyFromRecordset rs  
End With  
skipextract:  
 
' Write new entries to a table from the first sheet of the workbook  
GoTo skipwrite  
With Sheets(1)  
For i = 1 To 10000  
If Cells(i, 1) = "" Then Exit For  
sqlstr = "INSERT INTO " & table1 & " SET " _  
& field1 & " = '" & Cells(i, 1) & "', " _  
& field2 & " = '" & Cells(i, 2) & "'"  
conn.Execute sqlstr  
Next i  
End With  
skipwrite:  
 
'‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐‐  
' Close connections  
On Error Resume Next  
rs.Close  
Set rs = Nothing  
conn.Close  
Set conn = Nothing  
On Error GoTo 0  
End Sub 

S-ar putea să vă placă și