/[smecontribs]/rpms/ejabberd/contribs7/mod_ctlextra.erl
ViewVC logotype

Annotation of /rpms/ejabberd/contribs7/mod_ctlextra.erl

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.1 - (hide annotations) (download)
Thu May 8 19:50:18 2008 UTC (16 years, 1 month ago) by slords
Branch: MAIN
CVS Tags: ejabberd-2_0_0-3_el4_sme, ejabberd-2_0_1-4_el4_sme, ejabberd-2_0_0-4_el4_sme
Initial import of ejabberd-2.0.0-3.el4.sme.src.rpm

1 slords 1.1 %%%----------------------------------------------------------------------
2     %%% File : mod_ctlextra.erl
3     %%% Author : Badlop <badlop@ono.com>
4     %%% Purpose : Adds more commands to ejabberd_ctl
5     %%% Created : 30 Nov 2006 by Badlop <badlop@ono.com>
6     %%% Id : $Id$
7     %%%----------------------------------------------------------------------
8    
9     -module(mod_ctlextra).
10     -author('badlop@ono.com').
11     -vsn('$Revision$ ').
12    
13     -behaviour(gen_mod).
14    
15     -export([start/2,
16     stop/1,
17     ctl_process/2,
18     ctl_process/3
19     ]).
20    
21     -include("ejabberd.hrl").
22     -include("ejabberd_ctl.hrl").
23     -include("jlib.hrl").
24     -include("mod_roster.hrl").
25    
26     -record(session, {sid, usr, us, priority}). % copied from ejabberd_sm.erl
27    
28     start(Host, _Opts) ->
29     ejabberd_ctl:register_commands([
30     {"compile file", "recompile and reload file"},
31     {"load-config file", "load config from file"},
32     {"remove-node nodename", "remove an ejabberd node from the database"},
33    
34     %% ejabberd_auth
35     {"delete-older-users days", "delete users that have not logged in the last 'days'"},
36     {"set-password user server password", "set password to user@server"},
37    
38     %% ejd2odbc
39     {"export2odbc server output", "export Mnesia tables on server to files on output directory"},
40    
41     %% mod_offline
42     {"delete-older-messages days", "delete offline messages older than 'days'"},
43    
44     %% mod_shared_roster
45     {"srg-create group host name description display", "create the group with options"},
46     {"srg-delete group host", "delete the group"},
47     {"srg-user-add user server group host", "add user@server to group on host"},
48     {"srg-user-del user server group host", "delete user@server from group on host"},
49    
50     %% mod_vcard
51     {"vcard-get user host data [data2]", "get data from the vCard of the user"},
52     {"vcard-set user host data [data2] content", "set data to content on the vCard"},
53    
54     %% mod_announce
55     %% announce_send_online host message
56     %% announce_send_all host, message
57    
58     %% mod_muc
59     %% muc-add room opts
60     %% muc-del room
61     {"muc-purge days", "destroy rooms with not activity on the last 'days'"},
62     {"muc-online-rooms", "list existing rooms"},
63    
64     %% mod_roster
65     {"add-rosteritem user1 server1 user2 server2 nick group subs", "Add user2@server2 to user1@server1's roster"},
66     %%{"", "subs= none, from, to or both"},
67     %%{"", "example: add-roster peter localhost mike server.com MiKe Employees both"},
68     %%{"", "will add mike@server.com to peter@localhost roster"},
69     {"rem-rosteritem user1 server1 user2 server2", "Remove user2@server2 from user1@server1's roster"},
70     {"pushroster file user server", "push template roster in file to user@server"},
71     {"pushroster-all file", "push template roster in file to all those users"},
72     {"push-alltoall server group", "adds all the users to all the users in Group"},
73    
74     {"status-list status", "list the logged users with status"},
75     {"status-num status", "number of logged users with status"},
76    
77     {"stats registeredusers", "number of registered users"},
78     {"stats onlineusers", "number of logged users"},
79     {"stats uptime-seconds", "uptime of ejabberd node in seconds"},
80    
81     %% misc
82     {"get-cookie", "get the Erlang cookie of this node"},
83     {"killsession user server resource", "kill a user session"}
84     ], ?MODULE, ctl_process),
85     ejabberd_ctl:register_commands(Host, [
86     %% mod_muc
87     {"muc-purge days", "destroy rooms with not activity on the last 'days'"},
88     {"muc-online-rooms", "list existing rooms"},
89    
90     %% mod_last
91     {"num-active-users days", "number of users active in the last 'days'"},
92     {"status-list status", "list the logged users with status"},
93     {"status-num status", "number of logged users with status"},
94     {"stats registeredusers", "number of registered users"},
95     {"stats onlineusers", "number of logged users"}
96     ], ?MODULE, ctl_process),
97     ok.
98    
99     stop(_Host) ->
100     ok.
101    
102    
103     ctl_process(_Val, ["blo"]) ->
104     FResources = "eeeaaa aaa",
105     io:format("~s", [FResources]),
106     ?STATUS_SUCCESS;
107    
108     ctl_process(_Val, ["delete-older-messages", Days]) ->
109     mod_offline:remove_old_messages(list_to_integer(Days)),
110     ?STATUS_SUCCESS;
111    
112     ctl_process(_Val, ["delete-older-users", Days]) ->
113     {removed, N, UR} = delete_older_users(list_to_integer(Days)),
114     io:format("Deleted ~p users: ~p~n", [N, UR]),
115     ?STATUS_SUCCESS;
116    
117     ctl_process(_Val, ["export2odbc", Server, Output]) ->
118     Tables = [
119     {export_last, last},
120     {export_offline, offline},
121     {export_passwd, passwd},
122     {export_private_storage, private_storage},
123     {export_roster, roster},
124     {export_vcard, vcard},
125     {export_vcard_search, vcard_search}],
126     Export = fun({TableFun, Table}) ->
127     Filename = filename:join([Output, atom_to_list(Table)++".txt"]),
128     io:format("Trying to export Mnesia table '~p' on server '~s' to file '~s'~n", [Table, Server, Filename]),
129     catch ejd2odbc:TableFun(Server, Filename)
130     end,
131     lists:foreach(Export, Tables),
132     ?STATUS_SUCCESS;
133    
134     ctl_process(_Val, ["set-password", User, Server, Password]) ->
135     ejabberd_auth:set_password(User, Server, Password),
136     ?STATUS_SUCCESS;
137    
138     ctl_process(_Val, ["vcard-get", User, Server, Data]) ->
139     {ok, Res} = vcard_get(User, Server, [Data]),
140     io:format("~s~n", [Res]),
141     ?STATUS_SUCCESS;
142    
143     ctl_process(_Val, ["vcard-get", User, Server, Data1, Data2]) ->
144     {ok, Res} = vcard_get(User, Server, [Data1, Data2]),
145     io:format("~s~n", [Res]),
146     ?STATUS_SUCCESS;
147    
148     ctl_process(_Val, ["vcard-set", User, Server, Data1, Content]) ->
149     {ok, Res} = vcard_set(User, Server, [Data1], Content),
150     io:format("~s~n", [Res]),
151     ?STATUS_SUCCESS;
152    
153     ctl_process(_Val, ["vcard-set", User, Server, Data1, Data2, Content]) ->
154     {ok, Res} = vcard_set(User, Server, [Data1, Data2], Content),
155     io:format("~s~n", [Res]),
156     ?STATUS_SUCCESS;
157    
158     ctl_process(_Val, ["compile", Module]) ->
159     compile:file(Module),
160     ?STATUS_SUCCESS;
161    
162     ctl_process(_Val, ["remove-node", Node]) ->
163     mnesia:del_table_copy(schema, list_to_atom(Node)),
164     ?STATUS_SUCCESS;
165    
166     ctl_process(_Val, ["srg-create", Group, Host, Name, Description, Display]) ->
167     Opts = [{name, Name}, {displayed_groups, [Display]}, {description, Description}],
168     {atomic, ok} = mod_shared_roster:create_group(Host, Group, Opts),
169     ?STATUS_SUCCESS;
170    
171     ctl_process(_Val, ["srg-delete", Group, Host]) ->
172     {atomic, ok} = mod_shared_roster:delete_group(Host, Group),
173     ?STATUS_SUCCESS;
174    
175     ctl_process(_Val, ["srg-user-add", User, Server, Group, Host]) ->
176     {atomic, ok} = mod_shared_roster:add_user_to_group(Host, {User, Server}, Group),
177     ?STATUS_SUCCESS;
178    
179     ctl_process(_Val, ["srg-user-del", User, Server, Group, Host]) ->
180     {atomic, ok} = mod_shared_roster:remove_user_from_group(Host, {User, Server}, Group),
181     ?STATUS_SUCCESS;
182    
183     ctl_process(_Val, ["muc-purge", Days]) ->
184     {purged, Num_total, Num_purged, Names_purged} = muc_purge(list_to_integer(Days)),
185     io:format("Purged ~p chatrooms from a total of ~p on the server:~n~p~n", [Num_purged, Num_total, Names_purged]),
186     ?STATUS_SUCCESS;
187    
188     ctl_process(_Val, ["muc-online-rooms"]) ->
189     format_print_room(all, ets:tab2list(muc_online_room)),
190     ?STATUS_SUCCESS;
191    
192     ctl_process(_Val, ["add-rosteritem", LocalUser, LocalServer, RemoteUser, RemoteServer, Nick, Group, Subs]) ->
193     case add_rosteritem(LocalUser, LocalServer, RemoteUser, RemoteServer, Nick, Group, list_to_atom(Subs), []) of
194     {atomic, ok} ->
195     ?STATUS_SUCCESS;
196     {error, Reason} ->
197     io:format("Can't add ~p@~p to ~p@~p: ~p~n",
198     [RemoteUser, RemoteServer, LocalUser, LocalServer, Reason]),
199     ?STATUS_ERROR;
200     {badrpc, Reason} ->
201     io:format("Can't add roster item to user ~p: ~p~n",
202     [LocalUser, Reason]),
203     ?STATUS_BADRPC
204     end;
205    
206     ctl_process(_Val, ["rem-rosteritem", LocalUser, LocalServer, RemoteUser, RemoteServer]) ->
207     case rem_rosteritem(LocalUser, LocalServer, RemoteUser, RemoteServer) of
208     {atomic, ok} ->
209     ?STATUS_SUCCESS;
210     {error, Reason} ->
211     io:format("Can't remove ~p@~p to ~p@~p: ~p~n",
212     [RemoteUser, RemoteServer, LocalUser, LocalServer, Reason]),
213     ?STATUS_ERROR;
214     {badrpc, Reason} ->
215     io:format("Can't remove roster item to user ~p: ~p~n",
216     [LocalUser, Reason]),
217     ?STATUS_BADRPC
218     end;
219    
220     ctl_process(_Val, ["pushroster", File, User, Server]) ->
221     case pushroster(File, User, Server) of
222     ok ->
223     ?STATUS_SUCCESS;
224     {error, Reason} ->
225     io:format("Can't push roster ~p to ~p@~p: ~p~n",
226     [File, User, Server, Reason]),
227     ?STATUS_ERROR;
228     {badrpc, Reason} ->
229     io:format("Can't push roster ~p: ~p~n",
230     [File, Reason]),
231     ?STATUS_BADRPC
232     end;
233    
234     ctl_process(_Val, ["pushroster-all", File]) ->
235     case pushroster_all([File]) of
236     ok ->
237     ?STATUS_SUCCESS;
238     {error, Reason} ->
239     io:format("Can't push roster ~p: ~p~n",
240     [File, Reason]),
241     ?STATUS_ERROR;
242     {badrpc, Reason} ->
243     io:format("Can't push roster ~p: ~p~n",
244     [File, Reason]),
245     ?STATUS_BADRPC
246     end;
247    
248     ctl_process(_Val, ["push-alltoall", Server, Group]) ->
249     case push_alltoall(Server, Group) of
250     ok ->
251     ?STATUS_SUCCESS;
252     {error, Reason} ->
253     io:format("Can't push all to all: ~p~n",
254     [Reason]),
255     ?STATUS_ERROR;
256     {badrpc, Reason} ->
257     io:format("Can't push all to all: ~p~n",
258     [Reason]),
259     ?STATUS_BADRPC
260     end;
261    
262     ctl_process(_Val, ["load-config", Path]) ->
263     case ejabberd_config:load_file(Path) of
264     {atomic, ok} ->
265     ?STATUS_SUCCESS;
266     {error, Reason} ->
267     io:format("Can't load config file ~p: ~p~n",
268     [filename:absname(Path), Reason]),
269     ?STATUS_ERROR;
270     {badrpc, Reason} ->
271     io:format("Can't load config file ~p: ~p~n",
272     [filename:absname(Path), Reason]),
273     ?STATUS_BADRPC
274     end;
275    
276     ctl_process(_Val, ["stats", Stat]) ->
277     Res = case Stat of
278     "uptime-seconds" -> uptime_seconds();
279     "registeredusers" -> mnesia:table_info(passwd, size);
280     "onlineusers" -> mnesia:table_info(session, size)
281     end,
282     io:format("~p~n", [Res]),
283     ?STATUS_SUCCESS;
284    
285     ctl_process(_Val, ["status-num", Status_required]) ->
286     ctl_process(_Val, "all", ["status-num", Status_required]);
287    
288     ctl_process(_Val, ["status-list", Status_required]) ->
289     ctl_process(_Val, "all", ["status-list", Status_required]);
290    
291     ctl_process(_Val, ["get-cookie"]) ->
292     io:format("~s~n", [atom_to_list(erlang:get_cookie())]),
293     ?STATUS_SUCCESS;
294    
295     ctl_process(_Val, ["killsession", User, Server, Resource]) ->
296     ejabberd_router:route(
297     jlib:make_jid("", "", ""),
298     jlib:make_jid(User, Server, Resource),
299     {xmlelement, "broadcast", [], [{exit, "killed"}]}),
300     ?STATUS_SUCCESS;
301    
302     ctl_process(Val, _Args) ->
303     Val.
304    
305    
306     ctl_process(_Val, Host, ["muc-purge", Days]) ->
307     {purged, Num_total, Num_purged, Names_purged} = muc_purge(Host, list_to_integer(Days)),
308     io:format("Purged ~p chatrooms from a total of ~p on the host ~p:~n~p~n", [Num_purged, Num_total, Host, Names_purged]),
309     ?STATUS_SUCCESS;
310    
311     ctl_process(_Val, ServerHost, ["muc-online-rooms"]) ->
312     MUCHost = find_host(ServerHost),
313     format_print_room(MUCHost, ets:tab2list(muc_online_room)),
314     ?STATUS_SUCCESS;
315    
316     ctl_process(_Val, Host, ["num-active-users", Days]) ->
317     Number = num_active_users(Host, list_to_integer(Days)),
318     io:format("~p~n", [Number]),
319     ?STATUS_SUCCESS;
320    
321     ctl_process(_Val, Host, ["stats", Stat]) ->
322     Res = case Stat of
323     "registeredusers" -> length(ejabberd_auth:get_vh_registered_users(Host));
324     "onlineusers" -> length(ejabberd_sm:get_vh_session_list(Host))
325     end,
326     io:format("~p~n", [Res]),
327     ?STATUS_SUCCESS;
328    
329     ctl_process(_Val, Host, ["status-num", Status_required]) ->
330     Num = length(get_status_list(Host, Status_required)),
331     io:format("~p~n", [Num]),
332     ?STATUS_SUCCESS;
333    
334     ctl_process(_Val, Host, ["status-list", Status_required]) ->
335     Res = get_status_list(Host, Status_required),
336     [ io:format("~s@~s ~s ~p \"~s\"~n", [U, S, R, P, St]) || {U, S, R, P, St} <- Res],
337     ?STATUS_SUCCESS;
338    
339     ctl_process(Val, _Host, _Args) ->
340     Val.
341    
342    
343     %%-------------
344     %% UTILS
345     %%-------------
346    
347     get_status_list(Host, Status_required) ->
348     %% Get list of all logged users
349     Sessions = ejabberd_sm:dirty_get_my_sessions_list(),
350     %% Reformat the list
351     Sessions2 = [ {Session#session.usr, Session#session.sid, Session#session.priority} || Session <- Sessions],
352     Fhost = case Host of
353     "all" ->
354     %% All hosts are requested, so dont filter at all
355     fun(_, _) -> true end;
356     _ ->
357     %% Filter the list, only Host is interesting
358     fun(A, B) -> A == B end
359     end,
360     Sessions3 = [ {Pid, Server, Priority} || {{_User, Server, _Resource}, {_, Pid}, Priority} <- Sessions2, apply(Fhost, [Server, Host])],
361     %% For each Pid, get its presence
362     Sessions4 = [ {ejabberd_c2s:get_presence(Pid), Server, Priority} || {Pid, Server, Priority} <- Sessions3],
363     %% Filter by status
364     Fstatus = case Status_required of
365     "all" ->
366     fun(_, _) -> true end;
367     _ ->
368     fun(A, B) -> A == B end
369     end,
370     [{User, Server, Resource, Priority, stringize(Status_text)}
371     || {{User, Resource, Status, Status_text}, Server, Priority} <- Sessions4,
372     apply(Fstatus, [Status, Status_required])].
373    
374     %% Make string more print-friendly
375     stringize(String) ->
376     %% Replace newline characters with other code
377     element(2, regexp:gsub(String, "\n", "\\n")).
378    
379     add_rosteritem(LU, LS, RU, RS, Nick, Group, Subscription, Xattrs) ->
380     subscribe(LU, LS, RU, RS, Nick, Group, Subscription, Xattrs),
381     route_rosteritem(LU, LS, RU, RS, Nick, Group, Subscription),
382     {atomic, ok}.
383    
384     subscribe(LocalUser, LocalServer, RemoteUser, RemoteServer, Nick, Group, Subscription, Xattrs) ->
385     R = #roster{usj = {LocalUser,LocalServer,{RemoteUser,RemoteServer,[]}},
386     us = {LocalUser,LocalServer},
387     jid = {RemoteUser,RemoteServer,[]},
388     name = Nick,
389     subscription = Subscription, % none, to=you see him, from=he sees you, both
390     ask = none, % out=send request, in=somebody requests you, none
391     groups = [Group],
392     askmessage = Xattrs, % example: [{"category","conference"}]
393     xs = []},
394     mnesia:transaction(fun() -> mnesia:write(R) end).
395    
396     rem_rosteritem(LU, LS, RU, RS) ->
397     unsubscribe(LU, LS, RU, RS),
398     route_rosteritem(LU, LS, RU, RS, "", "", "remove"),
399     {atomic, ok}.
400    
401     unsubscribe(LocalUser, LocalServer, RemoteUser, RemoteServer) ->
402     Key = {{LocalUser,LocalServer,{RemoteUser,RemoteServer,[]}},
403     {LocalUser,LocalServer}},
404     mnesia:transaction(fun() -> mnesia:delete(roster, Key, write) end).
405    
406     route_rosteritem(LocalUser, LocalServer, RemoteUser, RemoteServer, Nick, Group, Subscription) ->
407     LJID = jlib:make_jid(LocalUser, LocalServer, ""),
408     RJID = jlib:make_jid(RemoteUser, RemoteServer, ""),
409     ToS = jlib:jid_to_string(LJID),
410     ItemJIDS = jlib:jid_to_string(RJID),
411     GroupXML = {xmlelement, "group", [], [{xmlcdata, Group}]},
412     Item = {xmlelement, "item",
413     [{"jid", ItemJIDS},
414     {"name", Nick},
415     {"subscription", Subscription}],
416     [GroupXML]},
417     Query = {xmlelement, "query", [{"xmlns", ?NS_ROSTER}], [Item]},
418     Packet = {xmlelement, "iq", [{"type", "set"}, {"to", ToS}], [Query]},
419     ejabberd_router:route(LJID, LJID, Packet).
420    
421     pushroster(File, User, Server) ->
422     {ok, [Roster]} = file:consult(File),
423     subscribe_roster({User, Server, "", User}, Roster).
424    
425     pushroster_all(File) ->
426     {ok, [Roster]} = file:consult(File),
427     subscribe_all(Roster).
428    
429     subscribe_all(Roster) ->
430     subscribe_all(Roster, Roster).
431     subscribe_all([], _) ->
432     ok;
433     subscribe_all([User1 | Users], Roster) ->
434     subscribe_roster(User1, Roster),
435     subscribe_all(Users, Roster).
436    
437     subscribe_roster(_, []) ->
438     ok;
439     %% Do not subscribe a user to itself
440     subscribe_roster({Name, Server, Group, Nick}, [{Name, Server, _, _} | Roster]) ->
441     subscribe_roster({Name, Server, Group, Nick}, Roster);
442     %% Subscribe Name2 to Name1
443     subscribe_roster({Name1, Server1, Group1, Nick1}, [{Name2, Server2, Group2, Nick2} | Roster]) ->
444     subscribe(Name1, Server1, Name2, Server2, Nick2, Group2, both, []),
445     subscribe_roster({Name1, Server1, Group1, Nick1}, Roster).
446    
447     push_alltoall(S, G) ->
448     Users = ejabberd_auth:get_vh_registered_users(S),
449     Users2 = build_list_users(G, Users, []),
450     subscribe_all(Users2).
451    
452     build_list_users(_Group, [], Res) ->
453     Res;
454     build_list_users(Group, [{User, Server}|Users], Res) ->
455     build_list_users(Group, Users, [{User, Server, Group, User}|Res]).
456    
457     vcard_get(User, Server, Data) ->
458     [{_, Module, Function, _Opts}] = ets:lookup(sm_iqtable, {?NS_VCARD, Server}),
459     JID = jlib:make_jid(User, Server, ""),
460     IQ = #iq{type = get, xmlns = ?NS_VCARD},
461     IQr = Module:Function(JID, JID, IQ),
462     Res = case IQr#iq.sub_el of
463     [A1] ->
464     case vcard_get(Data, A1) of
465     false -> no_value;
466     Elem -> xml:get_tag_cdata(Elem)
467     end;
468     [] ->
469     no_vcard
470     end,
471     {ok, Res}.
472    
473     vcard_get([Data1, Data2], A1) ->
474     case xml:get_subtag(A1, Data1) of
475     false -> false;
476     A2 -> vcard_get([Data2], A2)
477     end;
478    
479     vcard_get([Data], A1) ->
480     xml:get_subtag(A1, Data).
481    
482     vcard_set(User, Server, Data, Content) ->
483     [{_, Module, Function, _Opts}] = ets:lookup(sm_iqtable, {?NS_VCARD, Server}),
484     JID = jlib:make_jid(User, Server, ""),
485     IQ = #iq{type = get, xmlns = ?NS_VCARD},
486     IQr = Module:Function(JID, JID, IQ),
487    
488     %% Get old vcard
489     A4 = case IQr#iq.sub_el of
490     [A1] ->
491     {_, _, _, A2} = A1,
492     update_vcard_els(Data, Content, A2);
493     [] ->
494     update_vcard_els(Data, Content, [])
495     end,
496    
497     %% Build new vcard
498     SubEl = {xmlelement, "vCard", [{"xmlns","vcard-temp"}], A4},
499     IQ2 = #iq{type=set, sub_el = SubEl},
500    
501     Module:Function(JID, JID, IQ2),
502     {ok, "done"}.
503    
504     update_vcard_els(Data, Content, Els1) ->
505     Els2 = lists:keysort(2, Els1),
506     [Data1 | Data2] = Data,
507     NewEl = case Data2 of
508     [] ->
509     {xmlelement, Data1, [], [{xmlcdata,Content}]};
510     [D2] ->
511     OldEl = case lists:keysearch(Data1, 2, Els2) of
512     {value, A} -> A;
513     false -> {xmlelement, Data1, [], []}
514     end,
515     {xmlelement, _, _, ContentOld1} = OldEl,
516     Content2 = [{xmlelement, D2, [], [{xmlcdata,Content}]}],
517     ContentOld2 = lists:keysort(2, ContentOld1),
518     ContentOld3 = lists:keydelete(D2, 2, ContentOld2),
519     ContentNew = lists:keymerge(2, Content2, ContentOld3),
520     {xmlelement, Data1, [], ContentNew}
521     end,
522     Els3 = lists:keydelete(Data1, 2, Els2),
523     lists:keymerge(2, [NewEl], Els3).
524    
525     -record(last_activity, {us, timestamp, status}).
526    
527     delete_older_users(Days) ->
528     %% Convert older time
529     SecOlder = Days*24*60*60,
530    
531     %% Get current time
532     {MegaSecs, Secs, _MicroSecs} = now(),
533     TimeStamp_now = MegaSecs * 1000000 + Secs,
534    
535     %% Get the list of registered users
536     Users = ejabberd_auth:dirty_get_registered_users(),
537    
538     %% For a user, remove if required and answer true
539     F = fun({LUser, LServer}) ->
540     %% Check if the user is logged
541     case ejabberd_sm:get_user_resources(LUser, LServer) of
542     %% If it isnt
543     [] ->
544     %% Look for his last_activity
545     case mnesia:dirty_read(last_activity, {LUser, LServer}) of
546     %% If it is
547     %% existent:
548     [#last_activity{timestamp = TimeStamp}] ->
549     %% get his age
550     Sec = TimeStamp_now - TimeStamp,
551     %% If he is
552     if
553     %% younger than SecOlder:
554     Sec < SecOlder ->
555     %% do nothing
556     false;
557     %% older:
558     true ->
559     %% remove the user
560     ejabberd_auth:remove_user(LUser, LServer),
561     true
562     end;
563     %% nonexistent:
564     [] ->
565     %% remove the user
566     ejabberd_auth:remove_user(LUser, LServer),
567     true
568     end;
569     %% Else
570     _ ->
571     %% do nothing
572     false
573     end
574     end,
575     %% Apply the function to every user in the list
576     Users_removed = lists:filter(F, Users),
577     {removed, length(Users_removed), Users_removed}.
578    
579     num_active_users(Host, Days) ->
580     list_last_activity(Host, true, Days).
581    
582     %% Code based on ejabberd/src/web/ejabberd_web_admin.erl
583     list_last_activity(Host, Integral, Days) ->
584     {MegaSecs, Secs, _MicroSecs} = now(),
585     TimeStamp = MegaSecs * 1000000 + Secs,
586     TS = TimeStamp - Days * 86400,
587     case catch mnesia:dirty_select(
588     last_activity, [{{last_activity, {'_', Host}, '$1', '_'},
589     [{'>', '$1', TS}],
590     [{'trunc', {'/',
591     {'-', TimeStamp, '$1'},
592     86400}}]}]) of
593     {'EXIT', _Reason} ->
594     [];
595     Vals ->
596     Hist = histogram(Vals, Integral),
597     if
598     Hist == [] ->
599     0;
600     true ->
601     Left = if
602     Days == infinity ->
603     0;
604     true ->
605     Days - length(Hist)
606     end,
607     Tail = if
608     Integral ->
609     lists:duplicate(Left, lists:last(Hist));
610     true ->
611     lists:duplicate(Left, 0)
612     end,
613     lists:nth(Days, Hist ++ Tail)
614     end
615     end.
616     histogram(Values, Integral) ->
617     histogram(lists:sort(Values), Integral, 0, 0, []).
618     histogram([H | T], Integral, Current, Count, Hist) when Current == H ->
619     histogram(T, Integral, Current, Count + 1, Hist);
620     histogram([H | _] = Values, Integral, Current, Count, Hist) when Current < H ->
621     if
622     Integral ->
623     histogram(Values, Integral, Current + 1, Count, [Count | Hist]);
624     true ->
625     histogram(Values, Integral, Current + 1, 0, [Count | Hist])
626     end;
627     histogram([], _Integral, _Current, Count, Hist) ->
628     if
629     Count > 0 ->
630     lists:reverse([Count | Hist]);
631     true ->
632     lists:reverse(Hist)
633     end.
634    
635    
636     format_print_room(Host1, Rooms)->
637     lists:foreach(
638     fun({_, {Roomname, Host},_}) ->
639     case Host1 of
640     all ->
641     io:format("~s ~s ~n", [Roomname, Host]);
642     Host ->
643     io:format("~s ~s ~n", [Roomname, Host]);
644     _ ->
645     ok
646     end
647     end,
648     Rooms).
649    
650    
651     %%----------------------------
652     %% Purge MUC
653     %%----------------------------
654    
655     %% Required for muc_purge
656     %% Copied from mod_muc/mod_muc_room.erl
657     -define(DICT, dict).
658     -record(muc_online_room, {name_host, pid}).
659     -record(lqueue, {queue, len, max}).
660     -record(config, {title = "",
661     allow_change_subj = true,
662     allow_query_users = true,
663     allow_private_messages = true,
664     public = true,
665     public_list = true,
666     persistent = false,
667     moderated = false, % TODO
668     members_by_default = true,
669     members_only = false,
670     allow_user_invites = false,
671     password_protected = false,
672     password = "",
673     anonymous = true,
674     logging = false
675     }).
676     -record(state, {room,
677     host,
678     server_host,
679     access,
680     jid,
681     config = #config{},
682     users,
683     affiliations,
684     history,
685     subject = "",
686     subject_author = "",
687     just_created = false}).
688    
689     muc_purge(Days) ->
690     ServerHost = global,
691     Host = global,
692     muc_purge2(ServerHost, Host, Days).
693    
694     muc_purge(ServerHost, Days) ->
695     Host = find_host(ServerHost),
696     muc_purge2(ServerHost, Host, Days).
697    
698     muc_purge2(ServerHost, Host, Last_allowed) ->
699     Room_names = get_room_names(Host),
700    
701     Decide = fun(N) -> decide(N, Last_allowed) end,
702     Rooms_to_delete = lists:filter(Decide, Room_names),
703    
704     Num_rooms = length(Room_names),
705     Num_rooms_to_delete = length(Rooms_to_delete),
706    
707     Rooms_to_delete_full = fill_serverhost(Rooms_to_delete, ServerHost),
708    
709     Delete = fun({N, H, SH}) ->
710     mod_muc:room_destroyed(H, N, SH),
711     mod_muc:forget_room(H, N)
712     end,
713     lists:foreach(Delete, Rooms_to_delete_full),
714     {purged, Num_rooms, Num_rooms_to_delete, Rooms_to_delete}.
715    
716     fill_serverhost(Rooms_to_delete, global) ->
717     ServerHosts1 = ?MYHOSTS,
718     ServerHosts2 = [ {ServerHost, find_host(ServerHost)} || ServerHost <- ServerHosts1],
719     [ {Name, Host, find_serverhost(Host, ServerHosts2)} || {Name, Host} <- Rooms_to_delete];
720     fill_serverhost(Rooms_to_delete, ServerHost) ->
721     [ {Name, Host, ServerHost}|| {Name, Host} <- Rooms_to_delete].
722    
723     find_serverhost(Host, ServerHosts) ->
724     {value, {ServerHost, Host}} = lists:keysearch(Host, 2, ServerHosts),
725     ServerHost.
726    
727     find_host(ServerHost) ->
728     gen_mod:get_module_opt(ServerHost, mod_muc, host, "conference." ++ ServerHost).
729    
730     decide({Room_name, Host}, Last_allowed) ->
731     Room_pid = get_room_pid(Room_name, Host),
732    
733     C = get_room_config(Room_pid),
734     Persistent = C#config.persistent,
735    
736     S = get_room_state(Room_pid),
737     Just_created = S#state.just_created,
738    
739     Room_users = S#state.users,
740     Num_users = length(?DICT:to_list(Room_users)),
741    
742     History = (S#state.history)#lqueue.queue,
743     Ts_now = calendar:now_to_universal_time(now()),
744     Ts_uptime = element(1, erlang:statistics(wall_clock))/1000,
745     {Have_history, Last} = case queue:is_empty(History) of
746     true ->
747     {false, Ts_uptime};
748     false ->
749     Last_message = queue:last(History),
750     {_, _, _, Ts_last, _} = Last_message,
751     Ts_diff =
752     calendar:datetime_to_gregorian_seconds(Ts_now)
753     - calendar:datetime_to_gregorian_seconds(Ts_last),
754     {true, Ts_diff}
755     end,
756    
757     case {Persistent, Just_created, Num_users, Have_history, seconds_to_days(Last)} of
758     {true, false, 0, _, Last_days}
759     when Last_days > Last_allowed ->
760     true;
761     _ ->
762     false
763     end.
764    
765     seconds_to_days(S) ->
766     round(S) div 60*60*24.
767    
768     uptime_seconds() ->
769     trunc(element(1, erlang:statistics(wall_clock))/1000).
770    
771     get_room_names(Host) ->
772     Get_room_names = fun(Room_reg, Names) ->
773     case {Host, Room_reg#muc_online_room.name_host} of
774     {Host, {Name1, Host}} ->
775     [{Name1, Host} | Names];
776     {global, {Name1, Host1}} ->
777     [{Name1, Host1} | Names];
778     _ ->
779     Names
780     end
781     end,
782     ets:foldr(Get_room_names, [], muc_online_room).
783    
784     get_room_pid(Name, Host) ->
785     [Room_ets] = ets:lookup(muc_online_room, {Name, Host}),
786     Room_ets#muc_online_room.pid.
787    
788     get_room_config(Room_pid) ->
789     gen_fsm:sync_send_all_state_event(Room_pid, get_config).
790    
791     get_room_state(Room_pid) ->
792     gen_fsm:sync_send_all_state_event(Room_pid, get_state).

admin@koozali.org
ViewVC Help
Powered by ViewVC 1.2.1 RSS 2.0 feed