aboutsummaryrefslogtreecommitdiff
path: root/src/ejabberd_captcha.erl
diff options
context:
space:
mode:
Diffstat (limited to 'src/ejabberd_captcha.erl')
-rw-r--r--src/ejabberd_captcha.erl639
1 files changed, 291 insertions, 348 deletions
diff --git a/src/ejabberd_captcha.erl b/src/ejabberd_captcha.erl
index 157700c47..8190e6931 100644
--- a/src/ejabberd_captcha.erl
+++ b/src/ejabberd_captcha.erl
@@ -5,7 +5,7 @@
%%% Created : 26 Apr 2008 by Evgeniy Khramtsov <xramtsov@gmail.com>
%%%
%%%
-%%% ejabberd, Copyright (C) 2002-2016 ProcessOne
+%%% ejabberd, Copyright (C) 2002-2019 ProcessOne
%%%
%%% This program is free software; you can redistribute it and/or
%%% modify it under the terms of the GNU General Public License as
@@ -25,8 +25,6 @@
-module(ejabberd_captcha).
--behaviour(ejabberd_config).
-
-protocol({xep, 158, '1.0'}).
-behaviour(gen_server).
@@ -41,36 +39,26 @@
-export([create_captcha/6, build_captcha_html/2,
check_captcha/2, process_reply/1, process/2,
is_feature_available/0, create_captcha_x/5,
- create_captcha_x/6, opt_type/1]).
-
--include("jlib.hrl").
+ host_up/1, host_down/1,
+ config_reloaded/0, process_iq/1]).
--include("ejabberd.hrl").
+-include("xmpp.hrl").
-include("logger.hrl").
-
-include("ejabberd_http.hrl").
-
--define(VFIELD(Type, Var, Value),
- #xmlel{name = <<"field">>,
- attrs = [{<<"type">>, Type}, {<<"var">>, Var}],
- children =
- [#xmlel{name = <<"value">>, attrs = [],
- children = [Value]}]}).
-
--define(CAPTCHA_TEXT(Lang),
- translate:translate(Lang,
- <<"Enter the text you see">>)).
+-include("translate.hrl").
-define(CAPTCHA_LIFETIME, 120000).
-
-define(LIMIT_PERIOD, 60*1000*1000).
--type error() :: efbig | enodata | limit | malformed_image | timeout.
+-type image_error() :: efbig | enodata | limit | malformed_image | timeout.
+-type priority() :: neg_integer().
+-type callback() :: fun((captcha_succeed | captcha_failed) -> any()).
--record(state, {limits = treap:empty() :: treap:treap()}).
+-record(state, {limits = treap:empty() :: treap:treap(),
+ enabled = false :: boolean()}).
-record(captcha, {id :: binary(),
- pid :: pid(),
+ pid :: pid() | undefined,
key :: binary(),
tref :: reference(),
args :: any()}).
@@ -79,199 +67,73 @@ start_link() ->
gen_server:start_link({local, ?MODULE}, ?MODULE, [],
[]).
--spec create_captcha(binary(), jid(), jid(),
- binary(), any(), any()) -> {error, error()} |
- {ok, binary(), [xmlel()]}.
+-spec captcha_text(binary()) -> binary().
+captcha_text(Lang) ->
+ translate:translate(Lang, ?T("Enter the text you see")).
+
+-spec mk_ocr_field(binary(), binary(), binary()) -> xdata_field().
+mk_ocr_field(Lang, CID, Type) ->
+ URI = #media_uri{type = Type, uri = <<"cid:", CID/binary>>},
+ [_, F] = captcha_form:encode([{ocr, <<>>}], Lang, [ocr]),
+ xmpp:set_els(F, [#media{uri = [URI]}]).
+-spec create_captcha(binary(), jid(), jid(),
+ binary(), any(),
+ callback() | term()) -> {error, image_error()} |
+ {ok, binary(), [text()], [xmpp_element()]}.
create_captcha(SID, From, To, Lang, Limiter, Args) ->
case create_image(Limiter) of
{ok, Type, Key, Image} ->
- Id = <<(randoms:get_string())/binary>>,
- B64Image = jlib:encode_base64((Image)),
- JID = jid:to_string(From),
- CID = <<"sha1+", (p1_sha:sha(Image))/binary,
- "@bob.xmpp.org">>,
- Data = #xmlel{name = <<"data">>,
- attrs =
- [{<<"xmlns">>, ?NS_BOB}, {<<"cid">>, CID},
- {<<"max-age">>, <<"0">>}, {<<"type">>, Type}],
- children = [{xmlcdata, B64Image}]},
- Captcha = #xmlel{name = <<"captcha">>,
- attrs = [{<<"xmlns">>, ?NS_CAPTCHA}],
- children =
- [#xmlel{name = <<"x">>,
- attrs =
- [{<<"xmlns">>, ?NS_XDATA},
- {<<"type">>, <<"form">>}],
- children =
- [?VFIELD(<<"hidden">>,
- <<"FORM_TYPE">>,
- {xmlcdata, ?NS_CAPTCHA}),
- ?VFIELD(<<"hidden">>, <<"from">>,
- {xmlcdata,
- jid:to_string(To)}),
- ?VFIELD(<<"hidden">>,
- <<"challenge">>,
- {xmlcdata, Id}),
- ?VFIELD(<<"hidden">>, <<"sid">>,
- {xmlcdata, SID}),
- #xmlel{name = <<"field">>,
- attrs =
- [{<<"var">>, <<"ocr">>},
- {<<"label">>,
- ?CAPTCHA_TEXT(Lang)}],
- children =
- [#xmlel{name =
- <<"required">>,
- attrs = [],
- children = []},
- #xmlel{name =
- <<"media">>,
- attrs =
- [{<<"xmlns">>,
- ?NS_MEDIA}],
- children =
- [#xmlel{name
- =
- <<"uri">>,
- attrs
- =
- [{<<"type">>,
- Type}],
- children
- =
- [{xmlcdata,
- <<"cid:",
- CID/binary>>}]}]}]}]}]},
- BodyString1 = translate:translate(Lang,
- <<"Your messages to ~s are being blocked. "
- "To unblock them, visit ~s">>),
- BodyString = iolist_to_binary(io_lib:format(BodyString1,
- [JID, get_url(Id)])),
- Body = #xmlel{name = <<"body">>, attrs = [],
- children = [{xmlcdata, BodyString}]},
- OOB = #xmlel{name = <<"x">>,
- attrs = [{<<"xmlns">>, ?NS_OOB}],
- children =
- [#xmlel{name = <<"url">>, attrs = [],
- children = [{xmlcdata, get_url(Id)}]}]},
- Tref = erlang:send_after(?CAPTCHA_LIFETIME, ?MODULE,
- {remove_id, Id}),
- ets:insert(captcha,
- #captcha{id = Id, pid = self(), key = Key, tref = Tref,
- args = Args}),
- {ok, Id, [Body, OOB, Captcha, Data]};
- Err -> Err
+ Id = <<(p1_rand:get_string())/binary>>,
+ JID = jid:encode(From),
+ CID = <<"sha1+", (str:sha(Image))/binary, "@bob.xmpp.org">>,
+ Data = #bob_data{cid = CID, 'max-age' = 0, type = Type, data = Image},
+ Fs = captcha_form:encode(
+ [{from, To}, {challenge, Id}, {sid, SID},
+ mk_ocr_field(Lang, CID, Type)],
+ Lang, [challenge]),
+ X = #xdata{type = form, fields = Fs},
+ Captcha = #xcaptcha{xdata = X},
+ BodyString = {?T("Your subscription request and/or messages to ~ts have been blocked. "
+ "To unblock your subscription request, visit ~ts"), [JID, get_url(Id)]},
+ Body = xmpp:mk_text(BodyString, Lang),
+ OOB = #oob_x{url = get_url(Id)},
+ Hint = #hint{type = 'no-store'},
+ Tref = erlang:send_after(?CAPTCHA_LIFETIME, ?MODULE, {remove_id, Id}),
+ ets:insert(captcha,
+ #captcha{id = Id, pid = self(), key = Key, tref = Tref,
+ args = Args}),
+ {ok, Id, Body, [Hint, OOB, Captcha, Data]};
+ Err -> Err
end.
--spec create_captcha_x(binary(), jid(), binary(),
- any(), [xmlel()]) -> {ok, [xmlel()]} |
- {error, error()}.
-
-create_captcha_x(SID, To, Lang, Limiter, HeadEls) ->
- create_captcha_x(SID, To, Lang, Limiter, HeadEls, []).
-
--spec create_captcha_x(binary(), jid(), binary(),
- any(), [xmlel()], [xmlel()]) -> {ok, [xmlel()]} |
- {error, error()}.
-
-create_captcha_x(SID, To, Lang, Limiter, HeadEls,
- TailEls) ->
+-spec create_captcha_x(binary(), jid(), binary(), any(), xdata()) ->
+ {ok, [xmpp_element()]} | {error, image_error()}.
+create_captcha_x(SID, To, Lang, Limiter, #xdata{fields = Fs} = X) ->
case create_image(Limiter) of
{ok, Type, Key, Image} ->
- Id = <<(randoms:get_string())/binary>>,
- B64Image = jlib:encode_base64((Image)),
- CID = <<"sha1+", (p1_sha:sha(Image))/binary,
- "@bob.xmpp.org">>,
- Data = #xmlel{name = <<"data">>,
- attrs =
- [{<<"xmlns">>, ?NS_BOB}, {<<"cid">>, CID},
- {<<"max-age">>, <<"0">>}, {<<"type">>, Type}],
- children = [{xmlcdata, B64Image}]},
- HelpTxt = translate:translate(Lang,
- <<"If you don't see the CAPTCHA image here, "
- "visit the web page.">>),
- Imageurl = get_url(<<Id/binary, "/image">>),
- Captcha = #xmlel{name = <<"x">>,
- attrs =
- [{<<"xmlns">>, ?NS_XDATA},
- {<<"type">>, <<"form">>}],
- children =
- [?VFIELD(<<"hidden">>, <<"FORM_TYPE">>,
- {xmlcdata, ?NS_CAPTCHA})
- | HeadEls]
- ++
- [#xmlel{name = <<"field">>,
- attrs = [{<<"type">>, <<"fixed">>}],
- children =
- [#xmlel{name = <<"value">>,
- attrs = [],
- children =
- [{xmlcdata,
- HelpTxt}]}]},
- #xmlel{name = <<"field">>,
- attrs =
- [{<<"type">>, <<"hidden">>},
- {<<"var">>, <<"captchahidden">>}],
- children =
- [#xmlel{name = <<"value">>,
- attrs = [],
- children =
- [{xmlcdata,
- <<"workaround-for-psi">>}]}]},
- #xmlel{name = <<"field">>,
- attrs =
- [{<<"type">>, <<"text-single">>},
- {<<"label">>,
- translate:translate(Lang,
- <<"CAPTCHA web page">>)},
- {<<"var">>, <<"url">>}],
- children =
- [#xmlel{name = <<"value">>,
- attrs = [],
- children =
- [{xmlcdata,
- Imageurl}]}]},
- ?VFIELD(<<"hidden">>, <<"from">>,
- {xmlcdata, jid:to_string(To)}),
- ?VFIELD(<<"hidden">>, <<"challenge">>,
- {xmlcdata, Id}),
- ?VFIELD(<<"hidden">>, <<"sid">>,
- {xmlcdata, SID}),
- #xmlel{name = <<"field">>,
- attrs =
- [{<<"var">>, <<"ocr">>},
- {<<"label">>,
- ?CAPTCHA_TEXT(Lang)}],
- children =
- [#xmlel{name = <<"required">>,
- attrs = [], children = []},
- #xmlel{name = <<"media">>,
- attrs =
- [{<<"xmlns">>,
- ?NS_MEDIA}],
- children =
- [#xmlel{name =
- <<"uri">>,
- attrs =
- [{<<"type">>,
- Type}],
- children =
- [{xmlcdata,
- <<"cid:",
- CID/binary>>}]}]}]}]
- ++ TailEls},
- Tref = erlang:send_after(?CAPTCHA_LIFETIME, ?MODULE,
- {remove_id, Id}),
- ets:insert(captcha,
- #captcha{id = Id, key = Key, tref = Tref}),
- {ok, [Captcha, Data]};
- Err -> Err
+ Id = <<(p1_rand:get_string())/binary>>,
+ CID = <<"sha1+", (str:sha(Image))/binary, "@bob.xmpp.org">>,
+ Data = #bob_data{cid = CID, 'max-age' = 0, type = Type, data = Image},
+ HelpTxt = translate:translate(
+ Lang, ?T("If you don't see the CAPTCHA image here, visit the web page.")),
+ Imageurl = get_url(<<Id/binary, "/image">>),
+ [H|T] = captcha_form:encode(
+ [{'captcha-fallback-text', HelpTxt},
+ {'captcha-fallback-url', Imageurl},
+ {from, To}, {challenge, Id}, {sid, SID},
+ mk_ocr_field(Lang, CID, Type)],
+ Lang, [challenge]),
+ Captcha = X#xdata{type = form, fields = [H|Fs ++ T]},
+ Tref = erlang:send_after(?CAPTCHA_LIFETIME, ?MODULE, {remove_id, Id}),
+ ets:insert(captcha, #captcha{id = Id, key = Key, tref = Tref}),
+ {ok, [Captcha, Data]};
+ Err -> Err
end.
-spec build_captcha_html(binary(), binary()) -> captcha_not_found |
{xmlel(),
- {xmlel(), xmlel(),
+ {xmlel(), cdata(),
xmlel(), xmlel()}}.
build_captcha_html(Id, Lang) ->
@@ -281,7 +143,7 @@ build_captcha_html(Id, Lang) ->
attrs =
[{<<"src">>, get_url(<<Id/binary, "/image">>)}],
children = []},
- TextEl = {xmlcdata, ?CAPTCHA_TEXT(Lang)},
+ Text = {xmlcdata, captcha_text(Lang)},
IdEl = #xmlel{name = <<"input">>,
attrs =
[{<<"type">>, <<"hidden">>}, {<<"name">>, <<"id">>},
@@ -301,7 +163,7 @@ build_captcha_html(Id, Lang) ->
[ImgEl,
#xmlel{name = <<"br">>, attrs = [],
children = []},
- TextEl,
+ Text,
#xmlel{name = <<"br">>, attrs = [],
children = []},
IdEl, KeyEl,
@@ -311,39 +173,63 @@ build_captcha_html(Id, Lang) ->
attrs =
[{<<"type">>, <<"submit">>},
{<<"name">>, <<"enter">>},
- {<<"value">>, <<"OK">>}],
+ {<<"value">>, ?T("OK")}],
children = []}]},
- {FormEl, {ImgEl, TextEl, IdEl, KeyEl}};
+ {FormEl, {ImgEl, Text, IdEl, KeyEl}};
_ -> captcha_not_found
end.
--spec process_reply(xmlel()) -> ok | {error, bad_match | not_found | malformed}.
-
-process_reply(#xmlel{} = El) ->
- case fxml:get_subtag(El, <<"x">>) of
- false -> {error, malformed};
- Xdata ->
- Fields = jlib:parse_xdata_submit(Xdata),
- case catch {proplists:get_value(<<"challenge">>,
- Fields),
- proplists:get_value(<<"ocr">>, Fields)}
- of
- {[Id | _], [OCR | _]} ->
- case check_captcha(Id, OCR) of
- captcha_valid -> ok;
- captcha_non_valid -> {error, bad_match};
- captcha_not_found -> {error, not_found}
- end;
- _ -> {error, malformed}
- end
+-spec process_reply(xmpp_element()) -> ok | {error, bad_match | not_found | malformed}.
+
+process_reply(#xdata{} = X) ->
+ Required = [<<"challenge">>, <<"ocr">>],
+ Fs = lists:filter(
+ fun(#xdata_field{var = Var}) ->
+ lists:member(Var, [<<"FORM_TYPE">>|Required])
+ end, X#xdata.fields),
+ try captcha_form:decode(Fs, [?NS_CAPTCHA], Required) of
+ Props ->
+ Id = proplists:get_value(challenge, Props),
+ OCR = proplists:get_value(ocr, Props),
+ case check_captcha(Id, OCR) of
+ captcha_valid -> ok;
+ captcha_non_valid -> {error, bad_match};
+ captcha_not_found -> {error, not_found}
+ end
+ catch _:{captcha_form, Why} ->
+ ?WARNING_MSG("Malformed CAPTCHA form: ~ts",
+ [captcha_form:format_error(Why)]),
+ {error, malformed}
end;
-process_reply(_) -> {error, malformed}.
+process_reply(#xcaptcha{xdata = #xdata{} = X}) ->
+ process_reply(X);
+process_reply(_) ->
+ {error, malformed}.
+
+-spec process_iq(iq()) -> iq().
+process_iq(#iq{type = set, lang = Lang, sub_els = [#xcaptcha{} = El]} = IQ) ->
+ case process_reply(El) of
+ ok ->
+ xmpp:make_iq_result(IQ);
+ {error, malformed} ->
+ Txt = ?T("Incorrect CAPTCHA submit"),
+ xmpp:make_error(IQ, xmpp:err_bad_request(Txt, Lang));
+ {error, _} ->
+ Txt = ?T("The CAPTCHA verification has failed"),
+ xmpp:make_error(IQ, xmpp:err_not_allowed(Txt, Lang))
+ end;
+process_iq(#iq{type = get, lang = Lang} = IQ) ->
+ Txt = ?T("Value 'get' of 'type' attribute is not allowed"),
+ xmpp:make_error(IQ, xmpp:err_not_allowed(Txt, Lang));
+process_iq(#iq{lang = Lang} = IQ) ->
+ Txt = ?T("No module is handling this query"),
+ xmpp:make_error(IQ, xmpp:err_service_unavailable(Txt, Lang)).
process(_Handlers,
#request{method = 'GET', lang = Lang,
path = [_, Id]}) ->
case build_captcha_html(Id, Lang) of
- {FormEl, _} when is_tuple(FormEl) ->
+ {FormEl, _} ->
Form = #xmlel{name = <<"div">>,
attrs = [{<<"align">>, <<"center">>}],
children = [FormEl]},
@@ -378,7 +264,7 @@ process(_Handlers,
children =
[{xmlcdata,
translate:translate(Lang,
- <<"The CAPTCHA is valid.">>)}]},
+ ?T("The CAPTCHA is valid."))}]},
ejabberd_web:make_xhtml([Form]);
captcha_non_valid -> ejabberd_web:error(not_allowed);
captcha_not_found -> ejabberd_web:error(not_found)
@@ -386,12 +272,29 @@ process(_Handlers,
process(_Handlers, _Request) ->
ejabberd_web:error(not_found).
+host_up(Host) ->
+ gen_iq_handler:add_iq_handler(ejabberd_sm, Host, ?NS_CAPTCHA,
+ ?MODULE, process_iq).
+
+host_down(Host) ->
+ gen_iq_handler:remove_iq_handler(ejabberd_sm, Host, ?NS_CAPTCHA).
+
+config_reloaded() ->
+ gen_server:call(?MODULE, config_reloaded, timer:minutes(1)).
+
init([]) ->
- mnesia:delete_table(captcha),
- ets:new(captcha,
- [named_table, public, {keypos, #captcha.id}]),
- check_captcha_setup(),
- {ok, #state{}}.
+ _ = mnesia:delete_table(captcha),
+ _ = ets:new(captcha, [named_table, public, {keypos, #captcha.id}]),
+ case check_captcha_setup() of
+ true ->
+ register_handlers(),
+ ejabberd_hooks:add(config_reloaded, ?MODULE, config_reloaded, 50),
+ {ok, #state{enabled = true}};
+ false ->
+ {ok, #state{enabled = false}};
+ {error, Reason} ->
+ {stop, Reason}
+ end.
handle_call({is_limited, Limiter, RateLimit}, _From,
State) ->
@@ -410,43 +313,86 @@ handle_call({is_limited, Limiter, RateLimit}, _From,
Limits),
{reply, false, State#state{limits = NewLimits}}
end;
-handle_call(_Request, _From, State) ->
- {reply, bad_request, State}.
-
-handle_cast(_Msg, State) -> {noreply, State}.
+handle_call(config_reloaded, _From, #state{enabled = Enabled} = State) ->
+ State1 = case is_feature_available() of
+ true when not Enabled ->
+ case check_captcha_setup() of
+ true ->
+ register_handlers(),
+ State#state{enabled = true};
+ _ ->
+ State
+ end;
+ false when Enabled ->
+ unregister_handlers(),
+ State#state{enabled = false};
+ _ ->
+ State
+ end,
+ {reply, ok, State1};
+handle_call(Request, From, State) ->
+ ?WARNING_MSG("Unexpected call from ~p: ~p", [From, Request]),
+ {noreply, State}.
+
+handle_cast(Msg, State) ->
+ ?WARNING_MSG("Unexpected cast: ~p", [Msg]),
+ {noreply, State}.
handle_info({remove_id, Id}, State) ->
- ?DEBUG("captcha ~p timed out", [Id]),
+ ?DEBUG("CAPTCHA ~p timed out", [Id]),
case ets:lookup(captcha, Id) of
- [#captcha{args = Args, pid = Pid}] ->
- if is_pid(Pid) -> Pid ! {captcha_failed, Args};
- true -> ok
- end,
- ets:delete(captcha, Id);
- _ -> ok
+ [#captcha{args = Args, pid = Pid}] ->
+ callback(captcha_failed, Pid, Args),
+ ets:delete(captcha, Id);
+ _ -> ok
end,
{noreply, State};
-handle_info(_Info, State) -> {noreply, State}.
+handle_info(Info, State) ->
+ ?WARNING_MSG("Unexpected info: ~p", [Info]),
+ {noreply, State}.
+
+terminate(_Reason, #state{enabled = Enabled}) ->
+ if Enabled -> unregister_handlers();
+ true -> ok
+ end,
+ ejabberd_hooks:delete(config_reloaded, ?MODULE, config_reloaded, 50).
+
+register_handlers() ->
+ ejabberd_hooks:add(host_up, ?MODULE, host_up, 50),
+ ejabberd_hooks:add(host_down, ?MODULE, host_down, 50),
+ lists:foreach(fun host_up/1, ejabberd_option:hosts()).
-terminate(_Reason, _State) -> ok.
+unregister_handlers() ->
+ ejabberd_hooks:delete(host_up, ?MODULE, host_up, 50),
+ ejabberd_hooks:delete(host_down, ?MODULE, host_down, 50),
+ lists:foreach(fun host_down/1, ejabberd_option:hosts()).
code_change(_OldVsn, State, _Extra) -> {ok, State}.
-create_image() -> create_image(undefined).
+-spec create_image() -> {ok, binary(), binary(), binary()} |
+ {error, image_error()}.
+create_image() ->
+ create_image(undefined).
+-spec create_image(term()) -> {ok, binary(), binary(), binary()} |
+ {error, image_error()}.
create_image(Limiter) ->
- Key = str:substr(randoms:get_string(), 1, 6),
+ Key = str:substr(p1_rand:get_string(), 1, 6),
create_image(Limiter, Key).
+-spec create_image(term(), binary()) -> {ok, binary(), binary(), binary()} |
+ {error, image_error()}.
create_image(Limiter, Key) ->
case is_limited(Limiter) of
- true -> {error, limit};
- false -> do_create_image(Key)
+ true -> {error, limit};
+ false -> do_create_image(Key)
end.
+-spec do_create_image(binary()) -> {ok, binary(), binary(), binary()} |
+ {error, image_error()}.
do_create_image(Key) ->
FileName = get_prog_name(),
- Cmd = lists:flatten(io_lib:format("~s ~s", [FileName, Key])),
+ Cmd = lists:flatten(io_lib:format("~ts ~ts", [FileName, Key])),
case cmd(Cmd) of
{ok,
<<137, $P, $N, $G, $\r, $\n, 26, $\n, _/binary>> =
@@ -458,29 +404,24 @@ do_create_image(Key) ->
when X == $7; X == $9 ->
{ok, <<"image/gif">>, Key, Img};
{error, enodata = Reason} ->
- ?ERROR_MSG("Failed to process output from \"~s\". "
+ ?ERROR_MSG("Failed to process output from \"~ts\". "
"Maybe ImageMagick's Convert program "
"is not installed.",
[Cmd]),
{error, Reason};
{error, Reason} ->
- ?ERROR_MSG("Failed to process an output from \"~s\": ~p",
+ ?ERROR_MSG("Failed to process an output from \"~ts\": ~p",
[Cmd, Reason]),
{error, Reason};
_ ->
Reason = malformed_image,
- ?ERROR_MSG("Failed to process an output from \"~s\": ~p",
+ ?ERROR_MSG("Failed to process an output from \"~ts\": ~p",
[Cmd, Reason]),
{error, Reason}
end.
get_prog_name() ->
- case ejabberd_config:get_option(
- captcha_cmd,
- fun(FileName) ->
- F = iolist_to_binary(FileName),
- if F /= <<"">> -> F end
- end) of
+ case ejabberd_option:captcha_cmd() of
undefined ->
?DEBUG("The option captcha_cmd is not configured, "
"but some module wants to use the CAPTCHA "
@@ -491,69 +432,71 @@ get_prog_name() ->
FileName
end.
+-spec get_url(binary()) -> binary().
get_url(Str) ->
- CaptchaHost = ejabberd_config:get_option(
- captcha_host,
- fun iolist_to_binary/1,
- <<"">>),
+ case ejabberd_option:captcha_url() of
+ undefined ->
+ URL = parse_captcha_host(),
+ <<URL/binary, "/captcha/", Str/binary>>;
+ URL ->
+ <<URL/binary, $/, Str/binary>>
+ end.
+
+-spec parse_captcha_host() -> binary().
+parse_captcha_host() ->
+ CaptchaHost = ejabberd_option:captcha_host(),
case str:tokens(CaptchaHost, <<":">>) of
- [Host] ->
- <<"http://", Host/binary, "/captcha/", Str/binary>>;
- [<<"http", _/binary>> = TransferProt, Host] ->
- <<TransferProt/binary, ":", Host/binary, "/captcha/",
- Str/binary>>;
- [Host, PortString] ->
- TransferProt =
- iolist_to_binary(atom_to_list(get_transfer_protocol(PortString))),
- <<TransferProt/binary, "://", Host/binary, ":",
- PortString/binary, "/captcha/", Str/binary>>;
- [TransferProt, Host, PortString] ->
- <<TransferProt/binary, ":", Host/binary, ":",
- PortString/binary, "/captcha/", Str/binary>>;
+ [Host] ->
+ <<"http://", Host/binary>>;
+ [<<"http", _/binary>> = TransferProt, Host] ->
+ <<TransferProt/binary, ":", Host/binary>>;
+ [Host, PortString] ->
+ TransferProt = atom_to_binary(get_transfer_protocol(PortString), latin1),
+ <<TransferProt/binary, "://", Host/binary, ":", PortString/binary>>;
+ [TransferProt, Host, PortString] ->
+ <<TransferProt/binary, ":", Host/binary, ":", PortString/binary>>;
_ ->
- <<"http://", (?MYNAME)/binary, "/captcha/", Str/binary>>
+ <<"http://", (ejabberd_config:get_myname())/binary>>
end.
get_transfer_protocol(PortString) ->
- PortNumber = jlib:binary_to_integer(PortString),
+ PortNumber = binary_to_integer(PortString),
PortListeners = get_port_listeners(PortNumber),
get_captcha_transfer_protocol(PortListeners).
get_port_listeners(PortNumber) ->
- AllListeners = ejabberd_config:get_option(listen, fun(V) -> V end),
- lists:filter(fun (Listener) when is_list(Listener) ->
- case proplists:get_value(port, Listener) of
- PortNumber -> true;
- _ -> false
- end;
- (_) -> false
- end,
- AllListeners).
+ AllListeners = ejabberd_option:listen(),
+ lists:filter(
+ fun({{Port, _IP, _Transport}, _Module, _Opts}) ->
+ Port == PortNumber
+ end, AllListeners).
get_captcha_transfer_protocol([]) ->
throw(<<"The port number mentioned in captcha_host "
"is not a ejabberd_http listener with "
"'captcha' option. Change the port number "
"or specify http:// in that option.">>);
-get_captcha_transfer_protocol([Listener | Listeners]) when is_list(Listener) ->
- case proplists:get_value(module, Listener) == ejabberd_http andalso
- proplists:get_bool(captcha, Listener) of
- true ->
- case proplists:get_bool(tls, Listener) of
- true -> https;
- false -> http
- end;
- false -> get_captcha_transfer_protocol(Listeners)
+get_captcha_transfer_protocol([{_, ejabberd_http, Opts} | Listeners]) ->
+ Handlers = maps:get(request_handlers, Opts, []),
+ case lists:any(
+ fun({_, ?MODULE}) -> true;
+ ({_, _}) -> false
+ end, Handlers) of
+ true ->
+ case maps:get(tls, Opts) of
+ true -> https;
+ false -> http
+ end;
+ false ->
+ get_captcha_transfer_protocol(Listeners)
end;
get_captcha_transfer_protocol([_ | Listeners]) ->
get_captcha_transfer_protocol(Listeners).
is_limited(undefined) -> false;
is_limited(Limiter) ->
- case ejabberd_config:get_option(
- captcha_limit,
- fun(I) when is_integer(I), I > 0 -> I end) of
- undefined -> false;
+ case ejabberd_option:captcha_limit() of
+ infinity -> false;
Int ->
case catch gen_server:call(?MODULE,
{is_limited, Limiter, Int}, 5000)
@@ -568,12 +511,14 @@ is_limited(Limiter) ->
-define(MAX_FILE_SIZE, 64 * 1024).
+-spec cmd(string()) -> {ok, binary()} | {error, image_error()}.
cmd(Cmd) ->
Port = open_port({spawn, Cmd}, [stream, eof, binary]),
TRef = erlang:start_timer(?CMD_TIMEOUT, self(),
timeout),
recv_data(Port, TRef, <<>>).
+-spec recv_data(port(), reference(), binary()) -> {ok, binary()} | {error, image_error()}.
recv_data(Port, TRef, Buf) ->
receive
{Port, {data, Bytes}} ->
@@ -590,12 +535,10 @@ recv_data(Port, TRef, Buf) ->
return(Port, TRef, {error, timeout})
end.
+-spec return(port(), reference(), {ok, binary()} | {error, image_error()}) ->
+ {ok, binary()} | {error, image_error()}.
return(Port, TRef, Result) ->
- case erlang:cancel_timer(TRef) of
- false ->
- receive {timeout, TRef, _} -> ok after 0 -> ok end;
- _ -> ok
- end,
+ misc:cancel_timer(TRef),
catch port_close(Port),
Result.
@@ -607,22 +550,25 @@ is_feature_available() ->
check_captcha_setup() ->
case is_feature_available() of
- true ->
- case create_image() of
- {ok, _, _, _} -> ok;
- _Err ->
- ?CRITICAL_MSG("Captcha is enabled in the option captcha_cmd, "
- "but it can't generate images.",
- []),
- throw({error, captcha_cmd_enabled_but_fails})
- end;
- false -> ok
+ true ->
+ case create_image() of
+ {ok, _, _, _} ->
+ true;
+ Err ->
+ ?CRITICAL_MSG("Captcha is enabled in the option captcha_cmd, "
+ "but it can't generate images.",
+ []),
+ Err
+ end;
+ false ->
+ false
end.
+-spec lookup_captcha(binary()) -> {ok, #captcha{}} | {error, enoent}.
lookup_captcha(Id) ->
case ets:lookup(captcha, Id) of
[C] -> {ok, C};
- _ -> {error, enoent}
+ [] -> {error, enoent}
end.
-spec check_captcha(binary(), binary()) -> captcha_not_found |
@@ -630,25 +576,22 @@ lookup_captcha(Id) ->
captcha_non_valid.
check_captcha(Id, ProvidedKey) ->
- case ets:lookup(captcha, Id) of
- [#captcha{pid = Pid, args = Args, key = ValidKey,
- tref = Tref}] ->
- ets:delete(captcha, Id),
- erlang:cancel_timer(Tref),
- if ValidKey == ProvidedKey ->
- if is_pid(Pid) -> Pid ! {captcha_succeed, Args};
- true -> ok
- end,
- captcha_valid;
- true ->
- if is_pid(Pid) -> Pid ! {captcha_failed, Args};
- true -> ok
- end,
- captcha_non_valid
- end;
- _ -> captcha_not_found
+ case lookup_captcha(Id) of
+ {ok, #captcha{pid = Pid, args = Args, key = ValidKey, tref = Tref}} ->
+ ets:delete(captcha, Id),
+ misc:cancel_timer(Tref),
+ if ValidKey == ProvidedKey ->
+ callback(captcha_succeed, Pid, Args),
+ captcha_valid;
+ true ->
+ callback(captcha_failed, Pid, Args),
+ captcha_non_valid
+ end;
+ {error, _} ->
+ captcha_not_found
end.
+-spec clean_treap(treap:treap(), priority()) -> treap:treap().
clean_treap(Treap, CleanPriority) ->
case treap:is_empty(Treap) of
true -> Treap;
@@ -660,16 +603,16 @@ clean_treap(Treap, CleanPriority) ->
end
end.
+-spec callback(captcha_succeed | captcha_failed,
+ pid() | undefined,
+ callback() | term()) -> any().
+callback(Result, _Pid, F) when is_function(F) ->
+ F(Result);
+callback(Result, Pid, Args) when is_pid(Pid) ->
+ Pid ! {Result, Args};
+callback(_, _, _) ->
+ ok.
+
+-spec now_priority() -> priority().
now_priority() ->
- -p1_time_compat:system_time(micro_seconds).
-
-opt_type(captcha_cmd) ->
- fun (FileName) ->
- F = iolist_to_binary(FileName), if F /= <<"">> -> F end
- end;
-opt_type(captcha_host) -> fun iolist_to_binary/1;
-opt_type(captcha_limit) ->
- fun (I) when is_integer(I), I > 0 -> I end;
-opt_type(listen) -> fun (V) -> V end;
-opt_type(_) ->
- [captcha_cmd, captcha_host, captcha_limit, listen].
+ -erlang:system_time(microsecond).