1 /******************************* -*- C -*- ****************************
2  *
3  *      SQLite bindings
4  *
5  *
6  ***********************************************************************/
7 
8 /***********************************************************************
9  *
10  * Copyright 2007, 2008 Free Software Foundation, Inc.
11  * Written by Daniele Sciascia.
12  *
13  * This file is part of GNU Smalltalk.
14  *
15  * GNU Smalltalk is free software; you can redistribute it and/or modify it
16  * under the terms of the GNU General Public License as published by the Free
17  * Software Foundation; either version 2, or (at your option) any later
18  * version.
19  *
20  * Linking GNU Smalltalk statically or dynamically with other modules is
21  * making a combined work based on GNU Smalltalk.  Thus, the terms and
22  * conditions of the GNU General Public License cover the whole
23  * combination.
24  *
25  * In addition, as a special exception, the Free Software Foundation
26  * give you permission to combine GNU Smalltalk with free software
27  * programs or libraries that are released under the GNU LGPL and with
28  * independent programs running under the GNU Smalltalk virtual machine.
29  *
30  * You may copy and distribute such a system following the terms of the
31  * GNU GPL for GNU Smalltalk and the licenses of the other code
32  * concerned, provided that you include the source code of that other
33  * code when and as the GNU GPL requires distribution of source code.
34  *
35  * Note that people who make modified versions of GNU Smalltalk are not
36  * obligated to grant this special exception for their modified
37  * versions; it is their choice whether to do so.  The GNU General
38  * Public License gives permission to release a modified version without
39  * this exception; this exception also makes it possible to release a
40  * modified version which carries forward this exception.
41  *
42  * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
43  * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
44  * FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License for
45  * more details.
46  *
47  * You should have received a copy of the GNU General Public License along with
48  * GNU Smalltalk; see the file COPYING.  If not, write to the Free Software
49  * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
50  *
51  ***********************************************************************/
52 
53 
54 #include <stdio.h>
55 #include <stdlib.h>
56 #include "gstpub.h"
57 #include "sqlite3.h"
58 
59 typedef struct st_Sqlite3Handle
60 {
61   OBJ_HEADER;
62   OOP db;
63 } *SQLite3Handle;
64 
65 typedef struct st_SQLite3StmtHandle
66 {
67   OBJ_HEADER;
68   OOP db;
69   OOP stmt;
70   OOP colCount;
71   OOP colTypes;
72   OOP colNames;
73   OOP returnedRow;
74 } *SQLite3StmtHandle;
75 
76 
77 static VMProxy *vmProxy;
78 
79 
80 static int
gst_sqlite3_open(OOP self,const char * db_name)81 gst_sqlite3_open (OOP self, const char *db_name)
82 {
83   int rc;
84   sqlite3 *db;
85   OOP dbHandle;
86   SQLite3Handle h;
87 
88   rc = sqlite3_open (db_name, &db);
89   dbHandle = vmProxy->cObjectToOOP (db);
90   h = (SQLite3Handle) OOP_TO_OBJ (self);
91   h->db = dbHandle;
92 
93   return rc;
94 }
95 
96 static int
gst_sqlite3_close(OOP self)97 gst_sqlite3_close (OOP self)
98 {
99   sqlite3 *db;
100   SQLite3Handle h;
101 
102   h = (SQLite3Handle) OOP_TO_OBJ (self);
103   db = (sqlite3 *) vmProxy->OOPToCObject (h->db);
104   return sqlite3_close (db);
105 }
106 
107 static int
gst_sqlite3_prepare(OOP self,const char * sql)108 gst_sqlite3_prepare (OOP self, const char *sql)
109 {
110   int rc, i, cols;
111   sqlite3 *db;
112   sqlite3_stmt *stmt;
113   OOP tmpOOP;
114   SQLite3StmtHandle h;
115 
116   h = (SQLite3StmtHandle) OOP_TO_OBJ (self);
117   db = (sqlite3 *) vmProxy->OOPToCObject (h->db);
118 
119   rc = sqlite3_prepare (db, sql, -1, &stmt, 0);
120   if (rc != SQLITE_OK)
121     return rc;
122 
123   tmpOOP = vmProxy->cObjectToOOP (stmt);
124   h = (SQLite3StmtHandle) OOP_TO_OBJ (self);
125   h->stmt = tmpOOP;
126 
127   cols = sqlite3_column_count (stmt);
128   tmpOOP = vmProxy->intToOOP (cols);
129   h->colCount = tmpOOP;
130 
131   tmpOOP = vmProxy->objectAlloc (vmProxy->arrayClass, cols);
132   h = (SQLite3StmtHandle) OOP_TO_OBJ (self);
133   h->colTypes = tmpOOP;
134 
135   tmpOOP = vmProxy->objectAlloc (vmProxy->arrayClass, cols);
136   h = (SQLite3StmtHandle) OOP_TO_OBJ (self);
137   h->colNames = tmpOOP;
138 
139   tmpOOP = vmProxy->objectAlloc (vmProxy->arrayClass, cols);
140   h = (SQLite3StmtHandle) OOP_TO_OBJ (self);
141   h->returnedRow = tmpOOP;
142 
143   for (i = 0; i < cols; i++)
144     {
145       tmpOOP = vmProxy->stringToOOP (sqlite3_column_name (stmt, i));
146       h = (SQLite3StmtHandle) OOP_TO_OBJ (self);
147       vmProxy->OOPAtPut (h->colNames, i, tmpOOP);
148     }
149 
150   return rc;
151 }
152 
153 static int
gst_sqlite3_exec(OOP self)154 gst_sqlite3_exec (OOP self)
155 {
156   int rc;
157   sqlite3_stmt *stmt;
158   SQLite3StmtHandle h;
159 
160   h = (SQLite3StmtHandle) OOP_TO_OBJ (self);
161   if (h->stmt == vmProxy->nilOOP)
162     return SQLITE_MISUSE;
163 
164   stmt = (sqlite3_stmt *) vmProxy->OOPToCObject (h->stmt);
165   rc = sqlite3_step (stmt);
166 
167   if (rc == SQLITE_ROW)
168     {
169       int i, cols, type;
170       OOP tmpOOP;
171 
172       cols = sqlite3_column_count (stmt);
173       for (i = 0; i < cols; i++)
174 	{
175 	  type = sqlite3_column_type (stmt, i);
176 	  tmpOOP = vmProxy->intToOOP (type);
177 	  vmProxy->OOPAtPut (h->colTypes, i, tmpOOP);
178 
179 	  switch (type)
180 	    {
181 	    case SQLITE_INTEGER:
182 	      tmpOOP = vmProxy->intToOOP (sqlite3_column_int (stmt, i));
183 	      break;
184 	    case SQLITE_FLOAT:
185 	      tmpOOP = vmProxy->floatToOOP (sqlite3_column_double (stmt, i));
186 	      break;
187 	    case SQLITE_TEXT:
188 	      tmpOOP = vmProxy->stringToOOP (sqlite3_column_text (stmt, i));
189 	      break;
190 	    case SQLITE_BLOB:
191 	      tmpOOP = vmProxy->stringToOOP (sqlite3_column_text (stmt, i));
192 	      break;
193 	    case SQLITE_NULL:
194 	      tmpOOP = vmProxy->nilOOP;
195 	      break;
196 	    default:
197 	      fprintf (stderr, "sqlite3 error: %s\n",
198 		       "returned type not recognized");
199 	    }
200 
201 	  h = (SQLite3StmtHandle) OOP_TO_OBJ (self);
202 	  vmProxy->OOPAtPut (h->returnedRow, i, tmpOOP);
203 	}
204     }
205 
206   return rc;
207 }
208 
209 static int
gst_sqlite3_bind(OOP self,OOP key,OOP value)210 gst_sqlite3_bind (OOP self, OOP key, OOP value)
211 {
212     sqlite3_stmt *stmt;
213     SQLite3StmtHandle h;
214     int index;
215 
216     h = (SQLite3StmtHandle) OOP_TO_OBJ (self);
217     if (h->stmt == vmProxy->nilOOP)
218         return SQLITE_MISUSE;
219 
220     stmt = (sqlite3_stmt *) vmProxy->OOPToCObject (h->stmt);
221     if (vmProxy->objectIsKindOf (key, vmProxy->smallIntegerClass))
222       index = vmProxy->OOPToInt (key);
223 
224     else if (vmProxy->objectIsKindOf (key, vmProxy->stringClass))
225       {
226 	char *name = vmProxy->OOPToString (key);
227 	index = sqlite3_bind_parameter_index(stmt, name);
228 	free (name);
229 	if (index == 0)
230 	  return SQLITE_OK;
231       }
232 
233     else
234       return -1;
235 
236     if (vmProxy->objectIsKindOf (value, vmProxy->smallIntegerClass))
237 #if SIZEOF_LONG == 4
238         return sqlite3_bind_int (stmt, index, vmProxy->OOPToInt (value));
239 #else
240         return sqlite3_bind_int64 (stmt, index,
241 				   (sqlite_int64) vmProxy->OOPToInt (value));
242 #endif
243 
244     if (vmProxy->objectIsKindOf (value, vmProxy->stringClass)
245 	|| vmProxy->objectIsKindOf (value, vmProxy->byteArrayClass))
246         return sqlite3_bind_text (stmt, index, vmProxy->OOPIndexedBase (value),
247 				  vmProxy->basicSize (value), SQLITE_TRANSIENT);
248 
249     if (vmProxy->objectIsKindOf (value, vmProxy->floatDClass))
250         return sqlite3_bind_double (stmt, index, vmProxy->OOPToFloat (value));
251 
252     if (value == vmProxy->nilOOP)
253         return sqlite3_bind_null (stmt, index);
254 
255     return -1;
256 }
257 
258 #ifndef HAVE_LIBSQLITE3_SQLITE3_CLEAR_BINDINGS
259 #define sqlite3_clear_bindings my_sqlite3_clear_bindings
260 
261 static int
sqlite3_clear_bindings(sqlite3_stmt * stmt)262 sqlite3_clear_bindings (sqlite3_stmt *stmt)
263 {
264   int n = sqlite3_bind_parameter_count (stmt);
265   int index;
266 
267   for (index = 1; index <= n; index++)
268     {
269       int result = sqlite3_bind_null (stmt, index);
270       if (result != SQLITE_OK)
271 	return result;
272     }
273 
274   return SQLITE_OK;
275 }
276 
277 #endif
278 static int
gst_sqlite3_clear_bindings(OOP self)279 gst_sqlite3_clear_bindings (OOP self)
280 {
281     sqlite3_stmt *stmt;
282     SQLite3StmtHandle h;
283 
284     h = (SQLite3StmtHandle) OOP_TO_OBJ (self);
285     if (h->stmt == vmProxy->nilOOP)
286         return SQLITE_MISUSE;
287 
288     stmt = (sqlite3_stmt *) vmProxy->OOPToCObject (h->stmt);
289     return sqlite3_clear_bindings (stmt);
290 }
291 
292 static int
gst_sqlite3_reset(OOP self)293 gst_sqlite3_reset (OOP self)
294 {
295     sqlite3_stmt *stmt;
296     SQLite3StmtHandle h;
297 
298     h = (SQLite3StmtHandle) OOP_TO_OBJ (self);
299     if (h->stmt == vmProxy->nilOOP)
300         return SQLITE_MISUSE;
301 
302     stmt = (sqlite3_stmt *) vmProxy->OOPToCObject (h->stmt);
303     return sqlite3_reset (stmt);
304 }
305 
306 static const char *
gst_sqlite3_error_message(OOP self)307 gst_sqlite3_error_message (OOP self)
308 {
309   sqlite3 *db;
310   SQLite3Handle h;
311 
312   h = (SQLite3Handle) OOP_TO_OBJ (self);
313   db = (sqlite3 *) vmProxy->OOPToCObject (h->db);
314 
315   return sqlite3_errmsg (db);
316 }
317 
318 static int
gst_sqlite3_finalize(OOP self)319 gst_sqlite3_finalize (OOP self)
320 {
321   sqlite3_stmt *stmt;
322   SQLite3StmtHandle h;
323 
324   h = (SQLite3StmtHandle) OOP_TO_OBJ (self);
325   if (h->stmt == vmProxy->nilOOP)
326     return 0;
327 
328   stmt = (sqlite3_stmt *) vmProxy->OOPToCObject (h->stmt);
329   h->stmt = vmProxy->nilOOP;
330   return sqlite3_finalize (stmt);
331 }
332 
333 static int
gst_sqlite3_changes(OOP self)334 gst_sqlite3_changes (OOP self)
335 {
336   sqlite3 *db;
337   SQLite3StmtHandle h;
338 
339   h = (SQLite3StmtHandle) OOP_TO_OBJ (self);
340   db = (sqlite3 *) vmProxy->OOPToCObject (h->db);
341 
342   return sqlite3_changes (db);
343 }
344 
345 void
gst_initModule(VMProxy * proxy)346 gst_initModule (VMProxy * proxy)
347 {
348   vmProxy = proxy;
349   vmProxy->defineCFunc ("gst_sqlite3_open", gst_sqlite3_open);
350   vmProxy->defineCFunc ("gst_sqlite3_close", gst_sqlite3_close);
351   vmProxy->defineCFunc ("gst_sqlite3_prepare", gst_sqlite3_prepare);
352   vmProxy->defineCFunc ("gst_sqlite3_exec", gst_sqlite3_exec);
353   vmProxy->defineCFunc ("gst_sqlite3_bind", gst_sqlite3_bind);
354   vmProxy->defineCFunc ("gst_sqlite3_clear_bindings", gst_sqlite3_clear_bindings);
355   vmProxy->defineCFunc ("gst_sqlite3_reset", gst_sqlite3_reset);
356   vmProxy->defineCFunc ("gst_sqlite3_changes", gst_sqlite3_changes);
357   vmProxy->defineCFunc ("gst_sqlite3_error_message", gst_sqlite3_error_message);
358   vmProxy->defineCFunc ("gst_sqlite3_finalize", gst_sqlite3_finalize);
359 }
360