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

processone / ejabberd / 1212

18 Nov 2025 12:37PM UTC coverage: 33.784% (+0.003%) from 33.781%
1212

push

github

badlop
mod_conversejs: Improve link to conversejs in WebAdmin (#4495)

Until now, the WebAdmin menu included a link to the first request handler
with mod_conversejs that the admin configured in ejabberd.yml
That link included the authentication credentials hashed as URI arguments
if using HTTPS. Then process/2 extracted those arguments and passed them
as autologin options to Converse.

From now, mod_conversejs automatically adds a request_handler nested in
webadmin subpath. The webadmin menu links to that converse URI; this allows
to access the HTTP auth credentials, no need to explicitly pass them.
process/2 extracts this HTTP auth and passes autologin options to Converse.
Now scram password storage is supported too.

This minimum configuration allows WebAdmin to access Converse:

listen:
  -
    port: 5443
    module: ejabberd_http
    tls: true
    request_handlers:
      /admin: ejabberd_web_admin
      /ws: ejabberd_http_ws
modules:
  mod_conversejs:
    conversejs_resources: "/home/conversejs/12.0.0/dist"

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

11290 existing lines in 174 files now uncovered.

15515 of 45924 relevant lines covered (33.78%)

1277.8 hits per line

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

44.99
/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-2025   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
         sqlite_db/1,
56
         sqlite_file/1,
57
         encode_term/1,
58
         decode_term/1,
59
         odbcinst_config/0,
60
         init_mssql/1,
61
         keep_alive/2,
62
         to_list/2,
63
         to_array/2,
64
         parse_mysql_version/2]).
65

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

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

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

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

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

96

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

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

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

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

141
-spec sql_query(binary(), sql_query(T), pos_integer()) -> sql_query_result(T).
142
sql_query(Host, Query, Timeout) ->
UNCOV
143
    sql_call(Host, {sql_query, Query}, Timeout).
38,791✔
144

145
-spec sql_query(binary(), sql_query(T)) -> sql_query_result(T).
146
sql_query(Host, Query) ->
UNCOV
147
    sql_query(Host, Query, query_timeout(Host)).
38,791✔
148

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

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

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

179
sql_bloc(Host, F) ->
UNCOV
180
    sql_bloc(Host, F, query_timeout(Host)).
6,258✔
181

182
sql_call(Host, Msg, Timeout) ->
UNCOV
183
    case get(?STATE_KEY) of
51,485✔
184
        undefined ->
UNCOV
185
            sync_send_event(Host,
51,387✔
186
                            {sql_cmd, Msg, current_time() + Timeout},
187
                            Timeout);
188
        _State ->
UNCOV
189
            nested_op(Msg)
98✔
190
    end.
191

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

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

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

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

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

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

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

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

264
escape_like_arg(S) when is_binary(S) ->
UNCOV
265
    << <<(escape_like_arg(C))/binary>> || <<C>> <= S >>;
2,156✔
UNCOV
266
escape_like_arg($%) -> <<"\\%">>;
1,274✔
UNCOV
267
escape_like_arg($_) -> <<"\\_">>;
2,534✔
UNCOV
268
escape_like_arg($\\) -> <<"\\\\">>;
1,274✔
UNCOV
269
escape_like_arg($[) -> <<"\\[">>;     % For MSSQL
1,274✔
UNCOV
270
escape_like_arg($]) -> <<"\\]">>;
1,274✔
UNCOV
271
escape_like_arg(C) when is_integer(C), C >= 0, C =< 255 -> <<C>>.
68,143✔
272

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

282
to_bool(<<"t">>) -> true;
×
283
to_bool(<<"true">>) -> true;
×
UNCOV
284
to_bool(<<"1">>) -> true;
1,187✔
285
to_bool(true) -> true;
×
UNCOV
286
to_bool(1) -> true;
584✔
UNCOV
287
to_bool(_) -> false.
5,136✔
288

289
to_list(EscapeFun, Val) ->
290
    Escaped = lists:join(<<",">>, lists:map(EscapeFun, Val)),
×
291
    [<<"(">>, Escaped, <<")">>].
×
292

293
to_array(EscapeFun, Val) ->
294
    Escaped = lists:join(<<",">>, lists:map(EscapeFun, Val)),
×
295
    lists:flatten([<<"{">>, Escaped, <<"}">>]).
×
296

297
to_string_literal(odbc, S) ->
298
    <<"'", (escape(S))/binary, "'">>;
×
299
to_string_literal(mysql, S) ->
UNCOV
300
    <<"'", (escape(S))/binary, "'">>;
844✔
301
to_string_literal(mssql, S) ->
302
    <<"'", (standard_escape(S))/binary, "'">>;
×
303
to_string_literal(sqlite, S) ->
UNCOV
304
    <<"'", (standard_escape(S))/binary, "'">>;
1,266✔
305
to_string_literal(pgsql, S) ->
UNCOV
306
    <<"E'", (escape(S))/binary, "'">>.
844✔
307

308
to_string_literal_t(S) ->
UNCOV
309
    State = get(?STATE_KEY),
35✔
UNCOV
310
    to_string_literal(State#state.db_type, S).
35✔
311

312
encode_term(Term) ->
313
    escape(list_to_binary(
×
314
             erl_prettypr:format(erl_syntax:abstract(Term),
315
                                 [{paper, 65535}, {ribbon, 65535}]))).
316

317
decode_term(Bin) ->
UNCOV
318
    Str = binary_to_list(<<Bin/binary, ".">>),
3,930✔
UNCOV
319
    try
3,930✔
UNCOV
320
        {ok, Tokens, _} = erl_scan:string(Str),
3,930✔
UNCOV
321
        {ok, Term} = erl_parse:parse_term(Tokens),
3,930✔
UNCOV
322
        Term
3,930✔
323
    catch _:{badmatch, {error, {Line, Mod, Reason}, _}} ->
324
            ?ERROR_MSG("Corrupted Erlang term in SQL database:~n"
×
325
                       "** Scanner error: at line ~B: ~ts~n"
326
                       "** Term: ~ts",
327
                       [Line, Mod:format_error(Reason), Bin]),
×
328
            erlang:error(badarg);
×
329
          _:{badmatch, {error, {Line, Mod, Reason}}} ->
330
            ?ERROR_MSG("Corrupted Erlang term in SQL database:~n"
×
331
                       "** Parser error: at line ~B: ~ts~n"
332
                       "** Term: ~ts",
333
                       [Line, Mod:format_error(Reason), Bin]),
×
334
            erlang:error(badarg)
×
335
    end.
336

337
-spec sqlite_db(binary()) -> atom().
338
sqlite_db(Host) ->
UNCOV
339
    list_to_atom("ejabberd_sqlite_" ++ binary_to_list(Host)).
55,860✔
340

341
-spec sqlite_file(binary()) -> string().
342
sqlite_file(Host) ->
UNCOV
343
    case ejabberd_option:sql_database(Host) of
6✔
344
        undefined ->
UNCOV
345
            Path = ["sqlite", atom_to_list(node()),
6✔
346
                    binary_to_list(Host), "ejabberd.db"],
UNCOV
347
            case file:get_cwd() of
6✔
348
                {ok, Cwd} ->
UNCOV
349
                    filename:join([Cwd|Path]);
6✔
350
                {error, Reason} ->
351
                    ?ERROR_MSG("Failed to get current directory: ~ts",
×
352
                               [file:format_error(Reason)]),
×
353
                    filename:join(Path)
×
354
            end;
355
        File ->
356
            binary_to_list(File)
×
357
    end.
358

359
use_multihost_schema() ->
UNCOV
360
    ejabberd_option:sql_schema_multihost().
40,544✔
361

362
use_new_schema() ->
363
    use_multihost_schema().
×
364

365
-spec get_worker(binary()) -> atom().
366
get_worker(Host) ->
UNCOV
367
    PoolSize = ejabberd_option:sql_pool_size(Host),
51,387✔
UNCOV
368
    I = p1_rand:round_robin(PoolSize) + 1,
51,387✔
UNCOV
369
    binary_to_existing_atom(get_worker_name(Host, I), utf8).
51,387✔
370

371
-spec get_worker_name(binary(), pos_integer()) -> binary().
372
get_worker_name(Host, I) ->
UNCOV
373
    <<"ejabberd_sql_", Host/binary, $_, (integer_to_binary(I))/binary>>.
51,394✔
374

375
%%%----------------------------------------------------------------------
376
%%% Callback functions from gen_fsm
377
%%%----------------------------------------------------------------------
378
init([Host]) ->
UNCOV
379
    process_flag(trap_exit, true),
7✔
UNCOV
380
    case ejabberd_option:sql_keepalive_interval(Host) of
7✔
381
        undefined ->
UNCOV
382
            ok;
7✔
383
        KeepaliveInterval ->
384
            timer:apply_interval(KeepaliveInterval, ?MODULE,
×
385
                                 keep_alive, [Host, self()])
386
    end,
UNCOV
387
    [DBType | _] = db_opts(Host),
7✔
UNCOV
388
    p1_fsm:send_event(self(), connect),
7✔
UNCOV
389
    QueueType = ejabberd_option:sql_queue_type(Host),
7✔
UNCOV
390
    {ok, connecting,
7✔
391
     #state{db_type = DBType, host = Host,
392
            pending_requests = p1_queue:new(QueueType, max_fsm_queue()),
393
            timeout = query_timeout(Host)}}.
