Writing a DSL in Clojure for working with databases


Let's write a Clojure library for working with a relational database. At the same time practice in writing macros, try to use protocols and multimethods. There's no better way to learn the language, rather than something to write on it. Well... or read as written by someone else.

Why?
At the time, I needed this library for personal use. At that time there were two common solutions ClojureQL and Korma. For one reason or another they have not liked me (Yes, that is a fatal flaw), it was decided to make your bike. The bike is working perfectly, I'm happy. From the external differences — the higher the extensibility, the emphasis was on the ease of adding new operators and functions, was an important support for subqueries and inserts from the bare SQL.

The article describes the General structure of this bike, albeit in a slightly simplified form. Some feature is not present, code is usually developed in a different order, left behind many intermediate options API. But, in General, the main architectural idea is described accurately. I hope somebody will find the article useful.

So what do we write?


Create a DSL (not ORM). Unlike ORM:
— no "smart objects" — just functions and built in data structures (including records);
no "lazy" connections, magical loading of records and other "filth";
— we want to control accurately the time of occurrence of side effects — they have to happen in the expected places.

Add a few requirements:
the similarity with SQL;
— the transparency, the less "magic", the better;
— no validation query, schemes and the like — leave the conscience of the database;
automatic quoting of identifiers and arguments;
— ensuring the independence from a particular database (but without fanaticism);
— sometimes we need to write DB-zavisimy code (hranilki, triggers, etc.).

What is meant by "a little magic"? Roughly speaking, such a library should not to optimize queries, and any similar activities. Theoretically, this may allow a few (well, slightly) to unload the database, in practice, things usually get worse. It is only the DB and the programmer (sometimes), have sufficient knowledge to properly perform the desired optimization. Bad option: the developer writes the query, and then very carefully studying the logs of the application in order to find out what SQL is actually sent to the database. To double-check the logs regularly, because after a new release of the library may suddenly become "smarter"!

So, our DSL capabilities will be enough stupid transparent semantically, we work with bare SQL, but I use Clojure syntax. Something like write SQL via S-expressions taking into account the specifics of our language. Everything will look like this:

the
(select
(fields [:name :role_name])
(from :Users)
(join-inner :Roles (== :Users.role_id :Roles.id))
(where (= :Roles.name "admin"))
(order :Users.name)
(limit 100))


For this code you will need to create the query:

the
SELECT `name`, `role_name`
FROM `Users` INNER JOIN `Roles` ON `Users`.`role_id` = `Roles`.`id`
WHERE `Roles`.`name` = ?
ORDER BY `Users`.`name`
LIMIT ?


All the names we escapes using the reverse quotes. On good it is necessary to use double quotes (and even better to consider the type of DB), but in the interest of readability, in examples we will use MySQL-style. Constants are replaced with ? — jdbc driver of the specific database itself to do the transfer and screening settings.

Direct execution of SELECT queries we will have to do separate functions: fetch-all, fetch-one, with-fetch. They all take input from the parameters of connection to DB and query that we want to accomplish:

the
(def db
{:classname "com.mysql.jdbc.Driver"
:the Subprotocol "mysql"
:user "test"
:password "test"
:subname "//localhost/test"})

; pull out exactly 1 record from the Users table

(select
(from :Users)
(where (== :id 123))))

; all records from a table as a vector
(fetch-all db
(select (from :Users)))

(with-fetch db [rows (select (from :Users))]
; here we work with *lazy* sequence of `rows`
(doseq [r rows]
(print ">" r)))


Generated SQL


To begin, decide how we will store the queries inside of our library.

