sql_bridge icon indicating copy to clipboard operation
sql_bridge copied to clipboard

Use Erlang Records to construct SQL queries

Open choptastic opened this issue 12 years ago • 7 comments
trafficstars

I think the Erlang Record structure would be an interesting way to contruct SQL queries. Each record would represent a type of query (#select, #update, #delete, etc), and the attributes within each would represent the different clauses of the query:

The simple example:

#select{
    fields=[username, email],
    from=user,
    where={userid, Userid},
}

This presents all kinds of potential issues, however.

  • How to represent and or or in where clauses. I'm feeling prefix notation for that: {'or', [{email, Email}, {username, Username}]}
  • How about joins? Listing the tables in from as a list ([table1, table2, table3] then having to use the where clause to join is a bit nasty. Specifying a table as a 2 or 3-tuple as follows seems interesting:
#select{
    fields=[userid, username, email]
    from=[
        user,
        {inner, post, userid},
        {inner, thread, {thread@id, post@threadid}}
    ]
}

Would basically translate to Select userid, username, email from user inner join post using userid inner join thread on thread.id=post.threadid

Subqueries are simple here, using #select records in place of table names in queries, which can add to some interesting and convenient Erlang-based query composition without having to screw around with iolists and concatenation.

Anyway, food for thought!

choptastic avatar Sep 21 '13 19:09 choptastic

Hi,

I am working on similar project I named "eesql" (Erlang Embedded SQL) in order to represent SQL Abstract Syntax Tree as Erlanf records too.

My plan is to move it to the public domain in a pair of weeks, for the moment, with the hope of being inspiring, I paste here the record definitions as well as the pretty printers:

-record(
   select,
   {
     dup = all :: eesql:dup(),
     columns = [] :: list(eesql:column()), %% List of columns to retrieve, * as []
     from :: nonempty_list(eesql:table()), %% (FROM) Source of data, table names for the moment
     join = [] :: list(eesql:join_cond()), %% (JOIN) join_condition
     where = [] :: list(eesql:predicate()), %% (WHERE) search_condition
     group_by = [] :: list(eesql:group_by_expr()), %% (GROUP BY) group_by_expression
     having = [] :: list(eesql:predicate()), %% (HAVING) search_condition
     order_by = [] :: list(eesql:order_by_expr()) %% (ORDER BY) order_expression [ASC | DESC]
   }
  ).

-record(
   insert,
   {
     table :: eesql:table(),
     columns :: nonempty_list(eesql:column()), %% List of columns to set
     values :: nonempty_list(nonempty_list(eesql:value())) %% (VALUES) values to insert
   }
  ).

-record(
   update,
   {
     table :: eesql:table(),
     set :: nonempty_list({eesql:name(), eesql:expr()}), %% (SET) columns to update
     where = [] :: list(eesql:predicate()) %% (WHERE) search_condition
   }
  ).

-record(
   delete,
   {
     from :: eesql:table(), %% (FROM) Source of data, table names for the moment
     where = [] :: list(eesql:predicate()) %% (WHERE) search_condition
   }
  ).
-module(eesql).

-include("include/eesql.hrl").

-export_type(
   [sql_stmt/0,
    select_stmt/0, insert_stmt/0, update_stmt/0, delete_stmt/0,
    dup/0,
    name/0, column/0, table/0,
    predicate/0, join_cond/0, group_by_expr/0, order_by_expr/0,
    value/0,
    expr/0,
    binop/0]).
-export([to_sql/1]).

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% The following types represents the PG SQL Abstract Syntax Tree.

