1 %%%----------------------------------------------------------------------
2 %%% File    : jlib.erl
3 %%% Author  : Alexey Shchepin <[email protected]>
4 %%% Purpose : General XMPP library.
5 %%% Created : 23 Nov 2002 by Alexey Shchepin <[email protected]>
6 %%%
7 %%%
8 %%% ejabberd, Copyright (C) 2002-2012   ProcessOne
9 %%%
10 %%% This program is free software; you can redistribute it and/or
11 %%% modify it under the terms of the GNU General Public License as
12 %%% published by the Free Software Foundation; either version 2 of the
13 %%% License, or (at your option) any later version.
14 %%%
15 %%% This program is distributed in the hope that it will be useful,
16 %%% but WITHOUT ANY WARRANTY; without even the implied warranty of
17 %%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
18 %%% General Public License for more details.
19 %%%
20 %%% You should have received a copy of the GNU General Public License
21 %%% along with this program; if not, write to the Free Software
22 %%% Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA
23 %%% 02111-1307 USA
24 %%%
25 %%%----------------------------------------------------------------------
26 
27 
28 %% Some replacements to make in ejabberd source code to work with exmpp:
29 %% ```
30 %% - JID#jid.user
31 %% + exmpp_jid:prep_node(JID),
32 %% '''
33 %% ```
34 %% - JID#jid.server
35 %% + exmpp_jid:prep_domain(JID)
36 %% '''
37 %% ```
38 %% - ?SERR_INVALID_NAMESPACE
39 %% + exmpp_stream:error('invalid-namespace')
40 %% '''
41 %% ```
42 %% - ?POLICY_VIOLATION_ERR(Lang, "Use of STARTTLS required")
43 %% + exmpp_stream:error('policy-violation', {Lang, "Use of STARTTLS required"})
44 %% '''
45 %% ```
46 %% - IQ#iq{type = result, sub_el = Result}
47 %% + exmpp_iq:result(IQ, Result)
48 %% '''
49 
50 
51 -module(jlib).
52 
53 -author('[email protected]').
54 
55 -export([parse_xdata_submit/1, timestamp_to_iso/1, timestamp_to_iso/2, timestamp_to_xml/4,
56 	 timestamp_to_xml/1, now_to_utc_string/1, now_to_local_string/1,
57 	 datetime_string_to_timestamp/1, decode_base64/1, encode_base64/1, ip_to_list/1,
58 	 rsm_encode/1, rsm_encode/2, rsm_decode/1, from_old_jid/1, short_jid/1,
59 	 short_bare_jid/1, short_prepd_jid/1, short_prepd_bare_jid/1,
60 	 make_result_iq_reply/1, make_error_reply/3, make_error_reply/2,
61 	 make_error_element/2, make_correct_from_to_attrs/3, replace_from_to_attrs/3,
62 	 replace_from_to/3, replace_from_attrs/2, replace_from/2, remove_attr/2,
63 	 make_jid/3, make_jid/1, string_to_jid/1, jid_to_string/1, is_nodename/1,
64 	 tolower/1, nodeprep/1, nameprep/1, resourceprep/1, jid_tolower/1,
65 	 jid_remove_resource/1, jid_replace_resource/2, get_iq_namespace/1,
66 	 iq_query_info/1, iq_query_or_response_info/1, is_iq_request_type/1,
67 	 iq_to_xml/1]). % TODO: Remove once XEP-0091 is Obsolete
68 
69                              % TODO: Remove once XEP-0091 is Obsolete
70 
71 
72                                  % TODO: still uses xmlelement
73  % TODO: still uses xmlelement
74 
75                              % TODO: still uses xmlelement
76  % TODO: still uses xmlelement
77 
78                                        % TODO: still uses xmlelement
79  % TODO: still uses xmlelement
80 
81                             % TODO: still uses xmlelement
82  % TODO: still uses xmlelement
83 
84                          % TODO: still uses xmlelement
85  % TODO: still uses xmlelement
86 
87                              % TODO: still uses xmlelement
88 
89 
90 -include_lib("exmpp/include/exmpp.hrl").
91 
92 -include("jlib.hrl").
93 
94 %% @type shortjid() = {U, S, R}
95 %%     U = binary()
96 %%     S = binary()
97 %%     R = binary().
98 
99 
100 parse_xdata_submit(#xmlel{attrs = Attrs, children = Els}) ->
101     case exmpp_xml:get_attribute_from_list_as_list(Attrs, <<"type">>, "") of
102       "submit" -> lists:reverse(parse_xdata_fields(Els, []));
103       "form" -> %% This is a workaround to accept Psi's wrong forms
104 	  lists:reverse(parse_xdata_fields(Els, []));
105       _ -> invalid
106     end.
107 
108 parse_xdata_fields([], Res) -> Res;
109 parse_xdata_fields([#xmlel{name = field, attrs = Attrs, children = SubEls} | Els], Res) ->
110     case exmpp_xml:get_attribute_from_list_as_list(Attrs, <<"var">>, "") of
111       "" -> parse_xdata_fields(Els, Res);
112       Var ->
113 	  Field = {Var, lists:reverse(parse_xdata_values(SubEls, []))},
114 	  parse_xdata_fields(Els, [Field | Res])
115     end;
116 parse_xdata_fields([_ | Els], Res) -> parse_xdata_fields(Els, Res).
117 
118 parse_xdata_values([], Res) -> Res;
119 parse_xdata_values([#xmlel{name = value, children = SubEls} | Els], Res) ->
120     Val = exmpp_xml:get_cdata_from_list_as_list(SubEls),
121     parse_xdata_values(Els, [Val | Res]);
122 parse_xdata_values([_ | Els], Res) -> parse_xdata_values(Els, Res).
123 
124 rsm_decode(#iq{payload = SubEl}) -> rsm_decode(SubEl);
125 rsm_decode(#xmlel{} = SubEl) ->
126     case exmpp_xml:get_element(SubEl, set) of
127       undefined -> none;
128       #xmlel{name = set, children = SubEls} ->
129 	  lists:foldl(fun rsm_parse_element/2, #rsm_in{}, SubEls)
130     end.
131 
132 rsm_parse_element(#xmlel{name = max} = Elem, RsmIn) ->
133     CountStr = exmpp_xml:get_cdata_as_list(Elem),
134     {Count, _} = string:to_integer(CountStr),
135     RsmIn#rsm_in{max = Count};
136 rsm_parse_element(#xmlel{name = before} = Elem, RsmIn) ->
137     UID = exmpp_xml:get_cdata_as_list(Elem), RsmIn#rsm_in{direction = before, id = UID};
138 rsm_parse_element(#xmlel{name = 'after'} = Elem, RsmIn) ->
139     UID = exmpp_xml:get_cdata_as_list(Elem), RsmIn#rsm_in{direction = aft, id = UID};
140 rsm_parse_element(#xmlel{name = index} = Elem, RsmIn) ->
141     IndexStr = exmpp_xml:get_cdata_as_list(Elem),
142     {Index, _} = string:to_integer(IndexStr),
143     RsmIn#rsm_in{index = Index};
144 rsm_parse_element(_, RsmIn) -> RsmIn.
145 
146 rsm_encode(#iq{payload = SubEl} = IQ_Rec, RsmOut) ->
147     Set = #xmlel{ns = ?NS_RSM, name = set,
148 		 children = lists:reverse(rsm_encode_out(RsmOut))},
149     New = exmpp_xml:prepend_child(SubEl, Set),
150     IQ_Rec#iq{payload = New}.
151 
152 rsm_encode(none) -> [];
153 rsm_encode(RsmOut) ->
154     [#xmlel{ns = ?NS_RSM, name = set, children = lists:reverse(rsm_encode_out(RsmOut))}].
155 
156 rsm_encode_out(#rsm_out{count = Count, index = Index, first = First, last = Last}) ->
157     El = rsm_encode_first(First, Index, []),
158     El2 = rsm_encode_last(Last, El),
159     rsm_encode_count(Count, El2).
160 
161 rsm_encode_first(undefined, undefined, Arr) -> Arr;
162 rsm_encode_first(First, undefined, Arr) ->
163     [#xmlel{ns = ?NS_RSM, name = first,
164 	    children = [#xmlcdata{cdata = list_to_binary(First)}]}
165      | Arr];
166 rsm_encode_first(First, Index, Arr) ->
167     [#xmlel{ns = ?NS_RSM, name = first,
168 	    attrs = [?XMLATTR(<<"index">>, Index)],
169 	    children = [#xmlcdata{cdata = list_to_binary(First)}]}
170      | Arr].
171 
172 rsm_encode_last(undefined, Arr) -> Arr;
173 rsm_encode_last(Last, Arr) ->
174     [#xmlel{ns = ?NS_RSM, name = last,
175 	    children = [#xmlcdata{cdata = list_to_binary(Last)}]}
176      | Arr].
177 
178 rsm_encode_count(undefined, Arr) -> Arr;
179 rsm_encode_count(Count, Arr) ->
180     [#xmlel{ns = ?NS_RSM, name = count, children = [#xmlcdata{cdata = i2b(Count)}]}
181      | Arr].
182 
183 i2b(I) when is_integer(I) -> list_to_binary(integer_to_list(I));
184 i2b(L) when is_list(L) -> list_to_binary(L).
185 
186 %% Timezone = utc | {Sign::string(), {Hours, Minutes}} | {Hours, Minutes}
187 %% Hours = integer()
188 %% Minutes = integer()
189 timestamp_to_iso({{Year, Month, Day}, {Hour, Minute, Second}}, Timezone) ->
190     timestamp_to_iso({{Year, Month, Day}, {Hour, Minute, Second}, {milliseconds, 0}},
191 		     Timezone);
192 timestamp_to_iso({{Year, Month, Day}, {Hour, Minute, Second},
193 		  {_SubsecondUnit, SubsecondValue}},
194 		 Timezone) ->
195     Timestamp_string =
196 	lists:flatten(io_lib:format("~4..0w-~2..0w-~2..0wT~2..0w:~2..0w:~2..0w.~3..0w",
197 				    [Year, Month, Day, Hour, Minute, Second,
198 				     SubsecondValue])),
199     Timezone_string = case Timezone of
200 			utc -> "Z";
201 			{Sign, {TZh, TZm}} ->
202 			    io_lib:format("~s~2..0w:~2..0w", [Sign, TZh, TZm]);
203 			{TZh, TZm} ->
204 			    Sign = case TZh >= 0 of
205 				     true -> "+";
206 				     false -> "-"
207 				   end,
208 			    io_lib:format("~s~2..0w:~2..0w", [Sign, abs(TZh), TZm])
209 		      end,
210     {Timestamp_string, Timezone_string}.
211 
212 timestamp_to_iso({{Year, Month, Day}, {Hour, Minute, Second}}) ->
213     lists:flatten(io_lib:format("~4..0w~2..0w~2..0wT~2..0w:~2..0w:~2..0w",
214 				[Year, Month, Day, Hour, Minute, Second])).
215 
216 timestamp_to_xml(DateTime, Timezone, FromJID, Desc) ->
217     {T_string, Tz_string} = timestamp_to_iso(DateTime, Timezone),
218     From = exmpp_jid:to_list(FromJID),
219     P1 = exmpp_xml:set_attributes(#xmlel{ns = ?NS_DELAY, name = delay},
220 				  [{<<"from">>, From},
221 				   {<<"stamp">>, T_string ++ Tz_string}]),
222     exmpp_xml:set_cdata(P1, Desc).
223 
224 %% TODO: Remove this function once XEP-0091 is Obsolete
225 timestamp_to_xml({{Year, Month, Day}, {Hour, Minute, Second}}) ->
226     Timestamp = lists:flatten(io_lib:format("~4..0w~2..0w~2..0wT~2..0w:~2..0w:~2..0w",
227 					    [Year, Month, Day, Hour, Minute, Second])),
228     exmpp_xml:set_attribute(#xmlel{ns = ?NS_DELAY_OLD, name = x}, <<"stamp">>,
229 			    Timestamp).
230 
231 now_to_utc_string({MegaSecs, Secs, MicroSecs}) ->
232     {{Year, Month, Day}, {Hour, Minute, Second}} =
233 	calendar:now_to_universal_time({MegaSecs, Secs, MicroSecs}),
234     lists:flatten(io_lib:format("~4..0w-~2..0w-~2..0wT~2..0w:~2..0w:~2..0w.~6..0wZ",
235 				[Year, Month, Day, Hour, Minute, Second, MicroSecs])).
236 
237 now_to_local_string({MegaSecs, Secs, MicroSecs}) ->
238     LocalTime = calendar:now_to_local_time({MegaSecs, Secs, MicroSecs}),
239     UTCTime = calendar:now_to_universal_time({MegaSecs, Secs, MicroSecs}),
240     Seconds = calendar:datetime_to_gregorian_seconds(LocalTime) -
241 		calendar:datetime_to_gregorian_seconds(UTCTime),
242     {{H, M, _}, Sign} = if Seconds < 0 -> {calendar:seconds_to_time(-Seconds), "-"};
243 			   true -> {calendar:seconds_to_time(Seconds), "+"}
244 			end,
245     {{Year, Month, Day}, {Hour, Minute, Second}} = LocalTime,
246     lists:flatten(io_lib:format("~4..0w-~2..0w-~2..0wT~2..0w:~2..0w:~2..0w.~6..0w~s~2..0w:~2..0w",
247 				[Year, Month, Day, Hour, Minute, Second, MicroSecs, Sign,
248 				 H, M])).
249 
250 % {yyyy-mm-dd|yyyymmdd}Thh:mm:ss[.sss]{|Z|{+|-}hh:mm} -> {MegaSecs, Secs, MicroSecs} | undefined
251 datetime_string_to_timestamp(TimeStr) ->
252     case catch parse_datetime(TimeStr) of
253       {'EXIT', _Err} -> undefined;
254       TimeStamp -> TimeStamp
255     end.
256 
257 parse_datetime(TimeStr) ->
258     [Date, Time] = string:tokens(TimeStr, "T"),
259     D = parse_date(Date),
260     {T, MS, TZH, TZM} = parse_time(Time),
261     S = calendar:datetime_to_gregorian_seconds({D, T}),
262     S1 = calendar:datetime_to_gregorian_seconds({{1970, 1, 1}, {0, 0, 0}}),
263     Seconds = S - S1 - TZH * 60 * 60 - TZM * 60,
264     {Seconds div 1000000, Seconds rem 1000000, MS}.
265 
266 % yyyy-mm-dd | yyyymmdd
267 parse_date(Date) ->
268     {Y, M, D} = case string:tokens(Date, "-") of
269 		  [Y1, M1, D1] -> {Y1, M1, D1};
270 		  [[Y1, Y2, Y3, Y4, M1, M2, D1, D2]] ->
271 		      {[Y1, Y2, Y3, Y4], [M1, M2], [D1, D2]}
272 		end,
273     Date1 = {list_to_integer(Y), list_to_integer(M), list_to_integer(D)},
274     case calendar:valid_date(Date1) of
275       true -> Date1;
276       _ -> false
277     end.
278 
279 % hh:mm:ss[.sss]TZD
280 parse_time(Time) ->
281     case string:str(Time, "Z") of
282       0 -> parse_time_with_timezone(Time);
283       _ -> [T | _] = string:tokens(Time, "Z"), {TT, MS} = parse_time1(T), {TT, MS, 0, 0}
284     end.
285 
286 parse_time_with_timezone(Time) ->
287     case string:str(Time, "+") of
288       0 ->
289 	  case string:str(Time, "-") of
290 	    0 -> {TT, MS} = parse_time1(Time), {TT, MS, 0, 0};
291 	    _ -> parse_time_with_timezone(Time, "-")
292 	  end;
293       _ -> parse_time_with_timezone(Time, "+")
294     end.
295 
296 parse_time_with_timezone(Time, Delim) ->
297     [T, TZ] = string:tokens(Time, Delim),
298     {TZH, TZM} = parse_timezone(TZ),
299     {TT, MS} = parse_time1(T),
300     case Delim of
301       "-" -> {TT, MS, -TZH, -TZM};
302       "+" -> {TT, MS, TZH, TZM}
303     end.
304 
305 parse_timezone(TZ) ->
306     [H, M] = string:tokens(TZ, ":"),
307     {[H1, M1], true} = check_list([{H, 12}, {M, 60}]),
308     {H1, M1}.
309 
310 parse_time1(Time) ->
311     [HMS | T] = string:tokens(Time, "."),
312     MS = case T of
313 	   [] -> 0;
314 	   [Val] -> list_to_integer(string:left(Val, 6, $0))
315 	 end,
316     [H, M, S] = string:tokens(HMS, ":"),
317     {[H1, M1, S1], true} = check_list([{H, 24}, {M, 60}, {S, 60}]),
318     {{H1, M1, S1}, MS}.
319 
320 check_list(List) ->
321     lists:mapfoldl(fun ({L, N}, B) ->
322 			   V = list_to_integer(L),
323 			   if (V >= 0) and (V =< N) -> {V, B};
324 			      true -> {false, false}
325 			   end
326 		   end,
327 		   true, List).
328 
329 %
330 % Base64 stuff (based on httpd_util.erl)
331 %
332 
333 
334 decode_base64(S) -> decode1_base64([C || C <- S, C /= $\s, C /= $\t, C /= $\n, C /= $\r]).
335 
336 decode1_base64([]) -> [];
337 decode1_base64([Sextet1, Sextet2, $=, $= | Rest]) ->
338     Bits2x6 = d(Sextet1) bsl 18 bor (d(Sextet2) bsl 12),
339     Octet1 = Bits2x6 bsr 16,
340     [Octet1 | decode1_base64(Rest)];
341 decode1_base64([Sextet1, Sextet2, Sextet3, $= | Rest]) ->
342     Bits3x6 = d(Sextet1) bsl 18 bor (d(Sextet2) bsl 12) bor (d(Sextet3) bsl 6),
343     Octet1 = Bits3x6 bsr 16,
344     Octet2 = (Bits3x6 bsr 8) band 255,
345     [Octet1, Octet2 | decode1_base64(Rest)];
346 decode1_base64([Sextet1, Sextet2, Sextet3, Sextet4 | Rest]) ->
347     Bits4x6 = d(Sextet1) bsl 18 bor (d(Sextet2) bsl 12) bor (d(Sextet3) bsl 6) bor
348 		d(Sextet4),
349     Octet1 = Bits4x6 bsr 16,
350     Octet2 = (Bits4x6 bsr 8) band 255,
351     Octet3 = Bits4x6 band 255,
352     [Octet1, Octet2, Octet3 | decode1_base64(Rest)];
353 decode1_base64(_CatchAll) -> "".
354 
355 d(X) when X >= $A, X =< $Z -> X - 65;
356 d(X) when X >= $a, X =< $z -> X - 71;
357 d(X) when X >= $0, X =< $9 -> X + 4;
358 d($+) -> 62;
359 d($/) -> 63;
360 d(_) -> 63.
361 
362 encode_base64([]) -> [];
363 encode_base64([A]) -> [e(A bsr 2), e(A band 3 bsl 4), $=, $=];
364 encode_base64([A, B]) ->
365     [e(A bsr 2), e(A band 3 bsl 4 bor (B bsr 4)), e(B band 15 bsl 2), $=];
366 encode_base64([A, B, C | Ls]) -> encode_base64_do(A, B, C, Ls).
367 
368 encode_base64_do(A, B, C, Rest) ->
369     BB = A bsl 16 bor (B bsl 8) bor C,
370     [e(BB bsr 18), e((BB bsr 12) band 63), e((BB bsr 6) band 63), e(BB band 63)
371      | encode_base64(Rest)].
372 
373 e(X) when X >= 0, X < 26 -> X + 65;
374 e(X) when X > 25, X < 52 -> X + 71;
375 e(X) when X > 51, X < 62 -> X - 4;
376 e(62) -> $+;
377 e(63) -> $/;
378 e(X) -> exit({bad_encode_base64_token, X}).
379 
380 %% @doc Deprecated for {@link inet_parse:ntoa/1}.
381 %% ```
382 %% - jlib:ip_to_list
383 %% + inet_parse:ntoa(IpTuple)
384 %% '''
385 %% Convert Erlang inet IP to list
386 ip_to_list({IP, _Port}) -> ip_to_list(IP);
387 ip_to_list(IpTuple) when is_tuple(IpTuple) -> inet_parse:ntoa(IpTuple);
388 ip_to_list(IP) -> lists:flatten(io_lib:format("~w", [IP])).
389 
390 % --------------------------------------------------------------------
391 % Compat layer.
392 % --------------------------------------------------------------------
393 
394 
395 %% @spec (JID) -> New_JID
396 %%     JID = jid()
397 %%     New_JID = jid()
398 %% @doc Convert a JID from its ejabberd form to its exmpp form.
399 %%
400 %% Empty fields are set to `undefined', not the empty string.
401 
402 
403 %%TODO: this doesn't make sence!, it is still used?.
404 from_old_jid({jid, NodeRaw, DomainRaw, ResourceRaw, _, _, _}) ->
405     Node = exmpp_stringprep:nodeprep(NodeRaw),
406     Domain = exmpp_stringprep:resourceprep(DomainRaw),
407     Resource = exmpp_stringprep:nameprep(ResourceRaw),
408     exmpp_jid:make(Node, Domain, Resource).
409 
410 short_jid(JID) -> {exmpp_jid:node(JID), exmpp_jid:domain(JID), exmpp_jid:resource(JID)}.
411 
412 short_bare_jid(JID) -> short_jid(exmpp_jid:bare(JID)).
413 
414 short_prepd_jid(JID) ->
415     {exmpp_jid:prep_node(JID), exmpp_jid:prep_domain(JID), exmpp_jid:prep_resource(JID)}.
416 
417 short_prepd_bare_jid(JID) -> short_prepd_jid(exmpp_jid:bare(JID)).
418 
419 make_result_iq_reply({xmlelement, Name, Attrs, SubTags}) ->
420     NewAttrs = make_result_iq_reply_attrs(Attrs), {xmlelement, Name, NewAttrs, SubTags}.
421 
422 make_result_iq_reply_attrs(Attrs) ->
423     To = xml:get_attr("to", Attrs),
424     From = xml:get_attr("from", Attrs),
425     Attrs1 = lists:keydelete("to", 1, Attrs),
426     Attrs2 = lists:keydelete("from", 1, Attrs1),
427     Attrs3 = case To of
428 	       {value, ToVal} -> [{"from", ToVal} | Attrs2];
429 	       _ -> Attrs2
430 	     end,
431     Attrs4 = case From of
432 	       {value, FromVal} -> [{"to", FromVal} | Attrs3];
433 	       _ -> Attrs3
434 	     end,
435     Attrs5 = lists:keydelete("type", 1, Attrs4),
436     Attrs6 = [{"type", "result"} | Attrs5],
437     Attrs6.
438 
439 make_error_reply({xmlelement, Name, Attrs, SubTags}, Code, Desc) ->
440     NewAttrs = make_error_reply_attrs(Attrs),
441     {xmlelement, Name, NewAttrs,
442      SubTags ++ [{xmlelement, "error", [{"code", Code}], [{xmlcdata, Desc}]}]}.
443 
444 %% @doc Deprecated for {@link exmpp_iq:error/2},
445 %% {@link exmpp_iq:error_without_original/2}.
446 %% ```
447 %% - jlib:make_error_reply(Packet, ?ERR_FEATURE_NOT_IMPLEMENTED)
448 %% + exmpp_iq:error(Packet, 'feature-not-implemented')
449 %% '''
450 %% ```
451 %% - jlib:make_error_reply(El, ?ERR_JID_MALFORMED)
452 %% + exmpp_iq:error_without_original(El, 'jid-malformed')
453 %% '''
454 %% ```
455 %% - jlib:make_error_reply(El, ?ERR_AUTH_NO_RESOURCE_PROVIDED("en"))
456 %% + exmpp_iq:error(El, exmpp_stanza:error(Namespace, 'not-acceptable', {"en", "No resource provided"}))
457 %% '''
458 
459 
460 make_error_reply({xmlelement, Name, Attrs, SubTags}, Error) ->
461     NewAttrs = make_error_reply_attrs(Attrs),
462     {xmlelement, Name, NewAttrs, SubTags ++ [Error]}.
463 
464 make_error_reply_attrs(Attrs) ->
465     To = xml:get_attr("to", Attrs),
466     From = xml:get_attr("from", Attrs),
467     Attrs1 = lists:keydelete("to", 1, Attrs),
468     Attrs2 = lists:keydelete("from", 1, Attrs1),
469     Attrs3 = case To of
470 	       {value, ToVal} -> [{"from", ToVal} | Attrs2];
471 	       _ -> Attrs2
472 	     end,
473     Attrs4 = case From of
474 	       {value, FromVal} -> [{"to", FromVal} | Attrs3];
475 	       _ -> Attrs3
476 	     end,
477     Attrs5 = lists:keydelete("type", 1, Attrs4),
478     Attrs6 = [{"type", "error"} | Attrs5],
479     Attrs6.
480 
481 make_error_element(Code, Desc) ->
482     {xmlelement, "error", [{"code", Code}], [{xmlcdata, Desc}]}.
483 
484 make_correct_from_to_attrs(From, To, Attrs) ->
485     Attrs1 = lists:keydelete("from", 1, Attrs),
486     Attrs2 = case xml:get_attr("to", Attrs) of
487 	       {value, _} -> Attrs1;
488 	       _ -> [{"to", To} | Attrs1]
489 	     end,
490     Attrs3 = [{"from", From} | Attrs2],
491     Attrs3.
492 
493 %% @doc Deprecated for {@link exmpp_stanza:set_recipient_in_attrs/2}.
494 %% ```
495 %% - jlib:replace_from_to_attrs(String1, String2, Attrs)
496 %% + exmpp_stanza:set_recipient_in_attrs(exmpp_stanza:set_sender_in_attrs(Attrs, String1), String2)
497 %% '''
498 
499 
500 replace_from_to_attrs(From, To, Attrs) ->
501     Attrs1 = lists:keydelete("to", 1, Attrs),
502     Attrs2 = lists:keydelete("from", 1, Attrs1),
503     Attrs3 = [{"to", To} | Attrs2],
504     Attrs4 = [{"from", From} | Attrs3],
505     Attrs4.
506 
507 %% @doc Deprecated for {@link exmpp_stanza:set_recipient/2}.
508 %% ```
509 %% - jlib:replace_from_to(JID1, JID2, Stanza)
510 %% + exmpp_stanza:set_recipient(exmpp_stanza:set_sender(Stanza, JID1), JID2)
511 %% '''
512 
513 
514 replace_from_to(From, To, {xmlelement, Name, Attrs, Els}) ->
515     NewAttrs = replace_from_to_attrs(jlib:jid_to_string(From), jlib:jid_to_string(To),
516 				     Attrs),
517     {xmlelement, Name, NewAttrs, Els}.
518 
519 replace_from_attrs(From, Attrs) ->
520     Attrs1 = lists:keydelete("from", 1, Attrs), [{"from", From} | Attrs1].
521 
522 replace_from(From, {xmlelement, Name, Attrs, Els}) ->
523     NewAttrs = replace_from_attrs(jlib:jid_to_string(From), Attrs),
524     {xmlelement, Name, NewAttrs, Els}.
525 
526 %% @doc Deprecated for {@link exmpp_stanza:remove_recipient/1}.
527 %% ```
528 %% - jlib:remove_attr("to", Stanza)
529 %% + exmpp_stanza:remove_recipient(Stanza)
530 %% '''
531 
532 
533 remove_attr(Attr, {xmlelement, Name, Attrs, Els}) ->
534     NewAttrs = lists:keydelete(Attr, 1, Attrs), {xmlelement, Name, NewAttrs, Els}.
535 
536 %% @doc Deprecated for {@link exmpp_jid:make/3}.
537 %% ```
538 %% - jlib:make_jid({Username, Server, Resource})
539 %% + exmpp_jid:make(Username, Server, Resource)
540 %% '''
541 
542 
543 make_jid({U, S, R}) -> make({U, S, R}).
544 
545 %% @doc Deprecated for {@link exmpp_jid:make/3}.
546 %% ```
547 %% - jlib:make_jid(Username, Server, Resource)
548 %% + exmpp_jid:make(Username, Server, Resource)
549 %% '''
550 %% ```
551 %% - jlib:make_jid(Username, Server, "")
552 %% + exmpp_jid:bare(JID)
553 %% '''
554 
555 
556 make_jid(U, S, R) -> make(U, S, R).
557 
558 make(User, Server, Resource) ->
559     try exmpp_jid:make(User, Server, Resource) catch _Exception -> error end.
560 
561 make({User, Server, Resource}) -> make(User, Server, Resource).
562 
563 %% @doc Deprecated for {@link exmpp_jid:parse/1}.
564 %% ```
565 %% - jlib:string_to_jid(String)
566 %% + exmpp_jid:parse(String)
567 %% '''
568 
569 
570 string_to_jid(String) -> exmpp_jid:parse(String).
571 
572 %% @doc Deprecated for {@link exmpp_jid:to_list/1}.
573 %% ```
574 %% - jlib:jid_to_string({Node, Server, Resource}
575 %% + exmpp_jid:to_list(exmpp_jid:make(Node, Server, Resource))
576 %% '''
577 %% ```
578 %% - jlib:jid_to_string(JID)
579 %% + exmpp_jid:to_list(JID)
580 %% '''
581 
582 
583 jid_to_string({Node, Server, Resource}) ->
584     Jid = exmpp_jid:make(Node, Server, Resource), exmpp_jid:to_list(Jid);
585 jid_to_string(Jid) -> exmpp_jid:to_list(Jid).
586 
587 %% @doc Deprecated for {@link exmpp_stringprep:is_node/1}.
588 %% ```
589 %% - jlib:is_nodename(Username)
590 %% + exmpp_stringprep:is_node(Username)
591 %% '''
592 
593 
594 is_nodename(Username) -> exmpp_stringprep:is_node(Username).
595 
596 %% @doc Deprecated for {@link exmpp_stringprep:to_lower/1}.
597 %% ```
598 %% - jlib:tolower(String)
599 %% + exmpp_stringprep:to_lower(String)
600 %% '''
601 
602 
603 %% Not tail-recursive but it seems works faster than variants above
604 tolower(String) -> exmpp_stringprep:to_lower(String).
605 
606 %% @doc Deprecated for {@link exmpp_stringprep:nodeprep/1}.
607 %% ```
608 %% - jlib:nodeprep(Username)
609 %% + exmpp_stringprep:nodeprep(Username)
610 %% '''
611 
612 
613 nodeprep(Username) -> exmpp_stringprep:nodeprep(Username).
614 
615 %% @doc Deprecated for {@link exmpp_stringprep:nameprep/1}.
616 %% ```
617 %% - jlib:nameprep(Server)
618 %% + exmpp_stringprep:nameprep(Server)
619 %% '''
620 
621 
622 nameprep(Server) -> exmpp_stringprep:nameprep(Server).
623 
624 %% @doc Deprecated for {@link exmpp_stringprep:resourceprep/1}.
625 %% ```
626 %% - jlib:resourceprep(Resource)
627 %% + exmpp_stringprep:resourceprep(Resource)
628 %% '''
629 
630 
631 resourceprep(Resource) -> exmpp_stringprep:resourceprep(Resource).
632 
633 %% @doc Deprecated for {@link jlib:short_prepd_jid/1}.
634 %% ```
635 %% - jlib:jid_tolower(JID)
636 %% + jlib:short_prepd_jid(JID)
637 %% '''
638 %% ```
639 %% - jlib:jid_tolower(JID)
640 %% +  {exmpp_jid:prep_node_as_list(JID), exmpp_jid:prep_domain_as_list(JID), exmpp_jid:prep_resource_as_list(JID)}
641 %% '''
642 
643 
644 jid_tolower({U, S, R}) -> jid_tolower(exmpp_jid:make(U, S, R));
645 jid_tolower(JID) -> jlib:short_prepd_jid(JID).
646 
647 %% @doc Deprecated for {@link jlib:short_prepd_bare_jid/1}.
648 %% ```
649 %% - jlib:jid_remove_resource(jlib:jid_tolower(String))
650 %% + jlib:short_prepd_bare_jid(String)
651 %% '''
652 
653 
654 jid_remove_resource({U, S, R}) -> short_prepd_bare_jid(exmpp_jid:make(U, S, R));
655 jid_remove_resource(JID) -> short_prepd_bare_jid(JID).
656 
657 %% @doc Deprecated for {@link exmpp_jid:full/2}.
658 %% ```
659 %% - jlib:jid_replace_resource(JID, R)
660 %% + exmpp_jid:full(JID, R)
661 %% '''
662 
663 
664 jid_replace_resource(JID, Resource) -> exmpp_jid:full(JID, Resource).
665 
666 %% @deprecated
667 get_iq_namespace({xmlelement, Name, _Attrs, Els}) when Name == "iq" ->
668     case xml:remove_cdata(Els) of
669       [{xmlelement, _Name2, Attrs2, _Els2}] -> xml:get_attr_s("xmlns", Attrs2);
670       _ -> ""
671     end;
672 get_iq_namespace(_) -> "".
673 
674 %% @doc Deprecated for {@link exmpp_iq:xmlel_to_iq/1}.
675 %% ```
676 %% - jlib:iq_query_info(Packet)
677 %% + exmpp_iq:xmlel_to_iq(Packet)
678 %% '''
679 
680 
681 iq_query_info(El) -> exmpp_iq:xmlel_to_iq(El).
682 
683 iq_query_or_response_info(El) -> exmpp_iq:xmlel_to_iq(El).
684 
685 is_iq_request_type(set) -> true;
686 is_iq_request_type(get) -> true;
687 is_iq_request_type(_) -> false.
688 
689 %% @doc Deprecated for {@link exmpp_iq:iq_to_xmlel/1}.
690 %% ```
691 %% - jlib:iq_to_xml(IQ)
692 %% + exmpp_iq:iq_to_xmlel(IQ)
693 %% '''
694 
695 
696 iq_to_xml(IQ) -> exmpp_iq:iq_to_xmlel(IQ).