--- /dev/null
+%%%----------------------------------------------------------------------
+%%% File : mod_muc_odbc.erl
+%%% Author : Alexey Shchepin <alexey@process-one.net>
+%%% Purpose : MUC support (XEP-0045)
+%%% Created : 19 Mar 2003 by Alexey Shchepin <alexey@process-one.net>
+%%%
+%%%
+%%% ejabberd, Copyright (C) 2002-2012 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., 59 Temple Place, Suite 330, Boston, MA
+%%% 02111-1307 USA
+%%%
+%%%----------------------------------------------------------------------
+
+-module(mod_muc_odbc).
+-author('alexey@process-one.net').
+
+-behaviour(gen_server).
+-behaviour(gen_mod).
+
+%% API
+-export([start_link/2,
+ start/2,
+ stop/1,
+ room_destroyed/4,
+ store_room/4,
+ restore_room/3,
+ forget_room/3,
+ create_room/5,
+ process_iq_disco_items/4,
+ broadcast_service_message/2,
+ encode_opts/1,
+ decode_opts/1,
+ can_use_nick/4]).
+
+%% gen_server callbacks
+-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
+ terminate/2, code_change/3]).
+
+-include("ejabberd.hrl").
+-include("jlib.hrl").
+
+
+-record(muc_online_room, {name_host, pid}).
+
+-record(state, {host,
+ server_host,
+ access,
+ history_size,
+ default_room_opts,
+ room_shaper}).
+
+-define(PROCNAME, ejabberd_mod_muc).
+
+%%====================================================================
+%% API
+%%====================================================================
+%%--------------------------------------------------------------------
+%% Function: start_link() -> {ok,Pid} | ignore | {error,Error}
+%% Description: Starts the server
+%%--------------------------------------------------------------------
+start_link(Host, Opts) ->
+ Proc = gen_mod:get_module_proc(Host, ?PROCNAME),
+ gen_server:start_link({local, Proc}, ?MODULE, [Host, Opts], []).
+
+start(Host, Opts) ->
+ start_supervisor(Host),
+ Proc = gen_mod:get_module_proc(Host, ?PROCNAME),
+ ChildSpec =
+ {Proc,
+ {?MODULE, start_link, [Host, Opts]},
+ temporary,
+ 1000,
+ worker,
+ [?MODULE]},
+ supervisor:start_child(ejabberd_sup, ChildSpec).
+
+stop(Host) ->
+ stop_supervisor(Host),
+ Proc = gen_mod:get_module_proc(Host, ?PROCNAME),
+ gen_server:call(Proc, stop),
+ supervisor:delete_child(ejabberd_sup, Proc).
+
+%% This function is called by a room in three situations:
+%% A) The owner of the room destroyed it
+%% B) The only participant of a temporary room leaves it
+%% C) mod_muc:stop was called, and each room is being terminated
+%% In this case, the mod_muc process died before the room processes
+%% So the message sending must be catched
+room_destroyed(Host, Room, Pid, ServerHost) ->
+ catch gen_mod:get_module_proc(ServerHost, ?PROCNAME) !
+ {room_destroyed, {Room, Host}, Pid},
+ ok.
+
+%% @doc Create a room.
+%% If Opts = default, the default room options are used.
+%% Else use the passed options as defined in mod_muc_room.
+create_room(Host, Name, From, Nick, Opts) ->
+ Proc = gen_mod:get_module_proc(Host, ?PROCNAME),
+ gen_server:call(Proc, {create, Name, From, Nick, Opts}).
+
+store_room(ServerHost, Host, Name, Opts) ->
+ SName = ejabberd_odbc:escape(Name),
+ SHost = ejabberd_odbc:escape(Host),
+ LServer = jlib:nameprep(ServerHost),
+ F = fun() ->
+ update_t(
+ "muc_room",
+ ["name", "host", "opts"],
+ [SName, SHost, encode_opts(Opts)],
+ ["name='", SName, "' and host='", SHost, "'"])
+ end,
+ ejabberd_odbc:sql_transaction(LServer, F).
+
+restore_room(ServerHost, Host, Name) ->
+ SName = ejabberd_odbc:escape(Name),
+ SHost = ejabberd_odbc:escape(Host),
+ LServer = jlib:nameprep(ServerHost),
+ case catch ejabberd_odbc:sql_query(
+ LServer, ["select opts from muc_room where name='",
+ SName, "' and host='", SHost, "';"]) of
+ {selected, ["opts"], [{Opts}]} ->
+ decode_opts(Opts);
+ _ ->
+ error
+ end.
+
+forget_room(ServerHost, Host, Name) ->
+ SName = ejabberd_odbc:escape(Name),
+ SHost = ejabberd_odbc:escape(Host),
+ LServer = jlib:nameprep(ServerHost),
+ F = fun() ->
+ ejabberd_odbc:sql_query_t(
+ ["delete from muc_room where name='",
+ SName, "' and host='", SHost, "';"])
+ end,
+ ejabberd_odbc:sql_transaction(LServer, F).
+
+process_iq_disco_items(Host, From, To, #iq{lang = Lang} = IQ) ->
+ Rsm = jlib:rsm_decode(IQ),
+ Res = IQ#iq{type = result,
+ sub_el = [{xmlelement, "query",
+ [{"xmlns", ?NS_DISCO_ITEMS}],
+ iq_disco_items(Host, From, Lang, Rsm)}]},
+ ejabberd_router:route(To,
+ From,
+ jlib:iq_to_xml(Res)).
+
+can_use_nick(_ServerHost, _Host, _JID, "") ->
+ false;
+can_use_nick(ServerHost, Host, JID, Nick) ->
+ SJID = jlib:jid_to_string(
+ jlib:jid_tolower(
+ jlib:jid_remove_resource(JID))),
+ SNick = ejabberd_odbc:escape(Nick),
+ SHost = ejabberd_odbc:escape(Host),
+ LServer = jlib:nameprep(ServerHost),
+ case catch ejabberd_odbc:sql_query(
+ LServer, ["select jid from muc_registered ",
+ "where nick='", SNick, "' and host='",
+ SHost, "';"]) of
+ {selected, ["jid"], [{SJID1}]} ->
+ SJID == SJID1;
+ _ ->
+ true
+ end.
+
+%%====================================================================
+%% gen_server callbacks
+%%====================================================================
+
+%%--------------------------------------------------------------------
+%% Function: init(Args) -> {ok, State} |
+%% {ok, State, Timeout} |
+%% ignore |
+%% {stop, Reason}
+%% Description: Initiates the server
+%%--------------------------------------------------------------------
+init([Host, Opts]) ->
+ mnesia:create_table(muc_online_room,
+ [{ram_copies, [node()]},
+ {attributes, record_info(fields, muc_online_room)}]),
+ mnesia:add_table_copy(muc_online_room, node(), ram_copies),
+ catch ets:new(muc_online_users, [bag, named_table, public, {keypos, 2}]),
+ MyHost = gen_mod:get_opt_host(Host, Opts, "conference.@HOST@"),
+ clean_table_from_bad_node(node(), MyHost),
+ mnesia:subscribe(system),
+ Access = gen_mod:get_opt(access, Opts, all),
+ AccessCreate = gen_mod:get_opt(access_create, Opts, all),
+ AccessAdmin = gen_mod:get_opt(access_admin, Opts, none),
+ AccessPersistent = gen_mod:get_opt(access_persistent, Opts, all),
+ HistorySize = gen_mod:get_opt(history_size, Opts, 20),
+ DefRoomOpts = gen_mod:get_opt(default_room_options, Opts, []),
+ RoomShaper = gen_mod:get_opt(room_shaper, Opts, none),
+ ejabberd_router:register_route(MyHost),
+ load_permanent_rooms(MyHost, Host,
+ {Access, AccessCreate, AccessAdmin, AccessPersistent},
+ HistorySize,
+ RoomShaper),
+ {ok, #state{host = MyHost,
+ server_host = Host,
+ access = {Access, AccessCreate, AccessAdmin, AccessPersistent},
+ default_room_opts = DefRoomOpts,
+ history_size = HistorySize,
+ room_shaper = RoomShaper}}.
+
+%%--------------------------------------------------------------------
+%% Function: %% handle_call(Request, From, State) -> {reply, Reply, State} |
+%% {reply, Reply, State, Timeout} |
+%% {noreply, State} |
+%% {noreply, State, Timeout} |
+%% {stop, Reason, Reply, State} |
+%% {stop, Reason, State}
+%% Description: Handling call messages
+%%--------------------------------------------------------------------
+handle_call(stop, _From, State) ->
+ {stop, normal, ok, State};
+
+handle_call({create, Room, From, Nick, Opts},
+ _From,
+ #state{host = Host,
+ server_host = ServerHost,
+ access = Access,
+ default_room_opts = DefOpts,
+ history_size = HistorySize,
+ room_shaper = RoomShaper} = State) ->
+ ?DEBUG("MUC: create new room '~s'~n", [Room]),
+ NewOpts = case Opts of
+ default -> DefOpts;
+ _ -> Opts
+ end,
+ {ok, Pid} = mod_muc_room:start(
+ Host, ServerHost, Access,
+ Room, HistorySize,
+ RoomShaper, From,
+ Nick, NewOpts, ?MODULE),
+ register_room(Host, Room, Pid),
+ {reply, ok, State}.
+
+%%--------------------------------------------------------------------
+%% Function: handle_cast(Msg, State) -> {noreply, State} |
+%% {noreply, State, Timeout} |
+%% {stop, Reason, State}
+%% Description: Handling cast messages
+%%--------------------------------------------------------------------
+handle_cast(_Msg, State) ->
+ {noreply, State}.
+
+%%--------------------------------------------------------------------
+%% Function: handle_info(Info, State) -> {noreply, State} |
+%% {noreply, State, Timeout} |
+%% {stop, Reason, State}
+%% Description: Handling all non call/cast messages
+%%--------------------------------------------------------------------
+handle_info({route, From, To, Packet},
+ #state{host = Host,
+ server_host = ServerHost,
+ access = Access,
+ default_room_opts = DefRoomOpts,
+ history_size = HistorySize,
+ room_shaper = RoomShaper} = State) ->
+ case catch do_route(Host, ServerHost, Access, HistorySize, RoomShaper,
+ From, To, Packet, DefRoomOpts) of
+ {'EXIT', Reason} ->
+ ?ERROR_MSG("~p", [Reason]);
+ _ ->
+ ok
+ end,
+ {noreply, State};
+handle_info({room_destroyed, RoomHost, Pid}, State) ->
+ F = fun() ->
+ mnesia:delete_object(#muc_online_room{name_host = RoomHost,
+ pid = Pid})
+ end,
+ mnesia:transaction(F),
+ {noreply, State};
+handle_info({mnesia_system_event, {mnesia_down, Node}}, State) ->
+ clean_table_from_bad_node(Node),
+ {noreply, State};
+handle_info(_Info, State) ->
+ {noreply, State}.
+
+%%--------------------------------------------------------------------
+%% Function: terminate(Reason, State) -> void()
+%% Description: This function is called by a gen_server when it is about to
+%% terminate. It should be the opposite of Module:init/1 and do any necessary
+%% cleaning up. When it returns, the gen_server terminates with Reason.
+%% The return value is ignored.
+%%--------------------------------------------------------------------
+terminate(_Reason, State) ->
+ ejabberd_router:unregister_route(State#state.host),
+ ok.
+
+%%--------------------------------------------------------------------
+%% Func: code_change(OldVsn, State, Extra) -> {ok, NewState}
+%% Description: Convert process state when code is changed
+%%--------------------------------------------------------------------
+code_change(_OldVsn, State, _Extra) ->
+ {ok, State}.
+
+%%--------------------------------------------------------------------
+%%% Internal functions
+%%--------------------------------------------------------------------
+start_supervisor(Host) ->
+ Proc = gen_mod:get_module_proc(Host, ejabberd_mod_muc_sup),
+ ChildSpec =
+ {Proc,
+ {ejabberd_tmp_sup, start_link,
+ [Proc, mod_muc_room]},
+ permanent,
+ infinity,
+ supervisor,
+ [ejabberd_tmp_sup]},
+ supervisor:start_child(ejabberd_sup, ChildSpec).
+
+stop_supervisor(Host) ->
+ Proc = gen_mod:get_module_proc(Host, ejabberd_mod_muc_sup),
+ supervisor:terminate_child(ejabberd_sup, Proc),
+ supervisor:delete_child(ejabberd_sup, Proc).
+
+do_route(Host, ServerHost, Access, HistorySize, RoomShaper,
+ From, To, Packet, DefRoomOpts) ->
+ {AccessRoute, _AccessCreate, _AccessAdmin, _AccessPersistent} = Access,
+ case acl:match_rule(ServerHost, AccessRoute, From) of
+ allow ->
+ do_route1(Host, ServerHost, Access, HistorySize, RoomShaper,
+ From, To, Packet, DefRoomOpts);
+ _ ->
+ {xmlelement, _Name, Attrs, _Els} = Packet,
+ Lang = xml:get_attr_s("xml:lang", Attrs),
+ ErrText = "Access denied by service policy",
+ Err = jlib:make_error_reply(Packet,
+ ?ERRT_FORBIDDEN(Lang, ErrText)),
+ ejabberd_router:route_error(To, From, Err, Packet)
+ end.
+
+
+do_route1(Host, ServerHost, Access, HistorySize, RoomShaper,
+ From, To, Packet, DefRoomOpts) ->
+ {_AccessRoute, AccessCreate, AccessAdmin, _AccessPersistent} = Access,
+ {Room, _, Nick} = jlib:jid_tolower(To),
+ {xmlelement, Name, Attrs, _Els} = Packet,
+ case Room of
+ "" ->
+ case Nick of
+ "" ->
+ case Name of
+ "iq" ->
+ case jlib:iq_query_info(Packet) of
+ #iq{type = get, xmlns = ?NS_DISCO_INFO = XMLNS,
+ sub_el = _SubEl, lang = Lang} = IQ ->
+ Info = ejabberd_hooks:run_fold(
+ disco_info, ServerHost, [],
+ [ServerHost, ?MODULE, "", ""]),
+ Res = IQ#iq{type = result,
+ sub_el = [{xmlelement, "query",
+ [{"xmlns", XMLNS}],
+ iq_disco_info(Lang)
+ ++Info}]},
+ ejabberd_router:route(To,
+ From,
+ jlib:iq_to_xml(Res));
+ #iq{type = get,
+ xmlns = ?NS_DISCO_ITEMS} = IQ ->
+ spawn(?MODULE,
+ process_iq_disco_items,
+ [Host, From, To, IQ]);
+ #iq{type = get,
+ xmlns = ?NS_REGISTER = XMLNS,
+ lang = Lang,
+ sub_el = _SubEl} = IQ ->
+ Res = IQ#iq{type = result,
+ sub_el =
+ [{xmlelement, "query",
+ [{"xmlns", XMLNS}],
+ iq_get_register_info(
+ ServerHost, Host, From, Lang)}]},
+ ejabberd_router:route(To,
+ From,
+ jlib:iq_to_xml(Res));
+ #iq{type = set,
+ xmlns = ?NS_REGISTER = XMLNS,
+ lang = Lang,
+ sub_el = SubEl} = IQ ->
+ case process_iq_register_set(
+ ServerHost, Host, From, SubEl, Lang) of
+ {result, IQRes} ->
+ Res = IQ#iq{type = result,
+ sub_el =
+ [{xmlelement, "query",
+ [{"xmlns", XMLNS}],
+ IQRes}]},
+ ejabberd_router:route(
+ To, From, jlib:iq_to_xml(Res));
+ {error, Error} ->
+ Err = jlib:make_error_reply(
+ Packet, Error),
+ ejabberd_router:route(
+ To, From, Err)
+ end;
+ #iq{type = get,
+ xmlns = ?NS_VCARD = XMLNS,
+ lang = Lang,
+ sub_el = _SubEl} = IQ ->
+ Res = IQ#iq{type = result,
+ sub_el =
+ [{xmlelement, "vCard",
+ [{"xmlns", XMLNS}],
+ iq_get_vcard(Lang)}]},
+ ejabberd_router:route(To,
+ From,
+ jlib:iq_to_xml(Res));
+ #iq{type = get,
+ xmlns = ?NS_MUC_UNIQUE
+ } = IQ ->
+ Res = IQ#iq{type = result,
+ sub_el =
+ [{xmlelement, "unique",
+ [{"xmlns", ?NS_MUC_UNIQUE}],
+ [iq_get_unique(From)]}]},
+ ejabberd_router:route(To,
+ From,
+ jlib:iq_to_xml(Res));
+ #iq{} ->
+ Err = jlib:make_error_reply(
+ Packet,
+ ?ERR_FEATURE_NOT_IMPLEMENTED),
+ ejabberd_router:route(To, From, Err);
+ _ ->
+ ok
+ end;
+ "message" ->
+ case xml:get_attr_s("type", Attrs) of
+ "error" ->
+ ok;
+ _ ->
+ case acl:match_rule(ServerHost, AccessAdmin, From) of
+ allow ->
+ Msg = xml:get_path_s(
+ Packet,
+ [{elem, "body"}, cdata]),
+ broadcast_service_message(Host, Msg);
+ _ ->
+ Lang = xml:get_attr_s("xml:lang", Attrs),
+ ErrText = "Only service administrators "
+ "are allowed to send service messages",
+ Err = jlib:make_error_reply(
+ Packet,
+ ?ERRT_FORBIDDEN(Lang, ErrText)),
+ ejabberd_router:route(
+ To, From, Err)
+ end
+ end;
+ "presence" ->
+ ok
+ end;
+ _ ->
+ case xml:get_attr_s("type", Attrs) of
+ "error" ->
+ ok;
+ "result" ->
+ ok;
+ _ ->
+ Err = jlib:make_error_reply(
+ Packet, ?ERR_ITEM_NOT_FOUND),
+ ejabberd_router:route(To, From, Err)
+ end
+ end;
+ _ ->
+ case mnesia:dirty_read(muc_online_room, {Room, Host}) of
+ [] ->
+ Type = xml:get_attr_s("type", Attrs),
+ case {Name, Type} of
+ {"presence", ""} ->
+ case check_user_can_create_room(ServerHost,
+ AccessCreate, From,
+ Room) of
+ true ->
+ {ok, Pid} = start_new_room(
+ Host, ServerHost, Access,
+ Room, HistorySize,
+ RoomShaper, From,
+ Nick, DefRoomOpts),
+ register_room(Host, Room, Pid),
+ mod_muc_room:route(Pid, From, Nick, Packet),
+ ok;
+ false ->
+ Lang = xml:get_attr_s("xml:lang", Attrs),
+ ErrText = "Room creation is denied by service policy",
+ Err = jlib:make_error_reply(
+ Packet, ?ERRT_FORBIDDEN(Lang, ErrText)),
+ ejabberd_router:route(To, From, Err)
+ end;
+ _ ->
+ Lang = xml:get_attr_s("xml:lang", Attrs),
+ ErrText = "Conference room does not exist",
+ Err = jlib:make_error_reply(
+ Packet, ?ERRT_ITEM_NOT_FOUND(Lang, ErrText)),
+ ejabberd_router:route(To, From, Err)
+ end;
+ [R] ->
+ Pid = R#muc_online_room.pid,
+ ?DEBUG("MUC: send to process ~p~n", [Pid]),
+ mod_muc_room:route(Pid, From, Nick, Packet),
+ ok
+ end
+ end.
+
+check_user_can_create_room(ServerHost, AccessCreate, From, RoomID) ->
+ case acl:match_rule(ServerHost, AccessCreate, From) of
+ allow ->
+ (length(RoomID) =< gen_mod:get_module_opt(ServerHost, mod_muc,
+ max_room_id, infinite));
+ _ ->
+ false
+ end.
+
+
+load_permanent_rooms(Host, ServerHost, Access, HistorySize, RoomShaper) ->
+ SHost = ejabberd_odbc:escape(Host),
+ LServer = jlib:nameprep(ServerHost),
+ case catch ejabberd_odbc:sql_query(
+ LServer, ["select name, opts from muc_room ",
+ "where host='", SHost, "';"]) of
+ {'EXIT', Reason} ->
+ ?ERROR_MSG("~p", [Reason]),
+ ok;
+ {selected, ["name", "opts"], RoomOpts} ->
+ lists:foreach(
+ fun({Room, Opts}) ->
+ case mnesia:dirty_read(muc_online_room, {Room, Host}) of
+ [] ->
+ {ok, Pid} = mod_muc_room:start(
+ Host,
+ ServerHost,
+ Access,
+ Room,
+ HistorySize,
+ RoomShaper,
+ decode_opts(Opts),
+ ?MODULE),
+ register_room(Host, Room, Pid);
+ _ ->
+ ok
+ end
+ end, RoomOpts)
+ end.
+
+start_new_room(Host, ServerHost, Access, Room,
+ HistorySize, RoomShaper, From,
+ Nick, DefRoomOpts) ->
+ SHost = ejabberd_odbc:escape(Host),
+ LServer = jlib:nameprep(ServerHost),
+ SRoom = ejabberd_odbc:escape(Room),
+ case ejabberd_odbc:sql_query(
+ LServer, ["select opts from muc_room where name='", SRoom,
+ "' and host='", SHost, "';"]) of
+ {selected, ["opts"], []} ->
+ ?DEBUG("MUC: open new room '~s'~n", [Room]),
+ mod_muc_room:start(Host, ServerHost, Access,
+ Room, HistorySize,
+ RoomShaper, From,
+ Nick, DefRoomOpts, ?MODULE);
+ {selected, ["opts"], [{Opts}|_]} ->
+ ?DEBUG("MUC: restore room '~s'~n", [Room]),
+ mod_muc_room:start(Host, ServerHost, Access,
+ Room, HistorySize,
+ RoomShaper, decode_opts(Opts), ?MODULE)
+ end.
+
+register_room(Host, Room, Pid) ->
+ F = fun() ->
+ mnesia:write(#muc_online_room{name_host = {Room, Host},
+ pid = Pid})
+ end,
+ mnesia:transaction(F).
+
+
+iq_disco_info(Lang) ->
+ [{xmlelement, "identity",
+ [{"category", "conference"},
+ {"type", "text"},
+ {"name", translate:translate(Lang, "Chatrooms")}], []},
+ {xmlelement, "feature", [{"var", ?NS_DISCO_INFO}], []},
+ {xmlelement, "feature", [{"var", ?NS_DISCO_ITEMS}], []},
+ {xmlelement, "feature", [{"var", ?NS_MUC}], []},
+ {xmlelement, "feature", [{"var", ?NS_MUC_UNIQUE}], []},
+ {xmlelement, "feature", [{"var", ?NS_REGISTER}], []},
+ {xmlelement, "feature", [{"var", ?NS_RSM}], []},
+ {xmlelement, "feature", [{"var", ?NS_VCARD}], []}].
+
+
+iq_disco_items(Host, From, Lang, none) ->
+ lists:zf(fun(#muc_online_room{name_host = {Name, _Host}, pid = Pid}) ->
+ case catch gen_fsm:sync_send_all_state_event(
+ Pid, {get_disco_item, From, Lang}, 100) of
+ {item, Desc} ->
+ flush(),
+ {true,
+ {xmlelement, "item",
+ [{"jid", jlib:jid_to_string({Name, Host, ""})},
+ {"name", Desc}], []}};
+ _ ->
+ false
+ end
+ end, get_vh_rooms(Host));
+
+iq_disco_items(Host, From, Lang, Rsm) ->
+ {Rooms, RsmO} = get_vh_rooms(Host, Rsm),
+ RsmOut = jlib:rsm_encode(RsmO),
+ lists:zf(fun(#muc_online_room{name_host = {Name, _Host}, pid = Pid}) ->
+ case catch gen_fsm:sync_send_all_state_event(
+ Pid, {get_disco_item, From, Lang}, 100) of
+ {item, Desc} ->
+ flush(),
+ {true,
+ {xmlelement, "item",
+ [{"jid", jlib:jid_to_string({Name, Host, ""})},
+ {"name", Desc}], []}};
+ _ ->
+ false
+ end
+ end, Rooms) ++ RsmOut.
+
+get_vh_rooms(Host, #rsm_in{max=M, direction=Direction, id=I, index=Index})->
+ AllRooms = lists:sort(get_vh_rooms(Host)),
+ Count = erlang:length(AllRooms),
+ Guard = case Direction of
+ _ when Index =/= undefined -> [{'==', {element, 2, '$1'}, Host}];
+ aft -> [{'==', {element, 2, '$1'}, Host}, {'>=',{element, 1, '$1'} ,I}];
+ before when I =/= []-> [{'==', {element, 2, '$1'}, Host}, {'=<',{element, 1, '$1'} ,I}];
+ _ -> [{'==', {element, 2, '$1'}, Host}]
+ end,
+ L = lists:sort(
+ mnesia:dirty_select(muc_online_room,
+ [{#muc_online_room{name_host = '$1', _ = '_'},
+ Guard,
+ ['$_']}])),
+ L2 = if
+ Index == undefined andalso Direction == before ->
+ lists:reverse(lists:sublist(lists:reverse(L), 1, M));
+ Index == undefined ->
+ lists:sublist(L, 1, M);
+ Index > Count orelse Index < 0 ->
+ [];
+ true ->
+ lists:sublist(L, Index+1, M)
+ end,
+ if
+ L2 == [] ->
+ {L2, #rsm_out{count=Count}};
+ true ->
+ H = hd(L2),
+ NewIndex = get_room_pos(H, AllRooms),
+ T=lists:last(L2),
+ {F, _}=H#muc_online_room.name_host,
+ {Last, _}=T#muc_online_room.name_host,
+ {L2, #rsm_out{first=F, last=Last, count=Count, index=NewIndex}}
+ end.
+
+%% @doc Return the position of desired room in the list of rooms.
+%% The room must exist in the list. The count starts in 0.
+%% @spec (Desired::muc_online_room(), Rooms::[muc_online_room()]) -> integer()
+get_room_pos(Desired, Rooms) ->
+ get_room_pos(Desired, Rooms, 0).
+get_room_pos(Desired, [HeadRoom | _], HeadPosition)
+ when (Desired#muc_online_room.name_host ==
+ HeadRoom#muc_online_room.name_host) ->
+ HeadPosition;
+get_room_pos(Desired, [_ | Rooms], HeadPosition) ->
+ get_room_pos(Desired, Rooms, HeadPosition + 1).
+
+flush() ->
+ receive
+ _ ->
+ flush()
+ after 0 ->
+ ok
+ end.
+
+-define(XFIELD(Type, Label, Var, Val),
+ {xmlelement, "field", [{"type", Type},
+ {"label", translate:translate(Lang, Label)},
+ {"var", Var}],
+ [{xmlelement, "value", [], [{xmlcdata, Val}]}]}).
+
+%% @doc Get a pseudo unique Room Name. The Room Name is generated as a hash of
+%% the requester JID, the local time and a random salt.
+%%
+%% "pseudo" because we don't verify that there is not a room
+%% with the returned Name already created, nor mark the generated Name
+%% as "already used". But in practice, it is unique enough. See
+%% http://xmpp.org/extensions/xep-0045.html#createroom-unique
+iq_get_unique(From) ->
+ {xmlcdata, sha:sha(term_to_binary([From, now(), randoms:get_string()]))}.
+
+iq_get_register_info(ServerHost, Host, From, Lang) ->
+ SJID = ejabberd_odbc:escape(
+ jlib:jid_to_string(
+ jlib:jid_tolower(
+ jlib:jid_remove_resource(From)))),
+ SHost = ejabberd_odbc:escape(Host),
+ LServer = jlib:nameprep(ServerHost),
+ {Nick, Registered} =
+ case catch ejabberd_odbc:sql_query(
+ LServer, ["select nick from muc_registered where "
+ "jid='", SJID, "' and host='", SHost, "';"]) of
+ {selected, ["nick"], [{N}]} ->
+ {N, [{xmlelement, "registered", [], []}]};
+ _ ->
+ {"", []}
+ end,
+ Registered ++
+ [{xmlelement, "instructions", [],
+ [{xmlcdata,
+ translate:translate(
+ Lang, "You need a client that supports x:data to register the nickname")}]},
+ {xmlelement, "x",
+ [{"xmlns", ?NS_XDATA}],
+ [{xmlelement, "title", [],
+ [{xmlcdata,
+ translate:translate(
+ Lang, "Nickname Registration at ") ++ Host}]},
+ {xmlelement, "instructions", [],
+ [{xmlcdata,
+ translate:translate(
+ Lang, "Enter nickname you want to register")}]},
+ ?XFIELD("text-single", "Nickname", "nick", Nick)]}].
+
+iq_set_register_info(ServerHost, Host, From, Nick, Lang) ->
+ JID = jlib:jid_to_string(
+ jlib:jid_tolower(
+ jlib:jid_remove_resource(From))),
+ SJID = ejabberd_odbc:escape(JID),
+ SNick = ejabberd_odbc:escape(Nick),
+ SHost = ejabberd_odbc:escape(Host),
+ LServer = jlib:nameprep(ServerHost),
+ F = fun() ->
+ case Nick of
+ "" ->
+ ejabberd_odbc:sql_query_t(
+ ["delete from muc_registered where ",
+ "jid='", SJID, "' and host='", Host, "';"]),
+ ok;
+ _ ->
+ Allow =
+ case ejabberd_odbc:sql_query_t(
+ ["select jid from muc_registered ",
+ "where nick='", SNick, "' and host='",
+ SHost, "';"]) of
+ {selected, ["jid"], [{J}]} ->
+ J == JID;
+ _ ->
+ true
+ end,
+ if Allow ->
+ update_t(
+ "muc_registered",
+ ["jid", "host", "nick"],
+ [SJID, SHost, SNick],
+ ["jid='", SJID, "' and host='", SHost, "'"]),
+ ok;
+ true ->
+ false
+ end
+ end
+ end,
+ case catch ejabberd_odbc:sql_transaction(LServer, F) of
+ {atomic, ok} ->
+ {result, []};
+ {atomic, false} ->
+ ErrText = "That nickname is registered by another person",
+ {error, ?ERRT_CONFLICT(Lang, ErrText)};
+ _ ->
+ {error, ?ERR_INTERNAL_SERVER_ERROR}
+ end.
+
+process_iq_register_set(ServerHost, Host, From, SubEl, Lang) ->
+ {xmlelement, _Name, _Attrs, Els} = SubEl,
+ case xml:get_subtag(SubEl, "remove") of
+ false ->
+ case xml:remove_cdata(Els) of
+ [{xmlelement, "x", _Attrs1, _Els1} = XEl] ->
+ case {xml:get_tag_attr_s("xmlns", XEl),
+ xml:get_tag_attr_s("type", XEl)} of
+ {?NS_XDATA, "cancel"} ->
+ {result, []};
+ {?NS_XDATA, "submit"} ->
+ XData = jlib:parse_xdata_submit(XEl),
+ case XData of
+ invalid ->
+ {error, ?ERR_BAD_REQUEST};
+ _ ->
+ case lists:keysearch("nick", 1, XData) of
+ {value, {_, [Nick]}} when Nick /= "" ->
+ iq_set_register_info(ServerHost, Host,
+ From, Nick, Lang);
+ _ ->
+ ErrText = "You must fill in field \"Nickname\" in the form",
+ {error, ?ERRT_NOT_ACCEPTABLE(Lang, ErrText)}
+ end
+ end;
+ _ ->
+ {error, ?ERR_BAD_REQUEST}
+ end;
+ _ ->
+ {error, ?ERR_BAD_REQUEST}
+ end;
+ _ ->
+ iq_set_register_info(ServerHost, Host, From, "", Lang)
+ end.
+
+iq_get_vcard(Lang) ->
+ [{xmlelement, "FN", [],
+ [{xmlcdata, "ejabberd/mod_muc"}]},
+ {xmlelement, "URL", [],
+ [{xmlcdata, ?EJABBERD_URI}]},
+ {xmlelement, "DESC", [],
+ [{xmlcdata, translate:translate(Lang, "ejabberd MUC module") ++
+ "\nCopyright (c) 2003-2012 ProcessOne"}]}].
+
+
+broadcast_service_message(Host, Msg) ->
+ lists:foreach(
+ fun(#muc_online_room{pid = Pid}) ->
+ gen_fsm:send_all_state_event(
+ Pid, {service_message, Msg})
+ end, get_vh_rooms(Host)).
+
+get_vh_rooms(Host) ->
+ mnesia:dirty_select(muc_online_room,
+ [{#muc_online_room{name_host = '$1', _ = '_'},
+ [{'==', {element, 2, '$1'}, Host}],
+ ['$_']}]).
+
+
+clean_table_from_bad_node(Node) ->
+ F = fun() ->
+ Es = mnesia:select(
+ muc_online_room,
+ [{#muc_online_room{pid = '$1', _ = '_'},
+ [{'==', {node, '$1'}, Node}],
+ ['$_']}]),
+ lists:foreach(fun(E) ->
+ mnesia:delete_object(E)
+ end, Es)
+ end,
+ mnesia:async_dirty(F).
+
+clean_table_from_bad_node(Node, Host) ->
+ F = fun() ->
+ Es = mnesia:select(
+ muc_online_room,
+ [{#muc_online_room{pid = '$1',
+ name_host = {'_', Host},
+ _ = '_'},
+ [{'==', {node, '$1'}, Node}],
+ ['$_']}]),
+ lists:foreach(fun(E) ->
+ mnesia:delete_object(E)
+ end, Es)
+ end,
+ mnesia:async_dirty(F).
+
+encode_opts(Opts) ->
+ ejabberd_odbc:escape(erl_prettypr:format(erl_syntax:abstract(Opts))).
+
+decode_opts(Str) ->
+ {ok, Tokens, _} = erl_scan:string(Str ++ "."),
+ {ok, Opts} = erl_parse:parse_term(Tokens),
+ Opts.
+
+%% Almost a copy of string:join/2.
+%% We use this version because string:join/2 is relatively
+%% new function (introduced in R12B-0).
+join([], _Sep) ->
+ [];
+join([H|T], Sep) ->
+ [H, [[Sep, X] || X <- T]].
+
+%% Safe atomic update.
+update_t(Table, Fields, Vals, Where) ->
+ UPairs = lists:zipwith(fun(A, B) -> A ++ "='" ++ B ++ "'" end,
+ Fields, Vals),
+ case ejabberd_odbc:sql_query_t(
+ ["update ", Table, " set ",
+ join(UPairs, ", "),
+ " where ", Where, ";"]) of
+ {updated, 1} ->
+ ok;
+ _ ->
+ ejabberd_odbc:sql_query_t(
+ ["insert into ", Table, "(", join(Fields, ", "),
+ ") values ('", join(Vals, "', '"), "');"])
+ end.
%% External exports
--export([start_link/9,
- start_link/7,
- start/9,
- start/7,
+-export([start_link/10,
+ start_link/8,
+ start/10,
+ start/8,
route/4]).
%% gen_fsm callbacks
-ifdef(NO_TRANSIENT_SUPERVISORS).
-define(SUPERVISOR_START,
gen_fsm:start(?MODULE, [Host, ServerHost, Access, Room, HistorySize,
- RoomShaper, Creator, Nick, DefRoomOpts],
+ RoomShaper, Creator, Nick, DefRoomOpts, Mod],
?FSMOPTS)).
-else.
-define(SUPERVISOR_START,
Supervisor = gen_mod:get_module_proc(ServerHost, ejabberd_mod_muc_sup),
supervisor:start_child(
Supervisor, [Host, ServerHost, Access, Room, HistorySize, RoomShaper,
- Creator, Nick, DefRoomOpts])).
+ Creator, Nick, DefRoomOpts, Mod])).
-endif.
%%%----------------------------------------------------------------------
%%% API
%%%----------------------------------------------------------------------
start(Host, ServerHost, Access, Room, HistorySize, RoomShaper,
- Creator, Nick, DefRoomOpts) ->
+ Creator, Nick, DefRoomOpts, Mod) ->
?SUPERVISOR_START.
-start(Host, ServerHost, Access, Room, HistorySize, RoomShaper, Opts) ->
+start(Host, ServerHost, Access, Room, HistorySize, RoomShaper, Opts, Mod) ->
Supervisor = gen_mod:get_module_proc(ServerHost, ejabberd_mod_muc_sup),
supervisor:start_child(
Supervisor, [Host, ServerHost, Access, Room, HistorySize, RoomShaper,
- Opts]).
+ Opts, Mod]).
start_link(Host, ServerHost, Access, Room, HistorySize, RoomShaper,
- Creator, Nick, DefRoomOpts) ->
+ Creator, Nick, DefRoomOpts, Mod) ->
gen_fsm:start_link(?MODULE, [Host, ServerHost, Access, Room, HistorySize,
- RoomShaper, Creator, Nick, DefRoomOpts],
+ RoomShaper, Creator, Nick, DefRoomOpts, Mod],
?FSMOPTS).
-start_link(Host, ServerHost, Access, Room, HistorySize, RoomShaper, Opts) ->
+start_link(Host, ServerHost, Access, Room, HistorySize, RoomShaper, Opts, Mod) ->
gen_fsm:start_link(?MODULE, [Host, ServerHost, Access, Room, HistorySize,
- RoomShaper, Opts],
+ RoomShaper, Opts, Mod],
?FSMOPTS).
%%%----------------------------------------------------------------------
%% ignore |
%% {stop, StopReason}
%%----------------------------------------------------------------------
-init([Host, ServerHost, Access, Room, HistorySize, RoomShaper, Creator, _Nick, DefRoomOpts]) ->
+init([Host, ServerHost, Access, Room, HistorySize, RoomShaper, Creator, _Nick,
+ DefRoomOpts, Mod]) ->
process_flag(trap_exit, true),
Shaper = shaper:new(RoomShaper),
State = set_affiliation(Creator, owner,
#state{host = Host,
server_host = ServerHost,
+ mod = Mod,
access = Access,
room = Room,
history = lqueue_new(HistorySize),
add_to_log(room_existence, created, State1),
add_to_log(room_existence, started, State1),
{ok, normal_state, State1};
-init([Host, ServerHost, Access, Room, HistorySize, RoomShaper, Opts]) ->
+init([Host, ServerHost, Access, Room, HistorySize, RoomShaper, Opts, Mod]) ->
process_flag(trap_exit, true),
Shaper = shaper:new(RoomShaper),
State = set_opts(Opts, #state{host = Host,
server_host = ServerHost,
+ mod = Mod,
access = Access,
room = Room,
history = lqueue_new(HistorySize),
MinMessageInterval =
trunc(gen_mod:get_module_opt(
StateData#state.server_host,
- mod_muc, min_message_interval, 0) * 1000000),
+ StateData#state.mod,
+ min_message_interval, 0) * 1000000),
Size = element_size(Packet),
{MessageShaper, MessageShaperInterval} =
shaper:update(Activity#activity.message_shaper, Size),
StateData),
case (NSD#state.config)#config.persistent of
true ->
- mod_muc:store_room(
+ (NSD#state.mod):store_room(
+ NSD#state.server_host,
NSD#state.host,
NSD#state.room,
make_opts(NSD));
MinPresenceInterval =
trunc(gen_mod:get_module_opt(
StateData#state.server_host,
- mod_muc, min_presence_interval, 0) * 1000000),
+ StateData#state.mod, min_presence_interval, 0) * 1000000),
if
(Now >= Activity#activity.presence_time + MinPresenceInterval) and
(Activity#activity.presence == undefined) ->
tab_remove_online_user(LJID, StateData)
end, [], StateData#state.users),
add_to_log(room_existence, stopped, StateData),
- mod_muc:room_destroyed(StateData#state.host, StateData#state.room, self(),
- StateData#state.server_host),
+ (StateData#state.mod):room_destroyed(
+ StateData#state.host, StateData#state.room, self(),
+ StateData#state.server_host),
ok.
%%%----------------------------------------------------------------------
FromNick},
case (NSD#state.config)#config.persistent of
true ->
- mod_muc:store_room(
+ (NSD#state.mod):store_room(
+ NSD#state.server_host,
NSD#state.host,
NSD#state.room,
make_opts(NSD));
case is_nick_change(From, Nick, StateData) of
true ->
case {nick_collision(From, Nick, StateData),
- mod_muc:can_use_nick(
- StateData#state.host, From, Nick),
+ (StateData#state.mod):can_use_nick(
+ StateData#state.server_host,
+ StateData#state.host, From, Nick),
{(StateData#state.config)#config.allow_visitor_nickchange,
is_visitor(From, StateData)}} of
{_, _, {false, true}} ->
get_service_max_users(StateData) ->
gen_mod:get_module_opt(StateData#state.server_host,
- mod_muc, max_users, ?MAX_USERS_DEFAULT).
+ StateData#state.mod, max_users, ?MAX_USERS_DEFAULT).
get_max_users_admin_threshold(StateData) ->
gen_mod:get_module_opt(StateData#state.server_host,
- mod_muc, max_users_admin_threshold, 5).
+ StateData#state.mod, max_users_admin_threshold, 5).
get_user_activity(JID, StateData) ->
case treap:lookup(jlib:jid_tolower(JID),
MessageShaper =
shaper:new(gen_mod:get_module_opt(
StateData#state.server_host,
- mod_muc, user_message_shaper, none)),
+ StateData#state.mod, user_message_shaper, none)),
PresenceShaper =
shaper:new(gen_mod:get_module_opt(
StateData#state.server_host,
- mod_muc, user_presence_shaper, none)),
+ StateData#state.mod, user_presence_shaper, none)),
#activity{message_shaper = MessageShaper,
presence_shaper = PresenceShaper}
end.
MinMessageInterval =
gen_mod:get_module_opt(
StateData#state.server_host,
- mod_muc, min_message_interval, 0),
+ StateData#state.mod, min_message_interval, 0),
MinPresenceInterval =
gen_mod:get_module_opt(
StateData#state.server_host,
- mod_muc, min_presence_interval, 0),
+ StateData#state.mod, min_presence_interval, 0),
Key = jlib:jid_tolower(JID),
Now = now_to_usec(now()),
Activity1 = clean_treap(StateData#state.activity, {1, -Now}),
NConferences = tab_count_user(From),
MaxConferences = gen_mod:get_module_opt(
StateData#state.server_host,
- mod_muc, max_user_conferences, 10),
+ StateData#state.mod, max_user_conferences, 10),
Collision = nick_collision(From, Nick, StateData),
case {(ServiceAffiliation == owner orelse
((Affiliation == admin orelse Affiliation == owner) andalso
NUsers < MaxUsers) andalso
NConferences < MaxConferences,
Collision,
- mod_muc:can_use_nick(StateData#state.host, From, Nick),
+ (StateData#state.mod):can_use_nick(StateData#state.server_host,
+ StateData#state.host, From, Nick),
get_default_role(Affiliation, StateData)} of
{false, _, _, _} ->
% max user reached and user is not admin or owner
end, StateData, lists:flatten(Res)),
case (NSD#state.config)#config.persistent of
true ->
- mod_muc:store_room(NSD#state.host, NSD#state.room,
- make_opts(NSD));
+ (NSD#state.mod):store_room(NSD#state.server_host,
+ NSD#state.host, NSD#state.room,
+ make_opts(NSD));
_ ->
ok
end,
jlib:parse_xdata_submit(XEl)) of
{value, {_, [N]}} ->
length(N) =< gen_mod:get_module_opt(StateData#state.server_host,
- mod_muc, max_room_name,
- infinite);
+ StateData#state.mod,
+ max_room_name, infinite);
_ ->
true
end,
jlib:parse_xdata_submit(XEl)) of
{value, {_, [D]}} ->
length(D) =< gen_mod:get_module_opt(StateData#state.server_host,
- mod_muc, max_room_desc,
- infinite);
+ StateData#state.mod,
+ max_room_desc, infinite);
_ ->
true
end,
|| JID <- JIDList]}).
get_default_room_maxusers(RoomState) ->
- DefRoomOpts = gen_mod:get_module_opt(RoomState#state.server_host, mod_muc, default_room_options, []),
+ DefRoomOpts = gen_mod:get_module_opt(
+ RoomState#state.server_host,
+ RoomState#state.mod, default_room_options, []),
RoomState2 = set_opts(DefRoomOpts, RoomState),
(RoomState2#state.config)#config.max_users.
change_config(Config, StateData) ->
NSD = StateData#state{config = Config},
+ Mod = StateData#state.mod,
case {(StateData#state.config)#config.persistent,
Config#config.persistent} of
{_, true} ->
- mod_muc:store_room(NSD#state.host, NSD#state.room, make_opts(NSD));
+ Mod:store_room(NSD#state.server_host, NSD#state.host,
+ NSD#state.room, make_opts(NSD));
{true, false} ->
- mod_muc:forget_room(NSD#state.host, NSD#state.room);
+ Mod:forget_room(NSD#state.server_host, NSD#state.host, NSD#state.room);
{false, false} ->
ok
end,
end, ?DICT:to_list(StateData#state.users)),
case (StateData#state.config)#config.persistent of
true ->
- mod_muc:forget_room(StateData#state.host, StateData#state.room);
+ (StateData#state.mod):forget_room(
+ StateData#state.server_host,
+ StateData#state.host, StateData#state.room);
false ->
ok
end,