• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

processone / ejabberd / 1296

19 Jan 2026 11:25AM UTC coverage: 33.562% (+0.09%) from 33.468%
1296

push

github

badlop
mod_conversejs: Cosmetic change: sort paths alphabetically

0 of 4 new or added lines in 1 file covered. (0.0%)

11245 existing lines in 174 files now uncovered.

15580 of 46421 relevant lines covered (33.56%)

1074.56 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

45.09
/src/ejabberd_sql.erl
1
%%%----------------------------------------------------------------------
2
%%% File    : ejabberd_sql.erl
3
%%% Author  : Alexey Shchepin <alexey@process-one.net>
4
%%% Purpose : Serve SQL connection
5
%%% Created :  8 Dec 2004 by Alexey Shchepin <alexey@process-one.net>
6
%%%
7
%%%
8
%%% ejabberd, Copyright (C) 2002-2026   ProcessOne
9
%%%
10
%%% This program is free software; you can redistribute it and/or
11
%%% modify it under the terms of the GNU General Public License as
12
%%% published by the Free Software Foundation; either version 2 of the
13
%%% License, or (at your option) any later version.
14
%%%
15
%%% This program is distributed in the hope that it will be useful,
16
%%% but WITHOUT ANY WARRANTY; without even the implied warranty of
17
%%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
18
%%% General Public License for more details.
19
%%%
20
%%% You should have received a copy of the GNU General Public License along
21
%%% with this program; if not, write to the Free Software Foundation, Inc.,
22
%%% 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
23
%%%
24
%%%----------------------------------------------------------------------
25

26
-module(ejabberd_sql).
27

28
-author('alexey@process-one.net').
29

30
-behaviour(p1_fsm).
31

32
%% External exports
33
-export([start_link/2,
34
         sql_query/2,
35
         sql_query/3,
36
         sql_query_t/1,
37
         sql_transaction/2,
38
         sql_transaction/4,
39
         sql_bloc/2,
40
         sql_bloc/3,
41
         abort/1,
42
         restart/1,
43
         use_new_schema/0,
44
         use_multihost_schema/0,
45
         sql_query_to_iolist/1,
46
         sql_query_to_iolist/2,
47
         escape/1,
48
         standard_escape/1,
49
         escape_like/1,
50
         escape_like_arg/1,
51
         escape_like_arg_circumflex/1,
52
         to_string_literal/2,
53
         to_string_literal_t/1,
54
         to_bool/1,
55
         to_timestamp/2,
56
         sqlite_db/1,
57
         sqlite_file/1,
58
         encode_term/1,
59
         decode_term/1,
60
         odbcinst_config/0,
61
         init_mssql/1,
62
         keep_alive/2,
63
         to_list/2,
64
         to_array/2,
65
         parse_mysql_version/2]).
66

67
%% gen_fsm callbacks
68
-export([init/1, handle_event/3, handle_sync_event/4,
69
         handle_info/3, terminate/3, print_state/1,
70
         code_change/4]).
71

72
-export([connecting/2, connecting/3,
73
         session_established/2, session_established/3]).
74

75
-deprecated({use_new_schema, 0}).
76

77
-ifdef(OTP_BELOW_28).
78
-ifdef(OTP_BELOW_26).
79
%% OTP 25 or lower
80
-type(odbc_connection_reference() ::  pid()).
81
-type(db_ref_pid() :: pid()).
82
-else.
83
%% OTP 26 or 27
84
-type(odbc_connection_reference() ::  odbc:connection_reference()).
85
-type(db_ref_pid() :: pid()).
86
-endif.
87
-else.
88
%% OTP 28 or higher
89
-nominal(odbc_connection_reference() :: odbc:connection_reference()).
90
-nominal(db_ref_pid() :: pid()).
91
-dialyzer([no_opaque_union]).
92
-endif.
93

94
-include("logger.hrl").
95
-include("ejabberd_sql_pt.hrl").
96

97

98
-record(state,
99
        {db_ref               :: undefined | db_ref_pid() | odbc_connection_reference(),
100
         db_type = odbc       :: pgsql | mysql | sqlite | odbc | mssql,
101
         db_version           :: undefined | non_neg_integer() | {non_neg_integer(), atom(), non_neg_integer()},
102
         reconnect_count = 0  :: non_neg_integer(),
103
         host                 :: binary(),
104
         pending_requests     :: p1_queue:queue(),
105
         overload_reported    :: undefined | integer(),
106
         timeout              :: pos_integer()}).
107

108
-define(STATE_KEY, ejabberd_sql_state).
109
-define(NESTING_KEY, ejabberd_sql_nesting_level).
110
-define(TOP_LEVEL_TXN, 0).
111
-define(MAX_TRANSACTION_RESTARTS, 10).
112
-define(KEEPALIVE_QUERY, [<<"SELECT 1;">>]).
113
-define(PREPARE_KEY, ejabberd_sql_prepare).
114
%%-define(DBGFSM, true).
115
-ifdef(DBGFSM).
116
-define(FSMOPTS, [{debug, [trace]}]).
117
-else.
118
-define(FSMOPTS, []).
119
-endif.
120

121
-type state() :: #state{}.
122
-type sql_query_simple(T) :: [sql_query(T) | binary()] | binary() |
123
                             #sql_query{} |
124
                             fun(() -> T) | fun((atom(), _) -> T).
125
-type sql_query(T) :: sql_query_simple(T) |
126
                      [{atom() | {atom(), any()}, sql_query_simple(T)}].
127
-type sql_query_result(T) :: {updated, non_neg_integer()} |
128
                             {error, binary() | atom()} |
129
                             {selected, [binary()], [[binary()]]} |
130
                             {selected, [any()]} |
131
                             T.
132

133
%%%----------------------------------------------------------------------
134
%%% API
135
%%%----------------------------------------------------------------------
136
-spec start_link(binary(), pos_integer()) -> {ok, pid()} | {error, term()}.
137
start_link(Host, I) ->
UNCOV
138
    Proc = binary_to_atom(get_worker_name(Host, I), utf8),
6✔
UNCOV
139
    p1_fsm:start_link({local, Proc}, ?MODULE, [Host],
6✔
140
                      fsm_limit_opts() ++ ?FSMOPTS).
141

142
-spec sql_query(binary(), sql_query(T), pos_integer()) -> sql_query_result(T).
143
sql_query(Host, Query, Timeout) ->
UNCOV
144
    sql_call(Host, {sql_query, Query}, Timeout).
33,537✔
145

146
-spec sql_query(binary(), sql_query(T)) -> sql_query_result(T).
147
sql_query(Host, Query) ->
UNCOV
148
    sql_query(Host, Query, query_timeout(Host)).
33,537✔
149

150
%% SQL transaction based on a list of queries
151
%% This function automatically
152
-spec sql_transaction(binary(), [sql_query(T)] | fun(() -> T), pos_integer(), pos_integer()) ->
153
                             {atomic, T} |
154
                             {aborted, any()}.
155
sql_transaction(Host, Queries, Timeout, Restarts)
156
    when is_list(Queries) ->
UNCOV
157
    F = fun () ->
10✔
UNCOV
158
                lists:foreach(fun (Query) -> sql_query_t(Query) end,
10✔
159
                              Queries)
160
        end,
UNCOV
161
    sql_transaction(Host, F, Timeout, Restarts);
10✔
162
%% SQL transaction, based on a erlang anonymous function (F = fun)
163
sql_transaction(Host, F, Timeout, Restarts) when is_function(F) ->
UNCOV
164
    case sql_call(Host, {sql_transaction, F, Restarts}, Timeout) of
5,516✔
UNCOV
165
        {atomic, _} = Ret -> Ret;
5,516✔
166
        {aborted, _} = Ret -> Ret;
×
167
        Err -> {aborted, Err}
×
168
    end.
169

170
-spec sql_transaction(binary(), [sql_query(T)] | fun(() -> T)) ->
171
    {atomic, T} |
172
    {aborted, any()}.
173
sql_transaction(Host, Queries) ->
UNCOV
174
    sql_transaction(Host, Queries, query_timeout(Host), ?MAX_TRANSACTION_RESTARTS).
5,516✔
175

176
%% SQL bloc, based on a erlang anonymous function (F = fun)
177
sql_bloc(Host, F, Timeout) ->
UNCOV
178
    sql_call(Host, {sql_bloc, F}, Timeout).
5,364✔
179

180
sql_bloc(Host, F) ->
UNCOV
181
    sql_bloc(Host, F, query_timeout(Host)).
5,364✔
182

183
sql_call(Host, Msg, Timeout) ->
UNCOV
184
    case get(?STATE_KEY) of
44,417✔
185
        undefined ->
UNCOV
186
            sync_send_event(Host,
44,333✔
187
                            {sql_cmd, Msg, current_time() + Timeout},
188
                            Timeout);
189
        _State ->
UNCOV
190
            nested_op(Msg)
84✔
191
    end.
192

193
keep_alive(Host, Proc) ->
194
    Timeout = query_timeout(Host),
×
195
    case sync_send_event(
×
196
           Proc,
197
           {sql_cmd, {sql_query, ?KEEPALIVE_QUERY}, current_time() + Timeout},
198
           Timeout) of
199
        {selected,_,[[<<"1">>]]} ->
200
            ok;
×
201
        Err ->
202
            ?ERROR_MSG("Keep alive query failed, closing connection: ~p", [Err]),
×
203
            sync_send_event(Proc, force_timeout, Timeout)
×
204
    end.
205

206
sync_send_event(Host, Msg, Timeout) when is_binary(Host) ->
UNCOV
207
    case ejabberd_sql_sup:start(Host) of
