ODBCError.SqlState property (Excel)
Returns the SQL state error. Read-only String.
Syntax
expression.SqlState
expression A variable that represents an ODBCError object.
Remarks
For an explanation of the specific error, see your SQL documentation.
Example
This example refreshes query table one and displays any ODBC errors that occur.
With Worksheets(1).QueryTables(1)
.Refresh
Set errs = Application.ODBCErrors
If errs.Count > 0 Then
Set r = .Destination.Cells(1)
r.Value = "The following errors occurred:"
c = 0
For Each er In errs
c = c + 1
r.offset(c, 0).value = er.ErrorString
r.offset(c, 1).value = er.SqlState
Next
Else
MsgBox "Query complete: all records returned."
End If
End With
Support and feedback
Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.