Store walltimes as timestamptz by default in postgres
[clsql.git] / sql / generic-postgresql.lisp
1 ;;;; -*- Mode: LISP; Syntax: ANSI-Common-Lisp; Base: 10 -*-
2 ;;;; *************************************************************************
3 ;;;;
4 ;;;; Generic postgresql layer, used by db-postgresql and db-postgresql-socket
5 ;;;;
6 ;;;; This file is part of CLSQL.
7 ;;;;
8 ;;;; CLSQL users are granted the rights to distribute and use this software
9 ;;;; as governed by the terms of the Lisp Lesser GNU Public License
10 ;;;; (http://opensource.franz.com/preamble.html), also known as the LLGPL.
11 ;;;; *************************************************************************
12
13 (in-package #:clsql-sys)
14
15 (defclass generic-postgresql-database (database)
16   ((has-table-pg_roles :type boolean :reader has-table-pg_roles :initform nil))
17   (:documentation "Encapsulate same behavior across postgresql and postgresql-socket backends."))
18
19
20
21 ;; Object functions
22
23 (defmethod database-get-type-specifier ((type symbol) args database
24                                         (db-type (eql :postgresql)))
25   "Special database types for POSTGRESQL backends"
26   (declare (ignore database db-type))
27   (case type
28     ;; his used to be without because we didnt track timezones well
29     ;; Now we do, so it should include them
30     (wall-time
31      "TIMESTAMP WITH TIME ZONE")
32     (string
33      ;; TODO: the default to CHAR here seems specious as the PG docs claim
34      ;; that char is slower than varchar
35      (if args
36          (format nil "CHAR(~A)" (car args))
37          "VARCHAR"))
38     (number
39      (cond
40        ((and (consp args) (= (length args) 2))
41         (format nil "NUMERIC(~D,~D)" (first args) (second args)))
42        ((and (consp args) (= (length args) 1))
43         (format nil "NUMERIC(~D)" (first args)))
44        (t "NUMERIC")))
45     ((tinyint smallint) "INT2")
46     (t (call-next-method))))
47
48 ;;; Backend functions
49
50 (defun owner-clause (owner)
51   (cond
52    ((stringp owner)
53     (format
54      nil
55      " AND (relowner=(SELECT usesysid FROM pg_user WHERE (usename='~A')))"
56      owner))
57    ((null owner)
58     (format nil " AND (relowner<>(SELECT usesysid FROM pg_user WHERE usename='postgres'))"))
59    (t "")))
60
61 (defun has-table (name database)
62   (let ((name-retrieved
63          (caar (database-query
64                 (format nil "SELECT relname FROM pg_class WHERE relname='~A'"
65                         name)
66                 database nil nil))))
67     (if (and (stringp name-retrieved) (plusp (length name-retrieved)))
68         t
69         nil)))
70
71 (defmethod slot-unbound (class (obj generic-postgresql-database)
72                          (slot (eql 'has-table-pg_roles)))
73   ;; Lazily cache slot value
74   (declare (ignore class))
75   (setf (slot-value obj 'has-table-pg_roles) (has-table "pg_roles" obj)))
76
77 (defun database-list-objects-of-type (database type owner)
78   (mapcar #'car
79           (database-query
80            (format nil
81                    (if (and (has-table-pg_roles database)
82                             (not (eq owner :all)))
83                        "
84  SELECT c.relname
85  FROM pg_catalog.pg_class c
86       LEFT JOIN pg_catalog.pg_roles r ON r.oid = c.relowner
87       LEFT JOIN pg_catalog.pg_namespace n ON n.oid = c.relnamespace
88  WHERE c.relkind IN ('~A','')
89        AND n.nspname NOT IN ('pg_catalog', 'pg_toast')
90        AND pg_catalog.pg_table_is_visible(c.oid)
91        ~A"
92                        "SELECT relname FROM pg_class WHERE (relkind =
93 '~A')~A")
94                    type
95                    (owner-clause owner))
96            database nil nil)))
97
98 (defmethod database-list-tables ((database generic-postgresql-database)
99                                  &key (owner nil))
100   (database-list-objects-of-type database "r" owner))
101
102 (defmethod database-list-views ((database generic-postgresql-database)
103                                 &key (owner nil))
104   (database-list-objects-of-type database "v" owner))
105
106 (defmethod database-list-indexes ((database generic-postgresql-database)
107                                   &key (owner nil))
108   (database-list-objects-of-type database "i" owner))
109
110
111 (defmethod database-list-table-indexes (table (database generic-postgresql-database)
112                                         &key (owner nil))
113   (let ((indexrelids
114          (database-query
115           (format
116            nil
117            "select indexrelid from pg_index where indrelid=(select relfilenode from pg_class where LOWER(relname)='~A'~A)"
118            (string-downcase (unescaped-database-identifier table))
119            (owner-clause owner))
120           database :auto nil))
121         (result nil))
122     (dolist (indexrelid indexrelids (nreverse result))
123       (push
124        (caar (database-query
125               (format nil "select relname from pg_class where relfilenode='~A'"
126                       (car indexrelid))
127               database nil nil))
128        result))))
129
130 (defmethod database-list-attributes ((table %database-identifier)
131                                      (database generic-postgresql-database)
132                                      &key (owner nil))
133   (let* ((table (unescaped-database-identifier table))
134          (owner-clause
135           (cond ((stringp owner)
136                  (format nil " AND (relowner=(SELECT usesysid FROM pg_user WHERE usename='~A'))" owner))
137                 ((null owner) " AND (not (relowner=1))")
138                 (t "")))
139          (result
140           (mapcar #'car
141                   (database-query
142                    (format nil "SELECT attname FROM pg_class,pg_attribute WHERE pg_class.oid=attrelid AND attisdropped = FALSE AND relname='~A'~A"
143                            (string-downcase table)
144                            owner-clause)
145                    database nil nil))))
146     (if result
147         (remove-if #'(lambda (it) (member it '("cmin"
148                                                "cmax"
149                                                "xmax"
150                                                "xmin"
151                                                "oid"
152                                                "ctid"
153                                                ;; kmr -- added tableoid
154                                                "tableoid") :test #'equal))
155                    result))))
156
157 (defmethod database-attribute-type ((attribute %database-identifier)
158                                     (table %database-identifier)
159                                     (database generic-postgresql-database)
160                                     &key (owner nil)
161                                     &aux (table (unescaped-database-identifier table))
162                                     (attribute (unescaped-database-identifier attribute)))
163   (let ((row (car (database-query
164                    (format nil "SELECT pg_type.typname,pg_attribute.attlen,pg_attribute.atttypmod,pg_attribute.attnotnull FROM pg_type,pg_class,pg_attribute WHERE pg_class.oid=pg_attribute.attrelid AND pg_class.relname='~A' AND pg_attribute.attname='~A' AND pg_attribute.atttypid=pg_type.oid~A"
165                            (string-downcase table)
166                            (string-downcase attribute)
167                            (owner-clause owner))
168                    database nil nil))))
169     (when row
170       (destructuring-bind (typname attlen atttypmod attnull) row
171         (setf attlen (%get-int attlen)
172               atttypmod (%get-int atttypmod))
173         (let ((coltype (ensure-keyword typname))
174               (colnull (typecase attnull
175                          (string (if (string-equal "f" attnull) 1 0))
176                          (null 1)
177                          (T 0)))
178               collen
179               colprec)
180           (setf (values collen colprec)
181                 (case coltype
182                   ((:numeric :decimal)
183                    (if (= -1 atttypmod)
184                        (values nil nil)
185                        (values (ash (- atttypmod 4) -16)
186                                (boole boole-and (- atttypmod 4) #xffff))))
187                   (otherwise
188                    (values
189                     (cond ((and (= -1 attlen) (= -1 atttypmod)) nil)
190                           ((= -1 attlen) (- atttypmod 4))
191                           (t attlen))
192                     nil))))
193           (values coltype collen colprec colnull))))))
194
195 (defmethod database-create-sequence (sequence-name
196                                      (database generic-postgresql-database))
197   (let ((cmd (concatenate
198               'string "CREATE SEQUENCE " (escaped-database-identifier sequence-name database))))
199   (database-execute-command cmd database)))
200
201 (defmethod database-drop-sequence (sequence-name
202                                    (database generic-postgresql-database))
203   (database-execute-command
204    (concatenate 'string "DROP SEQUENCE " (escaped-database-identifier sequence-name database))
205    database))
206
207 (defmethod database-list-sequences ((database generic-postgresql-database)
208                                     &key (owner nil))
209   (database-list-objects-of-type database "S" owner))
210
211 (defmethod database-set-sequence-position (name (position integer)
212                                                 (database generic-postgresql-database))
213   (values
214    (%get-int
215     (caar
216      (database-query
217       (format nil "SELECT SETVAL ('~A', ~A)" (escaped-database-identifier name) position)
218       database nil nil)))))
219
220 (defmethod database-sequence-next (sequence-name
221                                    (database generic-postgresql-database))
222   (values
223    (%get-int
224     (caar
225      (database-query
226       (concatenate 'string "SELECT NEXTVAL ('" (escaped-database-identifier sequence-name) "')")
227       database nil nil)))))
228
229 (defmethod database-sequence-last (sequence-name (database generic-postgresql-database))
230   (values
231    (%get-int
232     (caar
233      (database-query
234       (concatenate 'string "SELECT LAST_VALUE FROM " (escaped-database-identifier sequence-name))
235       database nil nil)))))
236
237 (defmethod auto-increment-sequence-name (table column (database generic-postgresql-database))
238   (let* ((sequence-name (or (database-identifier (slot-value column 'autoincrement-sequence))
239                             (combine-database-identifiers
240                              (list table column 'seq)
241                              database))))
242     (when (search "'" (escaped-database-identifier sequence-name)
243                   :test #'string-equal)
244       (signal-database-too-strange
245        "PG Sequence names shouldnt contain single quotes for the sake of sanity"))
246     sequence-name))
247
248 (defmethod database-last-auto-increment-id ((database generic-postgresql-database) table column)
249   (let ((seq-name (auto-increment-sequence-name table column database)))
250     (first (clsql:query (format nil "SELECT currval ('~a')"
251                                 (escaped-database-identifier seq-name))
252                         :flatp t
253                         :database database
254                         :result-types '(:int)))))
255
256 (defmethod database-generate-column-definition
257     (class slotdef (database generic-postgresql-database))
258   (when (member (view-class-slot-db-kind slotdef) '(:base :key))
259     (let ((cdef
260             (list (sql-expression :attribute (database-identifier slotdef database))
261                   (specified-type slotdef)
262                   (view-class-slot-db-type slotdef)))
263           (const (listify (view-class-slot-db-constraints slotdef)))
264           (seq (auto-increment-sequence-name class slotdef database)))
265       (when seq
266         (setf const (remove :auto-increment const))
267         (unless (member :default const)
268           (let* ((next (format nil " nextval('~a')" (escaped-database-identifier seq))))
269             (setf const (append const (list :default next))))))
270       (append cdef const))))
271
272 (defmethod database-add-autoincrement-sequence
273     ((self standard-db-class) (database generic-postgresql-database))
274   (let ((ordered-slots (slots-for-possibly-normalized-class self)))
275     (dolist (slotdef ordered-slots)
276       ;; ensure that referenceed sequences actually exist before referencing them
277       (let ((sequence-name (auto-increment-sequence-name self slotdef database)))
278         (when (and sequence-name
279                    (not (sequence-exists-p sequence-name :database database)))
280           (create-sequence sequence-name :database database))))))
281
282 (defmethod database-remove-autoincrement-sequence
283     ((table standard-db-class)
284      (database generic-postgresql-database))
285   (let ((ordered-slots (slots-for-possibly-normalized-class table)))
286     (dolist (slotdef ordered-slots)
287       ;; ensure that referenceed sequences are dropped with the table
288       (let ((sequence-name (auto-increment-sequence-name table slotdef database)))
289         (when sequence-name (drop-sequence sequence-name))))))
290
291 (defun postgresql-database-list (connection-spec type)
292   (destructuring-bind (host name &rest other-args) connection-spec
293     (declare (ignore name))
294     (let ((database (database-connect (list* host "template1" other-args)
295                                       type)))
296       (unwind-protect
297            (progn
298              (setf (slot-value database 'clsql-sys::state) :open)
299              (mapcar #'car (database-query "select datname from pg_database"
300                                            database nil nil)))
301         (progn
302           (database-disconnect database)
303           (setf (slot-value database 'clsql-sys::state) :closed))))))
304
305 (defmethod database-list (connection-spec (type (eql :postgresql)))
306   (postgresql-database-list connection-spec type))
307
308 (defmethod database-list (connection-spec (type (eql :postgresql-socket)))
309   (postgresql-database-list connection-spec type))
310
311 #+nil
312 (defmethod database-describe-table ((database generic-postgresql-database) table)
313   ;; MTP: LIST-ATTRIBUTE-TYPES currently executes separate queries for
314   ;; each attribute. It would be more efficient to have a single SQL
315   ;; query return the type data for all attributes. This code is
316   ;; retained as an example of how to do this for PostgreSQL.
317   (database-query
318    (format nil "select a.attname, t.typname
319                                from pg_class c, pg_attribute a, pg_type t
320                                where c.relname = '~a'
321                                    and a.attnum > 0
322                                    and a.attrelid = c.oid
323                                    and a.atttypid = t.oid"
324            (sql-escape (string-downcase table)))
325    database :auto nil))
326
327 ;;; Prepared statements
328
329 (defvar *next-prepared-id-num* 0)
330 (defun next-prepared-id ()
331   (let ((num (incf *next-prepared-id-num*)))
332     (format nil "CLSQL_PS_~D" num)))
333
334 (defclass postgresql-stmt ()
335   ((database :initarg :database :reader database)
336    (id :initarg :id :reader id)
337    (bindings :initarg :bindings :reader bindings)
338    (field-names :initarg :field-names :accessor stmt-field-names)
339    (result-types :initarg :result-types :reader result-types)))
340
341 (defun clsql-type->postgresql-type (type)
342   (cond
343     ((in type :int :integer) "INT4")
344     ((in type :short) "INT2")
345     ((in type :bigint) "INT8")
346     ((in type :float :double :number) "NUMERIC")
347     ((and (consp type) (in (car type) :char :varchar)) "VARCHAR")
348     (t
349      (error 'sql-user-error
350             :message
351             (format nil "Unknown clsql type ~A." type)))))
352
353 (defun prepared-sql-to-postgresql-sql (sql)
354   ;; FIXME: Convert #\? to "$n". Don't convert within strings
355   (declare (simple-string sql))
356   (with-output-to-string (out)
357     (do ((len (length sql))
358          (param 0)
359          (in-str nil)
360          (pos 0 (1+ pos)))
361         ((= len pos))
362       (declare (fixnum len param pos))
363       (let ((c (schar sql pos)))
364         (declare (character c))
365         (cond
366          ((or (char= c #\") (char= c #\'))
367           (setq in-str (not in-str))
368           (write-char c out))
369          ((and (char= c #\?) (not in-str))
370           (write-char #\$ out)
371           (write-string (write-to-string (incf param)) out))
372          (t
373           (write-char c out)))))))
374
375 (defmethod database-prepare (sql-stmt types (database generic-postgresql-database) result-types field-names)
376   (let ((id (next-prepared-id)))
377     (database-execute-command
378      (format nil "PREPARE ~A (~{~A~^,~}) AS ~A"
379              id
380              (mapcar #'clsql-type->postgresql-type types)
381              (prepared-sql-to-postgresql-sql sql-stmt))
382      database)
383     (make-instance 'postgresql-stmt
384                    :id id
385                    :database database
386                    :result-types result-types
387                    :field-names field-names
388                    :bindings (make-list (length types)))))
389
390 (defmethod database-bind-parameter ((stmt postgresql-stmt) position value)
391   (setf (nth (1- position) (bindings stmt)) value))
392
393 (defun binding-to-param (binding)
394   (typecase binding
395     (string
396      (concatenate 'string "'" (sql-escape-quotes binding) "'"))
397     (t
398      binding)))
399
400 (defmethod database-run-prepared ((stmt postgresql-stmt))
401   (with-slots (database id bindings field-names result-types) stmt
402     (let ((query (format nil "EXECUTE ~A (~{~A~^,~})"
403                          id (mapcar #'binding-to-param bindings))))
404       (cond
405        ((and field-names (not (consp field-names)))
406         (multiple-value-bind (res names)
407             (database-query query database result-types field-names)
408           (setf field-names names)
409           (values res names)))
410        (field-names
411         (values (nth-value 0 (database-query query database result-types nil))
412                 field-names))
413        (t
414         (database-query query database result-types field-names))))))
415
416 ;;; Capabilities
417
418 (defmethod db-type-has-fancy-math? ((db-type (eql :postgresql)))
419   t)
420
421 (defmethod db-type-default-case ((db-type (eql :postgresql)))
422   :lower)
423
424 (defmethod db-type-has-prepared-stmt? ((db-type (eql :postgresql)))
425   t)
426
427 (defmethod db-type-has-prepared-stmt? ((db-type (eql :postgresql-socket)))
428   t)
429
430 (defmethod db-type-has-auto-increment? ((db-type (eql :postgresql)))
431   t)