44,333✔
208
        ok ->
UNCOV
209
            Proc = get_worker(Host),
44,333✔
UNCOV
210
            sync_send_event(Proc, Msg, Timeout);
44,333✔
211
        {error, _} = Err ->
212
            Err
×
213
    end;
214
sync_send_event(Proc, Msg, Timeout) ->
UNCOV
215
    try p1_fsm:sync_send_event(Proc, Msg, Timeout)
44,333✔
216
    catch _:{Reason, {p1_fsm, _, _}} ->
217
            {error, Reason}
×
218
    end.
219

220
-spec sql_query_t(sql_query(T)) -> sql_query_result(T).
221
%% This function is intended to be used from inside an sql_transaction:
222
sql_query_t(Query) ->
UNCOV
223
    QRes = sql_query_internal(Query),
40,277✔
UNCOV
224
    case QRes of
40,277✔
225
      {error, Reason} -> restart(Reason);
×
226
      Rs when is_list(Rs) ->
227
          case lists:keysearch(error, 1, Rs) of
×
228
            {value, {error, Reason}} -> restart(Reason);
×
229
            _ -> QRes
×
230
          end;
UNCOV
231
      _ -> QRes
40,277✔
232
    end.
233

234
abort(Reason) ->
235
    exit(Reason).
×
236

237
restart(Reason) ->
238
    throw({aborted, Reason}).
×
239