394

395
connecting(connect, #state{host = Host} = State) ->
UNCOV
396
    ConnectRes = case db_opts(Host) of
7✔
UNCOV
397
                     [mysql | Args] -> apply(fun mysql_connect/8, Args);
2✔
UNCOV
398
                     [pgsql | Args] -> apply(fun pgsql_connect/8, Args);
2✔
UNCOV
399
                     [sqlite | Args] -> apply(fun sqlite_connect/1, Args);
3✔
400
                     [mssql | Args] -> apply(fun odbc_connect/2, Args);
×
401
                     [odbc | Args] -> apply(fun odbc_connect/2, Args)
×
402
                 end,
UNCOV
403
    case ConnectRes of
7✔
404
        {ok, Ref} ->
UNCOV
405
            try link(Ref) of
7✔
406
                _ ->
UNCOV
407
                    lists:foreach(
7✔
408
                      fun({{?PREPARE_KEY, _} = Key, _}) ->
409
                              erase(Key);
×
410
                         (_) ->
UNCOV
411
                              ok
21✔
412
                      end, get()),
UNCOV
413
                    PendingRequests =
7✔
414
                        p1_queue:dropwhile(
415
                          fun(Req) ->
416
                                  p1_fsm:send_event(self(), Req),
×
417
                                  true
×
418
                          end, State#state.pending_requests),
UNCOV
419
                    State1 = State#state{db_ref = Ref,
7✔
420
                                         pending_requests = PendingRequests},
UNCOV
421
                    State2 = get_db_version(State1),
7✔
UNCOV
422
                    {next_state, session_established, State2#state{reconnect_count = 0}}
7✔
423
            catch _:Reason ->
424
                    handle_reconnect(Reason, State)
×
425
            end;
426
        {error, Reason} ->
427
            handle_reconnect(Reason, State)
×
428
    end;
429
connecting(Event, State) ->
430
    ?WARNING_MSG("Unexpected event in 'connecting': ~p",
×
431
                 [Event]),
×
432
    {next_state, connecting, State}.
×
433

434
connecting({sql_cmd, {sql_query, ?KEEPALIVE_QUERY}, Timestamp},
435
           From, State) ->
436
    reply(From, {error, <<"SQL connection failed">>}, Timestamp),
×
437
    {next_state, connecting, State};
×
438
connecting({sql_cmd, Command, Timestamp} = Req, From,
439
           State) ->
440
    ?DEBUG("Queuing pending request while connecting:~n\t~p",
×
441
           [Req]),
×
442
    PendingRequests =
×
443
        try p1_queue:in({sql_cmd, Command, From, Timestamp},
×
444
                        State#state.pending_requests)
445
        catch error:full ->
446
                Err = <<"SQL request queue is overfilled">>,
×
447
                ?ERROR_MSG("~ts, bouncing all pending requests", [Err]),
×
448
                Q = p1_queue:dropwhile(
×
449
                      fun({sql_cmd, _, To, TS}) ->
450
                              reply(To, {error, Err}, TS),
×
451
                              true
×
452
                      end, State#state.pending_requests),
453
                p1_queue:in({sql_cmd, Command, From, Timestamp}, Q)
×
454
        end,
455
    {next_state, connecting,
×
456
     State#state{pending_requests = PendingRequests}};
457
connecting(Request, {Who, _Ref}, State) ->
458
    ?WARNING_MSG("Unexpected call ~p from ~p in 'connecting'",
×
459
                 [Request, Who]),
×
460
    {next_state, connecting, State}.
×
461

462
session_established({sql_cmd, Command, Timestamp}, From,
463
                    State) ->
UNCOV
464
    run_sql_cmd(Command, From, State, Timestamp);
51,387✔
465
session_established(Request, {Who, _Ref}, State) ->
466
    ?WARNING_MSG("Unexpected call ~p from ~p in 'session_established'",
×
467
                 [Request, Who]),
×
468
    {next_state, session_established, State}.
×
469

470
session_established({sql_cmd, Command, From, Timestamp},
471
                    State) ->
472
    run_sql_cmd(Command, From, State, Timestamp);
×
473
session_established(force_timeout, State) ->
474
    {stop, timeout, State};
×
475
session_established(Event, State) ->
476
    ?WARNING_MSG("Unexpected event in 'session_established': ~p",
×
477
                 [Event]),
×
478
    {next_state, session_established, State}.
×
479

480
handle_event(_Event, StateName, State) ->
481
    {next_state, StateName, State}.
×
482

483
handle_sync_event(_Event, _From, StateName, State) ->
484
    {reply, {error, badarg}, StateName, State}.
×
485

486
code_change(_OldVsn, StateName, State, _Extra) ->
487
    {ok, StateName, State}.
×
488

489
handle_info({'EXIT', _Pid, _Reason}, connecting, State) ->
490
    {next_state, connecting, State};
×
491
handle_info({'EXIT', _Pid, Reason}, _StateName, State) ->
492
    handle_reconnect(Reason, State);
×
493
handle_info(Info, StateName, State) ->
494
    ?WARNING_MSG("Unexpected info in ~p: ~p",
×
495
                 [StateName, Info]),
×
496
    {next_state, StateName, State}.
×
497

498
terminate(_Reason, _StateName, State) ->
UNCOV
499
    case State#state.db_type of
7✔
UNCOV
500
        mysql -> catch p1_mysql_conn:stop(State#state.db_ref);
2✔
UNCOV
501
        sqlite -> catch sqlite3:close(sqlite_db(State#state.host));
3✔
UNCOV
502
        _ -> ok
2✔
503
    end,
UNCOV
504
    ok.
7✔
505

506
%%----------------------------------------------------------------------
507
%% Func: print_state/1
508
%% Purpose: Prepare the state to be printed on error log
509
%% Returns: State to print
510
%%----------------------------------------------------------------------
511
print_state(State) -> State.
×
512

513
%%%----------------------------------------------------------------------
514
%%% Internal functions
515
%%%----------------------------------------------------------------------
516
handle_reconnect(Reason, #state{host = Host, reconnect_count = RC} = State) ->
517
    StartInterval0 = ejabberd_option:sql_start_interval(Host),
×
518
    StartInterval = case RC of
×
519
                        0 -> erlang:min(5000, StartInterval0);
×
520
                        _ -> StartInterval0
×
521
                    end,
522
    ?WARNING_MSG("~p connection failed:~n"
×
523
                 "** Reason: ~p~n"
524
                 "** Retry after: ~B seconds",
525
                 [State#state.db_type, Reason,
526
                  StartInterval div 1000]),
×
527
    case State#state.db_type of
×
528
        mysql -> catch p1_mysql_conn:stop(State#state.db_ref);
×
529
        sqlite -> catch sqlite3:close(sqlite_db(State#state.host));
×
530
        pgsql -> catch pgsql:terminate(State#state.db_ref);
×
531
        _ -> ok
×
532
    end,
533
    p1_fsm:send_event_after(StartInterval, connect),
×
534
    {next_state, connecting, State#state{reconnect_count = RC + 1,
×
535
                                         timeout = query_timeout(Host)}}.
536

537
run_sql_cmd(Command, From, State, Timestamp) ->
UNCOV
538
    CT = current_time(),
51,387✔
UNCOV
539
    case CT >= Timestamp of
51,387✔
540
        true ->
541
            State1 = report_overload(State),
×
542
            {next_state, session_established, State1};
×
543
        false ->
UNCOV
544
            receive
51,387✔
545
                {'EXIT', _Pid, Reason} ->
546
                    PR = p1_queue:in({sql_cmd, Command, From, Timestamp},
×
547
                                     State#state.pending_requests),
548
                    handle_reconnect(Reason, State#state{pending_requests = PR})
×
549
            after 0 ->
UNCOV
550
                Timeout = min(query_timeout(State#state.host), Timestamp - CT),
51,387✔
UNCOV
551
                put(?NESTING_KEY, ?TOP_LEVEL_TXN),
51,387✔
UNCOV
552
                put(?STATE_KEY, State#state{timeout = Timeout}),
51,387✔
UNCOV
553
                abort_on_driver_error(outer_op(Command), From, Timestamp)
51,387✔
554
            end
555
    end.
556

557
%% @doc Only called by handle_call, only handles top level operations.
558
-spec outer_op(Op::{atom(), binary()} | {sql_transaction, binary(), pos_integer()}) ->
559
    {error, Reason::binary()} | {aborted, Reason::binary()} | {atomic, Result::any()}.
560
outer_op({sql_query, Query}) ->
UNCOV
561
    sql_query_internal(Query);
38,770✔
562
outer_op({sql_transaction, F, Restarts}) ->
UNCOV
563
    outer_transaction(F, Restarts, <<"">>);
6,422✔
UNCOV
564
outer_op({sql_bloc, F}) -> execute_bloc(F).
6,195✔
565

566
%% Called via sql_query/transaction/bloc from client code when inside a
567
%% nested operation
568
nested_op({sql_query, Query}) ->
UNCOV
569
    sql_query_internal(Query);
21✔
570
nested_op({sql_transaction, F, Restarts}) ->
UNCOV
571
    NestingLevel = get(?NESTING_KEY),
14✔
UNCOV
572
    if NestingLevel =:= (?TOP_LEVEL_TXN) ->
14✔
UNCOV
573
        outer_transaction(F, Restarts, <<"">>);
7✔
UNCOV
574
        true -> inner_transaction(F)
7✔
575
    end;
UNCOV
576
nested_op({sql_bloc, F}) -> execute_bloc(F).
63✔
577

578
%% Never retry nested transactions - only outer transactions
579
inner_transaction(F) ->
UNCOV
580
    PreviousNestingLevel = get(?NESTING_KEY),
7✔
UNCOV
581
    case get(?NESTING_KEY) of
7✔
582
      ?TOP_LEVEL_TXN ->
583
          {backtrace, T} = process_info(self(), backtrace),
×
584
          ?ERROR_MSG("Inner transaction called at outer txn "
×
585
                     "level. Trace: ~ts",
586
                     [T]),
×
587
          erlang:exit(implementation_faulty);
×
UNCOV
588
      _N -> ok
7✔
589
    end,
UNCOV
590
    put(?NESTING_KEY, PreviousNestingLevel + 1),
7✔
UNCOV
591
    Result = (catch F()),
7✔
UNCOV
592
    put(?NESTING_KEY, PreviousNestingLevel),
7✔
UNCOV
593
    case Result of
7✔
594
      {aborted, Reason} -> {aborted, Reason};
×
595
      {'EXIT', Reason} -> {'EXIT', Reason};
×
596
      {atomic, Res} -> {atomic, Res};
×
UNCOV
597
      Res -> {atomic, Res}
7✔
598
    end.
599

600
outer_transaction(F, NRestarts, _Reason) ->
UNCOV
601
    PreviousNestingLevel = get(?NESTING_KEY),
6,429✔
UNCOV
602
    case get(?NESTING_KEY) of
6,429✔
UNCOV
603
      ?TOP_LEVEL_TXN -> ok;
6,429✔
604
      _N ->
605
          {backtrace, T} = process_info(self(), backtrace),
×
606
          ?ERROR_MSG("Outer transaction called at inner txn "
×
607
                     "level. Trace: ~ts",
608
                     [T]),
×
609
          erlang:exit(implementation_faulty)
×
610
    end,
UNCOV
611
    case sql_begin() of
6,429✔
612
        {error, Reason} ->
613
            maybe_restart_transaction(F, NRestarts, Reason, false);
×
614
        _ ->
UNCOV
615
            put(?NESTING_KEY, PreviousNestingLevel + 1),
6,429✔
UNCOV
616
            try F() of
6,429✔
617
                Res ->
UNCOV
618
                    case sql_commit() of
6,429✔
619
                        {error, Reason} ->
620
                            restart(Reason);
×
621
                        _ ->
UNCOV
622
                            {atomic, Res}
6,429✔
623
                    end
624
            catch
625
                throw:{aborted, Reason}:_ when NRestarts > 0 ->
626
                    maybe_restart_transaction(F, NRestarts, Reason, true);
×
627
                throw:{aborted, Reason}:StackTrace when NRestarts =:= 0 ->
628
                    ?ERROR_MSG("SQL transaction restarts exceeded~n** "
×
629
                               "Restarts: ~p~n** Last abort reason: "
630
                               "~p~n** Stacktrace: ~p~n** When State "
631
                               "== ~p",
632
                               [?MAX_TRANSACTION_RESTARTS,
633
                                Reason,
634
                                StackTrace,
635
                                get(?STATE_KEY)]),
×
636
                    maybe_restart_transaction(F, NRestarts, Reason, true);
×
637
                _:Reason:_ ->
638
                    maybe_restart_transaction(F, 0, Reason, true)
×
639
            end
640
    end.
641

642
maybe_restart_transaction(F, NRestarts, Reason, DoRollback) ->
643
    Res = case driver_restart_required(Reason) of
×
644
              true ->
645
                  {aborted, Reason};
×
646
              _ when DoRollback ->
647
                  case sql_rollback() of
×
648
                      {error, Reason2} ->
649
                          case driver_restart_required(Reason2) of
×
650
                              true ->
651
                                  {aborted, Reason2};
×
652
                              _ ->
653
                                  continue
×
654
                          end;
655
                      _ ->
656
                          continue
×
657
                  end;
658
              _ ->
659
                  continue
×
660
    end,
661
    case Res of
×
662
        continue when NRestarts > 0 ->
663
            put(?NESTING_KEY, ?TOP_LEVEL_TXN),
×
664
            outer_transaction(F, NRestarts - 1, Reason);
×
665
        continue ->
666
            {aborted, Reason};
×
667
        Other ->
668
            Other
×
669
    end.
670

671
execute_bloc(F) ->
UNCOV
672
    case catch F() of
6,258✔
673
      {aborted, Reason} -> {aborted, Reason};
×
674
      {'EXIT', Reason} -> {aborted, Reason};
×
UNCOV
675
      Res -> {atomic, Res}
6,258✔
676
    end.
677

678
execute_fun(F) when is_function(F, 0) ->
UNCOV
679
    F();
151✔
680
execute_fun(F) when is_function(F, 2) ->
UNCOV
681
    State = get(?STATE_KEY),
8,702✔
UNCOV
682
    F(State#state.db_type, State#state.db_version).
8,702✔
683

684
sql_query_internal([{_, _} | _] = Queries) ->
UNCOV
685
    State = get(?STATE_KEY),
12,858✔
UNCOV
686
    case select_sql_query(Queries, State) of
12,858✔
687
        undefined ->
688
            {error, <<"no matching query for the current DBMS found">>};
×
689
        Query ->
UNCOV
690
            sql_query_internal(Query)
12,858✔
691
    end;
692
sql_query_internal(#sql_query{} = Query) ->
UNCOV
693
    State = get(?STATE_KEY),
73,524✔
UNCOV
694
    Res =
73,524✔
695
        try
UNCOV
696
            case State#state.db_type of
73,524✔
697
                odbc ->
698
                    generic_sql_query(Query);
×
699
                mssql ->
700
                    mssql_sql_query(Query);
×
701
                pgsql ->
UNCOV
702
                    Key = {?PREPARE_KEY, Query#sql_query.hash},
20,279✔
UNCOV
703
                    case get(Key) of
20,279✔
704
                        undefined ->
UNCOV
705
                            Host = State#state.host,
274✔
UNCOV
706
                            PreparedStatements =
274✔
707
                                ejabberd_option:sql_prepared_statements(Host),
UNCOV
708
                            case PreparedStatements of
274✔
709
                                false ->
710
                                    put(Key, ignore);
×
711
                                true ->
UNCOV
712
                                    case pgsql_prepare(Query, State) of
274✔
713
                                        {ok, _, _, _} ->
UNCOV
714
                                            put(Key, prepared);
274✔
715
                                        {error, Error} ->
716
                                            ?ERROR_MSG(
×
717
                                               "PREPARE failed for SQL query "
718
                                               "at ~p: ~p",
719
                                               [Query#sql_query.loc, Error]),
×
720
                                            put(Key, ignore)
×
721
                                    end
722
                            end;
723
                        _ ->
UNCOV
724
                            ok
20,005✔
725
                    end,
UNCOV
726
                    case get(Key) of
20,279✔
727
                        prepared ->
UNCOV
728
                            pgsql_execute_sql_query(Query, State);
20,279✔
729
                        _ ->
730
                            pgsql_sql_query(Query)
×
731
                    end;
732
                mysql ->
UNCOV
733
                    case {Query#sql_query.flags, ejabberd_option:sql_prepared_statements(State#state.host)} of
22,400✔
734
                        {1, _} ->
735
                            generic_sql_query(Query);
×
736
                        {_, false} ->
737
                            generic_sql_query(Query);
×
738
                        _ ->
UNCOV
739
                            mysql_prepared_execute(Query, State)
22,400✔
740
                    end;
741
                sqlite ->
UNCOV
742
                    sqlite_sql_query(Query)
30,845✔
743
            end
744
        catch exit:{timeout, _} ->
745
                {error, <<"timed out">>};
×
746
              exit:{killed, _} ->
747
                {error, <<"killed">>};
×
748
              exit:{normal, _} ->
749
                {error, <<"terminated unexpectedly">>};
×
750
              exit:{shutdown, _} ->
751
                {error, <<"shutdown">>};
×
752
            Class:Reason:StackTrace ->
753
                ?ERROR_MSG("Internal error while processing SQL query:~n** ~ts",
×
754
                           [misc:format_exception(2, Class, Reason, StackTrace)]),
×
755
                {error, <<"internal error">>}
×
756
        end,
UNCOV
757
    check_error(Res, Query);
73,524✔
758
sql_query_internal(F) when is_function(F) ->
UNCOV
759
    case catch execute_fun(F) of
8,853✔
760
        {aborted, Reason} -> {error, Reason};
×
761
        {'EXIT', Reason} -> {error, Reason};
×
UNCOV
762
        Res -> Res
8,853✔
763
    end;
764
sql_query_internal(Query) ->
UNCOV
765
    State = get(?STATE_KEY),
47,083✔
UNCOV
766
    ?DEBUG("SQL: \"~ts\"", [Query]),
47,083✔
UNCOV
767
    QueryTimeout = State#state.timeout,
47,083✔
UNCOV
768
    Res = case State#state.db_type of
47,083✔
769
            odbc ->
770
                to_odbc(odbc:sql_query(State#state.db_ref, [Query],
×
771
                                       QueryTimeout - 1000));
772
            mssql ->
773
                to_odbc(odbc:sql_query(State#state.db_ref, [Query],
×
774
                                       QueryTimeout - 1000));
775
            pgsql ->
UNCOV
776
                pgsql_to_odbc(pgsql:squery(State#state.db_ref, Query,
4,734✔
777
                                           QueryTimeout - 1000));
778
            mysql ->
UNCOV
779
                mysql_to_odbc(p1_mysql_conn:squery(State#state.db_ref,
4,736✔
780
                                                   [Query], self(),
781
                                                   [{timeout, QueryTimeout - 1000},
782
                                                    {result_type, binary}]));
783
              sqlite ->
UNCOV
784
                  Host = State#state.host,
37,613✔
UNCOV
785
                  sqlite_to_odbc(Host, sqlite3:sql_exec(sqlite_db(Host), Query))
37,613✔
786
          end,
UNCOV
787
    check_error(Res, Query).
47,083✔
788

789
select_sql_query(Queries, State) ->
UNCOV
790
    select_sql_query(
12,858✔
791
      Queries, State#state.db_type, State#state.db_version, undefined).
792

793
select_sql_query([], _Type, _Version, undefined) ->
794
    undefined;
×
795
select_sql_query([], _Type, _Version, Query) ->
796
    Query;
×
797
select_sql_query([{any, Query} | _], _Type, _Version, _) ->
UNCOV
798
    Query;
12,858✔
799
select_sql_query([{Type, Query} | _], Type, _Version, _) ->
800
    Query;
×
801
select_sql_query([{{Type, _Version1}, Query1} | Rest], Type, undefined, _) ->
802
    select_sql_query(Rest, Type, undefined, Query1);
×
803
select_sql_query([{{Type, Version1}, Query1} | Rest], Type, Version, Query) ->
804
    if
×
805
        Version >= Version1 ->
806
            Query1;
×
807
        true ->
808
            select_sql_query(Rest, Type, Version, Query)
×
809
    end;
810
select_sql_query([{_, _} | Rest], Type, Version, Query) ->
UNCOV
811
    select_sql_query(Rest, Type, Version, Query).
12,858✔
812

813
generic_sql_query(SQLQuery) ->
814
    sql_query_format_res(
×
815
      sql_query_internal(generic_sql_query_format(SQLQuery)),
816
      SQLQuery).
817

818
generic_sql_query_format(SQLQuery) ->
819
    Args = (SQLQuery#sql_query.args)(generic_escape()),
×
820
    (SQLQuery#sql_query.format_query)(Args).
×
821

822
generic_escape() ->
823
    #sql_escape{string = fun(X) -> <<"'", (escape(X))/binary, "'">> end,
×
824
                integer = fun(X) -> misc:i2l(X) end,
×
825
                boolean = fun(true) -> <<"1">>;
×
826
                             (false) -> <<"0">>
×
827
                          end,
828
                in_array_string = fun(X) -> <<"'", (escape(X))/binary, "'">> end,
×
829
                like_escape = fun() -> <<"">> end
×
830
               }.
831

832
pgsql_sql_query(SQLQuery) ->
833
    sql_query_format_res(
×
834
      sql_query_internal(pgsql_sql_query_format(SQLQuery)),
835
      SQLQuery).
836

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

841
pgsql_escape() ->
842
    #sql_escape{string = fun(X) -> <<"E'", (escape(X))/binary, "'">> end,
×
843
                integer = fun(X) -> misc:i2l(X) end,
×
844
                boolean = fun(true) -> <<"'t'">>;
×
845
                             (false) -> <<"'f'">>
×
846
                          end,
847
                in_array_string = fun(X) -> <<"E'", (escape(X))/binary, "'">> end,
×
848
                like_escape = fun() -> <<"ESCAPE E'\\\\'">> end
×
849
               }.
850

851
sqlite_sql_query(SQLQuery) ->
UNCOV
852
    sql_query_format_res(
30,845✔
853
      sql_query_internal(sqlite_sql_query_format(SQLQuery)),
854
      SQLQuery).
855

856
sqlite_sql_query_format(SQLQuery) ->
UNCOV
857
    Args = (SQLQuery#sql_query.args)(sqlite_escape()),
30,845✔
UNCOV
858
    (SQLQuery#sql_query.format_query)(Args).
30,845✔
859

860
sqlite_escape() ->
UNCOV
861
    #sql_escape{string = fun(X) -> <<"'", (standard_escape(X))/binary, "'">> end,
30,845✔
UNCOV
862
                integer = fun(X) -> misc:i2l(X) end,
8,718✔
UNCOV
863
                boolean = fun(true) -> <<"1">>;
345✔
UNCOV
864
                             (false) -> <<"0">>
870✔
865
                          end,
866
                in_array_string = fun(X) -> <<"'", (standard_escape(X))/binary, "'">> end,
×
UNCOV
867
                like_escape = fun() -> <<"ESCAPE '\\'">> end
924✔
868
               }.
869

870
standard_escape(S) ->
UNCOV
871
    << <<(case Char of
77,458✔
UNCOV
872
              $' -> << "''" >>;
27,885✔
UNCOV
873
              _ -> << Char >>
2,796,899✔
UNCOV
874
          end)/binary>> || <<Char>> <= S >>.
77,458✔
875

876
mssql_sql_query(SQLQuery) ->
877
    sqlite_sql_query(SQLQuery).
×
878

879
pgsql_prepare(SQLQuery, State) ->
UNCOV
880
    Escape = #sql_escape{_ = fun(_) -> arg end,
274✔
UNCOV
881
                         like_escape = fun() -> escape end},
12✔
UNCOV
882
    {RArgs, _} =
274✔
883
        lists:foldl(
884
            fun(arg, {Acc, I}) ->
UNCOV
885
                {[<<$$, (integer_to_binary(I))/binary>> | Acc], I + 1};
818✔
886
               (escape, {Acc, I}) ->
UNCOV
887
                   {[<<"ESCAPE E'\\\\'">> | Acc], I};
12✔
888
               (List, {Acc, I}) when is_list(List) ->
889
                   {[<<$$, (integer_to_binary(I))/binary>> | Acc], I + 1}
×
890
            end, {[], 1}, (SQLQuery#sql_query.args)(Escape)),
UNCOV
891
    Args = lists:reverse(RArgs),
274✔
892
    %N = length((SQLQuery#sql_query.args)(Escape)),
893
    %Args = [<<$$, (integer_to_binary(I))/binary>> || I <- lists:seq(1, N)],
UNCOV
894
    Query = (SQLQuery#sql_query.format_query)(Args),
274✔
UNCOV
895
    pgsql:prepare(State#state.db_ref, SQLQuery#sql_query.hash, Query).
274✔
896

897
pgsql_execute_escape() ->
UNCOV
898
    #sql_escape{string = fun(X) -> X end,
20,279✔
UNCOV
899
                integer = fun(X) -> [misc:i2l(X)] end,
5,218✔
UNCOV
900
                boolean = fun(true) -> "1";
230✔
UNCOV
901
                             (false) -> "0"
580✔
902
                          end,
903
                in_array_string = fun(X) -> <<"\"", (escape(X))/binary, "\"">> end,
×
UNCOV
904
                like_escape = fun() -> ignore end
616✔
905
               }.
906

907
pgsql_execute_sql_query(SQLQuery, State) ->
UNCOV
908
    Args = (SQLQuery#sql_query.args)(pgsql_execute_escape()),
20,279✔
UNCOV
909
    Args2 = lists:filter(fun(ignore) -> false; (_) -> true end, Args),
20,279✔
UNCOV
910
    ExecuteRes =
20,279✔
911
        pgsql:execute(State#state.db_ref, SQLQuery#sql_query.hash, Args2),
912
%    {T, ExecuteRes} =
913
%        timer:tc(pgsql, execute, [State#state.db_ref, SQLQuery#sql_query.hash, Args]),
914
%    io:format("T ~ts ~p~n", [SQLQuery#sql_query.hash, T]),
UNCOV
915
    Res = pgsql_execute_to_odbc(ExecuteRes),
20,279✔
UNCOV
916
    sql_query_format_res(Res, SQLQuery).
20,279✔
917

918
mysql_prepared_execute(#sql_query{hash = Hash} = Query, State) ->
UNCOV
919
    ValEsc = #sql_escape{like_escape = fun() -> ignore end, _ = fun(X) -> X end},
22,400✔
UNCOV
920
    TypesEsc = #sql_escape{string = fun(_) -> string end,
22,400✔
UNCOV
921
                           integer = fun(_) -> integer end,
5,842✔
UNCOV
922
                           boolean = fun(_) -> bool end,
810✔
923
                           in_array_string = fun(_) -> string end,
×
UNCOV
924
                           like_escape = fun() -> ignore end},
616✔
UNCOV
925
    Val = [X || X <- (Query#sql_query.args)(ValEsc), X /= ignore],
22,400✔
UNCOV
926
    Types = [X || X <- (Query#sql_query.args)(TypesEsc), X /= ignore],
22,400✔
UNCOV
927
    QueryFn = fun() ->
22,400✔
UNCOV
928
        PrepEsc = #sql_escape{like_escape = fun() -> <<>> end, _ = fun(_) -> <<"?">> end},
340✔
UNCOV
929
        (Query#sql_query.format_query)((Query#sql_query.args)(PrepEsc))
340✔
930
        end,
UNCOV
931
    QueryTimeout = query_timeout(State#state.host),
22,400✔
UNCOV
932
    Res = p1_mysql_conn:prepared_query(State#state.db_ref, QueryFn, Hash, Val, Types,
22,400✔
933
                                       self(), [{timeout, QueryTimeout - 1000}]),
UNCOV
934
    Res2 = mysql_to_odbc(Res),
22,400✔
UNCOV
935
    sql_query_format_res(Res2, Query).
22,400✔
936

937
sql_query_format_res({selected, _, Rows}, SQLQuery) ->
UNCOV
938
    Res =
46,371✔
939
        lists:flatmap(
940
          fun(Row) ->
UNCOV
941
                  try
72,069✔
UNCOV
942
                      [(SQLQuery#sql_query.format_res)(Row)]
72,069✔
943
                  catch
944
                      Class:Reason:StackTrace ->
945
                          ?ERROR_MSG("Error while processing SQL query result:~n"
×
946
                                     "** Row: ~p~n** ~ts",
947
                                     [Row,
948
                                      misc:format_exception(2, Class, Reason, StackTrace)]),
×
949
                          []
×
950
                  end
951
          end, Rows),
UNCOV
952
    {selected, Res};
46,371✔
953
sql_query_format_res(Res, _SQLQuery) ->
UNCOV
954
    Res.
27,153✔
955

956
sql_query_to_iolist(SQLQuery) ->
957
    generic_sql_query_format(SQLQuery).
×
958

959
sql_query_to_iolist(sqlite, SQLQuery) ->
960
    sqlite_sql_query_format(SQLQuery);
×
961
sql_query_to_iolist(_DbType, SQLQuery) ->
962
    generic_sql_query_format(SQLQuery).
×
963

964
sql_begin() ->
UNCOV
965
    sql_query_internal(
6,429✔
966
      [{mssql, [<<"begin transaction;">>]},
967
       {any, [<<"begin;">>]}]).
968

969
sql_commit() ->
UNCOV
970
    sql_query_internal(
6,429✔
971
      [{mssql, [<<"commit transaction;">>]},
972
       {any, [<<"commit;">>]}]).
973

974
sql_rollback() ->
975
    sql_query_internal(
×
976
      [{mssql, [<<"rollback transaction;">>]},
977
       {any, [<<"rollback;">>]}]).
978

979
driver_restart_required(<<"query timed out">>) -> true;
×
980
driver_restart_required(<<"connection closed">>) -> true;
×
981
driver_restart_required(<<"Failed sending data on socket", _/binary>>) -> true;
×
982
driver_restart_required(<<"SQL connection failed">>) -> true;
×
983
driver_restart_required(<<"Communication link failure">>) -> true;
×
984
driver_restart_required(_) -> false.
×
985

986
%% Generate the OTP callback return tuple depending on the driver result.
987
abort_on_driver_error({Tag, Msg} = Reply, From, Timestamp) when Tag == error; Tag == aborted ->
988
    reply(From, Reply, Timestamp),
×
989
    case driver_restart_required(Msg) of
×
990
        true ->
991
            handle_reconnect(Msg, get(?STATE_KEY));
×
992
        _ ->
993
            {next_state, session_established, get(?STATE_KEY)}
×
994
    end;
995
abort_on_driver_error(Reply, From, Timestamp) ->
UNCOV
996
    reply(From, Reply, Timestamp),
51,387✔
UNCOV
997
    {next_state, session_established, get(?STATE_KEY)}.
51,387✔
998

999
-spec report_overload(state()) -> state().
1000
report_overload(#state{overload_reported = PrevTime} = State) ->
1001
    CurrTime = current_time(),
×
1002
    case PrevTime == undefined orelse (CurrTime - PrevTime) > timer:seconds(30) of
×
1003
        true ->
1004
            ?ERROR_MSG("SQL connection pool is overloaded, "
×
1005
                       "discarding stale requests", []),
×
1006
            State#state{overload_reported = current_time()};
×
1007
        false ->
1008
            State
×
1009
    end.
1010

1011
-spec reply({pid(), term()}, term(), integer()) -> term().
1012
reply(From, Reply, Timestamp) ->
UNCOV
1013
    case current_time() >= Timestamp of
51,387✔
1014
        true -> ok;
×
UNCOV
1015
        false -> p1_fsm:reply(From, Reply)
51,387✔
1016
    end.
1017

1018
%% == pure ODBC code
1019

1020
%% part of init/1
1021
%% Open an ODBC database connection
1022
odbc_connect(SQLServer, Timeout) ->
1023
    ejabberd:start_app(odbc),
×
1024
    odbc:connect(binary_to_list(SQLServer),
×
1025
                 [{scrollable_cursors, off},
1026
                  {extended_errors, on},
1027
                  {tuple_row, off},
1028
                  {timeout, Timeout},
1029
                  {binary_strings, on}]).
1030

1031
%% == Native SQLite code
1032

1033
%% part of init/1
1034
%% Open a database connection to SQLite
1035

1036
sqlite_connect(Host) ->
UNCOV
1037
    File = sqlite_file(Host),
3✔
UNCOV
1038
    case filelib:ensure_dir(File) of
3✔
1039
        ok ->
UNCOV
1040
            case sqlite3:open(sqlite_db(Host), [{file, File}]) of
3✔
1041
                {ok, Ref} ->
UNCOV
1042
                    sqlite3:sql_exec(
3✔
1043
                      sqlite_db(Host), "pragma foreign_keys = on"),
UNCOV
1044
                    {ok, Ref};
3✔
1045
                {error, {already_started, Ref}} ->
1046
                    {ok, Ref};
×
1047
                {error, Reason} ->
1048
                    {error, Reason}
×
1049
            end;
1050
        Err ->
1051
            Err
×
1052
    end.
1053

1054
%% Convert SQLite query result to Erlang ODBC result formalism
1055
sqlite_to_odbc(Host, ok) ->
UNCOV
1056
    {updated, sqlite3:changes(sqlite_db(Host))};
12,502✔
1057
sqlite_to_odbc(Host, {rowid, _}) ->
UNCOV
1058
    {updated, sqlite3:changes(sqlite_db(Host))};
5,733✔
1059
sqlite_to_odbc(_Host, [{columns, Columns}, {rows, TRows}]) ->
UNCOV
1060
    Rows = [lists:map(
19,378✔
1061
              fun(I) when is_integer(I) ->
UNCOV
1062
                      integer_to_binary(I);
8,636✔
1063
                 (B) ->
UNCOV
1064
                      B
85,678✔
UNCOV
1065
              end, tuple_to_list(Row)) || Row <- TRows],
19,378✔
UNCOV
1066
    {selected, [list_to_binary(C) || C <- Columns], Rows};
19,378✔
1067
sqlite_to_odbc(_Host, {error, _Code, Reason}) ->
1068
    {error, Reason};
×
1069
sqlite_to_odbc(_Host, _) ->
1070
    {updated, undefined}.
×
1071

1072
%% == Native PostgreSQL code
1073

1074
%% part of init/1
1075
%% Open a database connection to PostgreSQL
1076
pgsql_connect(Server, Port, DB, Username, Password, ConnectTimeout,
1077
              Transport, SSLOpts) ->
UNCOV
1078
    pgsql:connect([{host, Server},
2✔
1079
                   {database, DB},
1080
                   {user, Username},
1081
                   {password, Password},
1082
                   {port, Port},
1083
                   {transport, Transport},
1084
                   {connect_timeout, ConnectTimeout},
1085
                   {as_binary, true}|SSLOpts]).
1086

1087
%% Convert PostgreSQL query result to Erlang ODBC result formalism
1088
pgsql_to_odbc({ok, PGSQLResult}) ->
UNCOV
1089
    case PGSQLResult of
4,734✔
UNCOV
1090
      [Item] -> pgsql_item_to_odbc(Item);
4,734✔
1091
      Items -> [pgsql_item_to_odbc(Item) || Item <- Items]
×
1092
    end.
1093

1094
pgsql_item_to_odbc({<<"SELECT", _/binary>>, Rows,
1095
                    Recs}) ->
UNCOV
1096
    {selected, [element(1, Row) || Row <- Rows], Recs};
832✔
1097
pgsql_item_to_odbc({<<"FETCH", _/binary>>, Rows,
1098
                    Recs}) ->
1099
    {selected, [element(1, Row) || Row <- Rows], Recs};
×
1100
pgsql_item_to_odbc(<<"INSERT ", OIDN/binary>>) ->
1101
    [_OID, N] = str:tokens(OIDN, <<" ">>),
×
1102
    {updated, binary_to_integer(N)};
×
1103
pgsql_item_to_odbc(<<"DELETE ", N/binary>>) ->
UNCOV
1104
    {updated, binary_to_integer(N)};
74✔
1105
pgsql_item_to_odbc(<<"UPDATE ", N/binary>>) ->
1106
    {updated, binary_to_integer(N)};
×
1107
pgsql_item_to_odbc({error, Error}) -> {error, Error};
×
UNCOV
1108
pgsql_item_to_odbc(_) -> {updated, undefined}.
3,828✔
1109

1110
pgsql_execute_to_odbc({ok, {<<"SELECT", _/binary>>, Rows}}) ->
UNCOV
1111
    {selected, [], [[Field || {_, Field} <- Row] || Row <- Rows]};
12,997✔
1112
pgsql_execute_to_odbc({ok, {'INSERT', N}}) ->
UNCOV
1113
    {updated, N};
4,886✔
1114
pgsql_execute_to_odbc({ok, {'DELETE', N}}) ->
UNCOV
1115
    {updated, N};
2,388✔
1116
pgsql_execute_to_odbc({ok, {'UPDATE', N}}) ->
UNCOV
1117
    {updated, N};
8✔
1118
pgsql_execute_to_odbc({error, Error}) -> {error, Error};
×
1119
pgsql_execute_to_odbc(_) -> {updated, undefined}.
×
1120

1121

1122
%% == Native MySQL code
1123

1124
%% part of init/1
1125
%% Open a database connection to MySQL
1126
mysql_connect(Server, Port, DB, Username, Password, ConnectTimeout, Transport, SSLOpts0) ->
UNCOV
1127
    SSLOpts = case Transport of
2✔
1128
                  ssl ->
1129
                      [ssl_required|SSLOpts0];
×
1130
                  _ ->
UNCOV
1131
                      []
2✔
1132
              end,
UNCOV
1133
    case p1_mysql_conn:start(binary_to_list(Server), Port,
2✔
1134
                             binary_to_list(Username),
1135
                             binary_to_list(Password),
1136
                             binary_to_list(DB),
1137
                             ConnectTimeout, fun log/3, SSLOpts)
1138
        of
1139
        {ok, Ref} ->
UNCOV
1140
            p1_mysql_conn:fetch(
2✔
1141
                Ref, [<<"set names 'utf8mb4' collate 'utf8mb4_bin';">>], self()),
UNCOV
1142
            {ok, Ref};
2✔
1143
        Err -> Err
×
1144
    end.
1145

1146
%% Convert MySQL query result to Erlang ODBC result formalism
1147
mysql_to_odbc({updated, MySQLRes}) ->
UNCOV
1148
    {updated, p1_mysql:get_result_affected_rows(MySQLRes)};
11,063✔
1149
mysql_to_odbc({data, MySQLRes}) ->
UNCOV
1150
    mysql_item_to_odbc(p1_mysql:get_result_field_info(MySQLRes),
16,075✔
1151
                       p1_mysql:get_result_rows(MySQLRes));
1152
mysql_to_odbc({error, MySQLRes})
1153
  when is_binary(MySQLRes) ->
1154
    {error, MySQLRes};
×
1155
mysql_to_odbc({error, MySQLRes})
1156
  when is_list(MySQLRes) ->
1157
    {error, list_to_binary(MySQLRes)};
×
1158
mysql_to_odbc({error, MySQLRes}) ->
1159
    mysql_to_odbc({error, p1_mysql:get_result_reason(MySQLRes)});
×
1160
mysql_to_odbc(ok) ->
1161
    ok.
×
1162

1163

1164
%% When tabular data is returned, convert it to the ODBC formalism
1165
mysql_item_to_odbc(Columns, Recs) ->
UNCOV
1166
    {selected, [element(2, Column) || Column <- Columns], Recs}.
16,075✔
1167

1168
to_odbc({selected, Columns, Rows}) ->
1169
    Rows2 = lists:map(
×
1170
        fun(Row) ->
1171
            Row2 = if is_tuple(Row) -> tuple_to_list(Row);
×
1172
                       is_list(Row) -> Row
×
1173
                   end,
1174
            lists:map(
×
1175
                fun(I) when is_integer(I) -> integer_to_binary(I);
×
1176
                    (B) -> B
×
1177
                end, Row2)
1178
        end, Rows),
1179
    {selected, [list_to_binary(C) || C <- Columns], Rows2};
×
1180
to_odbc({error, Reason}) when is_list(Reason) ->
1181
    {error, list_to_binary(Reason)};
×
1182
to_odbc(Res) ->
1183
    Res.
×
1184

1185
parse_mysql_version(SVersion, DefaultUpsert) ->
UNCOV
1186
    case re:run(SVersion, <<"(\\d+)\\.(\\d+)(?:\\.(\\d+))?(?:-([^-]*))?">>,
2✔
1187
                [{capture, all_but_first, binary}]) of
1188
        {match, [V1, V2, V3, Type]} ->
UNCOV
1189
            V = ((bin_to_int(V1)*1000)+bin_to_int(V2))*1000+bin_to_int(V3),
2✔
UNCOV
1190
            TypeA = binary_to_atom(Type, utf8),
2✔
UNCOV
1191
            Flags = case TypeA of
2✔
1192
                        'MariaDB' -> DefaultUpsert;
×
1193
                        _ when V >= 5007026 andalso V < 8000000 -> 1;
×
UNCOV
1194
                        _ when V >= 8000020 -> 1;
2✔
1195
                        _ -> DefaultUpsert
×
1196
                    end,
UNCOV
1197
            {ok, {V, TypeA, Flags}};
2✔
1198
        {match, [V1, V2, V3]} ->
1199
            V = ((bin_to_int(V1)*1000)+bin_to_int(V2))*1000+bin_to_int(V3),
×
1200
            Flags = case V of
×
1201
                        _ when V >= 5007026 andalso V < 8000000 -> 1;
×
1202
                        _ when V >= 8000020 -> 1;
×
1203
                        _ -> DefaultUpsert
×
1204
                    end,
1205
            {ok, {V, unknown, Flags}};
×
1206
        _ ->
1207
            error
×
1208
    end.
1209

1210
get_db_version(#state{db_type = pgsql} = State) ->
UNCOV
1211
    case pgsql:squery(State#state.db_ref,
2✔
1212
                      <<"select current_setting('server_version_num')">>) of
1213
        {ok, [{_, _, [[SVersion]]}]} ->
UNCOV
1214
            case catch binary_to_integer(SVersion) of
2✔
1215
                Version when is_integer(Version) ->
UNCOV
1216
                    State#state{db_version = Version};
2✔
1217
                Error ->
1218
                    ?WARNING_MSG("Error getting pgsql version: ~p", [Error]),
×
1219
                    State
×
1220
            end;
1221
        Res ->
1222
            ?WARNING_MSG("Error getting pgsql version: ~p", [Res]),
×
1223
            State
×
1224
    end;
1225
get_db_version(#state{db_type = mysql, host = Host} = State) ->
UNCOV
1226
    DefaultUpsert = case lists:member(mysql_alternative_upsert, ejabberd_option:sql_flags(Host)) of
2✔
1227
                        true -> 1;
×
UNCOV
1228
                        _ -> 0
2✔
1229
                    end,
UNCOV
1230
    case mysql_to_odbc(p1_mysql_conn:squery(State#state.db_ref,
2✔
1231
                                            [<<"select version();">>], self(),
1232
                                            [{timeout, 5000},
1233
                                             {result_type, binary}])) of
1234
        {selected, _, [SVersion]} ->
UNCOV
1235
            case parse_mysql_version(SVersion, DefaultUpsert) of
2✔
1236
                {ok, V} ->
UNCOV
1237
                    State#state{db_version = V};
2✔
1238
                error ->
1239
                    ?WARNING_MSG("Error parsing mysql version: ~p", [SVersion]),
×
1240
                    State
×
1241
            end;
1242
        Res ->
1243
            ?WARNING_MSG("Error getting mysql version: ~p", [Res]),
×
1244
            State
×
1245
    end;
1246
get_db_version(State) ->
UNCOV
1247
    State.
3✔
1248

1249
bin_to_int(<<>>) -> 0;
×
UNCOV
1250
bin_to_int(V) -> binary_to_integer(V).
6✔
1251

1252
log(Level, Format, Args) ->
UNCOV
1253
    case Level of
9✔
UNCOV
1254
      debug -> ?DEBUG(Format, Args);
8✔
1255
      info -> ?INFO_MSG(Format, Args);
1✔
1256
      normal -> ?INFO_MSG(Format, Args);
×
1257
      error -> ?ERROR_MSG(Format, Args)
×
1258
    end.
1259

1260
db_opts(Host) ->
UNCOV
1261
    Type = ejabberd_option:sql_type(Host),
14✔
UNCOV
1262
    Server = ejabberd_option:sql_server(Host),
14✔
UNCOV
1263
    Timeout = ejabberd_option:sql_connect_timeout(Host),
14✔
UNCOV
1264
    Transport = case ejabberd_option:sql_ssl(Host) of
14✔
UNCOV
1265
                    false -> tcp;
14✔
1266
                    true -> ssl
×
1267
                end,
UNCOV
1268
    warn_if_ssl_unsupported(Transport, Type),
14✔
UNCOV
1269
    case Type of
14✔
1270
        odbc ->
1271
            [odbc, Server, Timeout];
×
1272
        sqlite ->
UNCOV
1273
            [sqlite, Host];
6✔
1274
        _ ->
UNCOV
1275
            Port = ejabberd_option:sql_port(Host),
8✔
UNCOV
1276
            DB = case ejabberd_option:sql_database(Host) of
8✔
1277
                     undefined -> <<"ejabberd">>;
×
UNCOV
1278
                     D -> D
8✔
1279
                 end,
UNCOV
1280
            User = ejabberd_option:sql_username(Host),
8✔
UNCOV
1281
            Pass = ejabberd_option:sql_password(Host),
8✔
UNCOV
1282
            SSLOpts = get_ssl_opts(Transport, Host),
8✔
UNCOV
1283
            case Type of
8✔
1284
                mssql ->
1285
                    case odbc_server_is_connstring(Server) of
×
1286
                        true ->
1287
                            [mssql, Server, Timeout];
×
1288
                        false ->
1289
                            Encryption = case Transport of
×
1290
                                tcp -> <<"">>;
×
1291
                                ssl -> <<";ENCRYPTION=require;ENCRYPT=yes">>
×
1292
                            end,
1293
                            [mssql, <<"DRIVER=ODBC;SERVER=", Server/binary, ";DATABASE=", DB/binary,
×
1294
                                      ";UID=", User/binary, ";PWD=", Pass/binary,
1295
                                      ";PORT=", (integer_to_binary(Port))/binary, Encryption/binary,
1296
                                      ";CLIENT_CHARSET=UTF-8;">>, Timeout]
1297
                    end;
1298
                _ ->
UNCOV
1299
                    [Type, Server, Port, DB, User, Pass, Timeout, Transport, SSLOpts]
8✔
1300
            end
1301
    end.
1302

1303
warn_if_ssl_unsupported(tcp, _) ->
UNCOV
1304
    ok;
14✔
1305
warn_if_ssl_unsupported(ssl, pgsql) ->
1306
    ok;
×
1307
warn_if_ssl_unsupported(ssl, mssql) ->
1308
    ok;
×
1309
warn_if_ssl_unsupported(ssl, mysql) ->
1310
    ok;
×
1311
warn_if_ssl_unsupported(ssl, Type) ->
1312
    ?WARNING_MSG("SSL connection is not supported for ~ts", [Type]).
×
1313

1314
get_ssl_opts(ssl, Host) ->
1315
    Opts1 = case ejabberd_option:sql_ssl_certfile(Host) of
×
1316
                undefined -> [];
×
1317
                CertFile -> [{certfile, CertFile}]
×
1318
            end,
1319
    Opts2 = case ejabberd_option:sql_ssl_cafile(Host) of
×
1320
                undefined -> Opts1;
×
1321
                CAFile -> [{cacertfile, CAFile}|Opts1]
×
1322
            end,
1323
    case ejabberd_option:sql_ssl_verify(Host) of
×
1324
        true ->
1325
            case lists:keymember(cacertfile, 1, Opts2) of
×
1326
                true ->
1327
                    [{verify, verify_peer}|Opts2];
×
1328
                false ->
1329
                    ?WARNING_MSG("SSL verification is enabled for "
×
1330
                                 "SQL connection, but option "
1331
                                 "'sql_ssl_cafile' is not set; "
1332
                                 "verification will be disabled", []),
×
1333
                    Opts2
×
1334
            end;
1335
        false ->
1336
            [{verify, verify_none}|Opts2]
×
1337
    end;
1338
get_ssl_opts(tcp, _) ->
UNCOV
1339
    [].
8✔
1340

1341
init_mssql_odbcinst(Host) ->
1342
    Driver = ejabberd_option:sql_odbc_driver(Host),
×
1343
    ODBCINST = io_lib:fwrite("[ODBC]~n"
×
1344
                             "Driver = ~s~n", [Driver]),
1345
    ?DEBUG("~ts:~n~ts", [odbcinst_config(), ODBCINST]),
×
1346
    case filelib:ensure_dir(odbcinst_config()) of
×
1347
        ok ->
1348
            try
×
1349
                ok = write_file_if_new(odbcinst_config(), ODBCINST),
×
1350
                os:putenv("ODBCSYSINI", tmp_dir()),
×
1351
                ok
×
1352
            catch error:{badmatch, {error, Reason} = Err} ->
1353
                    ?ERROR_MSG("Failed to create temporary files in ~ts: ~ts",
×
1354
                               [tmp_dir(), file:format_error(Reason)]),
×
1355
                    Err
×
1356
            end;
1357
        {error, Reason} = Err ->
1358
            ?ERROR_MSG("Failed to create temporary directory ~ts: ~ts",
×
1359
                       [tmp_dir(), file:format_error(Reason)]),
×
1360
            Err
×
1361
    end.
1362

1363
init_mssql(Host) ->
1364
    Server = ejabberd_option:sql_server(Host),
×
1365
    case odbc_server_is_connstring(Server) of
×
1366
        true -> ok;
×
1367
        false -> init_mssql_odbcinst(Host)
×
1368
    end.
1369

1370
odbc_server_is_connstring(Server) ->
1371
    case binary:match(Server, <<"=">>) of
×
1372
        nomatch -> false;
×
1373
        _ -> true
×
1374
    end.
1375

1376
write_file_if_new(File, Payload) ->
1377
    case filelib:is_file(File) of
×
1378
        true -> ok;
×
1379
        false -> file:write_file(File, Payload)
×
1380
    end.
1381

1382
tmp_dir() ->
1383
    case os:type() of
16✔
1384
        {win32, _} -> filename:join([misc:get_home(), "conf"]);
×
1385
        _ -> filename:join(["/tmp", "ejabberd"])
16✔
1386
    end.
1387

1388
odbcinst_config() ->
1389
    filename:join(tmp_dir(), "odbcinst.ini").
16✔
1390

1391
max_fsm_queue() ->
UNCOV
1392
    proplists:get_value(max_queue, fsm_limit_opts(), unlimited).
7✔
1393

1394
fsm_limit_opts() ->
UNCOV
1395
    ejabberd_config:fsm_limit_opts([]).
14✔
1396

1397
query_timeout(LServer) ->
UNCOV
1398
    ejabberd_option:sql_query_timeout(LServer).
125,279✔
1399

1400
current_time() ->
UNCOV
1401
    erlang:monotonic_time(millisecond).
154,161✔
1402

1403
%% ***IMPORTANT*** This error format requires extended_errors turned on.
1404
extended_error({"08S01", _, Reason}) ->
1405
    % TCP Provider: The specified network name is no longer available
1406
    ?DEBUG("ODBC Link Failure: ~ts", [Reason]),
×
1407
    <<"Communication link failure">>;
×
1408
extended_error({"08001", _, Reason}) ->
1409
    % Login timeout expired
1410
    ?DEBUG("ODBC Connect Timeout: ~ts", [Reason]),
×
1411
    <<"SQL connection failed">>;
×
1412
extended_error({"IMC01", _, Reason}) ->
1413
    % The connection is broken and recovery is not possible
1414
    ?DEBUG("ODBC Link Failure: ~ts", [Reason]),
×
1415
    <<"Communication link failure">>;
×
1416
extended_error({"IMC06", _, Reason}) ->
1417
    % The connection is broken and recovery is not possible
1418
    ?DEBUG("ODBC Link Failure: ~ts", [Reason]),
×
1419
    <<"Communication link failure">>;
×
1420
extended_error({Code, _, Reason}) ->
1421
    ?DEBUG("ODBC Error ~ts: ~ts", [Code, Reason]),
×
1422
    iolist_to_binary(Reason);
×
1423
extended_error(Error) ->
1424
    Error.
×
1425

1426
check_error({error, Why} = Err, _Query) when Why == killed ->
1427
    Err;
×
1428
check_error({error, Why}, #sql_query{} = Query) ->
1429
    Err = extended_error(Why),
×
1430
    ?ERROR_MSG("SQL query '~ts' at ~p failed: ~p",
×
1431
               [Query#sql_query.hash, Query#sql_query.loc, Err]),
×
1432
    {error, Err};
×
1433
check_error({error, Why}, Query) ->
1434
    Err = extended_error(Why),
×
1435
    case catch iolist_to_binary(Query) of
×
1436
        SQuery when is_binary(SQuery) ->
1437
            ?ERROR_MSG("SQL query '~ts' failed: ~p", [SQuery, Err]);
×
1438
        _ ->
1439
            ?ERROR_MSG("SQL query ~p failed: ~p", [Query, Err])
×
1440
    end,
1441
    {error, Err};
×
1442
check_error(Result, _Query) ->
UNCOV
1443
    Result.
120,607✔
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