-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathOracleConnection.cls
133 lines (108 loc) · 3.45 KB
/
OracleConnection.cls
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
VERSION 1.0 CLASS
BEGIN
MultiUse = -1 'True
END
Attribute VB_Name = "OracleConnection"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
Option Explicit
Private conn As Object
Public Sub Initialize(ByVal connection As Object)
Set conn = connection
End Sub
Public Function ExecuteNonQuery(ByVal sql As String, Optional ByRef affectedRows As Long = -1) As Boolean
On Error GoTo ErrorHandler
conn.Execute sql, affectedRows
ExecuteNonQuery = True
Exit Function
ErrorHandler:
MsgBox "Erro ao executar a consulta: " & Err.Description, vbCritical
ExecuteNonQuery = False
End Function
Public Function ExecuteQuery(ByVal sql As String, ParamArray params() As Variant) As Object
Dim cmd As Object
Dim rs As Object
Dim i As Integer
On Error GoTo ErrorHandler
Set cmd = CreateObject("ADODB.Command")
Set cmd.ActiveConnection = conn
cmd.CommandText = sql
cmd.CommandType = 1 ' adCmdText
For i = LBound(params) To UBound(params) Step 2
Dim paramType As Integer
paramType = GetADOType(params(i + 1))
Dim paramSize As Integer
If paramType = 200 Then
paramSize = Len(params(i + 1))
Else
paramSize = 0
End If
Dim param As Object
Set param = cmd.CreateParameter(params(i), paramType, 1, paramSize, params(i + 1)) ' 1 = adParamInput
cmd.Parameters.Append param
Next i
Set rs = CreateObject("ADODB.Recordset")
rs.CursorType = 3 ' adOpenStatic
rs.Open cmd
Set ExecuteQuery = rs
Exit Function
ErrorHandler:
MsgBox "Erro ao executar a consulta: " & Err.Description, vbCritical
Set ExecuteQuery = Nothing
End Function
Private Function GetADOType(v As Variant) As Integer
Select Case VarType(v)
Case vbInteger
GetADOType = 3 ' adInteger
Case vbLong
GetADOType = 3 ' adInteger
Case vbSingle
GetADOType = 4 ' adSingle
Case vbDouble
GetADOType = 5 ' adDouble
Case vbCurrency
GetADOType = 6 ' adCurrency
Case vbDate
GetADOType = 7 ' adDate
Case vbString
GetADOType = 200 ' adVarChar
Case vbBoolean
GetADOType = 11 ' adBoolean
Case Else
GetADOType = 200 ' adVarChar
End Select
End Function
Public Sub CloseConnection()
If Not conn Is Nothing Then
conn.Close
Set conn = Nothing
End If
End Sub
Public Function IsConnected() As Boolean
On Error Resume Next
IsConnected = Not (conn Is Nothing Or conn.State = 0)
End Function
Public Sub BeginTransaction()
On Error GoTo ErrorHandler
conn.BeginTrans
Exit Sub
ErrorHandler:
MsgBox "Erro ao iniciar a transação: " & Err.Description, vbCritical
End Sub
Public Sub CommitTransaction()
On Error GoTo ErrorHandler
conn.CommitTrans
Exit Sub
ErrorHandler:
MsgBox "Erro ao confirmar a transação: " & Err.Description & ". Realizando rollback.", vbCritical
RollbackTransaction
End Sub
Public Sub RollbackTransaction()
On Error GoTo ErrorHandler
conn.RollbackTrans
Exit Sub
ErrorHandler:
MsgBox "Erro ao reverter a transação: " & Err.Description, vbCritical
End Sub