240
-spec escape_char(char()) -> binary().
241
escape_char($\000) -> <<"\\0">>;
×
242
escape_char($\n) -> <<"\\n">>;
×
243
escape_char($\t) -> <<"\\t">>;
×
244
escape_char($\b) -> <<"\\b">>;
×
245
escape_char($\r) -> <<"\\r">>;
×
UNCOV
246
escape_char($') -> <<"''">>;
32✔
UNCOV
247
escape_char($") -> <<"\\\"">>;
32✔
UNCOV
248
escape_char($\\) -> <<"\\\\">>;
880✔
UNCOV
249
escape_char(C) -> <<C>>.
41,217✔
250

251
-spec escape(binary()) -> binary().
252
escape(S) ->
UNCOV
253
        <<  <<(escape_char(Char))/binary>> || <<Char>> <= S >>.
1,688✔
254

255
%% Escape character that will confuse an SQL engine
256
%% Percent and underscore only need to be escaped for pattern matching like
257
%% statement
258
escape_like(S) when is_binary(S) ->
259
    << <<(escape_like(C))/binary>> || <<C>> <= S >>;
×
260
escape_like($%) -> <<"\\%">>;
×
261
escape_like($_) -> <<"\\_">>;
×
262
escape_like($\\) -> <<"\\\\\\\\">>;
×
263
escape_like(C) when is_integer(C), C >= 0, C =< 255 -> escape_char(C).
×
264

265
escape_like_arg(S) when is_binary(S) ->
UNCOV
266
    << <<(escape_like_arg(C))/binary>> || <<C>> <= S >>;
1,848✔
UNCOV
267
escape_like_arg($%) -> <<"\\%">>;
1,092✔
UNCOV
268
escape_like_arg($_) -> <<"\\_">>;
2,172✔
UNCOV
269
escape_like_arg($\\) -> <<"\\\\">>;
1,092✔
UNCOV
270
escape_like_arg($[) -> <<"\\[">>;     % For MSSQL
1,092✔
UNCOV
271
escape_like_arg($]) -> <<"\\]">>;
1,092✔
UNCOV
272
escape_like_arg(C) when is_integer(C), C >= 0, C =< 255 -> <<C>>.
58,261✔
273

274
escape_like_arg_circumflex(S) when is_binary(S) ->
275
    << <<(escape_like_arg_circumflex(C))/binary>> || <<C>> <= S >>;
×
276
escape_like_arg_circumflex($%) -> <<"^%">>;
×
277
escape_like_arg_circumflex($_) -> <<"^_">>;
×
278
escape_like_arg_circumflex($^) -> <<"^^">>;
×
279
escape_like_arg_circumflex($[) -> <<"^[">>;     % For MSSQL
×
280
escape_like_arg_circumflex($]) -> <<"^]">>;
×
281
escape_like_arg_circumflex(C) when is_integer(C), C >= 0, C =< 255 -> <<C>>.
×
282

283
to_bool(<<"t">>) -> true;
×
284
to_bool(<<"true">>) -> true;
×
UNCOV
285
to_bool(<<"1">>) -> true;
944✔
286
to_bool(true) -> true;
×
UNCOV
287
to_bool(1) -> true;
584✔
UNCOV
288
to_bool(_) -> false.
4,562✔
289

290
escape_timestamp({{Y, Mo, D}, {H, Mi, S}}) ->
UNCOV
291
    list_to_binary(io_lib:format("~4..0B-~2..0B-~2..0B "
1,066✔
292
                                 "~2..0B:~2..0B:~2..0B",
293
                                 [Y, Mo, D, H, Mi, S])).
294

295

296
to_timestamp({Y, {H, M, S, _}}, mysql_prepared) -> {Y, {H, M, S}};
×
297
to_timestamp(<<TS:64/signed-big-integer>>, pgsql_prepared) ->
298
    calendar:gregorian_seconds_to_datetime(
×
299
      calendar:datetime_to_gregorian_seconds({{2000, 1, 1}, {0, 0, 0}}) + TS div 1_000_000);
300
to_timestamp(<<Y:4/binary, $-, Mo:2/binary, $-, D:2/binary, " ",
301
               H:2/binary, $:, Mi:2/binary, $:, S:2/binary>>,
302
             _) ->
303
    {{binary_to_integer(Y), binary_to_integer(Mo), binary_to_integer(D)},
×
304
     {binary_to_integer(H), binary_to_integer(Mi), binary_to_integer(S)}}.
305

306

307
to_list(EscapeFun, Val) ->
308
    Escaped = lists:join(<<",">>, lists:map(EscapeFun, Val)),
×
309
    [<<"(">>, Escaped, <<")">>].
×
310

311
to_array(EscapeFun, Val) ->
312
    Escaped = lists:join(<<",">>, lists:map(EscapeFun, Val)),
×
313
    lists:flatten([<<"{">>, Escaped, <<"}">>]).
×
314

315
to_string_literal(odbc, S) ->
316
    <<"'", (escape(S))/binary, "'">>;
×
317
to_string_literal(mysql, S) ->
UNCOV
318
    <<"'", (escape(S))/binary, "'">>;
844✔
319
to_string_literal(mssql, S) ->
320
    <<"'", (standard_escape(S))/binary, "'">>;
×
321
to_string_literal(sqlite, S) ->
UNCOV
322
    <<"'", (standard_escape(S))/binary, "'">>;
844✔
323
to_string_literal(pgsql, S) ->
UNCOV
324
    <<"E'", (escape(S))/binary, "'">>.
844✔
325

326
to_string_literal_t(S) ->
UNCOV
327
    State = get(?STATE_KEY),
30✔
UNCOV
328
    to_string_literal(State#state.db_type, S).
30✔
329

330
encode_term(Term) ->
331
    escape(list_to_binary(
×
332
             erl_prettypr:format(erl_syntax:abstract(Term),
333
                                 [{paper, 65535}, {ribbon, 65535}]))).
334

335
decode_term(Bin) ->
UNCOV
336
    Str = binary_to_list(<<Bin/binary, ".">>),
3,368✔
UNCOV
337
    try
3,368✔
UNCOV
338
        {ok, Tokens, _} = erl_scan:string(Str),
3,368✔
UNCOV
339
        {ok, Term} = erl_parse:parse_term(Tokens),
3,368✔
UNCOV
340
        Term
3,368✔
341
    catch _:{badmatch, {error, {Line, Mod, Reason}, _}} ->
342
            ?ERROR_MSG("Corrupted Erlang term in SQL database:~n"
×
343
                       "** Scanner error: at line ~B: ~ts~n"
344
                       "** Term: ~ts",
345
                       [Line, Mod:format_error(Reason), Bin]),
×
346
            erlang:error(badarg);
×
347
          _:{badmatch, {error, {Line, Mod, Reason}}} ->
348
            ?ERROR_MSG("Corrupted Erlang term in SQL database:~n"
×
349
                       "** Parser error: at line ~B: ~ts~n"
350
                       "** Term: ~ts",
351
                       [Line, Mod:format_error(Reason), Bin]),
×
352
            erlang:error(badarg)
×
353
    end.
354

355
-spec sqlite_db(binary()) -> atom().
356
sqlite_db(Host) ->
UNCOV
357
    list_to_atom("ejabberd_sqlite_" ++ binary_to_list(Host)).
37,243✔
358

359
-spec sqlite_file(binary()) -> string().
360
sqlite_file(Host) ->
UNCOV
361
    case ejabberd_option:sql_database(Host) of
4✔
362
        undefined ->
UNCOV
363
            Path = ["sqlite", atom_to_list(node()),
4✔
364
                    binary_to_list(Host), "ejabberd.db"],
UNCOV
365
            case file:get_cwd() of
4✔
366
                {ok, Cwd} ->
UNCOV
367
                    filename:join([Cwd|Path]);
4✔
368
                {error, Reason} ->
369
                    ?ERROR_MSG("Failed to get current directory: ~ts",
×
370
                               [file:format_error(Reason)]),
×
371
                    filename:join(Path)
×
372
            end;
373
        File ->
374
            binary_to_list(File)
×
375
    end.
376

377
use_multihost_schema() ->
UNCOV
378
    ejabberd_option:sql_schema_multihost().
35,015✔
379

380
use_new_schema() ->
381
    use_multihost_schema().
×
382

383
-spec get_worker(binary()) -> atom().
384
get_worker(Host) ->
UNCOV
385
    PoolSize = ejabberd_option:sql_pool_size(Host),
44,333✔
UNCOV
386
    I = p1_rand:round_robin(PoolSize) + 1,
44,333✔
UNCOV
387
    binary_to_existing_atom(get_worker_name(Host, I), utf8).
44,333✔
388

389
-spec get_worker_name(binary(), pos_integer()) -> binary().
390
get_worker_name(Host, I) ->
UNCOV
391
    <<"ejabberd_sql_", Host/binary, $_, (integer_to_binary(I))/binary>>.
44,339✔
392

393
%%%----------------------------------------------------------------------
394
%%% Callback functions from gen_fsm
395
%%%----------------------------------------------------------------------
396
init([Host]) ->
UNCOV
397
    process_flag(trap_exit, true),
6✔
UNCOV
398
    case ejabberd_option:sql_keepalive_interval(Host) of
6✔
399
        undefined ->
UNCOV
400
            ok;
6✔
401
        KeepaliveInterval ->
402
            timer:apply_interval(KeepaliveInterval, ?MODULE,
×
403
                                 keep_alive, [Host, self()])
404
    end,
UNCOV
405
    [DBType | _] = db_opts(Host),
6✔
UNCOV
406
    p1_fsm:send_event(self(), connect),
6✔
UNCOV
407
    QueueType = ejabberd_option:sql_queue_type(Host),
6✔
UNCOV
408
    {ok, connecting,
6✔
409
     #state{db_type = DBType, host = Host,
410
            pending_requests = p1_queue:new(QueueType, max_fsm_queue()),
411
            timeout = query_timeout(Host)}}.
412

413
connecting(connect, #state{host = Host} = State) ->
UNCOV
414
    ConnectRes = case db_opts(Host) of
6✔
UNCOV
415
                     [mysql | Args] -> apply(fun mysql_connect/8, Args);
2✔
UNCOV
416
                     [pgsql | Args] -> apply(fun pgsql_connect/8, Args);
2✔
UNCOV
417
                     [sqlite | Args] -> apply(fun sqlite_connect/1, Args);
2✔
418
                     [mssql | Args] -> apply(fun odbc_connect/2, Args);
×
419
                     [odbc | Args] -> apply(fun odbc_connect/2, Args)
×
420
                 end,
UNCOV
421
    case ConnectRes of
6✔
422
        {ok, Ref} ->
UNCOV
423
            try link(Ref) of
6✔
424
                _ ->
UNCOV
425
                    lists:foreach(
6✔
426
                      fun({{?PREPARE_KEY, _} = Key, _}) ->
427
                              erase(Key);
×
428
                         (_) ->
UNCOV
429
                              ok
18✔
430
                      end, get()),
UNCOV
431
                    PendingRequests =
6✔
432
                        p1_queue:dropwhile(
433
                          fun(Req) ->
434
                                  p1_fsm:send_event(self(), Req),
×
435
                                  true
×
436
                          end, State#state.pending_requests),
UNCOV
437
                    State1 = State#state{db_ref = Ref,
6✔
438
                                         pending_requests = PendingRequests},
UNCOV
439
                    State2 = get_db_version(State1),
6✔
UNCOV
440
                    {next_state, session_established, State2#state{reconnect_count = 0}}
6✔
441
            catch _:Reason ->
442
                    handle_reconnect(Reason, State)
×
443
            end;
444
        {error, Reason} ->
445
            handle_reconnect(Reason, State)
×
446
    end;
447
connecting(Event, State) ->
448
    ?WARNING_MSG("Unexpected event in 'connecting': ~p",
×
449
                 [Event]),
×
450
    {next_state, connecting, State}.
×
451

452
connecting({sql_cmd, {sql_query, ?KEEPALIVE_QUERY}, Timestamp},
453
           From, State) ->
454
    reply(From, {error, <<"SQL connection failed">>}, Timestamp),
×
455
    {next_state, connecting, State};
×
456
connecting({sql_cmd, Command, Timestamp} = Req, From,
457
           State) ->
458
    ?DEBUG("Queuing pending request while connecting:~n\t~p",
×
459
           [Req]),
×
460
    PendingRequests =
×
461
        try p1_queue:in({sql_cmd, Command, From, Timestamp},
×
462
                        State#state.pending_requests)
463
        catch error:full ->
464
                Err = <<"SQL request queue is overfilled">>,
×
465
                ?ERROR_MSG("~ts, bouncing all pending requests", [Err]),
×
466
                Q = p1_queue:dropwhile(
×
467
                      fun({sql_cmd, _, To, TS}) ->
468
                              reply(To, {error, Err}, TS),
×
469
                              true
×
470
                      end, State#state.pending_requests),
471
                p1_queue:in({sql_cmd, Command, From, Timestamp}, Q)
×
472
        end,
473
    {next_state, connecting,
×
474
     State#state{pending_requests = PendingRequests}};
475
connecting(Request, {Who, _Ref}, State) ->
476
    ?WARNING_MSG("Unexpected call ~p from ~p in 'connecting'",
×
477
                 [Request, Who]),
×
478
    {next_state, connecting, State}.
×
479

480
session_established({sql_cmd, Command, Timestamp}, From,
481
                    State) ->
UNCOV
482
    run_sql_cmd(Command, From, State, Timestamp);
44,333✔
483
session_established(Request, {Who, _Ref}, State) ->
484
    ?WARNING_MSG("Unexpected call ~p from ~p in 'session_established'",
×
485
                 [Request, Who]),
×
486
    {next_state, session_established, State}.
×
487

488
session_established({sql_cmd, Command, From, Timestamp},
489
                    State) ->
490
    run_sql_cmd(Command, From, State, Timestamp);
×
491
session_established(force_timeout, State) ->
492
    {stop, timeout, State};
×
493
session_established(Event, State) ->
494
    ?WARNING_MSG("Unexpected event in 'session_established': ~p",
×
495
                 [Event]),
×
496
    {next_state, session_established, State}.
×
497

498
handle_event(_Event, StateName, State) ->
499
    {next_state, StateName, State}.
×
500

501
handle_sync_event(_Event, _From, StateName, State) ->
502
    {reply, {error, badarg}, StateName, State}.
×
503

504
code_change(_OldVsn, StateName, State, _Extra) ->
505
    {ok, StateName, State}.
×
506

507
handle_info({'EXIT', _Pid, _Reason}, connecting, State) ->
508
    {next_state, connecting, State};
×
509
handle_info({'EXIT', _Pid, Reason}, _StateName, State) ->
510
    handle_reconnect(Reason, State);
×
511
handle_info(Info, StateName, State) ->
512
    ?WARNING_MSG("Unexpected info in ~p: ~p",
×
513
                 [StateName, Info]),
×
514
    {next_state, StateName, State}.
×
515

516
terminate(_Reason, _StateName, State) ->
UNCOV
517
    case State#state.db_type of
6✔
UNCOV
518
        mysql -> catch p1_mysql_conn:stop(State#state.db_ref);
2✔
UNCOV
519
        sqlite -> catch sqlite3:close(sqlite_db(State#state.host));
2✔
UNCOV
520
        _ -> ok
2✔
521
    end,
UNCOV
522
    ok.
6✔
523

524
%%----------------------------------------------------------------------
525
%% Func: print_state/1
526
%% Purpose: Prepare the state to be printed on error log
527
%% Returns: State to print
528
%%----------------------------------------------------------------------
529
print_state(State) -> State.
×
530

531
%%%----------------------------------------------------------------------
532
%%% Internal functions
533
%%%----------------------------------------------------------------------
534
handle_reconnect(Reason, #state{host = Host, reconnect_count = RC} = State) ->
535
    StartInterval0 = ejabberd_option:sql_start_interval(Host),
×
536
    StartInterval = case RC of
×
537
                        0 -> erlang:min(5000, StartInterval0);
×
538
                        _ -> StartInterval0
×
539
                    end,
540
    ?WARNING_MSG("~p connection failed:~n"
×
541
                 "** Reason: ~p~n"
542
                 "** Retry after: ~B seconds",
543
                 [State#state.db_type, Reason,
544
                  StartInterval div 1000]),
×
545
    case State#state.db_type of
×
546
        mysql -> catch p1_mysql_conn:stop(State#state.db_ref);
×
547
        sqlite -> catch sqlite3:close(sqlite_db(State#state.host));
×
548
        pgsql -> catch pgsql:terminate(State#state.db_ref);
×
549
        _ -> ok
×
550
    end,
551
    p1_fsm:send_event_after(StartInterval, connect),
×
552
    {next_state, connecting, State#state{reconnect_count = RC + 1,
×
553
                                         timeout = query_timeout(Host)}}.
554

555
run_sql_cmd(Command, From, State, Timestamp) ->
UNCOV
556
    CT = current_time(),
44,333✔
UNCOV
557
    case CT >= Timestamp of
44,333✔
558
        true ->
559
            State1 = report_overload(State),
×
560
            {next_state, session_established, State1};
×
561
        false ->
UNCOV
562
            receive
44,333✔
563
                {'EXIT', _Pid, Reason} ->
564
                    PR = p1_queue:in({sql_cmd, Command, From, Timestamp},
×
565
                                     State#state.pending_requests),
566
                    handle_reconnect(Reason, State#state{pending_requests = PR})
×
567
            after 0 ->
UNCOV
568
                Timeout = min(query_timeout(State#state.host), Timestamp - CT),
44,333✔
UNCOV
569
                put(?NESTING_KEY, ?TOP_LEVEL_TXN),
44,333✔
UNCOV
570
                put(?STATE_KEY, State#state{timeout = Timeout}),
44,333✔
UNCOV
571
                abort_on_driver_error(outer_op(Command), From, Timestamp)
44,333✔
572
            end
573
    end.
574

575
%% @doc Only called by handle_call, only handles top level operations.
576
-spec outer_op(Op::{atom(), binary()} | {sql_transaction, binary(), pos_integer()}) ->
577
    {error, Reason::binary()} | {aborted, Reason::binary()} | {atomic, Result::any()}.
578
outer_op({sql_query, Query}) ->
UNCOV
579
    sql_query_internal(Query);
33,519✔
580
outer_op({sql_transaction, F, Restarts}) ->
UNCOV
581
    outer_transaction(F, Restarts, <<"">>);
5,504✔
UNCOV
582
outer_op({sql_bloc, F}) -> execute_bloc(F).
5,310✔
583

584
%% Called via sql_query/transaction/bloc from client code when inside a
585
%% nested operation
586
nested_op({sql_query, Query}) ->
UNCOV
587
    sql_query_internal(Query);
18✔
588
nested_op({sql_transaction, F, Restarts}) ->
UNCOV
589
    NestingLevel = get(?NESTING_KEY),
12✔
UNCOV
590
    if NestingLevel =:= (?TOP_LEVEL_TXN) ->
12✔
UNCOV
591
        outer_transaction(F, Restarts, <<"">>);
6✔
UNCOV
592
        true -> inner_transaction(F)
6✔
593
    end;
UNCOV
594
nested_op({sql_bloc, F}) -> execute_bloc(F).
54✔
595

596
%% Never retry nested transactions - only outer transactions
597
inner_transaction(F) ->
UNCOV
598
    PreviousNestingLevel = get(?NESTING_KEY),
6✔
UNCOV
599
    case get(?NESTING_KEY) of
6✔
600
      ?TOP_LEVEL_TXN ->
601
          {backtrace, T} = process_info(self(), backtrace),
×
602
          ?ERROR_MSG("Inner transaction called at outer txn "
×
603
                     "level. Trace: ~ts",
604
                     [T]),
×
605
          erlang:exit(implementation_faulty);
×
UNCOV
606
      _N -> ok
6✔
607
    end,
UNCOV
608
    put(?NESTING_KEY, PreviousNestingLevel + 1),
6✔
UNCOV
609
    Result = (catch F()),
6✔
UNCOV
610
    put(?NESTING_KEY, PreviousNestingLevel),
6✔
UNCOV
611
    case Result of
6✔
612
      {aborted, Reason} -> {aborted, Reason};
×
613
      {'EXIT', Reason} -> {'EXIT', Reason};
×
614
      {atomic, Res} -> {atomic, Res};
×
UNCOV
615
      Res -> {atomic, Res}
6✔
616
    end.
617

618
outer_transaction(F, NRestarts, _Reason) ->
UNCOV
619
    PreviousNestingLevel = get(?NESTING_KEY),
5,510✔
UNCOV
620
    case get(?NESTING_KEY) of
5,510✔
UNCOV
621
      ?TOP_LEVEL_TXN -> ok;
5,510✔
622
      _N ->
623
          {backtrace, T} = process_info(self(), backtrace),
×
624
          ?ERROR_MSG("Outer transaction called at inner txn "
×
625
                     "level. Trace: ~ts",
626
                     [T]),
×
627
          erlang:exit(implementation_faulty)
×
628
    end,
UNCOV
629
    case sql_begin() of
5,510✔
630
        {error, Reason} ->
631
            maybe_restart_transaction(F, NRestarts, Reason, false);
×
632
        _ ->
UNCOV
633
            put(?NESTING_KEY, PreviousNestingLevel + 1),
5,510✔
UNCOV
634
            try F() of
5,510✔
635
                Res ->
UNCOV
636
                    case sql_commit() of
5,510✔
637
                        {error, Reason} ->
638
                            restart(Reason);
×
639
                        _ ->
UNCOV
640
                            {atomic, Res}
5,510✔
641
                    end
642
            catch
643
                throw:{aborted, Reason}:_ when NRestarts > 0 ->
644
                    maybe_restart_transaction(F, NRestarts, Reason, true);
×
645
                throw:{aborted, Reason}:StackTrace when NRestarts =:= 0 ->
646
                    ?ERROR_MSG("SQL transaction restarts exceeded~n** "
×
647
                               "Restarts: ~p~n** Last abort reason: "
648
                               "~p~n** Stacktrace: ~p~n** When State "
649
                               "== ~p",
650
                               [?MAX_TRANSACTION_RESTARTS,
651
                                Reason,
652
                                StackTrace,
653
                                get(?STATE_KEY)]),
×
654
                    maybe_restart_transaction(F, NRestarts, Reason, true);
×
655
                _:Reason:_ ->
656
                    maybe_restart_transaction(F, 0, Reason, true)
×
657
            end
658
    end.
659

660
maybe_restart_transaction(F, NRestarts, Reason, DoRollback) ->
661
    Res = case driver_restart_required(Reason) of
×
662
              true ->
663
                  {aborted, Reason};
×
664
              _ when DoRollback ->
665
                  case sql_rollback() of
×
666
                      {error, Reason2} ->
667
                          case driver_restart_required(Reason2) of
×
668
                              true ->
669
                                  {aborted, Reason2};
×
670
                              _ ->
671
                                  continue
×
672
                          end;
673
                      _ ->
674
                          continue
×
675
                  end;
676
              _ ->
677
                  continue
×
678
    end,
679
    case Res of
×
680
        continue when NRestarts > 0 ->
681
            put(?NESTING_KEY, ?TOP_LEVEL_TXN),
×
682
            outer_transaction(F, NRestarts - 1, Reason);
×
683
        continue ->
684
            {aborted, Reason};
×
685
        Other ->
686
            Other
×
687
    end.
688

689
execute_bloc(F) ->
UNCOV
690
    case catch F() of
5,364✔
691
      {aborted, Reason} -> {aborted, Reason};
×
692
      {'EXIT', Reason} -> {aborted, Reason};
×
UNCOV
693
      Res -> {atomic, Res}
5,364✔
694
    end.
695

696
execute_fun(F) when is_function(F, 0) ->
UNCOV
697
    F();
150✔
698
execute_fun(F) when is_function(F, 2) ->
UNCOV
699
    State = get(?STATE_KEY),
7,455✔
UNCOV
700
    F(State#state.db_type, State#state.db_version).
7,455✔
701

702
sql_query_internal([{_, _} | _] = Queries) ->
UNCOV
703
    State = get(?STATE_KEY),
11,020✔
UNCOV
704
    case select_sql_query(Queries, State) of
11,020✔
705
        undefined ->
706
            {error, <<"no matching query for the current DBMS found">>};
×
707
        Query ->
UNCOV
708
            sql_query_internal(Query)
11,020✔
709
    end;
710
sql_query_internal(#sql_query{} = Query) ->
UNCOV
711
    State = get(?STATE_KEY),
63,247✔
UNCOV
712
    Res =
63,247✔
713
        try
UNCOV
714
            case State#state.db_type of
63,247✔
715
                odbc ->
716
                    generic_sql_query(Query);
×
717
                mssql ->
718
                    mssql_sql_query(Query);
×
719
                pgsql ->
UNCOV
720
                    Key = {?PREPARE_KEY, Query#sql_query.hash},
20,276✔
UNCOV
721
                    case get(Key) of
20,276✔
722
                        undefined ->
UNCOV
723
                            Host = State#state.host,
274✔
UNCOV
724
                            PreparedStatements =
274✔
725
                                ejabberd_option:sql_prepared_statements(Host),
UNCOV
726
                            case PreparedStatements of
274✔
727
                                false ->
728
                                    put(Key, ignore);
×
729
                                true ->
UNCOV
730
                                    case pgsql_prepare(Query, State) of
274✔
731
                                        {ok, _, _, _} ->
UNCOV
732
                                            put(Key, prepared);
274✔
733
                                        {error, Error} ->
734
                                            ?ERROR_MSG(
×
735
                                               "PREPARE failed for SQL query "
736
                                               "at ~p: ~p",
737
                                               [Query#sql_query.loc, Error]),
×
738
                                            put(Key, ignore)
×
739
                                    end
740
                            end;
741
                        _ ->
UNCOV
742
                            ok
20,002✔
743
                    end,
UNCOV
744
                    case get(Key) of
20,276✔
745
                        prepared ->
UNCOV
746
                            pgsql_execute_sql_query(Query, State);
20,276✔
747
                        _ ->
748
                            pgsql_sql_query(Query)
×
749
                    end;
750
                mysql ->
UNCOV
751
                    case {Query#sql_query.flags, ejabberd_option:sql_prepared_statements(State#state.host)} of
22,407✔
752
                        {1, _} ->
753
                            generic_sql_query(Query);
×
754
                        {_, false} ->
755
                            generic_sql_query(Query);
×
756
                        _ ->
UNCOV
757
                            mysql_prepared_execute(Query, State)
22,407✔
758
                    end;
759
                sqlite ->
UNCOV
760
                    sqlite_sql_query(Query)
20,564✔
761
            end
762
        catch exit:{timeout, _} ->
763
                {error, <<"timed out">>};
×
764
              exit:{killed, _} ->
765
                {error, <<"killed">>};
×
766
              exit:{normal, _} ->
767
                {error, <<"terminated unexpectedly">>};
×
768
              exit:{shutdown, _} ->
769
                {error, <<"shutdown">>};
×
770
            Class:Reason:StackTrace ->
771
                ?ERROR_MSG("Internal error while processing SQL query:~n** ~ts",
×
772
                           [misc:format_exception(2, Class, Reason, StackTrace)]),
×
773
                {error, <<"internal error">>}
×
774
        end,
UNCOV
775
    check_error(Res, Query);
63,247✔
776
sql_query_internal(F) when is_function(F) ->
UNCOV
777
    case catch execute_fun(F) of
7,605✔
778
        {aborted, Reason} -> {error, Reason};
×
779
        {'EXIT', Reason} -> {error, Reason};
×
UNCOV
780
        Res -> Res
7,605✔
781
    end;
782
sql_query_internal(Query) ->
UNCOV
783
    State = get(?STATE_KEY),
34,546✔
UNCOV
784
    ?DEBUG("SQL: \"~ts\"", [Query]),
34,546✔
UNCOV
785
    QueryTimeout = State#state.timeout,
34,546✔
UNCOV
786
    Res = case State#state.db_type of
34,546✔
787
            odbc ->
788
                to_odbc(odbc:sql_query(State#state.db_ref, [Query],
×
789
                                       QueryTimeout - 1000));
790
            mssql ->
791
                to_odbc(odbc:sql_query(State#state.db_ref, [Query],
×
792
                                       QueryTimeout - 1000));
793
            pgsql ->
UNCOV
794
                pgsql_to_odbc(pgsql:squery(State#state.db_ref, Query,
4,734✔
795
                                           QueryTimeout - 1000));
796
            mysql ->
UNCOV
797
                mysql_to_odbc(p1_mysql_conn:squery(State#state.db_ref,
4,736✔
798
                                                   [Query], self(),
799
                                                   [{timeout, QueryTimeout - 1000},
800
                                                    {result_type, binary}]));
801
              sqlite ->
UNCOV
802
                  Host = State#state.host,
25,076✔
UNCOV
803
                  sqlite_to_odbc(Host, sqlite3:sql_exec(sqlite_db(Host), Query))
25,076✔
804
          end,
UNCOV
805
    check_error(Res, Query).
34,546✔
806

807
select_sql_query(Queries, State) ->
UNCOV
808
    select_sql_query(
11,020✔
809
      Queries, State#state.db_type, State#state.db_version, undefined).
810

811
select_sql_query([], _Type, _Version, undefined) ->
812
    undefined;
×
813
select_sql_query([], _Type, _Version, Query) ->
814
    Query;
×
815
select_sql_query([{any, Query} | _], _Type, _Version, _) ->
UNCOV
816
    Query;
11,020✔
817
select_sql_query([{Type, Query} | _], Type, _Version, _) ->
818
    Query;
×
819
select_sql_query([{{Type, _Version1}, Query1} | Rest], Type, undefined, _) ->
820
    select_sql_query(Rest, Type, undefined, Query1);
×
821
select_sql_query([{{Type, Version1}, Query1} | Rest], Type, Version, Query) ->
822
    if
×
823
        Version >= Version1 ->
824
            Query1;
×
825
        true ->
826
            select_sql_query(Rest, Type, Version, Query)
×
827
    end;
828
select_sql_query([{_, _} | Rest], Type, Version, Query) ->
UNCOV
829
    select_sql_query(Rest, Type, Version, Query).
11,020✔
830

831
generic_sql_query(SQLQuery) ->
832
    sql_query_format_res(
×
833
      sql_query_internal(generic_sql_query_format(SQLQuery)),
834
      SQLQuery,
835
      generic).
836

837
generic_sql_query_format(SQLQuery) ->
838
    Args = (SQLQuery#sql_query.args)(generic_escape()),
×
839
    (SQLQuery#sql_query.format_query)(Args).
×
840

841
generic_escape() ->
842
    #sql_escape{string = fun(X) -> <<"'", (escape(X))/binary, "'">> end,
×
843
                integer = fun(X) -> misc:i2l(X) end,
×
844
                boolean = fun(true) -> <<"1">>;
×
845
                             (false) -> <<"0">>
×
846
                          end,
847
      timestamp = fun(X) -> <<"'", (escape_timestamp(X))/binary, "'">> end,
×
848
                in_array_string = fun(X) -> <<"'", (escape(X))/binary, "'">> end,
×
849
                like_escape = fun() -> <<"">> end
×
850
               }.
851

852
pgsql_sql_query(SQLQuery) ->
853
    sql_query_format_res(
×
854
      sql_query_internal(pgsql_sql_query_format(SQLQuery)),
855
      SQLQuery,
856
      pgsql).
857

858
pgsql_sql_query_format(SQLQuery) ->
859
    Args = (SQLQuery#sql_query.args)(pgsql_escape()),
×
860
    (SQLQuery#sql_query.format_query)(Args).
×
861

862
pgsql_escape() ->
863
    #sql_escape{string = fun(X) -> <<"E'", (escape(X))/binary, "'">> end,
×
864
                integer = fun(X) -> misc:i2l(X) end,
×
865
                boolean = fun(true) -> <<"'t'">>;
×
866
                             (false) -> <<"'f'">>
×
867
                          end,
868
      timestamp = fun(X) -> <<"E'", (escape_timestamp(X))/binary, "'">> end,
×
869
                in_array_string = fun(X) -> <<"E'", (escape(X))/binary, "'">> end,
×
870
                like_escape = fun() -> <<"ESCAPE E'\\\\'">> end
×
871
               }.
872

873
sqlite_sql_query(SQLQuery) ->
UNCOV
874
    sql_query_format_res(
20,564✔
875
      sql_query_internal(sqlite_sql_query_format(SQLQuery)),
876
      SQLQuery,
877
      sqlite).
878

879
sqlite_sql_query_format(SQLQuery) ->
UNCOV
880
    Args = (SQLQuery#sql_query.args)(sqlite_escape()),
20,564✔
UNCOV
881
    (SQLQuery#sql_query.format_query)(Args).
20,564✔
882

883
sqlite_escape() ->
UNCOV
884
    #sql_escape{string = fun(X) -> <<"'", (standard_escape(X))/binary, "'">> end,
20,564✔
UNCOV
885
                integer = fun(X) -> misc:i2l(X) end,
5,812✔
UNCOV
886
                boolean = fun(true) -> <<"1">>;
230✔
UNCOV
887
                             (false) -> <<"0">>
580✔
888
                          end,
UNCOV
889
      timestamp = fun(X) -> <<"'", (escape_timestamp(X))/binary, "'">> end,
284✔
890
                in_array_string = fun(X) -> <<"'", (standard_escape(X))/binary, "'">> end,
×
UNCOV
891
                like_escape = fun() -> <<"ESCAPE '\\'">> end
616✔
892
               }.
893

894
standard_escape(S) ->
UNCOV
895
    << <<(case Char of
53,298✔
UNCOV
896
              $' -> << "''" >>;
18,590✔
UNCOV
897
              _ -> << Char >>
1,890,104✔
UNCOV
898
          end)/binary>> || <<Char>> <= S >>.
53,298✔
899

900
mssql_sql_query(SQLQuery) ->
901
    sqlite_sql_query(SQLQuery).
×
902

903
pgsql_prepare(SQLQuery, State) ->
UNCOV
904
    Escape = #sql_escape{_ = fun(_) -> arg end,
274✔
UNCOV
905
                         like_escape = fun() -> escape end},
12✔
UNCOV
906
    {RArgs, _} =
274✔
907
        lists:foldl(
908
            fun(arg, {Acc, I}) ->
UNCOV
909
                {[<<$$, (integer_to_binary(I))/binary>> | Acc], I + 1};
818✔
910
               (escape, {Acc, I}) ->
UNCOV
911
                   {[<<"ESCAPE E'\\\\'">> | Acc], I};
12✔
912
               (List, {Acc, I}) when is_list(List) ->
913
                   {[<<$$, (integer_to_binary(I))/binary>> | Acc], I + 1}
×
914
            end, {[], 1}, (SQLQuery#sql_query.args)(Escape)),
UNCOV
915
    Args = lists:reverse(RArgs),
274✔
916
    %N = length((SQLQuery#sql_query.args)(Escape)),
917
    %Args = [<<$$, (integer_to_binary(I))/binary>> || I <- lists:seq(1, N)],
UNCOV
918
    Query = (SQLQuery#sql_query.format_query)(Args),
274✔
UNCOV
919
    pgsql:prepare(State#state.db_ref, SQLQuery#sql_query.hash, Query).
274✔
920

921

922
pgsql_execute_escape() ->
UNCOV
923
    #sql_escape{
20,276✔
UNCOV
924
      string = fun(X) -> X end,
54,071✔
UNCOV
925
      integer = fun(X) -> [misc:i2l(X)] end,
5,218✔
UNCOV
926
      boolean = fun(true) -> "1";
230✔
UNCOV
927
                   (false) -> "0"
580✔
928
                end,
929
      timestamp = fun escape_timestamp/1,
930
                in_array_string = fun(X) -> <<"\"", (escape(X))/binary, "\"">> end,
×
UNCOV
931
                like_escape = fun() -> ignore end
616✔
932
               }.
933

934
pgsql_execute_sql_query(SQLQuery, State) ->
UNCOV
935
    Args = (SQLQuery#sql_query.args)(pgsql_execute_escape()),
20,276✔
UNCOV
936
    Args2 = lists:filter(fun(ignore) -> false; (_) -> true end, Args),
20,276✔
UNCOV
937
    ExecuteRes =
20,276✔
938
        pgsql:execute(State#state.db_ref, SQLQuery#sql_query.hash, Args2),
939
%    {T, ExecuteRes} =
940
%        timer:tc(pgsql, execute, [State#state.db_ref, SQLQuery#sql_query.hash, Args]),
941
%    io:format("T ~ts ~p~n", [SQLQuery#sql_query.hash, T]),
UNCOV
942
    Res = pgsql_execute_to_odbc(ExecuteRes),
20,276✔
UNCOV
943
    sql_query_format_res(Res, SQLQuery, pgsql_prepared).
20,276✔
944

945

946
mysql_prepared_execute(#sql_query{hash = Hash} = Query, State) ->
UNCOV
947
    ValEsc = #sql_escape{
22,407✔
UNCOV
948
               like_escape = fun() -> ignore end,
616✔
949
               timestamp = fun escape_timestamp/1,
UNCOV
950
               _ = fun(X) -> X end
64,259✔
951
              },
UNCOV
952
    TypesEsc = #sql_escape{
22,407✔
UNCOV
953
                 string = fun(_) -> string end,
57,607✔
UNCOV
954
                 integer = fun(_) -> integer end,
5,842✔
UNCOV
955
                 boolean = fun(_) -> bool end,
810✔
UNCOV
956
                 timestamp = fun(_) -> string end,
390✔
957
                           in_array_string = fun(_) -> string end,
×
UNCOV
958
                           like_escape = fun() -> ignore end},
616✔
UNCOV
959
    Val = [X || X <- (Query#sql_query.args)(ValEsc), X /= ignore],
22,407✔
UNCOV
960
    Types = [X || X <- (Query#sql_query.args)(TypesEsc), X /= ignore],
22,407✔
UNCOV
961
    QueryFn = fun() ->
22,407✔
UNCOV
962
                      PrepEsc = #sql_escape{like_escape = fun() -> <<>> end, _ = fun(_) -> <<"?">> end},
340✔
UNCOV
963
                      (Query#sql_query.format_query)((Query#sql_query.args)(PrepEsc))
340✔
964
              end,
UNCOV
965
    QueryTimeout = query_timeout(State#state.host),
22,407✔
UNCOV
966
    Res = p1_mysql_conn:prepared_query(State#state.db_ref,
22,407✔
967
                                       QueryFn,
968
                                       Hash,
969
                                       Val,
970
                                       Types,
971
                                       self(),
972
                                       [{timeout, QueryTimeout - 1000}]),
UNCOV
973
    Res2 = mysql_to_odbc(Res),
22,407✔
UNCOV
974
    sql_query_format_res(Res2, Query, mysql_prepared).
22,407✔
975

976

977
sql_query_format_res({selected, _, Rows}, SQLQuery, DbType) ->
UNCOV
978
    Res =
40,328✔
979
        lists:flatmap(
980
          fun(Row) ->
UNCOV
981
                  try
61,855✔
UNCOV
982
                      [(SQLQuery#sql_query.format_res)(Row, DbType)]
61,855✔
983
                  catch
984
                      Class:Reason:StackTrace ->
985
                          ?ERROR_MSG("Error while processing SQL query result:~n"
×
986
                                     "** Row: ~p~n** ~ts",
987
                                     [Row,
988
                                      misc:format_exception(2, Class, Reason, StackTrace)]),
×
989
                          []
×
990
                  end
991
          end, Rows),
UNCOV
992
    {selected, Res};
40,328✔
993
sql_query_format_res(Res, _SQLQuery, _DbType) ->
UNCOV
994
    Res.
22,919✔
995

996
sql_query_to_iolist(SQLQuery) ->
997
    generic_sql_query_format(SQLQuery).
×
998

999
sql_query_to_iolist(sqlite, SQLQuery) ->
1000
    sqlite_sql_query_format(SQLQuery);
×
1001
sql_query_to_iolist(_DbType, SQLQuery) ->
1002
    generic_sql_query_format(SQLQuery).
×
1003

1004
sql_begin() ->
UNCOV
1005
    sql_query_internal(
5,510✔
1006
      [{mssql, [<<"begin transaction;">>]},
1007
       {any, [<<"begin;">>]}]).
1008

1009
sql_commit() ->
UNCOV
1010
    sql_query_internal(
5,510✔
1011
      [{mssql, [<<"commit transaction;">>]},
1012
       {any, [<<"commit;">>]}]).
1013

1014
sql_rollback() ->
1015
    sql_query_internal(
×
1016
      [{mssql, [<<"rollback transaction;">>]},
1017
       {any, [<<"rollback;">>]}]).
1018

1019
driver_restart_required(<<"query timed out">>) -> true;
×
1020
driver_restart_required(<<"connection closed">>) -> true;
×
1021
driver_restart_required(<<"Failed sending data on socket", _/binary>>) -> true;
×
1022
driver_restart_required(<<"SQL connection failed">>) -> true;
×
1023
driver_restart_required(<<"Communication link failure">>) -> true;
×
1024
driver_restart_required(_) -> false.
×
1025

1026
%% Generate the OTP callback return tuple depending on the driver result.
1027
abort_on_driver_error({Tag, Msg} = Reply, From, Timestamp) when Tag == error; Tag == aborted ->
1028
    reply(From, Reply, Timestamp),
×
1029
    case driver_restart_required(Msg) of
×
1030
        true ->
1031
            handle_reconnect(Msg, get(?STATE_KEY));
×
1032
        _ ->
1033
            {next_state, session_established, get(?STATE_KEY)}
×
1034
    end;
1035
abort_on_driver_error(Reply, From, Timestamp) ->
UNCOV
1036
    reply(From, Reply, Timestamp),
44,333✔
UNCOV
1037
    {next_state, session_established, get(?STATE_KEY)}.
44,333✔
1038

1039
-spec report_overload(state()) -> state().
1040
report_overload(#state{overload_reported = PrevTime} = State) ->
1041
    CurrTime = current_time(),
×
1042
    case PrevTime == undefined orelse (CurrTime - PrevTime) > timer:seconds(30) of
×
1043
        true ->
1044
            ?ERROR_MSG("SQL connection pool is overloaded, "
×
1045
                       "discarding stale requests", []),
×
1046
            State#state{overload_reported = current_time()};
×
1047
        false ->
1048
            State
×
1049
    end.
1050

1051
-spec reply({pid(), term()}, term(), integer()) -> term().
1052
reply(From, Reply, Timestamp) ->
UNCOV
1053
    case current_time() >= Timestamp of
44,333✔
1054
        true -> ok;
×
UNCOV
1055
        false -> p1_fsm:reply(From, Reply)
44,333✔
1056
    end.
1057

1058
%% == pure ODBC code
1059

1060
%% part of init/1
1061
%% Open an ODBC database connection
1062
odbc_connect(SQLServer, Timeout) ->
1063
    ejabberd:start_app(odbc),
×
1064
    odbc:connect(binary_to_list(SQLServer),
×
1065
                 [{scrollable_cursors, off},
1066
                  {extended_errors, on},
1067
                  {tuple_row, off},
1068
                  {timeout, Timeout},
1069
                  {binary_strings, on}]).
1070

1071
%% == Native SQLite code
1072

1073
%% part of init/1
1074
%% Open a database connection to SQLite
1075

1076
sqlite_connect(Host) ->
UNCOV
1077
    File = sqlite_file(Host),
2✔
UNCOV
1078
    case filelib:ensure_dir(File) of
2✔
1079
        ok ->
UNCOV
1080
            case sqlite3:open(sqlite_db(Host), [{file, File}]) of
2✔
1081
                {ok, Ref} ->
UNCOV
1082
                    sqlite3:sql_exec(
2✔
1083
                      sqlite_db(Host), "pragma foreign_keys = on"),
UNCOV
1084
                    {ok, Ref};
2✔
1085
                {error, {already_started, Ref}} ->
1086
                    {ok, Ref};
×
1087
                {error, Reason} ->
1088
                    {error, Reason}
×
1089
            end;
1090
        Err ->
1091
            Err
×
1092
    end.
1093

1094
%% Convert SQLite query result to Erlang ODBC result formalism
1095
sqlite_to_odbc(Host, ok) ->
UNCOV
1096
    {updated, sqlite3:changes(sqlite_db(Host))};
8,337✔
1097
sqlite_to_odbc(Host, {rowid, _}) ->
UNCOV
1098
    {updated, sqlite3:changes(sqlite_db(Host))};
3,822✔
1099
sqlite_to_odbc(_Host, [{columns, Columns}, {rows, TRows}]) ->
UNCOV
1100
    Rows = [lists:map(
12,917✔
1101
              fun(I) when is_integer(I) ->
UNCOV
1102
                      integer_to_binary(I);
5,758✔
1103
                 (B) ->
UNCOV
1104
                      B
57,138✔
UNCOV
1105
              end, tuple_to_list(Row)) || Row <- TRows],
12,917✔
UNCOV
1106
    {selected, [list_to_binary(C) || C <- Columns], Rows};
12,917✔
1107
sqlite_to_odbc(_Host, {error, _Code, Reason}) ->
1108
    {error, Reason};
×
1109
sqlite_to_odbc(_Host, _) ->
1110
    {updated, undefined}.
×
1111

1112
%% == Native PostgreSQL code
1113

1114
%% part of init/1
1115
%% Open a database connection to PostgreSQL
1116
pgsql_connect(Server, Port, DB, Username, Password, ConnectTimeout,
1117
              Transport, SSLOpts) ->
UNCOV
1118
    pgsql:connect([{host, Server},
2✔
1119
                   {database, DB},
1120
                   {user, Username},
1121
                   {password, Password},
1122
                   {port, Port},
1123
                   {transport, Transport},
1124
                   {connect_timeout, ConnectTimeout},
1125
                   {as_binary, true}|SSLOpts]).
1126

1127
%% Convert PostgreSQL query result to Erlang ODBC result formalism
1128
pgsql_to_odbc({ok, PGSQLResult}) ->
UNCOV
1129
    case PGSQLResult of
4,734✔
UNCOV
1130
      [Item] -> pgsql_item_to_odbc(Item);
4,734✔
1131
      Items -> [pgsql_item_to_odbc(Item) || Item <- Items]
×
1132
    end.
1133

1134
pgsql_item_to_odbc({<<"SELECT", _/binary>>, Rows,
1135
                    Recs}) ->
UNCOV
1136
    {selected, [element(1, Row) || Row <- Rows], Recs};
832✔
1137
pgsql_item_to_odbc({<<"FETCH", _/binary>>, Rows,
1138
                    Recs}) ->
1139
    {selected, [element(1, Row) || Row <- Rows], Recs};
×
1140
pgsql_item_to_odbc(<<"INSERT ", OIDN/binary>>) ->
1141
    [_OID, N] = str:tokens(OIDN, <<" ">>),
×
1142
    {updated, binary_to_integer(N)};
×
1143
pgsql_item_to_odbc(<<"DELETE ", N/binary>>) ->
UNCOV
1144
    {updated, binary_to_integer(N)};
74✔
1145
pgsql_item_to_odbc(<<"UPDATE ", N/binary>>) ->
1146
    {updated, binary_to_integer(N)};
×
1147
pgsql_item_to_odbc({error, Error}) -> {error, Error};
×
UNCOV
1148
pgsql_item_to_odbc(_) -> {updated, undefined}.
3,828✔
1149

1150
pgsql_execute_to_odbc({ok, {<<"SELECT", _/binary>>, Rows}}) ->
UNCOV
1151
    {selected, [], [[Field || {_, Field} <- Row] || Row <- Rows]};
12,996✔
1152
pgsql_execute_to_odbc({ok, {'INSERT', N}}) ->
UNCOV
1153
    {updated, N};
4,884✔
1154
pgsql_execute_to_odbc({ok, {'DELETE', N}}) ->
UNCOV
1155
    {updated, N};
2,388✔
1156
pgsql_execute_to_odbc({ok, {'UPDATE', N}}) ->
UNCOV
1157
    {updated, N};
8✔
1158
pgsql_execute_to_odbc({error, Error}) -> {error, Error};
×
1159
pgsql_execute_to_odbc(_) -> {updated, undefined}.
×
1160

1161

1162
%% == Native MySQL code
1163

1164
%% part of init/1
1165
%% Open a database connection to MySQL
1166
mysql_connect(Server, Port, DB, Username, Password, ConnectTimeout, Transport, SSLOpts0) ->
UNCOV
1167
    SSLOpts = case Transport of
2✔
1168
                  ssl ->
1169
                      [ssl_required|SSLOpts0];
×
1170
                  _ ->
UNCOV
1171
                      []
2✔
1172
              end,
UNCOV
1173
    case p1_mysql_conn:start(binary_to_list(Server), Port,
2✔
1174
                             binary_to_list(Username),
1175
                             binary_to_list(Password),
1176
                             binary_to_list(DB),
1177
                             ConnectTimeout, fun log/3, SSLOpts)
1178
        of
1179
        {ok, Ref} ->
UNCOV
1180
            p1_mysql_conn:fetch(
2✔
1181
                Ref, [<<"set names 'utf8mb4' collate 'utf8mb4_bin';">>], self()),
UNCOV
1182
            {ok, Ref};
2✔
1183
        Err -> Err
×
1184
    end.
1185

1186
%% Convert MySQL query result to Erlang ODBC result formalism
1187
mysql_to_odbc({updated, MySQLRes}) ->
UNCOV
1188
    {updated, p1_mysql:get_result_affected_rows(MySQLRes)};
11,066✔
1189
mysql_to_odbc({data, MySQLRes}) ->
UNCOV
1190
    mysql_item_to_odbc(p1_mysql:get_result_field_info(MySQLRes),
16,079✔
1191
                       p1_mysql:get_result_rows(MySQLRes));
1192
mysql_to_odbc({error, MySQLRes})
1193
  when is_binary(MySQLRes) ->
1194
    {error, MySQLRes};
×
1195
mysql_to_odbc({error, MySQLRes})
1196
  when is_list(MySQLRes) ->
1197
    {error, list_to_binary(MySQLRes)};
×
1198
mysql_to_odbc({error, MySQLRes}) ->
1199
    mysql_to_odbc({error, p1_mysql:get_result_reason(MySQLRes)});
×
1200
mysql_to_odbc(ok) ->
1201
    ok.
×
1202

1203

1204
%% When tabular data is returned, convert it to the ODBC formalism
1205
mysql_item_to_odbc(Columns, Recs) ->
UNCOV
1206
    {selected, [element(2, Column) || Column <- Columns], Recs}.
16,079✔
1207

1208
to_odbc({selected, Columns, Rows}) ->
1209
    Rows2 = lists:map(
×
1210
        fun(Row) ->
1211
            Row2 = if is_tuple(Row) -> tuple_to_list(Row);
×
1212
                       is_list(Row) -> Row
×
1213
                   end,
1214
            lists:map(
×
1215
                fun(I) when is_integer(I) -> integer_to_binary(I);
×
1216
                    (B) -> B
×
1217
                end, Row2)
1218
        end, Rows),
1219
    {selected, [list_to_binary(C) || C <- Columns], Rows2};
×
1220
to_odbc({error, Reason}) when is_list(Reason) ->
1221
    {error, list_to_binary(Reason)};
×
1222
to_odbc(Res) ->
1223
    Res.
×
1224

1225
parse_mysql_version(SVersion, DefaultUpsert) ->
UNCOV
1226
    case re:run(SVersion, <<"(\\d+)\\.(\\d+)(?:\\.(\\d+))?(?:-([^-]*))?">>,
2✔
1227
                [{capture, all_but_first, binary}]) of
1228
        {match, [V1, V2, V3, Type]} ->
UNCOV
1229
            V = ((bin_to_int(V1)*1000)+bin_to_int(V2))*1000+bin_to_int(V3),
2✔
UNCOV
1230
            TypeA = binary_to_atom(Type, utf8),
2✔
UNCOV
1231
            Flags = case TypeA of
2✔
1232
                        'MariaDB' -> DefaultUpsert;
×
1233
                        _ when V >= 5007026 andalso V < 8000000 -> 1;
×
UNCOV
1234
                        _ when V >= 8000020 -> 1;
2✔
1235
                        _ -> DefaultUpsert
×
1236
                    end,
UNCOV
1237
            {ok, {V, TypeA, Flags}};
2✔
1238
        {match, [V1, V2, V3]} ->
1239
            V = ((bin_to_int(V1)*1000)+bin_to_int(V2))*1000+bin_to_int(V3),
×
1240
            Flags = case V of
×
1241
                        _ when V >= 5007026 andalso V < 8000000 -> 1;
×
1242
                        _ when V >= 8000020 -> 1;
×
1243
                        _ -> DefaultUpsert
×
1244
                    end,
1245
            {ok, {V, unknown, Flags}};
×
1246
        _ ->
1247
            error
×
1248
    end.
1249

1250
get_db_version(#state{db_type = pgsql} = State) ->
UNCOV
1251
    case pgsql:squery(State#state.db_ref,
2✔
1252
                      <<"select current_setting('server_version_num')">>) of
1253
        {ok, [{_, _, [[SVersion]]}]} ->
UNCOV
1254
            case catch binary_to_integer(SVersion) of
2✔
1255
                Version when is_integer(Version) ->
UNCOV
1256
                    State#state{db_version = Version};
2✔
1257
                Error ->
1258
                    ?WARNING_MSG("Error getting pgsql version: ~p", [Error]),
×
1259
                    State
×
1260
            end;
1261
        Res ->
1262
            ?WARNING_MSG("Error getting pgsql version: ~p", [Res]),
×
1263
            State
×
1264
    end;
1265
get_db_version(#state{db_type = mysql, host = Host} = State) ->
UNCOV
1266
    DefaultUpsert = case lists:member(mysql_alternative_upsert, ejabberd_option:sql_flags(Host)) of
2✔
1267
                        true -> 1;
×
UNCOV
1268
                        _ -> 0
2✔
1269
                    end,
UNCOV
1270
    case mysql_to_odbc(p1_mysql_conn:squery(State#state.db_ref,
2✔
1271
                                            [<<"select version();">>], self(),
1272
                                            [{timeout, 5000},
1273
                                             {result_type, binary}])) of
1274
        {selected, _, [SVersion]} ->
UNCOV
1275
            case parse_mysql_version(SVersion, DefaultUpsert) of
2✔
1276
                {ok, V} ->
UNCOV
1277
                    State#state{db_version = V};
2✔
1278
                error ->
1279
                    ?WARNING_MSG("Error parsing mysql version: ~p", [SVersion]),
×
1280
                    State
×
1281
            end;
1282
        Res ->
1283
            ?WARNING_MSG("Error getting mysql version: ~p", [Res]),
×
1284
            State
×
1285
    end;
1286
get_db_version(State) ->
UNCOV
1287
    State.
2✔
1288

1289
bin_to_int(<<>>) -> 0;
×
UNCOV
1290
bin_to_int(V) -> binary_to_integer(V).
6✔
1291

1292
log(Level, Format, Args) ->
UNCOV
1293
    case Level of
8✔
UNCOV
1294
      debug -> ?DEBUG(Format, Args);
8✔
1295
      info -> ?INFO_MSG(Format, Args);
×
1296
      normal -> ?INFO_MSG(Format, Args);
×
1297
      error -> ?ERROR_MSG(Format, Args)
×
1298
    end.
1299

1300
db_opts(Host) ->
UNCOV
1301
    Type = ejabberd_option:sql_type(Host),
12✔
UNCOV
1302
    Server = ejabberd_option:sql_server(Host),
12✔
UNCOV
1303
    Timeout = ejabberd_option:sql_connect_timeout(Host),
12✔
UNCOV
1304
    Transport = case ejabberd_option:sql_ssl(Host) of
12✔
UNCOV
1305
                    false -> tcp;
12✔
1306
                    true -> ssl
×
1307
                end,
UNCOV
1308
    warn_if_ssl_unsupported(Transport, Type),
12✔
UNCOV
1309
    case Type of
12✔
1310
        odbc ->
1311
            [odbc, Server, Timeout];
×
1312
        sqlite ->
UNCOV
1313
            [sqlite, Host];
4✔
1314
        _ ->
UNCOV
1315
            Port = ejabberd_option:sql_port(Host),
8✔
UNCOV
1316
            DB = case ejabberd_option:sql_database(Host) of
8✔
1317
                     undefined -> <<"ejabberd">>;
×
UNCOV
1318
                     D -> D
8✔
1319
                 end,
UNCOV
1320
            User = ejabberd_option:sql_username(Host),
8✔
UNCOV
1321
            Pass = ejabberd_option:sql_password(Host),
8✔
UNCOV
1322
            SSLOpts = get_ssl_opts(Transport, Host),
8✔
UNCOV
1323
            case Type of
8✔
1324
                mssql ->
1325
                    case odbc_server_is_connstring(Server) of
×
1326
                        true ->
1327
                            [mssql, Server, Timeout];
×
1328
                        false ->
1329
                            Encryption = case Transport of
×
1330
                                tcp -> <<"">>;
×
1331
                                ssl -> <<";ENCRYPTION=require;ENCRYPT=yes">>
×
1332
                            end,
1333
                            [mssql, <<"DRIVER=ODBC;SERVER=", Server/binary, ";DATABASE=", DB/binary,
×
1334
                                      ";UID=", User/binary, ";PWD=", Pass/binary,
1335
                                      ";PORT=", (integer_to_binary(Port))/binary, Encryption/binary,
1336
                                      ";CLIENT_CHARSET=UTF-8;">>, Timeout]
1337
                    end;
1338
                _ ->
UNCOV
1339
                    [Type, Server, Port, DB, User, Pass, Timeout, Transport, SSLOpts]
8✔
1340
            end
1341
    end.
1342

1343
warn_if_ssl_unsupported(tcp, _) ->
UNCOV
1344
    ok;
12✔
1345
warn_if_ssl_unsupported(ssl, pgsql) ->
1346
    ok;
×
1347
warn_if_ssl_unsupported(ssl, mssql) ->
1348
    ok;
×
1349
warn_if_ssl_unsupported(ssl, mysql) ->
1350
    ok;
×
1351
warn_if_ssl_unsupported(ssl, Type) ->
1352
    ?WARNING_MSG("SSL connection is not supported for ~ts", [Type]).
×
1353

1354
get_ssl_opts(ssl, Host) ->
1355
    Opts1 = case ejabberd_option:sql_ssl_certfile(Host) of
×
1356
                undefined -> [];
×
1357
                CertFile -> [{certfile, CertFile}]
×
1358
            end,
1359
    Opts2 = case ejabberd_option:sql_ssl_cafile(Host) of
×
1360
                undefined -> Opts1;
×
1361
                CAFile -> [{cacertfile, CAFile}|Opts1]
×
1362
            end,
1363
    case ejabberd_option:sql_ssl_verify(Host) of
×
1364
        true ->
1365
            case lists:keymember(cacertfile, 1, Opts2) of
×
1366
                true ->
1367
                    [{verify, verify_peer}|Opts2];
×
1368
                false ->
1369
                    ?WARNING_MSG("SSL verification is enabled for "
×
1370
                                 "SQL connection, but option "
1371
                                 "'sql_ssl_cafile' is not set; "
1372
                                 "verification will be disabled", []),
×
1373
                    Opts2
×
1374
            end;
1375
        false ->
1376
            [{verify, verify_none}|Opts2]
×
1377
    end;
1378
get_ssl_opts(tcp, _) ->
UNCOV
1379
    [].
8✔
1380

1381
init_mssql_odbcinst(Host) ->
1382
    Driver = ejabberd_option:sql_odbc_driver(Host),
×
1383
    ODBCINST = io_lib:fwrite("[ODBC]~n"
×
1384
                             "Driver = ~s~n", [Driver]),
1385
    ?DEBUG("~ts:~n~ts", [odbcinst_config(), ODBCINST]),
×
1386
    case filelib:ensure_dir(odbcinst_config()) of
×
1387
        ok ->
1388
            try
×
1389
                ok = write_file_if_new(odbcinst_config(), ODBCINST),
×
1390
                os:putenv("ODBCSYSINI", tmp_dir()),
×
1391
                ok
×
1392
            catch error:{badmatch, {error, Reason} = Err} ->
1393
                    ?ERROR_MSG("Failed to create temporary files in ~ts: ~ts",
×
1394
                               [tmp_dir(), file:format_error(Reason)]),
×
1395
                    Err
×
1396
            end;
1397
        {error, Reason} = Err ->
1398
            ?ERROR_MSG("Failed to create temporary directory ~ts: ~ts",
×
1399
                       [tmp_dir(), file:format_error(Reason)]),
×
1400
            Err
×
1401
    end.
1402

1403
init_mssql(Host) ->
1404
    Server = ejabberd_option:sql_server(Host),
×
1405
    case odbc_server_is_connstring(Server) of
×
1406
        true -> ok;
×
1407
        false -> init_mssql_odbcinst(Host)
×
1408
    end.
1409

1410
odbc_server_is_connstring(Server) ->
1411
    case binary:match(Server, <<"=">>) of
×
1412
        nomatch -> false;
×
1413
        _ -> true
×
1414
    end.
1415

1416
write_file_if_new(File, Payload) ->
1417
    case filelib:is_file(File) of
×
1418
        true -> ok;
×
1419
        false -> file:write_file(File, Payload)
×
1420
    end.
1421

1422
tmp_dir() ->
1423
    case os:type() of
11✔
1424
        {win32, _} -> filename:join([misc:get_home(), "conf"]);
×
1425
        _ -> filename:join(["/tmp", "ejabberd"])
11✔
1426
    end.
1427

1428
odbcinst_config() ->
1429
    filename:join(tmp_dir(), "odbcinst.ini").
11✔
1430

1431
max_fsm_queue() ->
UNCOV
1432
    proplists:get_value(max_queue, fsm_limit_opts(), unlimited).
6✔
1433

1434
fsm_limit_opts() ->
UNCOV
1435
    ejabberd_config:fsm_limit_opts([]).
12✔
1436

1437
query_timeout(LServer) ->
UNCOV
1438
    ejabberd_option:sql_query_timeout(LServer).
111,163✔
1439

1440
current_time() ->
UNCOV
1441
    erlang:monotonic_time(millisecond).
132,999✔
1442

1443
%% ***IMPORTANT*** This error format requires extended_errors turned on.
1444
extended_error({"08S01", _, Reason}) ->
1445
    % TCP Provider: The specified network name is no longer available
1446
    ?DEBUG("ODBC Link Failure: ~ts", [Reason]),
×
1447
    <<"Communication link failure">>;
×
1448
extended_error({"08001", _, Reason}) ->
1449
    % Login timeout expired
1450
    ?DEBUG("ODBC Connect Timeout: ~ts", [Reason]),
×
1451
    <<"SQL connection failed">>;
×
1452
extended_error({"IMC01", _, Reason}) ->
1453
    % The connection is broken and recovery is not possible
1454
    ?DEBUG("ODBC Link Failure: ~ts", [Reason]),
×
1455
    <<"Communication link failure">>;
×
1456
extended_error({"IMC06", _, Reason}) ->
1457
    % The connection is broken and recovery is not possible
1458
    ?DEBUG("ODBC Link Failure: ~ts", [Reason]),
×
1459
    <<"Communication link failure">>;
×
1460
extended_error({Code, _, Reason}) ->
1461
    ?DEBUG("ODBC Error ~ts: ~ts", [Code, Reason]),
×
1462
    iolist_to_binary(Reason);
×
1463
extended_error(Error) ->
1464
    Error.
×
1465

1466
check_error({error, Why} = Err, _Query) when Why == killed ->
1467
    Err;
×
1468
check_error({error, Why}, #sql_query{} = Query) ->
1469
    Err = extended_error(Why),
×
1470
    ?ERROR_MSG("SQL query '~ts' at ~p failed: ~p",
×
1471
               [Query#sql_query.hash, Query#sql_query.loc, Err]),
×
1472
    {error, Err};
×
1473
check_error({error, Why}, Query) ->
1474
    Err = extended_error(Why),
×
1475
    case catch iolist_to_binary(Query) of
×
1476
        SQuery when is_binary(SQuery) ->
1477
            ?ERROR_MSG("SQL query '~ts' failed: ~p", [SQuery, Err]);
×
1478
        _ ->
1479
            ?ERROR_MSG("SQL query ~p failed: ~p", [Query, Err])
×
1480
    end,
1481
    {error, Err};
×
1482
check_error(Result, _Query) ->
UNCOV
1483
    Result.
97,793✔
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc