]> granicus.if.org Git - ejabberd/commitdiff
Remove http_poll module
authorPaweł Chmielowski <pawel@process-one.net>
Wed, 15 Apr 2015 08:47:10 +0000 (10:47 +0200)
committerPaweł Chmielowski <pawel@process-one.net>
Wed, 15 Apr 2015 08:47:10 +0000 (10:47 +0200)
For couple years browsers did limit ability to change cookies from js
for different domains, this made http_poll connections practically not
usuable. I don't think this module is used at all so it's time to put it
to rest.

ejabberd.yml.example
src/ejabberd_c2s.erl
src/ejabberd_http.erl
src/ejabberd_http_poll.erl [deleted file]
src/ejabberd_socket.erl
src/ejabberd_sup.erl
src/ejabberd_web_admin.erl

index 4bf2dcffd579185b4bfea56e452db3f89f732769..5f577d1ad5b0532e0ee3506f2cc3b66830a64ef9 100644 (file)
@@ -165,7 +165,6 @@ listen:
       "/websocket": ejabberd_http_ws
     ##  "/pub/archive": mod_http_fileserver
     web_admin: true
-    http_poll: true
     http_bind: true
     ## register: true
     captcha: true
index 7e83fb8c15340bd7f3f44f2a38173541ceba5459..4603af9985b0e867238e1ee41bfa94477bded746 100644 (file)
@@ -1798,7 +1798,7 @@ print_state(State = #state{pres_t = T, pres_f = F, pres_a = A}) ->
                pres_f = {pres_f, ?SETS:size(F)},
                pres_a = {pres_a, ?SETS:size(A)}
                }.
-    
+
 %%----------------------------------------------------------------------
 %% Func: terminate/3
 %% Purpose: Shutdown the fsm
@@ -1881,7 +1881,7 @@ send_text(StateData, Text) when StateData#state.mgmt_state == pending ->
     ?DEBUG("Cannot send text while waiting for resumption: ~p", [Text]);
 send_text(StateData, Text) when StateData#state.xml_socket ->
     ?DEBUG("Send Text on stream = ~p", [Text]),
-    (StateData#state.sockmod):send_xml(StateData#state.socket, 
+    (StateData#state.sockmod):send_xml(StateData#state.socket,
                                       {xmlstreamraw, Text});
 send_text(StateData, Text) when StateData#state.mgmt_state == active ->
     ?DEBUG("Send XML on stream = ~p", [Text]),
@@ -2024,7 +2024,6 @@ get_conn_type(StateData) ->
            gen_tcp -> c2s_compressed;
            p1_tls -> c2s_compressed_tls
        end;
-    ejabberd_http_poll -> http_poll;
     ejabberd_http_bind -> http_bind;
     _ -> unknown
     end.
index a06d3f99bf4d79c061fd31482acb27b63c3237af..4e7f4b554ebd7cc97fbb4694912315f783233420 100644 (file)
@@ -56,7 +56,7 @@
                %% to have the module test_web handle requests with
                %% paths starting with "/test/module":
                %%
-               %%   {5280, ejabberd_http,    [http_poll, web_admin,
+               %%   {5280, ejabberd_http,    [http_bind, web_admin,
                %%                             {request_handlers, [{["test", "module"], mod_test_web}]}]}
                %%
                request_handlers = [],
@@ -135,10 +135,6 @@ init({SockMod, Socket}, Opts) ->
              true -> [{[<<"http-bind">>], mod_http_bind}];
              false -> []
            end,
-    Poll = case proplists:get_bool(http_poll, Opts) of
-             true -> [{[<<"http-poll">>], ejabberd_http_poll}];
-             false -> []
-           end,
     XMLRPC = case proplists:get_bool(xmlrpc, Opts) of
                 true -> [{[], ejabberd_xmlrpc}];
                 false -> []
@@ -151,7 +147,7 @@ init({SockMod, Socket}, Opts) ->
                                   Mod} || {Path, Mod} <- Hs]
                         end, []),
     RequestHandlers = DefinedHandlers ++ Captcha ++ Register ++
-        Admin ++ Bind ++ Poll ++ XMLRPC,
+        Admin ++ Bind ++ XMLRPC,
     ?DEBUG("S: ~p~n", [RequestHandlers]),
 
     DefaultHost = gen_mod:get_opt(default_host, Opts, fun(A) -> A end, undefined),
