1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1997-2021. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20-module(inet_parse).
21
22%% Parser for all kinds of ineternet configuration files
23
24%% Avoid warning for local function error/2 clashing with autoimported BIF.
25-compile({no_auto_import,[error/2]}).
26-export([hosts/1, hosts/2]).
27-export([protocols/1, protocols/2]).
28-export([netmasks/1, netmasks/2]).
29-export([networks/1, networks/2]).
30-export([services/1, services/2]).
31-export([rpc/1, rpc/2]).
32-export([resolv/1, resolv/2]).
33-export([host_conf_linux/1, host_conf_linux/2]).
34-export([host_conf_freebsd/1, host_conf_freebsd/2]).
35-export([host_conf_bsdos/1, host_conf_bsdos/2]).
36-export([nsswitch_conf/1, nsswitch_conf/2]).
37
38-export([ipv4_address/1, ipv6_address/1]).
39-export([ipv4strict_address/1, ipv6strict_address/1]).
40-export([address/1, strict_address/1]).
41-export([visible_string/1, domain/1]).
42-export([ntoa/1, dots/1]).
43-export([split_line/1]).
44
45-import(lists, [reverse/1]).
46
47-include_lib("kernel/include/file.hrl").
48-include("inet_int.hrl").
49
50%% --------------------------------------------------------------------------
51%% Parse services internet style
52%% Syntax:
53%%      Name   Port/Protocol    [Aliases]  \n
54%%      # comment
55%% --------------------------------------------------------------------------
56
57services(File) ->
58    services(noname, File).
59
60services(Fname, File) ->
61    Fn = fun([Name, PortProto | Aliases]) ->
62		 {Proto,Port} = port_proto(PortProto, 0),
63		 {Name,Proto,Port,Aliases}
64	 end,
65    parse_file(Fname, File, Fn).
66
67%% --------------------------------------------------------------------------
68%% Parse rpc program names
69%% Syntax:
70%%      Name   Program  [Aliases]  \n |
71%%      # comment
72%% --------------------------------------------------------------------------
73
74rpc(File) ->
75    rpc(noname, File).
76
77rpc(Fname, File) ->
78    Fn = fun([Name,Program | Aliases]) ->
79		 Prog = list_to_integer(Program),
80		 {Name,Prog,Aliases}
81	 end,
82    parse_file(Fname, File, Fn).
83
84%% --------------------------------------------------------------------------
85%% Parse hosts file unix style
86%% Syntax:
87%%      IP Name [Aliases]  \n |
88%%      # comment
89%% --------------------------------------------------------------------------
90hosts(File) ->
91    hosts(noname,File).
92
93hosts(Fname,File) ->
94    Fn = fun([Address, Name | Aliases]) ->
95		 %% XXX Fix for link-local IPv6 addresses that specify
96		 %% interface with a %if suffix. These kind of
97		 %% addresses maybe need to be gracefully handled
98		 %% throughout inet* and inet_drv.
99		 case string:lexemes(Address, "%") of
100		     [Addr,_] ->
101			 {ok,_} = address(Addr),
102			 skip;
103		     _ ->
104			 {ok,IP} = address(Address),
105			 {IP, Name, Aliases}
106		 end
107	 end,
108    parse_file(Fname, File, Fn).
109
110%% --------------------------------------------------------------------------
111%% Parse resolv file unix style
112%% Syntax:
113%%      domain Domain \n
114%%      nameserver IP \n
115%%      search Dom1 Dom2 ... \n
116%%      lookup Method1 Method2 Method3 \n
117%%      # comment
118%% --------------------------------------------------------------------------
119
120resolv(File) ->
121    resolv(noname,File).
122
123resolv(Fname, File) ->
124    Fn = fun(["domain", Domain]) ->
125		 {domain, Domain};
126	    (["nameserver", Address]) ->
127		 {ok,IP} = address(Address),
128		 {nameserver,IP};
129	    (["search" | List]) ->
130		 {search, List};
131	    (["lookup" | Types]) ->
132		 {lookup, Types};
133	    (_) ->
134		 skip  %% there are too many local options, we MUST skip
135	 end,
136    parse_file(Fname, File, Fn).
137
138%% --------------------------------------------------------------------------
139%%
140%% Parse Linux host.conf file
141%% find "order" only.
142%%
143%% --------------------------------------------------------------------------
144host_conf_linux(File) ->
145    host_conf_linux(noname,File).
146
147host_conf_linux(Fname, File) ->
148    Fn = fun(["order" | Order]) ->
149		 %% XXX remove ',' between entries
150		 {lookup, split_comma(Order)};
151	    (_) ->
152		 skip
153	 end,
154    parse_file(Fname, File, Fn).
155
156%% --------------------------------------------------------------------------
157%%
158%% Parse Freebsd/Netbsd host.conf file
159%% find "order" only.
160%%
161%% --------------------------------------------------------------------------
162host_conf_freebsd(File) ->
163    host_conf_freebsd(noname,File).
164
165host_conf_freebsd(Fname, File) ->
166    Fn = fun([Type]) -> Type end,
167    case parse_file(Fname, File, Fn) of
168	{ok, Ls} -> {ok, [{lookup, Ls}]};
169	Error -> Error
170    end.
171
172
173
174%% --------------------------------------------------------------------------
175%%
176%% Parse BSD/OS irs.conf file
177%% find "hosts" only and ignore options.
178%%
179%% Syntax:
180%%      Map AccessMethod [,AccessMethod] [continue|merge [,merge|,continue]] \n
181%%      # comment
182
183%% --------------------------------------------------------------------------
184host_conf_bsdos(File) ->
185    host_conf_bsdos(noname,File).
186
187host_conf_bsdos(Fname, File) ->
188    Fn = fun(["hosts" | List]) ->
189		 delete_options(split_comma(List));
190	    (_) ->
191		 skip
192	 end,
193    case parse_file(Fname, File, Fn) of
194	{ok, Ls} ->
195	    {ok, [{lookup, lists:append(Ls)}]};
196	Error -> Error
197    end.
198
199delete_options(["continue"|T]) ->
200    delete_options(T);
201delete_options(["merge"|T]) ->
202    delete_options(T);
203delete_options([H|T]) ->
204    [H|delete_options(T)];
205delete_options([]) ->
206    [].
207
208
209%% --------------------------------------------------------------------------
210%%
211%% Parse Solaris nsswitch.conf
212%% find "hosts:" only
213%%
214%% --------------------------------------------------------------------------
215
216nsswitch_conf(File) ->
217    nsswitch_conf(noname,File).
218
219nsswitch_conf(Fname, File) ->
220    Fn = fun(["hosts:" | Types]) ->
221		 {lookup, Types};
222	    (_) -> skip
223	 end,
224    parse_file(Fname, File, Fn).
225
226%% --------------------------------------------------------------------------
227%% Parse protocol file unix style
228%% Syntax:
229%%      name protocol number name \n
230%%      # comment
231%% --------------------------------------------------------------------------
232
233protocols(File) ->
234    protocols(noname,File).
235
236protocols(Fname, File) ->
237    Fn = fun([Name, Number, DName]) ->
238		 {list_to_atom(Name), list_to_integer(Number), DName}
239	 end,
240    parse_file(Fname, File, Fn).
241
242%% --------------------------------------------------------------------------
243%% Parse netmasks file unix style
244%% Syntax:
245%%      Network  Subnetmask
246%%      # comment
247%% --------------------------------------------------------------------------
248
249netmasks(File) ->
250    netmasks(noname, File).
251
252netmasks(Fname, File) ->
253    Fn = fun([Net, Subnetmask]) ->
254		 {ok, NetIP} = address(Net),
255		 {ok, Mask} =  address(Subnetmask),
256		 {NetIP, Mask}
257	 end,
258    parse_file(Fname, File, Fn).
259
260%% --------------------------------------------------------------------------
261%% Parse networks file unix style
262%% Syntax:
263%%      network-name  network-number aliases ...
264%%      # comment
265%% --------------------------------------------------------------------------
266
267networks(File) ->
268    networks(noname, File).
269
270networks(Fname, File) ->
271    Fn = fun([NetName, NetNumber]) ->
272		 Number = list_to_integer(NetNumber),
273		 {NetName, Number}
274	 end,
275    parse_file(Fname, File, Fn).
276
277%% --------------------------------------------------------------------------
278%%
279%% Simple Line by Line parser
280%%
281%% --------------------------------------------------------------------------
282
283parse_file(Fname, {fd,Fd}, Fn) ->
284    parse_fd(Fname,Fd, 1, Fn, []);
285parse_file(Fname, {chars,Cs}, Fn) when is_list(Cs) ->
286    parse_cs(Fname, Cs, 1, Fn, []);
287parse_file(Fname, {chars,Cs}, Fn) when is_binary(Cs) ->
288    parse_cs(Fname, binary_to_list(Cs), 1, Fn, []);
289parse_file(_, File, Fn) ->
290    case file:open(File, [read]) of
291	{ok, Fd} ->
292	    Result = parse_fd(File,Fd, 1, Fn, []),
293	    _ = file:close(Fd),
294	    Result;
295	Error -> Error
296    end.
297
298parse_fd(Fname,Fd, Line, Fun, Ls) ->
299    case read_line(Fd) of
300	eof -> {ok, reverse(Ls)};
301	Cs ->
302	    case split_line(Cs) of
303		[] -> parse_fd(Fname, Fd, Line+1, Fun, Ls);
304		Toks ->
305		    case catch Fun(Toks) of
306			{'EXIT',_} ->
307			    error("~p:~p: erroneous line, SKIPPED~n",[Fname,Line]),
308			    parse_fd(Fname, Fd,Line+1,Fun,Ls);
309			{warning,Wlist,Val} ->
310			    warning("~p:~p: warning! strange domain name(s) ~p ~n",[Fname,Line,Wlist]),
311			    parse_fd(Fname, Fd,Line+1,Fun,[Val|Ls]);
312
313			skip ->
314			    parse_fd(Fname, Fd, Line+1, Fun, Ls);
315			Val -> parse_fd(Fname, Fd, Line+1, Fun, [Val|Ls])
316		    end
317	    end
318    end.
319
320parse_cs(Fname, Chars, Line, Fun, Ls) ->
321    case get_line(Chars) of
322	eof -> {ok, reverse(Ls)};
323	{Cs,Chars1} ->
324	    case split_line(Cs) of
325		[] -> parse_cs(Fname, Chars1, Line+1, Fun, Ls);
326		Toks ->
327		    case catch Fun(Toks) of
328			{'EXIT',_} ->
329			    error("~p:~p: erroneous line, SKIPPED~n",[Fname,Line]),
330 			    parse_cs(Fname, Chars1, Line+1, Fun, Ls);
331			{warning,Wlist,Val} ->
332			    warning("~p:~p: warning! strange domain name(s) ~p ~n",[Fname,Line,Wlist]),
333			    parse_cs(Fname, Chars1, Line+1, Fun, [Val|Ls]);
334
335			skip -> parse_cs(Fname, Chars1, Line+1, Fun, Ls);
336			Val -> parse_cs(Fname, Chars1, Line+1, Fun, [Val|Ls])
337		    end
338	    end
339    end.
340
341get_line([]) -> eof;
342get_line(Chars) -> get_line(Chars,[]).
343
344get_line([], Acc) -> {reverse(Acc), []};
345get_line([$\r, $\n | Cs], Acc) -> {reverse([$\n|Acc]), Cs};
346get_line([$\n | Cs], Acc) -> {reverse([$\n|Acc]), Cs};
347get_line([C | Cs], Acc) -> get_line(Cs, [C|Acc]).
348
349%%
350%% Read a line
351%%
352read_line(Fd) when is_pid(Fd) -> io:get_line(Fd, '');
353read_line(Fd = #file_descriptor{}) ->
354    collect_line(Fd, []).
355
356collect_line(Fd, Cs) ->
357    case file:read(Fd, 80) of
358	{ok, Line} when is_binary(Line) ->
359	    collect_line(Fd, byte_size(Line), binary_to_list(Line), Cs);
360	{ok, Line} ->
361	    collect_line(Fd, length(Line), Line, Cs);
362	eof when Cs =:= [] ->
363	    eof;
364	eof -> reverse(Cs)
365    end.
366
367collect_line(Fd, N, [$\r, $\n|_], Cs) ->
368    {ok, _} = file:position(Fd, {cur,-(N-2)}),
369    reverse([$\n|Cs]);
370collect_line(Fd, N, [$\n|_], Cs) ->
371    {ok, _} = file:position(Fd, {cur,-(N-1)}),
372    reverse([$\n|Cs]);
373collect_line(Fd, _, [], Cs) ->
374    collect_line(Fd, Cs);
375collect_line(Fd, N, [X|Xs], Cs) ->
376    collect_line(Fd, N-1, Xs, [X|Cs]).
377
378
379%% split Port/Proto -> {Port, Proto}
380port_proto([X|Xs], N) when X >= $0, X =< $9 ->
381    port_proto(Xs, N*10 + (X - $0));
382port_proto([$/ | Proto], Port) when Port =/= 0 ->
383    {list_to_atom(Proto), Port}.
384
385%%
386%% Check if a String is a string with visible characters #21..#7E
387%% visible_string(String) -> Bool
388%%
389visible_string([H|T]) ->
390    is_vis1([H|T]);
391visible_string(_) ->
392    false.
393
394is_vis1([C | Cs]) when C >= 16#21, C =< 16#7e -> is_vis1(Cs);
395is_vis1([]) -> true;
396is_vis1(_) -> false.
397
398%%
399%% Check if a String is a domain name according to RFC XXX.
400%% domain(String) -> Bool
401%%
402domain([H|T]) ->
403    is_dom1([H|T]);
404domain(_) ->
405    false.
406
407is_dom1([C | Cs]) when C >= $a, C =< $z -> is_dom_ldh(Cs);
408is_dom1([C | Cs]) when C >= $A, C =< $Z -> is_dom_ldh(Cs);
409is_dom1([C | Cs]) when C >= $0, C =< $9 ->
410    case is_dom_ldh(Cs) of
411	true  -> is_dom2(string:lexemes([C | Cs],"."));
412	false -> false
413    end;
414is_dom1(_) -> false.
415
416is_dom_ldh([C | Cs]) when C >= $a, C =< $z -> is_dom_ldh(Cs);
417is_dom_ldh([C | Cs]) when C >= $A, C =< $Z -> is_dom_ldh(Cs);
418is_dom_ldh([C | Cs]) when C >= $0, C =< $9 -> is_dom_ldh(Cs);
419is_dom_ldh([$-,$. | _]) -> false;
420is_dom_ldh([$_,$. | _]) -> false;
421is_dom_ldh([$_ | Cs]) -> is_dom_ldh(Cs);
422is_dom_ldh([$- | Cs]) -> is_dom_ldh(Cs);
423is_dom_ldh([$. | Cs]) -> is_dom1(Cs);
424is_dom_ldh([]) -> true;
425is_dom_ldh(_) -> false.
426
427%%% Check that we don't get a IP-address as a domain name.
428
429-define(L2I(L), (catch list_to_integer(L))).
430
431is_dom2([A,B,C,D]) ->
432    case ?L2I(D) of
433	Di when is_integer(Di) ->
434	    case {?L2I(A),?L2I(B),?L2I(C)} of
435		{Ai,Bi,Ci} when is_integer(Ai),
436                                is_integer(Bi),
437                                is_integer(Ci) -> false;
438		_ -> true
439	    end;
440	_ -> true
441    end;
442is_dom2(_) ->
443    true.
444
445
446
447%%
448%% Parse ipv4 address or ipv6 address
449%% Return {ok, Address} | {error, Reason}
450%%
451address(Cs) when is_list(Cs) ->
452    case ipv4_address(Cs) of
453	{ok,IP} ->
454	    {ok,IP};
455	_ ->
456	    ipv6strict_address(Cs)
457    end;
458address(_) ->
459    {error, einval}.
460
461%%Parse ipv4 strict address or ipv6 strict address
462strict_address(Cs) when is_list(Cs) ->
463    case ipv4strict_address(Cs) of
464	{ok,IP} ->
465	    {ok,IP};
466	_ ->
467	    ipv6strict_address(Cs)
468    end;
469strict_address(_) ->
470    {error, einval}.
471
472%%
473%% Parse IPv4 address:
474%%    d1.d2.d3.d4
475%%    d1.d2.d4
476%%    d1.d4
477%%    d4
478%% Any d may be octal, hexadecimal or decimal by C language standards.
479%% d4 fills all LSB bytes. This is legacy behaviour from Solaris
480%% and FreeBSD. And partly Linux that behave the same except
481%% it does not accept hexadecimal.
482%%
483%% Return {ok, IP} | {error, einval}
484%%
485ipv4_address(Cs) ->
486    try ipv4_addr(Cs) of
487	Addr ->
488	    {ok,Addr}
489    catch
490	error:badarg ->
491	    {error,einval}
492    end.
493
494ipv4_addr(Cs) ->
495    case ipv4_addr(Cs, []) of
496	[D] when D < (1 bsl 32) ->
497	    <<D1,D2,D3,D4>> = <<D:32>>,
498	    {D1,D2,D3,D4};
499	[D,D1] when D < (1 bsl 24), D1 < 256 ->
500	    <<D2,D3,D4>> = <<D:24>>,
501	    {D1,D2,D3,D4};
502	[D,D2,D1] when D < (1 bsl 16), (D2 bor D1) < 256 ->
503	    <<D3,D4>> = <<D:16>>,
504	    {D1,D2,D3,D4};
505	[D4,D3,D2,D1] when (D4 bor D3 bor D2 bor D1) < 256 ->
506	    {D1,D2,D3,D4};
507	_ ->
508	    erlang:error(badarg)
509    end.
510
511ipv4_addr([_|_], [_,_,_,_]) ->
512    %% Early bailout for extra characters
513    erlang:error(badarg);
514ipv4_addr("0x"++Cs, Ds) ->
515    ipv4_addr(strip0(Cs), Ds, [], 16, 8);
516ipv4_addr("0X"++Cs, Ds) ->
517    ipv4_addr(strip0(Cs), Ds, [], 16, 8);
518ipv4_addr("0"++Cs, Ds) ->
519    ipv4_addr(strip0(Cs), Ds, [$0], 8, 11);
520ipv4_addr(Cs, Ds) when is_list(Cs) ->
521    ipv4_addr(Cs, Ds, [], 10, 10).
522
523ipv4_addr(Cs0, Ds, Rs, Base, N) ->
524    case ipv4_field(Cs0, N, Rs, Base) of
525	{D,""} ->
526	    [D|Ds];
527	{D,[$.|[_|_]=Cs]} ->
528	    ipv4_addr(Cs, [D|Ds]);
529	{_,_} ->
530	    erlang:error(badarg)
531    end.
532
533strip0("0"++Cs) ->
534    strip0(Cs);
535strip0(Cs) when is_list(Cs) ->
536    Cs.
537
538
539%%
540%% Parse IPv4 strict dotted decimal address, no leading zeros:
541%%    d1.d2.d3.d4
542%%
543%% Return {ok, IP} | {error, einval}
544%%
545ipv4strict_address(Cs) ->
546    try ipv4strict_addr(Cs) of
547	Addr ->
548	    {ok,Addr}
549    catch
550	error:badarg ->
551	    {error,einval}
552    end.
553
554ipv4strict_addr(Cs) ->
555    case ipv4strict_addr(Cs, []) of
556	[D4,D3,D2,D1] when (D4 bor D3 bor D2 bor D1) < 256 ->
557	    {D1,D2,D3,D4};
558	_ ->
559	    erlang:error(badarg)
560    end.
561
562ipv4strict_addr([_|_], [_,_,_,_]) ->
563    %% Early bailout for extra characters
564    erlang:error(badarg);
565ipv4strict_addr("0", Ds) ->
566    [0|Ds];
567ipv4strict_addr("0."++Cs, Ds) ->
568    ipv4strict_addr(Cs, [0|Ds]);
569ipv4strict_addr(Cs0, Ds) when is_list(Cs0) ->
570    case ipv4_field(Cs0, 3, [], 10) of
571	{D,""} ->
572	    [D|Ds];
573	{D,[$.|[_|_]=Cs]} ->
574	    ipv4strict_addr(Cs, [D|Ds]);
575	{_,_} ->
576	    erlang:error(badarg)
577    end.
578
579
580
581ipv4_field("", _, Rs, Base) ->
582    {ipv4_field(Rs, Base),""};
583ipv4_field("."++_=Cs, _, Rs, Base) ->
584    {ipv4_field(Rs, Base),Cs};
585ipv4_field("0"++_, _, [], _) ->
586    erlang:error(badarg);
587ipv4_field([C|Cs], N, Rs, Base) when N > 0 ->
588    ipv4_field(Cs, N-1, [C|Rs], Base);
589ipv4_field(Cs, _, _, _) when is_list(Cs) ->
590    erlang:error(badarg).
591
592ipv4_field(Rs, Base) ->
593    V = erlang:list_to_integer(lists:reverse(Rs), Base),
594    if  V < 0 ->
595	    erlang:error(badarg);
596	true ->
597	    V
598    end.
599
600
601
602%%
603%% Forgiving IPv6 address
604%%
605%% Accepts IPv4 address and returns it as a IPv4 compatible IPv6 address
606%%
607ipv6_address(Cs) ->
608    case ipv4_address(Cs) of
609	{ok,{D1,D2,D3,D4}} ->
610	    {ok,{0,0,0,0,0,16#ffff,(D1 bsl 8) bor D2,(D3 bsl 8) bor D4}};
611	_ ->
612	    ipv6strict_address(Cs)
613    end.
614
615%%
616%% Parse IPv6 address according to RFC 4291:
617%%     x1:x2:x3:x4:x5:x6:x7:x8
618%%     x1:x2::x7:x8
619%%     ::x7:x8
620%%     x1:x2::
621%%     ::
622%%     x1:x2:x3:x4:x5:x6:d7a.d7b.d8a.d8b
623%%     x1:x2::x5:x6:d7a.d7b.d8a.d8b
624%%     ::x5:x6:d7a.d7b.d8a.d8b
625%%     x1:x2::d7a.d7b.d8a.d8b
626%%     ::d7a.d7b.d8a.d8b
627%%     etc
628%%
629%% Return {ok, IP} | {error, einval}
630%%
631ipv6strict_address(Cs) ->
632    try ipv6_addr(Cs) of
633	Addr ->
634	    {ok,Addr}
635    catch
636	error:badarg ->
637	    {error,einval}
638    end.
639
640ipv6_addr("::") ->
641    ipv6_addr_done([], [], 0);
642ipv6_addr("::"++Cs) ->
643    ipv6_addr(hex(Cs), [], [], 0);
644ipv6_addr(Cs) ->
645    ipv6_addr(hex(Cs), [], 0).
646
647%% Before "::"
648ipv6_addr({Cs0,"%"++Cs1}, A, N) when N == 7 ->
649    ipv6_addr_scope(Cs1, [hex_to_int(Cs0)|A], [], N+1, []);
650ipv6_addr({Cs0,[]}, A, N) when N == 7 ->
651    ipv6_addr_done([hex_to_int(Cs0)|A]);
652ipv6_addr({Cs0,"::%"++Cs1}, A, N) when N =< 6 ->
653    ipv6_addr_scope(Cs1, [hex_to_int(Cs0)|A], [], N+1, []);
654ipv6_addr({Cs0,"::"}, A, N) when N =< 6 ->
655    ipv6_addr_done([hex_to_int(Cs0)|A], [], N+1);
656ipv6_addr({Cs0,"::"++Cs1}, A, N) when N =< 5 ->
657    ipv6_addr(hex(Cs1), [hex_to_int(Cs0)|A], [], N+1);
658ipv6_addr({Cs0,":"++Cs1}, A, N) when N =< 6 ->
659    ipv6_addr(hex(Cs1), [hex_to_int(Cs0)|A], N+1);
660ipv6_addr({Cs0,"."++_=Cs1}, A, N) when N == 6 ->
661    ipv6_addr_done(A, [], N, ipv4strict_addr(Cs0++Cs1));
662ipv6_addr(_, _, _) ->
663    erlang:error(badarg).
664
665%% After "::"
666ipv6_addr({Cs0,"%"++Cs1}, A, B, N) when N =< 6 ->
667    ipv6_addr_scope(Cs1, A, [hex_to_int(Cs0)|B], N+1, []);
668ipv6_addr({Cs0,[]}, A, B, N) when N =< 6 ->
669    ipv6_addr_done(A, [hex_to_int(Cs0)|B], N+1);
670ipv6_addr({Cs0,":"++Cs1}, A, B, N) when N =< 5 ->
671    ipv6_addr(hex(Cs1), A, [hex_to_int(Cs0)|B], N+1);
672ipv6_addr({Cs0,"."++_=Cs1}, A, B, N) when N =< 5 ->
673    ipv6_addr_done(A, B, N, ipv4strict_addr(Cs0++Cs1));
674ipv6_addr(_, _, _, _) ->
675    erlang:error(badarg).
676
677%% After "%"
678ipv6_addr_scope([], Ar, Br, N, Sr) ->
679    ScopeId =
680        case lists:reverse(Sr) of
681            %% Empty scope id
682            "" -> 0;
683            %% Scope id starts with 0
684            "0"++S -> dec16(S);
685            _ -> 0
686        end,
687    %% Suggested formats for scope id parsing:
688    %%   "" -> "0"
689    %%   "0" -> Scope id 0
690    %%   "1" - "9", "10" - "99" -> "0"++S
691    %%   "0"++DecimalScopeId -> decimal scope id
692    %%   "25"++PercentEncoded -> Percent encoded interface name
693    %%   S -> Interface name (Unicode?)
694    %% Missing: translation from interface name into integer scope id.
695    %% XXX: scope id is actually 32 bit, but we only have room for
696    %% 16 bit in the second address word - ignore or fix (how)?
697    ipv6_addr_scope(ScopeId, Ar, Br, N);
698ipv6_addr_scope([C|Cs], Ar, Br, N, Sr) ->
699    ipv6_addr_scope(Cs, Ar, Br, N, [C|Sr]).
700%%
701ipv6_addr_scope(ScopeId, [P], Br, N)
702  when N =< 7, P =:= 16#fe80;
703       N =< 7, P =:= 16#ff02 ->
704    %% Optimized special case
705    ipv6_addr_done([ScopeId,P], Br, N+1);
706ipv6_addr_scope(ScopeId, Ar, Br, N) ->
707    case lists:reverse(Br++dup(8-N, 0, Ar)) of
708        [P,0|Xs] when P =:= 16#fe80; P =:= 16#ff02 ->
709            list_to_tuple([P,ScopeId|Xs]);
710        _ ->
711            erlang:error(badarg)
712    end.
713
714ipv6_addr_done(Ar, Br, N, {D1,D2,D3,D4}) ->
715    ipv6_addr_done(Ar, [((D3 bsl 8) bor D4),((D1 bsl 8) bor D2)|Br], N+2).
716
717ipv6_addr_done(Ar, Br, N) ->
718    ipv6_addr_done(Br++dup(8-N, 0, Ar)).
719
720ipv6_addr_done(Ar) ->
721    list_to_tuple(lists:reverse(Ar)).
722
723%% Collect 1-4 Hex digits
724hex(Cs) -> hex(Cs, [], 4).
725%%
726hex([C|Cs], R, N) when C >= $0, C =< $9, N > 0 ->
727    hex(Cs, [C|R], N-1);
728hex([C|Cs], R, N) when C >= $a, C =< $f, N > 0 ->
729    hex(Cs, [C|R], N-1);
730hex([C|Cs], R, N) when C >= $A, C =< $F, N > 0 ->
731    hex(Cs, [C|R], N-1);
732hex(Cs, [_|_]=R, _) when is_list(Cs) ->
733    {lists:reverse(R),Cs};
734hex(_, _, _) ->
735    erlang:error(badarg).
736
737%% Parse a reverse decimal integer string, empty is 0
738dec16(Cs) -> dec16(Cs, 0).
739%%
740dec16([], I) -> I;
741dec16([C|Cs], I) when C >= $0, C =< $9 ->
742    case 10*I + (C - $0) of
743        J when 16#ffff < J ->
744            erlang:error(badarg);
745        J ->
746            dec16(Cs, J)
747    end;
748dec16(_, _) -> erlang:error(badarg).
749
750%% Hex string to integer
751hex_to_int(Cs) -> erlang:list_to_integer(Cs, 16).
752
753%% Dup onto head of existing list
754dup(0, _, L) ->
755    L;
756dup(N, E, L) when is_integer(N), N >= 1 ->
757    dup(N-1, E, [E|L]).
758
759
760
761%% Convert IPv4 address to ascii
762%% Convert IPv6 / IPV4 address to ascii (plain format)
763ntoa({A,B,C,D}) when ?ip(A,B,C,D) ->
764    integer_to_list(A) ++ "." ++ integer_to_list(B) ++ "." ++
765	integer_to_list(C) ++ "." ++ integer_to_list(D);
766%% ANY
767ntoa({0,0,0,0,0,0,0,0}) -> "::";
768%% LOOPBACK
769ntoa({0,0,0,0,0,0,0,1}) -> "::1";
770%% IPV4 ipv6 host address
771ntoa({0,0,0,0,0,0,A,B}) when ?ip6(0,0,0,0,0,0,A,B) ->
772    "::" ++ dig_to_dec(A) ++ "." ++ dig_to_dec(B);
773%% IPV4 non ipv6 host address
774ntoa({0,0,0,0,0,16#ffff=X,A,B}) when ?ip6(0,0,0,0,0,X,A,B) ->
775    "::ffff:" ++ dig_to_dec(A) ++ "." ++ dig_to_dec(B);
776ntoa({A,B,C,D,E,F,G,H}) when ?ip6(A,B,C,D,E,F,G,H) ->
777    if
778        A =:= 16#fe80, B =/= 0;
779        A =:= 16#ff02, B =/= 0 ->
780            %% Find longest sequence of zeros, at least 2,
781            %% to replace with "::"
782            ntoa([A,0,C,D,E,F,G,H], []) ++ "%0" ++ integer_to_list(B);
783        true ->
784            %% Find longest sequence of zeros, at least 2,
785            %% to replace with "::"
786            ntoa([A,B,C,D,E,F,G,H], [])
787    end;
788ntoa(_) ->
789    {error, einval}.
790
791%% Find first double zero
792ntoa([], R) ->
793    ntoa_done(R);
794ntoa([0,0|T], R) ->
795    ntoa(T, R, 2);
796ntoa([D|T], R) ->
797    ntoa(T, [D|R]).
798
799%% Count consecutive zeros
800ntoa([], R, _) ->
801    ntoa_done(R, []);
802ntoa([0|T], R, N) ->
803    ntoa(T, R, N+1);
804ntoa([D|T], R, N) ->
805    ntoa(T, R, N, [D]).
806
807%% Find alternate double zero
808ntoa([], R1, _N1, R2) ->
809    ntoa_done(R1, R2);
810ntoa([0,0|T], R1, N1, R2) ->
811    ntoa(T, R1, N1, R2, 2);
812ntoa([D|T], R1, N1, R2) ->
813    ntoa(T, R1, N1, [D|R2]).
814
815%% Count consecutive alternate zeros
816ntoa(T, R1, N1, R2, N2) when N2 > N1 ->
817    %% Alternate zero sequence is longer - use it instead
818    ntoa(T, R2++dup(N1, 0, R1), N2);
819ntoa([], R1, _N1, R2, N2) ->
820    ntoa_done(R1, dup(N2, 0, R2));
821ntoa([0|T], R1, N1, R2, N2) ->
822    ntoa(T, R1, N1, R2, N2+1);
823ntoa([D|T], R1, N1, R2, N2) ->
824    ntoa(T, R1, N1, [D|dup(N2, 0, R2)]).
825
826ntoa_done(R1, R2) ->
827    lists:append(
828      separate(":", lists:map(fun dig_to_hex/1, lists:reverse(R1)))++
829      ["::"|separate(":", lists:map(fun dig_to_hex/1, lists:reverse(R2)))]).
830
831ntoa_done(R) ->
832    lists:append(separate(":", lists:map(fun dig_to_hex/1, lists:reverse(R)))).
833
834separate(_E, []) ->
835    [];
836separate(E, [_|_]=L) ->
837    separate(E, L, []).
838
839separate(E, [H|[_|_]=T], R) ->
840    separate(E, T, [E,H|R]);
841separate(_E, [H], R) ->
842    lists:reverse(R, [H]).
843
844%% convert to A.B decimal form
845dig_to_dec(0) -> "0.0";
846dig_to_dec(X) ->
847    integer_to_list((X bsr 8) band 16#ff) ++ "." ++
848	integer_to_list(X band 16#ff).
849
850%% Convert a integer to hex string (lowercase)
851dig_to_hex(0) -> "0";
852dig_to_hex(X) when is_integer(X), 0 < X ->
853    dig_to_hex(X, "").
854%%
855dig_to_hex(0, Acc) -> Acc;
856dig_to_hex(X, Acc) ->
857    dig_to_hex(
858      X bsr 4,
859      [case X band 15 of
860           D when D < 10 -> D + $0;
861           D -> D - 10 + $a
862       end|Acc]).
863
864%%
865%% Count number of '.' in a name
866%% return {Number of non-terminating dots, has-terminating dot?}
867%%        {integer, bool}
868%%
869dots(Name) -> dots(Name, 0).
870
871dots([$.], N) -> {N, true};
872dots([$. | T], N) -> dots(T, N+1);
873dots([_C | T], N) -> dots(T, N);
874dots([], N) -> {N, false}.
875
876
877split_line(Line) ->
878    split_line(Line, []).
879
880split_line([$# | _], Tokens) ->  reverse(Tokens);
881split_line([$\s| L], Tokens) ->  split_line(L, Tokens);
882split_line([$\t | L], Tokens) -> split_line(L, Tokens);
883split_line([$\n | L], Tokens) -> split_line(L, Tokens);
884split_line([], Tokens) -> reverse(Tokens);
885split_line([C|Cs], Tokens) -> split_mid(Cs, [C], Tokens).
886
887split_mid([$# | _Cs], Acc, Tokens) -> split_end(Acc, Tokens);
888split_mid([$\s | Cs], Acc, Tokens) -> split_line(Cs, [reverse(Acc) | Tokens]);
889split_mid([$\t | Cs], Acc, Tokens) -> split_line(Cs, [reverse(Acc) | Tokens]);
890split_mid([$\r, $\n | Cs], Acc, Tokens) -> split_line(Cs, [reverse(Acc) | Tokens]);
891split_mid([$\n | Cs], Acc, Tokens) -> split_line(Cs, [reverse(Acc) | Tokens]);
892split_mid([], Acc, Tokens) -> split_end(Acc, Tokens);
893split_mid([C|Cs], Acc, Tokens) -> split_mid(Cs, [C|Acc], Tokens).
894
895split_end(Acc, Tokens) -> reverse([reverse(Acc) | Tokens]).
896
897
898%% Split a comma separated tokens. Because we already have split on
899%% spaces we may have the cases
900%%
901%%        ",foo"
902%%        "foo,"
903%%        "foo,bar..."
904
905split_comma([]) ->
906    [];
907split_comma([Token | Tokens]) ->
908    split_comma(Token, []) ++ split_comma(Tokens).
909
910split_comma([], Tokens) ->       reverse(Tokens);
911split_comma([$, | L], Tokens) -> split_comma(L, Tokens);
912split_comma([C|Cs], Tokens) ->   split_mid_comma(Cs, [C], Tokens).
913
914split_mid_comma([$, | Cs], Acc, Tokens) ->
915    split_comma(Cs, [reverse(Acc) | Tokens]);
916split_mid_comma([], Acc, Tokens) ->
917    split_end(Acc, Tokens);
918split_mid_comma([C|Cs], Acc, Tokens) ->
919    split_mid_comma(Cs, [C|Acc], Tokens).
920
921%%
922
923warning(Fmt, Args) ->
924    case application:get_env(kernel,inet_warnings) of
925	{ok,on} ->
926	    error_logger:info_msg("inet_parse:" ++ Fmt, Args);
927	_ ->
928	    ok
929    end.
930
931error(Fmt, Args) ->
932    error_logger:info_msg("inet_parse:" ++ Fmt, Args).
933
934