the
(def raw-select
['SELECT :name :role_name
['FROM :Users ['JOIN,: Roles ['ON :Users.role_id :Roles_id]]]
['WHERE ['LIKE :Users.name "And%"]
['LIMIT 100]]])


In this example, we have a tree of vectors, symbols and keys. Symbols will be denoted by the SQL keyword, with keys — names of tables and fields, values (strings, numbers, dates, etc.) leave "as is". The compiled query will be presented in the form of a pair: SQL code (string) and a vector of arguments. Set up a particular type:

the
(defrecord Sql [sql args])

;; queries after compilation would look like this:
(Sql. "SELECT * FROM `Users` WHERE `id` = ?" [123])


This lower performance in our library. Implement the transformation from one representation to another representation. This requires a universal method to convert any entity in the Sql. Perfect protocols:

the
(defprotocol SqlLike
(as-sql [this]))

; auxiliary function
(defn quote-name
[s]
(let [x (name s)]
(if (=*x)
x
(str \` x \`))))

(extend-protocol SqlLike

; for any `x` (= (as-sql (as-sql x)) (as-sql x))
Sql
(as-sql [this] this)

; by default we consider all objects with parameters for queries
Object
(as-sql [this] (. Sql. "?" [this]))

; escapes table names and columns
clojure.lang.Keyword
(as-sql [this] (. Sql. (quote-name this) nil))

; symbols denote SQL keywords
clojure.lang.Symbol
(as-sql [this] (. Sql. (name this) nil))

; nil for a special keyword
nil
(as-sql [this] (. Sql. "NULL" nil)))


Instead of protocols one could use a set of ifs, or even pattern matching. But the protocols is a plus: library users can themselves implement a specific transformation to any types. For example, someone may want to automagically retrieve the values from links:

the
(extend-protocol SqlLike
clojure.lang.ARef
(as-sql [this] (as-sql @this)))

; now, instead of constants you can pass
; references (ref, agent, var, atom)
(def a (atom 123))
(assert
(=
(as-sql a)
(as-sql @a)
(Sql. "?" [123])))


We implement our Protocol for vectors and lists:

the
; helper function combines 2 of the sql object in one
(defn - join-sqls
([] (Sql. "" nil))
([^Sql s1 ^s2 Sql]
(Sql. (str (.sql s1) "" (.sql s2)) (concat (.args s1) (.args s2)))))

(extend-protocol SqlLike
clojure.lang.Sequential
(as-sql [this]
(reduce join-sqls (map as-sql this))))


With the efficiency of the algorithm here is not very good, you can write code quickly. But now:

the
(as-sql ['SELECT '* ['FROM :Users] ['WHERE :id '= 1 'AND :name 'IS 'NOT nil]])
; => #user.Sql{:sql "SELECT * FROM `Users` WHERE `id` = ? AND `name` IS NOT NULL" :args (1)}


Great! Let's define a couple of functions...

the
(require '[clojure.java.jdbc :as jdbc])

(defn - to-sql-params
[relation]
(let [{s :sql p :args} (as-sql relation)]
(vec (cons s p))))

(defn fetch-all
[db relation]
(jdbc/query
db
(to-sql-params relation)
:result-set-fn vec))

; similarly, implement `fetch-one`


To work directly with JDBC otopitelno, so cunning — all the dirty work for us makes clojure.java.jdbc. Finally, we already have perfectly acceptable results, even the library can be used:

the
; settings DB connection
(def db
{:classname "com.mysql.jdbc.Driver"
:the Subprotocol "mysql"
:user "test"
:password "test"
:subname "//localhost/test"})

; do a DB query
(fetch-all
db
(as-sql '[SELECT * FROM users ORDER BY name]))


Oh yeah, we forgot about with-fetch. We sell:

the
(defmacro with-fetch
[db [v rel :as vr] &body]
`(let [params# (to-sql-params ~rel)
rsf# (fn [~v] ~@body)]
(jdbc/query
~db
params#
:result-set-fn rsf# ; all RS are passing to the function rsf#
:row-fn identity))) ; rows are not processed


Stackable iteratively queries


The selected view has serious disadvantages — queries are difficult to build iterative. Suppose we have a tree for the query SELECT FROM `Users` LIMIT 10, and we want to add a WHERE. In General, for such will have to parse the SQL syntax (parse AST tree), which, in truth, I'd love to avoid.

Why do we "iterative build"? Well, first, it is a useful option in itself. When writing a program we often do not know beforehand which queries will execute. Example: dynamically build arbitrary conditions of sections WHERE and ORDER BY in the admin area.
But more importantly, it is a good practice when writing programs in Clojure. We divide the work into many small pieces, iteratively doing his job. Each brick (pure function) receives data and returns "doctored" results. The bricks are easy to test and develop. But in the end the pieces are easily assembled together.

Requests submitted in the form of a hash table. Example:

the
(def some-query-example
{
; show "alias of the table name of the table"
:tables {r:Roles, :u :Users},

; list [alias table, type join, the expression for the partition ON]
; the first element -- [source table, nil, nil]
; use list, because we, the order joins s
:joins
[[:u nil nil]
[:r :inner ['= :Users.role_id :Roles.id]]]

; ast-expression tree
:where [:= :u.name "Ivan"],

; display "alias column - name column"
fields {:name,: name, :role_name :role_name},

; just numbers
:offset 1000,
:limit 100,

; order, group, having, etc...
})


For partitions WHERE, ORDER BY etc. we store the AST is an expression tree — it's easier. For a list of the tables and fields we stored the dictionaries, the keys are alias names, values, expressions or table names. In this structure implement required functions:

the
; `limit` & `offset` trivial
(defn limit
[relation, v]
(assoc relation :limit v))

; ** will do such implementation
(defn fields
[query fd]
(assoc query :fields fd))

(defn where
[query wh]
(assoc query :where wh))

; helper function
(defn join*
[{:keys [tables joins] :as q} the type alias table on]
(let [a (or alias table)]
(assoc
q
:tables (assoc tables a table)
:joins (conj (or joins []) [a type on]))))

(defn from
([q table] (join* q nil table table nil))
([q table alias] (join* q nil table alias nil)))

(defn join-cross
([q table] (join* q :cross table table nil))
([q table alias] (join* q :cross table alias nil)))

;; for other joins (left, right, full) of the desired macro is omitted


So we have a lot of functions (where, fields, from, join, limit and others), able to "correct" requests. The starting point is an empty query.

the
(def empty-select {})


We can now write:

the
(-> empty-select
(fields [:name :role_name])
(from :Users)
(limit 100))


This code uses the macro ->, which unfolds in something like:

the
(limit
(from
(fields
empty-select
[:name,: role_name])
:Users)
100)


Beauty define the macro select, which behaves like ->:

the
(defmacro select
[&body]
`(-> empty-select ~@body))


Left to teach our library to convert one representation to another.

the
; an empty SQL because nil is converted to "NULL"
(def NONE (Sql. "" nil))

most functions are implemented is trivial
(defn render-limit [s]
(if-let [l (:limit s)]
['L LIMIT]
NONE))

(defn render-fields [s] '*) ; but will return all columns

; these functions implement later
(defn render-where [s] is NONE)
(defn render-order [s], NONE)
(defn render-expression [s], NONE)

; and these are beyond the scope of this article
(defn render-group [s], NONE)
(defn render-having [s], NONE)
(defn render-offset [s], NONE)

; auxiliary function
(defn render-table
[[table alias]]
(if (= alias table)
; if the alias and the table coincide, then do not print 'AS'
table
[table 'AS alias]))

(defn render-join-type
[jt]
(get
{nil (symbol"")
:cross '[CROSS JOIN],
:left '[LEFT OUTER JOIN],
:right '[RIGHT OUTER JOIN],
the :inner '[INNER JOIN],
full '[FULL JOIN],
} jt jt))

; some functions are quite complex
(defn render-from
[{:keys [tables joins]}]
; section FROM may not be!
(if (not (empty? joins))
['FROM
; the first join
(let [[a jn] (first joins)
t (tables a)]
; the first join should be using `(from ..)`
(assert (nil? jn))
(render-table [a t]))
; iterate through remaining joiny
(for [[a jn c] (rest joins)
:let [t (tables a)]]
[(render-join-type jn) ; bundle JOIN XX or comma
(render-table [a t]) ; the table name and alias
(if c ['ON (render-expression c)] NONE) ; section 'ON'
])]
NONE))

(defn render-select
[select]
['SELECT
(mapv
#(% select)
[render-fields
render-from
render-where
render-group
render-having
render-order
render limit
render-offset])])


Library users might not know about the Protocol SqlLike and as-sql. Good practice. For comparison, in Java interfaces often define the API of a module/library. Clojure protocols are typically created for the low-level operations of a base, which is already running a set of helper functions. And now these helper-provide a public API of the library. Try to generate a simple query:
the
(fetch-all db
(render-select
(select
(from :Users)
(limit 10)))


Ready! True to call render-select manually is tiresome. Correct:

the
(declare render-select)

; all fields do not have to declare
; record the keys that are not listed in the type Declaration
(defrecord Select [fields order tables where joins offet limit]
SqlLike
(as-sql [this] (as-sql (render-select this))))

(def empty-select (map->Select {}))


Now, when you run (as-sql (select ...)) will be automatically called and render-select:

the
(fetch-all db
(select
(from :Users)
(limit 10)))

; if we just want to see SQL query
(as-sql
(select
(from :Table)
(limit 10)))

; or even
(select
(from :Table)
(limit 10)
(as-sql))


Support


Let's write the function where. We want to be able to use it like this:

the
(select
(from :Table)
(where (and (> :x 1) (==y z))))


It is clearly not possible to compute (> :x 1) when you call where — the desired macro. The constructed expression will store in the form AST: nodes are operators, leaves are constants and fields. For starters, let's write a helper function where*:

the
; bonded 2 expressions together with AND
(defn - conj-expression
[e1 e2]
(cond
(not (seq e1)) e2
(= 'and (first e1)) (conj (vec e1) e2)
:else (vector 'and e1 e2)))

(conj-expression '[> 1 2] '[< "a" "b"])
; => '[and [>1 2] [< "a" "b"]])

(conj-expression '[& [> 1 [+ 2 3]] [= :x :y]] '[<> "a" "b"])
; => '[& [> 1 [+ 2 3]] [= :x :y] [<> "a" "b"]]

(defn where*
[query expr]
(assoc query :where (conj-expression (:where query) expr)))


Now came the time for the render-where:

the
; vzaimodeystviye functions
(declare render-operator)
(declare render-expression)

; a function or operator?
(defn - function-symbol? [s]
(re-matches #"\w+" (name s)))

; formatted function call or operator
(defn render-operator
[op &args]
(let [ra (map render-expression args)
lb (symbol "(")
rb (symbol ")")]
(if (function-symbol? op)
function (count, max, ...)
[op lb (interpose (symbol"") ra) rb]
; the operator (+, *, ...)
[lb (interpose op (map render-expression args)) rb])))

(defn render-expression
[etree]
(if (and (sequential? etree) (symbol? (first etree)))
(apply render-operator etree)
etree))

(defn render-where
[{:keys [where]}]
(if where
['WHERE (render-expression where)]
NONE))


Great, now we can write simple expressions:

the
(select
(from :Users)
(where* ['= :id 1])
(as-sql))
; => (Sql. "SELECT * FROM `Users` WHERE ( `id` = ? )" [1])


It turned ugly, fix this simple macro:

the
(defn prepare-expression
[e]
(if (seq? e)
`(vector
(quote ~(first e))
~@(map prepare-expression (rest e)))
e))

(defmacro where
[body q]
`(where* ~q ~(prepare-expression body)))


Model all sequences (lists) on vector. Other values left as is. We missed an important point — some operators in Clojure and SQL have different names, such as <&gt and not=. The philosophical question, what is the best option to use. On the one hand, we decided to leave the library as "stupid" on the other — much prefer "native" for Clojure functions. Let's solve both versions:

the
(defn - canonize-operator-symbol
[op]
(get '{not= <>===} op op))

; rewrite the function
(defn prepare-expression
[e]
(if (seq? e)
`(vector
(quote ~(canonize-operator-symbol (first e)))
~@(map prepare-expression (rest e)))
e))


Well, when you use the macro where you can write both, but in our submission there will be only one. Something that is necessary. We have a small favor — do not work joini.

the
(defmacro join-left
([q table cond] `(let [t# ~table] (join-left ~q t# t# ~cond)))
([cond q table alias] (join* ~q :cross ~table ~alias ~(prepare-expression cond))))
; similarly for other dainow, changing only the key...


Write several similar macros — base case:

the
; we import a very useful macro `do-template`
(use 'clojure.template)

; this code takes place in the 5 listings of the macros
(do-template
[join-name join-key] ; the parameters for the template

; the template itself
(defmacro join-name
([relation alias table cond]
`(join* ~relation ~join-key ~alias ~table ~(prepare-expression cond)))
([relation table cond]
`(let [table# ~table]
(join* ~relation ~join-key nil table# ~(prepare-expression cond)))))

; value for parameters
join-inner :inner,
join :inner,
join-right :right,
join-left :left,
join-full :full)


More opportunities


Until we are able to perform only the simplest queries. Do support expressions in the enumeration of the columns.
the
; apply `f` to the values `m` (not keys)
(defn - map-vals
[f m]
(into (if (map? m) (empty m) {}) (for [[k v] m] [k (f v)])))

; counter for generating unique IDs
(def surrogate-alias-counter (atom 0))

; generated IDs :__00001234
(defn generate-surrogate-alias
[]
(let [k (swap! surrogate-alias-counter #(- >% inc (mod 1000000)))]
(keyword (format "__%08d" k))))

; convert an arbitrary expression in "alias"
(defn as-alias
[n]
(cond
(keyword? n) n ; the name of the column/table left as is
(string? n) (keyword n) ; similarly for rows
:else (generate-surrogate-alias))) ; expressions generated surrogate alias

; the list of columns to query-Glossary "alias - expression", or column vector
(defn - prepare-fields
[fs]
(if (map? fs)
(map-vals prepare-expression fs)
(into {} (map (juxt as-alias prepare-expression) fs))))

(defn fields*
[query fd]
(assoc query :fields fd))

(defmacro fields
[query fd]
`(fields* ~query ~(prepare-fields fd)))

(defn render-field
[[alias nm]]
(if (= alias nm)
nm ; just the column name
[(render-expression nm) 'AS alias]))

(defn render-fields
[{:keys [fields]}]
(if (or (nil? fields) (= fields :*))
'*
(interpose (symbol"") (map render-field fields))))


Well. Now you can write this:

the
(select
(fields {n :name, a :age}) ; aliases for the columns
(from :users))

; or so
(select
(fields {:cnt (count :*), :max-age (max-age)})
(from :users))

; or even
(select
(fields [(count :*)]) (from :users))


Added sorting. Is the usual procedure: create a function called order* and a macro order implement render-order:

the
(defn order*
([relation column] (order* relation column nil))
([{order :order :as relation} column dir]
(assoc
relation
order (cons [column dir] order))))

(defmacro order
([relation column]
`(order* ~relation
~(prepare-expression column)))
([relation column dir]
`(order* ~relation
~(prepare-expression column) ~dir)))

(defn render-order
[{order :order}]
(let [f (fn [[c d]]
[(render-expression c)
(get {nil [] :asc 'ASC :desc 'DESC} d d)])]
(if order
['[ORDER BY] (interpose (symbol"") (map f order))]
[])))


Have the opportunity to sort the selection in our queries, including arbitrary expression:

the
(select
(from :User)
(order (+ :message_cnt :post_cnt)))


The same way you can add support groups, subqueries and the like... so, for example, may look the implementation for the UNION ALL:

the
; auxiliary function-render
(defn render-union-all
[{ss :selects}]
(interpose ['UNION 'ALL] (map render-select ss)))

; separate type, just keep a list of all selectors
(defrecord UnionAll [selects]
SqlLike
(as-sql [this] (as-sql (render-union-all this))))

; here we *do not* need a pair of function-macro
(defn union-all
[&ss]
(->UnionAll ss))

;; use ...
(as-sql
(union-all
(select (from :Users) (fields [:email]))
(select (from :Accounts) (fields [:email]))))


supports multiple database dialects


Add support for multiple databases. The idea is simple: a number of functions in our library can change its behavior depending on the kind of database we use. Organize a tree hierarchy of dialects:

the
; the most common dialect
(def ^:const default-dialect ::sql92)

; here we will store the dialect for the current database connection
(def ^:dynamic *dialect* nil)

; this hierarchy of dialects
(def dialects-hierarchy (make-hierarchy))

; function to register the dialects easier
(defn register-dialect
([parent dialect]
(alter-var-root #'dialects-hierarchy derive dialect parent))
; default dialects are inherited from the ::sql92
([dialect]
(register-dialect dialect default-dialect)))

; example
(register-dialect ::pgsql)
(register-dialect ::pgsql92 ::pgsql)

; postgresql allows you to define your own operators
you can create ad-hoc dialect for a specific database 
(register-dialect ::my-custom-db-with-extra-functions ::pgsql92)


Now define a small macro defndialect:

the
; just return the current dialect
; ignore all parameters
(defn current-dialect
[&_]
(or *dialect* default-dialect))

; macro to define "normal" functions
(defmacro defndialect
[name &args-and-body]
`(do
; define a multimethod
(defmulti ~name current-dialect :hierarchy #'dialects-hierarchy)
; implementation for the dialect `sql92`
(defmethod ~name default-dialect ~@args-and-body)))


Now you need not to forget to bring the value of the dialect in the variable *dialect*:

the
(defmacro with-db-dialect
[db &body]
; the dialect has to be done in the connection settings to the database
`(binding [*dialect* (:dialect ~db)]
~@body))


Great. The last step: rewriting all the function definitions to render, replacing defn to defndialect. Body functions should not be changed. And now we have the opportunity to generate different SQL depending on the database:
the
(defndialect quote-name
[s]
(let [x (name s)]
(if (=*x) x (str "\"" x "\""))))

; MySQL uses backticks
(defmethod quote-name ::mysql
[s]
(let [x (name s)]
(if (=*x) x (str "`" x "`"))))


Finally, notice that it is not necessary to call with-db-dialect manually, we can rewrite our function fetch-*:

the
(defn fetch-all
[db relation]
(jdbc/query
db
(with-db-dialect db (to-sql-params relation))
:result-set-fn vec))
; similarly rewrite the other functions fetch-*


RAW queries


Sometimes you need to use very specific queries are easier to write to a string, bypassing the DSL. Not a problem:

the
(require '[clojure.string :as s])

(defn format-sql
[raw-sql-args]
(let [; find all the placeholders of the form :x
al (map
(comp keyword second)
(re-seq #":([\w.-]+)" raw-sql))
; replace all placeholders with "?"
pq (s/replace raw sql #":[\w.-]+" "?")]
(->Sql pq (map args, al))))

; use...
(fetch-all db
(format-sql
"SELECT * FROM Users WHERE role = :rl AND age < :age"
{:rl "admin" :age 18}))


By the way formed this way queries can be used in UNION ALL, which we have implemented just above. Unfortunately, incremental change will not work — it would have to parse a string with SQL code. Workaround — subquery:

the
(defn users-by-role
[r]
(format-sql "SELECT * FROM Users WHERE role = :r" {:r r}))

; it is impossible
(->
(users-by-role "ADMIN")
(order :name)
(as-sql))

; here is a way..?
(select
(from :x (users-by-role "ADMIN"))
(order :name)
(as-sql))
; => #user.Sql{:sql "SELECT * FROM SELECT * FROM Users WHERE role = ? AS `x` ORDER BY `name`", :args ("ADMIN")}


Oops, the SQL generated lacks the round brackets. Fixed the mistake, here is the corrected version of render in table:

the
(defn render-table
[[table alias]]
(if (= alias table)
; if the alias and the table coincide, then do not print 'AS'
table
; if the table is sql adding parenthesis
(if (or (instance? Sql table) (instance? Select table))
[(symbol "(") table (symbol ")") 'AS alias]
[table 'AS alias])))

; now works as expected
(select
(from :x (users-by-role "ADMIN"))
(order :name)
(as-sql))


connection to database


Of course, open each time a new connection inside the function fetch-* is not an option. Again the macro:

the
(defn with-connection*
[db body-fn]
(assert (nil? (jdbc/db-find-connection db)))
(with-open [conn (jdbc/get-connection db)]
(body-fn (jdbc/add-connection db conn))))

(defmacro with-connection
[binding &body]
`(with-connection* ~(second binding) (fn [~(first binding)] ~@body)))


Here we verify that an open connection is still present, open a new and "attach" to the dictionary with the database settings. You need to use:

the
(def db {...})

(with-connection [c db]
; parameter `c` stores the options from `db` + open connection
(fetch-all c in (select (from :B)))
; ...
(fetch-all c in (select (from :A))))


Similarly, you can add transaction support.

Small bonus - more speed with elements of abnormal programming
Obviously, the library introduces additional costs: it is necessary to form the original query in the high-level representation, transform it using the render-select, the result is pass through the as-sql. In addition, many of the features we have implemented through the defndialect, which also negatively affects performance. It is especially insulting to repeat such operation for the simplest of queries like "get the record id". In truth, the overhead is quite negligible compared to the time the DB... But if you really want, you can add even more speed. So our goal:

the
; a special macro, which compiles the SQL only once
(defselect get-user-by-id [x]
(from :Users)
(where (= :id x))))

; or so, especially convenient to make legacy queries
(defselect get-user-by-id [x]
"SELECT * FROM `Users` WHERE `id` = :x")

; use
(fetch-one db (get-user-by-id 123))


There's a problem — dialects. We can't calculate the query at the compilation stage of the program (in the body of the macro), because they do not know what dialect will be active during execution. You can predicast request for all available dialects, but they can be added dynamically (in runtime) — probably we miss need you, bad.

An alternative solution is to cache the computed queries. I.e., each defselect keeps a cache dictionary "dialect — SqlLike object". Thus, for each dialect, we perform compilation (potentially expensive for complex queries) once for each dialect. After extracting record Sql we just need to substitute the arguments for the :args not changing sql.
the
; query lazy - just stored the function for the calculation SQL code
(defrecord LazySelect [content-fn]
SqlLike
(as-sql [this] (content-fn)))

; ready-made query as a string
(defrecord RenderedSelect [content]
SqlLike
(as-sql [this] (as-sql content)))

; accessory type
(defrecord SurrogatedArg [symbol]
SqlLike
(as-sql [this] (. Sql. symbol "?")))

(defn emit-precompiled-select
[name args body]

(let [; here, args is the names of function parameters
sargs (map ->SurrogatedArg args)
; display a surrogate arguments to symbols
sargs-args (into {} (map vector sargs args))]

`(let [sqls# (atom {}) ; here is stored vychislenie requests

; the "original" function
original# (fn ~name ~args (as-sql (select ~@body)))

; calculated the original function,
; but with surrogate parameters
compile# (fn [] (apply original# (list ~@sargs)))]

(defn ~name ~args
(->LazySelect
(fn []
(let [; take the dialect, check whether
; the calculated request
dialect# (current-dialect)
cached-sql# (get @sqls# dialect#)

if it isn't calculated new
sql# (if cached-sql#
cached-sql#

sync simplified
; the query may compile multiple times
; but we are not terribly ignored
(let [new-sql# (compile#)]
(swap! sqls# assoc dialect# new-sql#)
new-sql#))

; extract the vector with surrogate parameters
args# (:sql args#)]

; surrogate  model  parameters for real
(assoc sql# :args (replace ~sargs-args args#)))))))))

; the query is specified as a string
(defn emit-raw-select
[name args sql]
; calculated the parameter list
(let [args-map (into {} (map (juxt keyword identity) args))]
; define a function that generates RenderedSelect
`(defn ~name ~args
(->RenderedSelect
(format-sql ~sql ~args-map)))))

(defmacro defselect
[name args &body]
(if (and (== 1 (count body)) (string? (first body)))
(emit-raw-select name args (first body))
(emit-precompiled-select name args body)))



In closing


The article does not address the implementation of the functions to modify the database: insert, delete, update records. No tools for working with DDL, transactions and much more. But the new functionality to add quite easily, often without modifying the existing code. The proposed method is one of the many, not without nedostatok, but it has the right to life. Finally leave a link to code-full version, in explanation of which was the article was written.
Article based on information from habrahabr.ru

Комментарии

Популярные сообщения из этого блога

Fresh hay from the cow, or 3000 icons submitted!

Knowledge base. Part 2. Freebase: make requests to the Google Knowledge Graph

Group edit the resources (documents) using MIGXDB