@@ -862,7 +858,7 @@ transform_listen_option(web_admin, Opts) ->
 transform_listen_option(http_bind, Opts) ->
     [{http_bind, true}|Opts];
 transform_listen_option(http_poll, Opts) ->
-    [{http_poll, true}|Opts];
+    Opts;
 transform_listen_option({request_handlers, Hs}, Opts) ->
     Hs1 = lists:map(
             fun({PList, Mod}) when is_list(PList) ->
diff --git a/src/ejabberd_http_poll.erl b/src/ejabberd_http_poll.erl
deleted file mode 100644 (file)
index 174c782..0000000
+++ /dev/null
@@ -1,425 +0,0 @@
-%%%----------------------------------------------------------------------
-%%% File    : ejabberd_http_poll.erl
-%%% Author  : Alexey Shchepin <alexey@process-one.net>
-%%% Purpose : HTTP Polling support (XEP-0025)
-%%% Created :  4 Mar 2004 by Alexey Shchepin <alexey@process-one.net>
-%%%
-%%%
-%%% ejabberd, Copyright (C) 2002-2015   ProcessOne
-%%%
-%%% This program is free software; you can redistribute it and/or
-%%% modify it under the terms of the GNU General Public License as
-%%% published by the Free Software Foundation; either version 2 of the
-%%% License, or (at your option) any later version.
-%%%
-%%% This program is distributed in the hope that it will be useful,
-%%% but WITHOUT ANY WARRANTY; without even the implied warranty of
-%%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
-%%% General Public License for more details.
-%%%
-%%% You should have received a copy of the GNU General Public License along
-%%% with this program; if not, write to the Free Software Foundation, Inc.,
-%%% 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
-%%%
-%%%----------------------------------------------------------------------
-
--module(ejabberd_http_poll).
-
--author('alexey@process-one.net').
-
--behaviour(gen_fsm).
-
-%% External exports
--export([start_link/3, init/1, handle_event/3,
-        handle_sync_event/4, code_change/4, handle_info/3,
-        terminate/3, send/2, setopts/2, sockname/1, peername/1,
-        controlling_process/2, close/1, process/2]).
-
--include("ejabberd.hrl").
--include("logger.hrl").
-
--include("jlib.hrl").
-
--include("ejabberd_http.hrl").
-
--record(http_poll, {id :: pid() | binary(), pid :: pid()}).
-
--type poll_socket() :: #http_poll{}.
--export_type([poll_socket/0]).
-
--record(state,
-       {id, key, socket, output = [], input = <<"">>,
-        waiting_input = false, last_receiver, http_poll_timeout,
-        timer}).
-
-%-define(DBGFSM, true).
-
--ifdef(DBGFSM).
-
--define(FSMOPTS, [{debug, [trace]}]).
-
--else.
-
--define(FSMOPTS, []).
-
--endif.
-
--define(HTTP_POLL_TIMEOUT, 300).
-
--define(CT,
-       {<<"Content-Type">>, <<"text/xml; charset=utf-8">>}).
-
--define(BAD_REQUEST,
-       [?CT, {<<"Set-Cookie">>, <<"ID=-3:0; expires=-1">>}]).
-
-%%%----------------------------------------------------------------------
-%%% API
-%%%----------------------------------------------------------------------
-start(ID, Key, IP) ->
-    mnesia:create_table(http_poll,
-                       [{ram_copies, [node()]},
-                        {attributes, record_info(fields, http_poll)}]),
-    supervisor:start_child(ejabberd_http_poll_sup, [ID, Key, IP]).
-
-start_link(ID, Key, IP) ->
-    gen_fsm:start_link(?MODULE, [ID, Key, IP], ?FSMOPTS).
-
-send({http_poll, FsmRef, _IP}, Packet) ->
-    gen_fsm:sync_send_all_state_event(FsmRef,
-                                     {send, Packet}).
-
-setopts({http_poll, FsmRef, _IP}, Opts) ->
-    case lists:member({active, once}, Opts) of
-      true ->
-         gen_fsm:send_all_state_event(FsmRef,
-                                      {activate, self()});
-      _ -> ok
-    end.
-
-sockname(_Socket) -> {ok, {{0, 0, 0, 0}, 0}}.
-
-peername({http_poll, _FsmRef, IP}) -> {ok, IP}.
-
-controlling_process(_Socket, _Pid) -> ok.
-
-close({http_poll, FsmRef, _IP}) ->
-    catch gen_fsm:sync_send_all_state_event(FsmRef, close).
-
-process([],
-       #request{data = Data, ip = IP} = _Request) ->
-    case catch parse_request(Data) of
-       {ok, ID1, Key, NewKey, Packet} ->
-           ID = if
-                    (ID1 == <<"0">>) or (ID1 == <<"mobile">>) ->
-                        NewID = p1_sha:sha(term_to_binary({now(), make_ref()})),
-                        {ok, Pid} = start(NewID, <<"">>, IP),
-                        mnesia:transaction(
-                          fun() ->
-                                  mnesia:write(#http_poll{id = NewID, pid = Pid})
-                          end),
-                        NewID;
-                    true ->
-                        ID1
-                end,
-           case http_put(ID, Key, NewKey, Packet) of
-               {error, not_exists} ->
-                   {200, ?BAD_REQUEST, <<"">>};
-               {error, bad_key} ->
-                   {200, ?BAD_REQUEST, <<"">>};
-               ok ->
-                   receive
-                   after 100 -> ok
-                   end,
-                   case http_get(ID) of
-                       {error, not_exists} ->
-                           {200, ?BAD_REQUEST, <<"">>};
-                       {ok, OutPacket} ->
-                           if
-                               ID == ID1 ->
-                                   Cookie = <<"ID=", ID/binary, "; expires=-1">>,
-                                   {200, [?CT, {<<"Set-Cookie">>, Cookie}],
-                                    OutPacket};
-                               ID1 == <<"mobile">> ->
-                                   {200, [?CT], [ID, $\n, OutPacket]};
-                               true ->
-                                   Cookie = <<"ID=", ID/binary, "; expires=-1">>,
-                                   {200, [?CT, {<<"Set-Cookie">>, Cookie}],
-                                    OutPacket}
-                           end
-                   end
-           end;
-       _ ->
-           HumanHTMLxmlel = get_human_html_xmlel(),
-           {200, [?CT, {<<"Set-Cookie">>, <<"ID=-2:0; expires=-1">>}], HumanHTMLxmlel}
-    end;
-process(_, _Request) ->
-    {400, [],
-     #xmlel{name = <<"h1">>, attrs = [],
-           children = [{xmlcdata, <<"400 Bad Request">>}]}}.
-
-%% Code copied from mod_http_bind.erl and customized
-get_human_html_xmlel() ->
-    Heading = <<"ejabberd ",
-               (iolist_to_binary(atom_to_list(?MODULE)))/binary>>,
-    #xmlel{name = <<"html">>,
-          attrs =
-              [{<<"xmlns">>, <<"http://www.w3.org/1999/xhtml">>}],
-          children =
-              [#xmlel{name = <<"head">>, attrs = [],
-                      children =
-                          [#xmlel{name = <<"title">>, attrs = [],
-                                  children = [{xmlcdata, Heading}]}]},
-               #xmlel{name = <<"body">>, attrs = [],
-                      children =
-                          [#xmlel{name = <<"h1">>, attrs = [],
-                                  children = [{xmlcdata, Heading}]},
-                           #xmlel{name = <<"p">>, attrs = [],
-                                  children =
-                                      [{xmlcdata, <<"An implementation of ">>},
-                                       #xmlel{name = <<"a">>,
-                                              attrs =
-                                                  [{<<"href">>,
-                                                    <<"http://xmpp.org/extensions/xep-0025.html">>}],
-                                              children =
-                                                  [{xmlcdata,
-                                                    <<"Jabber HTTP Polling (XEP-0025)">>}]}]},
-                           #xmlel{name = <<"p">>, attrs = [],
-                                  children =
-                                      [{xmlcdata,
-                                        <<"This web page is only informative. To "
-                                          "use HTTP-Poll you need a Jabber/XMPP "
-                                          "client that supports it.">>}]}]}]}.
-
-%%%----------------------------------------------------------------------
-%%% Callback functions from gen_fsm
-%%%----------------------------------------------------------------------
-
-%%----------------------------------------------------------------------
-%% Func: init/1
-%% Returns: {ok, StateName, StateData}          |
-%%          {ok, StateName, StateData, Timeout} |
-%%          ignore                              |
-%%          {stop, StopReason}                   
-%%----------------------------------------------------------------------
-init([ID, Key, IP]) ->
-    ?INFO_MSG("started: ~p", [{ID, Key, IP}]),
-    Opts = ejabberd_c2s_config:get_c2s_limits(),
-    HTTPPollTimeout = ejabberd_config:get_option(
-                        {http_poll_timeout, ?MYNAME},
-                        fun(I) when is_integer(I), I>0 -> I end,
-                        ?HTTP_POLL_TIMEOUT) * 1000,
-    Socket = {http_poll, self(), IP},
-    ejabberd_socket:start(ejabberd_c2s, ?MODULE, Socket,
-                         Opts),
-    Timer = erlang:start_timer(HTTPPollTimeout, self(), []),
-    {ok, loop,
-     #state{id = ID, key = Key, socket = Socket,
-           http_poll_timeout = HTTPPollTimeout, timer = Timer}}.
-
-%%----------------------------------------------------------------------
-%% Func: StateName/2
-%% Returns: {next_state, NextStateName, NextStateData}          |
-%%          {next_state, NextStateName, NextStateData, Timeout} |
-%%          {stop, Reason, NewStateData}                         
-%%          {stop, Reason, NewStateData}
-%%----------------------------------------------------------------------
-
-%%----------------------------------------------------------------------
-%% Func: StateName/3
-%% Returns: {next_state, NextStateName, NextStateData}            |
-%%          {next_state, NextStateName, NextStateData, Timeout}   |
-%%          {reply, Reply, NextStateName, NextStateData}          |
-%%          {reply, Reply, NextStateName, NextStateData, Timeout} |
-%%          {stop, Reason, NewStateData}                          |
-%%          {stop, Reason, Reply, NewStateData}                    
-%%          {stop, Reason, Reply, NewStateData}
-%%----------------------------------------------------------------------
-%state_name(Event, From, StateData) ->
-%    Reply = ok,
-%    {reply, Reply, state_name, StateData}.
-
-%%----------------------------------------------------------------------
-%% Func: handle_event/3
-%% Returns: {next_state, NextStateName, NextStateData}          |
-%%          {next_state, NextStateName, NextStateData, Timeout} |
-%%          {stop, Reason, NewStateData}                         
-%%----------------------------------------------------------------------
-handle_event({activate, From}, StateName, StateData) ->
-    case StateData#state.input of
-      <<"">> ->
-         {next_state, StateName,
-          StateData#state{waiting_input = {From, ok}}};
-      Input ->
-         Receiver = From,
-         Receiver !
-           {tcp, StateData#state.socket, Input},
-         {next_state, StateName,
-          StateData#state{input = <<"">>, waiting_input = false,
-                          last_receiver = Receiver}}
-    end;
-handle_event(_Event, StateName, StateData) ->
-    {next_state, StateName, StateData}.
-
-%%----------------------------------------------------------------------
-%% Func: handle_sync_event/4
-%% Returns: {next_state, NextStateName, NextStateData}            |
-%%          {next_state, NextStateName, NextStateData, Timeout}   |
-%%          {reply, Reply, NextStateName, NextStateData}          |
-%%          {reply, Reply, NextStateName, NextStateData, Timeout} |
-%%          {stop, Reason, NewStateData}                          |
-%%          {stop, Reason, Reply, NewStateData}                    
-%%----------------------------------------------------------------------
-handle_sync_event({send, Packet}, _From, StateName,
-                 StateData) ->
-    Packet2 = iolist_to_binary(Packet),
-    Output = StateData#state.output ++ [Packet2],
-    Reply = ok,
-    {reply, Reply, StateName,
-     StateData#state{output = Output}};
-handle_sync_event(stop, _From, _StateName, StateData) ->
-    Reply = ok, {stop, normal, Reply, StateData};
-handle_sync_event({http_put, Key, NewKey, Packet},
-                 _From, StateName, StateData) ->
-    Allow = case StateData#state.key of
-             <<"">> -> true;
-             OldKey ->
-                 NextKey = jlib:encode_base64((p1_sha:sha1(Key))),
-                 if OldKey == NextKey -> true;
-                    true -> false
-                 end
-           end,
-    if Allow ->
-          case StateData#state.waiting_input of
-            false ->
-                Input = <<(StateData#state.input)/binary, Packet/binary>>,
-                Reply = ok,
-                {reply, Reply, StateName,
-                 StateData#state{input = Input, key = NewKey}};
-            {Receiver, _Tag} ->
-                Receiver !
-                  {tcp, StateData#state.socket, iolist_to_binary(Packet)},
-                cancel_timer(StateData#state.timer),
-                Timer =
-                    erlang:start_timer(StateData#state.http_poll_timeout,
-                                       self(), []),
-                Reply = ok,
-                {reply, Reply, StateName,
-                 StateData#state{waiting_input = false,
-                                 last_receiver = Receiver, key = NewKey,
-                                 timer = Timer}}
-          end;
-       true ->
-          Reply = {error, bad_key},
-          {reply, Reply, StateName, StateData}
-    end;
-handle_sync_event(http_get, _From, StateName,
-                 StateData) ->
-    Reply = {ok, StateData#state.output},
-    {reply, Reply, StateName,
-     StateData#state{output = []}};
-handle_sync_event(_Event, _From, StateName,
-                 StateData) ->
-    Reply = ok, {reply, Reply, StateName, StateData}.
-
-code_change(_OldVsn, StateName, StateData, _Extra) ->
-    {ok, StateName, StateData}.
-
-%%----------------------------------------------------------------------
-%% Func: handle_info/3
-%% Returns: {next_state, NextStateName, NextStateData}          |
-%%          {next_state, NextStateName, NextStateData, Timeout} |
-%%          {stop, Reason, NewStateData}                         
-%%----------------------------------------------------------------------
-handle_info({timeout, Timer, _}, _StateName,
-           #state{timer = Timer} = StateData) ->
-    {stop, normal, StateData};
-handle_info(_, StateName, StateData) ->
-    {next_state, StateName, StateData}.
-
-%%----------------------------------------------------------------------
-%% Func: terminate/3
-%% Purpose: Shutdown the fsm
-%% Returns: any
-%%----------------------------------------------------------------------
-terminate(_Reason, _StateName, StateData) ->
-    mnesia:transaction(
-      fun() ->
-             mnesia:delete({http_poll, StateData#state.id})
-      end),
-    case StateData#state.waiting_input of
-      false ->
-         case StateData#state.last_receiver of
-           undefined -> ok;
-           Receiver ->
-               Receiver ! {tcp_closed, StateData#state.socket}
-         end;
-      {Receiver, _Tag} ->
-         Receiver ! {tcp_closed, StateData#state.socket}
-    end,
-    catch resend_messages(StateData#state.output),
-    ok.
-
-%%%----------------------------------------------------------------------
-%%% Internal functions
-%%%----------------------------------------------------------------------
-
-http_put(ID, Key, NewKey, Packet) ->
-    case mnesia:dirty_read({http_poll, ID}) of
-       [] ->
-           {error, not_exists};
-       [#http_poll{pid = FsmRef}] ->
-           gen_fsm:sync_send_all_state_event(
-             FsmRef, {http_put, Key, NewKey, Packet})
-    end.
-
-http_get(ID) ->
-    case mnesia:dirty_read({http_poll, ID}) of
-       [] ->
-           {error, not_exists};
-       [#http_poll{pid = FsmRef}] ->
-           gen_fsm:sync_send_all_state_event(FsmRef, http_get)
-    end.
-
-parse_request(Data) ->
-    Comma = str:chr(Data, $,),
-    Header = str:substr(Data, 1, Comma - 1),
-    Packet = str:substr(Data, Comma + 1, byte_size(Data)),
-    {ID, Key, NewKey} = case str:tokens(Header, <<";">>) of
-                         [ID1] -> {ID1, <<"">>, <<"">>};
-                         [ID1, Key1] -> {ID1, Key1, Key1};
-                         [ID1, Key1, NewKey1] -> {ID1, Key1, NewKey1}
-                       end,
-    {ok, ID, Key, NewKey, Packet}.
-
-cancel_timer(Timer) ->
-    erlang:cancel_timer(Timer),
-    receive {timeout, Timer, _} -> ok after 0 -> ok end.
-
-%% Resend the polled messages
-resend_messages(Messages) ->
-%% This function is used to resend messages that have been polled but not
-%% delivered.
-    lists:foreach(fun (Packet) -> resend_message(Packet)
-                 end,
-                 Messages).
-
-resend_message(Packet) ->
-    #xmlel{name = Name} = ParsedPacket =
-                             xml_stream:parse_element(Packet),
-    if Name == <<"iq">>;
-       Name == <<"message">>;
-       Name == <<"presence">> ->
-          From = get_jid(<<"from">>, ParsedPacket),
-          To = get_jid(<<"to">>, ParsedPacket),
-          ?DEBUG("Resend ~p ~p ~p~n", [From, To, ParsedPacket]),
-          ejabberd_router:route(From, To, ParsedPacket);
-       true -> ok
-    end.
-
-%% Type can be "from" or "to"
-%% Parsed packet is a parsed Jabber packet.
-get_jid(Type, ParsedPacket) ->
-    case xml:get_tag_attr(Type, ParsedPacket) of
-      {value, StringJid} -> jlib:string_to_jid(StringJid);
-      false -> jlib:make_jid(<<"">>, <<"">>, <<"">>)
-    end.
index 86f6971b688893d1fd543082aab0d3d464a16685..29c7774e4a2f2c5508c1a8ab7c8667a80786b868 100644 (file)
 -include("logger.hrl").
 -include("jlib.hrl").
 
--type sockmod() :: ejabberd_http_poll |
-                   ejabberd_http_bind |
+-type sockmod() :: ejabberd_http_bind |
                    ejabberd_http_ws |
                    gen_tcp | p1_tls | ezlib.
 -type receiver() :: pid () | atom().
 -type socket() :: pid() | inet:socket() |
                   p1_tls:tls_socket() |
                   ezlib:zlib_socket() |
-                  ejabberd_http_bind:bind_socket() |
-                  ejabberd_http_poll:poll_socket().
+                  ejabberd_http_bind:bind_socket().
 
 -record(socket_state, {sockmod = gen_tcp :: sockmod(),
                        socket = self() :: socket(),
@@ -192,7 +190,7 @@ send(SocketData, Data) ->
 
 %% Can only be called when in c2s StateData#state.xml_socket is true
 %% This function is used for HTTP bind
-%% sockmod=ejabberd_http_poll|ejabberd_http_bind or any custom module
+%% sockmod=ejabberd_http_ws|ejabberd_http_bind or any custom module
 -spec send_xml(socket_state(), xmlel()) -> any().
 
 send_xml(SocketData, Data) ->
index 423f84ab95446e1d412cee26035f145aa203860c..da25af2c7873f2e97b0c6f016e2b5212c7cbf1f9 100644 (file)
@@ -144,14 +144,6 @@ init([]) ->
         infinity,
         supervisor,
         [ejabberd_tmp_sup]},
-    HTTPPollSupervisor =
-       {ejabberd_http_poll_sup,
-        {ejabberd_tmp_sup, start_link,
-         [ejabberd_http_poll_sup, ejabberd_http_poll]},
-        permanent,
-        infinity,
-        supervisor,
-        [ejabberd_tmp_sup]},
     FrontendSocketSupervisor =
        {ejabberd_frontend_socket_sup,
         {ejabberd_tmp_sup, start_link,
@@ -183,9 +175,6 @@ init([]) ->
           S2SOutSupervisor,
           ServiceSupervisor,
           HTTPSupervisor,
-          HTTPPollSupervisor,
           IQSupervisor,
           FrontendSocketSupervisor,
           Listener]}}.
-
-
index 65bac357f49c276d1a740cde064d016af5d8ed14..29ecb7346ea31293c3e27c5db42fe516a890c5a3 100644 (file)
@@ -1549,9 +1549,7 @@ user_info(User, Server, Query, Lang) ->
                                                           c2s_compressed_tls ->
                                                               <<"tls+zlib">>;
                                                           http_bind ->
-                                                              <<"http-bind">>;
-                                                          http_poll ->
-                                                              <<"http-poll">>
+                                                              <<"http-bind">>
                                                       end,
                                               <<" (", ConnS/binary,
                                                 "://",
@@ -2879,4 +2877,3 @@ make_menu_item(item, 3, URI, Name, Lang) ->
 %%%==================================
 
 %%% vim: set foldmethod=marker foldmarker=%%%%,%%%=:
-