%% Any SQL value in the rows (inspired by epgsql:bind_param())
-type value() ::
        null
      | boolean()
      %% | string() %% Let's avoid confussion with arrays
      | binary()
      | integer()
      | float()
      %% | calendar:date()
      %% | calendar:time() %actualy, `Seconds' may be float()
      %% | calendar:datetime()
      %% | {calendar:time(), Days::non_neg_integer(), Months::non_neg_integer()}
      | [value()]. %array (maybe nested)

%% Any name (column name, table name, alias, ...)
-type name() :: atom().

%% Expressions for describing columns (eg. in a SELECT statement)
-type column() :: name()
                | {name(), name()}. %% AS

%% Expressions for describing "tables" (eg. FROM in a SELECT statement)
-type table() :: name()
               | {name(), name()}. % AS

%% ALL and DISTINCT
-type dup() :: all | distinct.

%% Join condition (not contemplated for the moment).
-type join_cond() :: undefined.

%% Predicates
-type predicate() ::
        {'not', predicate()}
      | {'and', [predicate()]}
      | {'or', [predicate()]}
      | {expr(), binop(), expr()}
      | {column(), like, binary()}
      | {is_null, column()}
      | {exists, select_stmt()}
      | {between, expr(), expr(), expr()}
      | {in, expr(), select_stmt()}.
      %% | some, all, ...

%% Expressions
-type expr() :: column() | value().

%% Binary operators
-type binop() :: '=' | '!=' | '<' | '>' | '<=' | '>=' | like.

%% Group by expression (not contemplated for the moment).
-type group_by_expr() :: undefined.

%% Order by expression (not contemplated for the moment).
-type order_by_expr() :: undefined.

%% A select statement
-type select_stmt() :: #select{}.

%% A insert statement
-type insert_stmt() :: #insert{}.

%% A update statement
-type update_stmt() :: #update{}.

%% A select statement
-type delete_stmt() :: #delete{}.

%% A SQL statement
-type sql_stmt() :: select_stmt()
                  | insert_stmt()
                  | update_stmt()
                  | delete_stmt().

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% @doc X = [1,2,3], [1, x, 2, x, 3] = intersperse(X, x)
-spec intersperse(list(),list()) -> list().
intersperse([], _) -> [];
intersperse([X | Xs], I) ->
  [X | lists:foldr(fun(Y, Acc) -> [I, Y | Acc] end,
                   [],
                   Xs)].

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% @doc Serializes an SQL statement.
%%
%% Usage examples:
%% ([email protected])45> io:format("~s~n",[sql:to_sql(#select{from = [users]})]).
%% SELECT ALL * FROM users ;
%% ok
%% ([email protected])47> io:format("~s~n",[sql:to_sql(#select{columns=[username, name],from = [users]})]).
%% SELECT ALL username, name FROM users ;
%% ok
%% ([email protected])48> io:format("~s~n",[sql:to_sql(#select{columns=['users.name','emails.address'],from = [users,emails], where=[{'users.id','=','emails.id'}]})]).
%% SELECT ALL users.name, emails.address FROM users, emails WHERE users.id = emails.id;
%% ok
%% ([email protected])50> io:format("~s~n",[sql:to_sql(#select{from = [users], where = [{created,'>',cw_time:now()}]})]).
%% SELECT ALL * FROM users WHERE created > 1459286860;
%% ok
%% ([email protected])11> sql:to_sql(#delete{from=preuser}).
%% ["DELETE FROM ",<<"preuser">>,[]," RETURNING *;"]
%% ok
-spec to_sql(select_stmt()
             | insert_stmt()
             | update_stmt()
             | delete_stmt())
            -> Equery :: iodata().
to_sql(#select{dup = Duplicate,
               columns = Columns,
               from = From,
               where = Where}) ->
  Dup = dup_to_sql(Duplicate),
  case Columns of
    [] ->
      Items = "*";
    _ ->
      Items = intersperse([col_to_sql(Column) || Column <- Columns], ", ")
  end,
  From_Clause = ["FROM ", intersperse([table_to_sql(Table) || Table <- From], ", ")],
  Where_Clause =
    case Where of
      [] -> "";
      [Predicate] -> ["WHERE ", pred_to_sql(Predicate)]
    end,
  Equery = intersperse(
             ["SELECT", Dup, Items, From_Clause, Where_Clause],
             " "
            ),
  [Equery, ";"];
to_sql(#insert{table = Table, columns = Columns, values = Rows}) ->
  ["INSERT INTO ", table_to_sql(Table),
   " (",
   intersperse([col_to_sql(Column) || Column <- Columns], ", "),
   ")",
   " VALUES ", intersperse([["(",
                             intersperse([expr_to_sql(Expr)
                                          || Expr <- Row],
                                         ", "),
                             ")"]
                            || Row <- Rows],
                           ", "),
   " RETURNING *;"];
to_sql(#update{table = Table,
               set = Set,
               where = Where}) ->
  Where_Clause =
    case Where of
      [] -> "";
      [Predicate] -> [" WHERE ", pred_to_sql(Predicate)]
    end,
  ["UPDATE ", table_to_sql(Table),
   " SET ",
   intersperse([[col_to_sql(Column), " = ", expr_to_sql(Expr)]
                || {Column, Expr} <- Set],
               ", "),
   Where_Clause,
   " RETURNING *;"];
to_sql(#delete{from = Table,
               where = Where}) ->
  Where_Clause =
    case Where of
      [] -> "";
      [Predicate] -> [" WHERE ", pred_to_sql(Predicate)]
    end,
  ["DELETE FROM ", table_to_sql(Table),
   Where_Clause,
   " RETURNING *;"].

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% @doc Serialize a name
-spec name_to_sql(name()) -> iodata().
name_to_sql(Name) ->
  atom_to_binary(Name, utf8).

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% @doc Serialize all and distinct
-spec dup_to_sql(dup()) -> iodata().
dup_to_sql(all) -> "ALL";
dup_to_sql(distinct) -> "DISTINCT".

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% @doc Serialize a column description
-spec col_to_sql(column()) -> iodata().
col_to_sql(Column) when is_atom(Column) ->
  name_to_sql(Column);
col_to_sql({Column, Alias}) ->
  [name_to_sql(Column), " AS ", name_to_sql(Alias)].

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% @doc Serialize a data source description
-spec table_to_sql(column()) -> iodata().
table_to_sql(Table) when is_atom(Table) ->
  name_to_sql(Table);
table_to_sql({Table, Alias}) ->
  [name_to_sql(Table), " AS ", name_to_sql(Alias)].

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% @doc Serialize a predicate to SQL.
-spec pred_to_sql(Predicate :: predicate()) -> iodata().
pred_to_sql({'not', Predicate}) ->
  ["NOT ", pred_to_sql(Predicate)];
pred_to_sql({'and', Predicates}) ->
  intersperse([pred_to_sql(Predicate) || Predicate <- Predicates],
              " AND ");
pred_to_sql({'or', Predicates}) ->
  intersperse([pred_to_sql(Predicate) || Predicate <- Predicates],
              " OR ");
pred_to_sql({is_null, Column}) ->
  [name_to_sql(Column), " IS NULL"];
pred_to_sql({Left, Bin_Op, Right}) when Bin_Op == '=';
                                        Bin_Op == '!=';
                                        Bin_Op == '<>';
                                        Bin_Op == '<';
                                        Bin_Op == '>';
                                        Bin_Op == '<=';
                                        Bin_Op == '>=' ->
  [expr_to_sql(Left), " ",
   atom_to_binary(Bin_Op, utf8),
   " ", expr_to_sql(Right)];
pred_to_sql({Column, like, Match_String}) ->
  [name_to_sql(Column), " LIKE ", "'", Match_String, "'"];
pred_to_sql({exists, Select = #select{}}) ->
  ["EXISTS ", "(", to_sql(Select), ")"];
pred_to_sql({between, Expr, Min, Max}) ->
  [expr_to_sql(Expr),
   " BETWEEN ",
   expr_to_sql(Min), " AND ", expr_to_sql(Max)];
pred_to_sql({in, Expr, Select = #select{}}) ->
  [expr_to_sql(Expr), " IN ", to_sql(Select)].


%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% @doc Serialize a expression to SQL.
-spec expr_to_sql(Expr :: expr()) -> iodata().
expr_to_sql(null) ->
  <<"NULL">>;
expr_to_sql(true) ->
  <<"TRUE">>;
expr_to_sql(false) ->
  <<"FALSE">>;
expr_to_sql(Column) when is_atom(Column) ->
  name_to_sql(Column);
expr_to_sql(Binary) when is_binary(Binary) ->
  ["'", Binary, "'"];
expr_to_sql(Integer) when is_integer(Integer) ->
  integer_to_binary(Integer);
expr_to_sql(Float) when is_float(Float) ->
  float_to_binary(Float);
expr_to_sql(Values) when is_list(Values) ->
  ["{",
   intersperse([expr_to_sql(Value) || Value <- Values],
               ", "),
   "}"].

aherranz avatar Apr 22 '16 21:04 aherranz

@choptastic, I did not realize that the issue was created almost three years ago so I am not sure if my contribution is relevant or some work is already done in other project.

aherranz avatar Apr 22 '16 21:04 aherranz

Of course. It's something I've been wanting to do but haven't done so yet. If what you have works well (please keep me posted), I may just use that as a records-to-sql compiler, or some such.

I'm very much example-driven, could you post a sample query written with your library?

Thank you for posting.

Jesse Gumm Owner, Sigma Star Systems 414.940.4866 || sigma-star.com || @jessegumm On Apr 22, 2016 4:48 PM, "Ángel Herranz" [email protected] wrote:

@choptastic https://github.com/choptastic, I did not realize that the issue was created almost three years ago so I am not sure if my contribution is relevant or some work is already done in other project.

— You are receiving this because you were mentioned. Reply to this email directly or view it on GitHub https://github.com/choptastic/sql_bridge/issues/1#issuecomment-213599801

choptastic avatar Apr 22 '16 21:04 choptastic

There are some examples in comments, let me uncomment them:

([email protected])45> io:format("~s~n",[sql:to_sql(#select{from = [users]})]).
SELECT ALL * FROM users ;
ok
([email protected])47> io:format("~s~n",[sql:to_sql(#select{columns=[username, name],from = [users]})]).
SELECT ALL username, name FROM users ;
ok
([email protected])48> io:format("~s~n",[sql:to_sql(#select{columns=['users.name','emails.address'],from = [users,emails], where=[{'users.id','=','emails.id'}]})]).
SELECT ALL users.name, emails.address FROM users, emails WHERE users.id = emails.id;
ok
([email protected])50> io:format("~s~n",[sql:to_sql(#select{from = [users], where = [{created,'>',my_time:now()}]})]).
SELECT ALL * FROM users WHERE created > 1459286860;
ok
([email protected])11> sql:to_sql(#delete{from=preuser}).
["DELETE FROM ",<<"preuser">>,[]," RETURNING *;"]

aherranz avatar Apr 22 '16 21:04 aherranz

Seems pretty nice. How does it do outer joins?

Jesse Gumm Owner, Sigma Star Systems 414.940.4866 || sigma-star.com || @jessegumm On Apr 22, 2016 4:57 PM, "Ángel Herranz" [email protected] wrote:

There are some examples in comments, let me uncomment them:

([email protected])45> io:format("~s~n",[sql:to_sql(#select{from = [users]})]).SELECT ALL * FROM users ;ok ([email protected])47> io:format("~s~n",[sql:to_sql(#select{columns=[username, name],from = [users]})]).SELECT ALL username, name FROM users ;ok ([email protected])48> io:format("~s~n",[sql:to_sql(#select{columns=['users.name','emails.address'],from = [users,emails], where=[{'users.id','=','emails.id'}]})]).SELECT ALL users.name, emails.address FROM users, emails WHERE users.id = emails.id;ok ([email protected])50> io:format("~s~n",[sql:to_sql(#select{from = [users], where = [{created,'>',my_time:now()}]})]).SELECT ALL * FROM users WHERE created > 1459286860;ok ([email protected])11> sql:to_sql(#delete{from=preuser}). ["DELETE FROM ",<<"preuser">>,[]," RETURNING *;"]

— You are receiving this because you were mentioned. Reply to this email directly or view it on GitHub https://github.com/choptastic/sql_bridge/issues/1#issuecomment-213602519

choptastic avatar Apr 22 '16 22:04 choptastic

I am afraid it is not represented yet but, according to the SQL syntax my first approach would be to define something like this:

-type join_cond() ::
    {inner_join | left_join | right_join | full_join,
     eesql:table(),
     eesql:predicate()}.
#select{columns=['users.name','emails.address'],from = [users], join = {left_join, emails, {'users.id','=','emails.id'}}]}.

But a more careful analysis is needed (eg. to support multiple joins).

aherranz avatar Apr 22 '16 22:04 aherranz

That's fair. I definitely understand. I know that it adds a rather significant level of complexity.

Jesse Gumm Owner, Sigma Star Systems 414.940.4866 || sigma-star.com || @jessegumm On Apr 22, 2016 5:52 PM, "Ángel Herranz" [email protected] wrote:

I am afraid it is not represented yet but, according to the SQL syntax my first approach would be to define something like this:

-type join_cond() :: {inner_join | left_join | right_join | full_join, eesql:table(), eesql:predicate()}.

#select{columns=['users.name','emails.address'],from = [users], join = {left_join, emails, {'users.id','=','emails.id'}}]}.

But a more careful analysis is needed (eg. to support multiple joins).

— You are receiving this because you were mentioned. Reply to this email directly or view it on GitHub https://github.com/choptastic/sql_bridge/issues/1#issuecomment-213617201

choptastic avatar Apr 22 '16 23:04 choptastic