Curlys wrote:

hi ,
mysql databse server is in Red Hat Linux 8 box. I have an application which is developed from Visual Basic . So that application included a reqiurement to connect mysql data base.
Can somebody help me how to connect mysql database via VB ?
thanx in advance
curlys

First of all you will need a ODCB driver (you can download this from mysql.com. Then you will need to write some functions. I have attached a vb module including the functions I use.


--

Peter Bruggink

Manager mechanical Design
+31 76 5792732
[EMAIL PROTECTED] <mailto:[EMAIL PROTECTED]>

*Steelweld BV*
Terheijdenseweg 169
The Netherlands

www.steelweld.com <http://www.steelweld.com/>

------------------------------------------------------------------------

*DISCLAIMER* The information transmitted is confidential and may be legally privileged. It is intended solely for the use of the individual or entity to whom it is addressed. If you received this in error, please contact the sender and delete the material from any computer.

This mail has been checked for all known viruses by McAfee Virusscan.

VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
  Persistable = 0  'NotPersistable
  DataBindingBehavior = 0  'vbNone
  DataSourceBehavior  = 0  'vbNone
  MTSTransactionMode  = 0  'NotAnMTSObject
END
Attribute VB_Name = "swMyDBConnection"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = True
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
Attribute VB_Ext_KEY = "SavedWithClassBuilder6" ,"Yes"
Attribute VB_Ext_KEY = "Top_Level" ,"Yes"
Option Explicit

Private strServer As String
Private strDatabase As String
Private strDBUserId As String
Private strDBPassword As String

Private WithEvents CurConnection As ADODB.Connection
Attribute CurConnection.VB_VarHelpID = -1
Private bConnected As Boolean
Private bExecuteReady As Boolean
Private bCommitReady As Boolean
Private bRollbackReady As Boolean

Public Property Get Connected() As Boolean
   Connected = bConnected
End Property

Public Property Get ConnectionString() As String
' Provide proper connection string for current database settings.
' Return "" when no data set yet.
   Dim strOut As String
   strOut = "DRIVER={" & objProperties.MYSPINSQLDRIVER & "};"
   strOut = strOut & "SERVER=" & strServer & ";"
   strOut = strOut & "DATABASE=" & strDatabase & ";"
   strOut = strOut & "UID=" & strDBUserId & ";"
   strOut = strOut & "PWD=" & strDBPassword & ";"
   strOut = strOut & "OPTION=35"
    
   ConnectionString = strOut
End Property

Public Function MakeConnection() As Boolean
' Make connection, when not made yet. For access, test if the given database
' can be found. If not, open dialog to set database data.
   Dim file As String
   MakeConnection = False
   If Not bConnected Then
      On Error GoTo Error_Conn
      
      Set CurConnection = New ADODB.Connection
      CurConnection.CursorLocation = adUseServer
      CurConnection.ConnectionString = ConnectionString
      CurConnection.Open    'Open de verbinding
      bConnected = True

   End If
   MakeConnection = bConnected
   Exit Function
   
Error_Conn:
  
   Debug.Print Err.Description
End Function



Public Function Execute(sqlstr As String, Errstr As String, _
                        Optional bErr As Boolean = True) As Recordset
' Execute the given sqlstring, and return the recordset.
' Wait until the command has been executed.
   bExecuteReady = False
   Errstr = ""
   Debug.Print sqlstr
   On Error GoTo err_execute
   Set Execute = CurConnection.Execute(sqlstr)
   Do While Not bExecuteReady
      DoEvents
   Loop
   Exit Function

err_execute:
   If Err.Number = &H80004005 Then
      If Not bErr Then Exit Function
      Errstr = "Item with these data already in database!" & vbCrLf & _
             "Please change data before trying again"
   Else
      Errstr = Err.Description
      Debug.Print Errstr
   End If
End Function

Public Function ExecuteAff(sqlstr As String, Errstr As String, _
                           Optional bErr As Boolean = True) As Long
' Execute the given sqlstring, and return the number of affected records.
' This function should only be used for sql-commands that do not return
' a recordset. bErr allows surpression of the duplicate error message.
' Wait until the command has been executed.
   Dim nraff As Long
   bExecuteReady = False
   Errstr = ""
   Debug.Print sqlstr
   On Error GoTo err_execute
   CurConnection.Execute sqlstr, nraff
   Do While Not bExecuteReady
      DoEvents
   Loop
   ExecuteAff = nraff
   Exit Function

err_execute:
   If Err.Number = &H80004005 Then
   If Not bErr Then Exit Function
      Errstr = "Item with these data already in database!" & vbCrLf & _
             "Please change data before trying again"
   Else
      Errstr = Err.Description
   End If
End Function

Public Sub OpenStatic(aRset As ADODB.Recordset, sqlstr As String)
' Open a static recordset with the given sqlstring
   aRset.Open sqlstr, CurConnection, adOpenStatic
End Sub

Public Sub OpenDynamic(aRset As ADODB.Recordset, sqlstr As String)
' Open a dynamic recordset with the given sqlstring
   aRset.Open sqlstr, CurConnection, adOpenDynamic, adLockOptimistic
End Sub

Private Sub SetData(adb As String, auid As String, apassw As String)
   strServer = objProperties.MYSPINDBSERVER
   strDatabase = adb
   strDBUserId = auid
   strDBPassword = apassw
End Sub

Private Sub Class_Initialize()
   'SetData "MySpin", "admin", "admin"
   SetData "MySpin", "admin", "admin"
   bConnected = False
End Sub

Private Sub Class_Terminate()
   If bConnected Then
      CurConnection.Close
      Set CurConnection = Nothing
      bConnected = False
   End If
End Sub

Private Sub CurConnection_CommitTransComplete(ByVal pError As ADODB.Error, adStatus As 
ADODB.EventStatusEnum, ByVal pConnection As ADODB.Connection)
' Set indicator that commit has been completed
   bCommitReady = True
End Sub

Private Sub CurConnection_ExecuteComplete(ByVal RecordsAffected As Long, ByVal pError 
As ADODB.Error, adStatus As ADODB.EventStatusEnum, ByVal pCommand As ADODB.Command, 
ByVal pRecordset As ADODB.Recordset, ByVal pConnection As ADODB.Connection)
' Set indicator that command has been executed
   bExecuteReady = True
End Sub

Private Sub CurConnection_RollbackTransComplete(ByVal pError As ADODB.Error, adStatus 
As ADODB.EventStatusEnum, ByVal pConnection As ADODB.Connection)
' Set indicator that rollback has been completed
   bRollbackReady = True
End Sub

'Private Sub frmSetDb_NewData(adbtype As Integer, aserver As String, adb As String, 
auid As String, apassw As String)
'   SetData aserver, adb, auid, apassw
'   MakeConnection
'End Sub


Public Sub BeginTransaction()
   Dim level As Long
   level = CurConnection.BeginTrans
   If level > 1 Then
      MsgBox "begin nested transaction !!!!!"
   End If
End Sub

Public Sub CommitTransaction()
' Start commit to ensure all data are saved
' Wait until the commit has been executed.
   bCommitReady = False
   CurConnection.CommitTrans
   Do While Not bCommitReady
      DoEvents
   Loop
End Sub

Public Sub RollbackTransaction()
' Start commit to ensure all data are saved
' Wait until the commit has been executed.
   bRollbackReady = False
   CurConnection.RollbackTrans
   Do While Not bRollbackReady
      DoEvents
   Loop
End Sub




-- 
MySQL General Mailing List
For list archives: http://lists.mysql.com/mysql
To unsubscribe:    http://lists.mysql.com/[EMAIL PROTECTED]

Reply via email to