~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/kernel/src/inet.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1997-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(inet).
45
45
%% resolve
46
46
-export([gethostbyname/1, gethostbyname/2, gethostbyname/3, 
47
47
         gethostbyname_tm/3]).
 
48
-export([gethostbyname_string/2, gethostbyname_self/2]).
48
49
-export([gethostbyaddr/1, gethostbyaddr/2, 
49
50
         gethostbyaddr_tm/2]).
50
51
 
411
412
    Res.
412
413
 
413
414
gethostbyname_tm(Name,Family,Timer) ->
414
 
    gethostbyname_tm(Name,Family,Timer,inet_db:res_option(lookup)).
 
415
    Opts0 = inet_db:res_option(lookup),
 
416
    Opts =
 
417
        case (lists:member(native, Opts0) orelse
 
418
              lists:member(string, Opts0) orelse
 
419
              lists:member(nostring, Opts0)) of
 
420
            true ->
 
421
                Opts0;
 
422
            false ->
 
423
                [string|Opts0]
 
424
        end,
 
425
    gethostbyname_tm(Name, Family, Timer, Opts).
415
426
 
416
427
 
417
428
-spec gethostbyaddr(Address :: string() | ip_address()) ->
850
861
%%
851
862
%% gethostbyname with option search
852
863
%%
853
 
gethostbyname_tm(Name, Type, Timer, [dns | Opts]) ->
854
 
    Res = inet_res:gethostbyname_tm(Name, Type, Timer),
855
 
    case Res of
856
 
        {ok,_} -> Res;
857
 
        {error,timeout} -> Res;
858
 
        {error,formerr} -> {error,einval};
859
 
        {error,_} -> gethostbyname_tm(Name,Type,Timer,Opts)
860
 
    end;
861
 
gethostbyname_tm(Name, Type, Timer, [file | Opts]) ->
862
 
    case inet_hosts:gethostbyname(Name, Type) of
863
 
        {error,formerr} -> {error,einval};
864
 
        {error,_} -> gethostbyname_tm(Name,Type,Timer,Opts);
865
 
        Result -> Result
866
 
    end;
867
 
gethostbyname_tm(Name, Type, Timer, [yp | Opts]) ->
868
 
    gethostbyname_tm_native(Name, Type, Timer, Opts);
869
 
gethostbyname_tm(Name, Type, Timer, [nis | Opts]) ->
870
 
    gethostbyname_tm_native(Name, Type, Timer, Opts);
871
 
gethostbyname_tm(Name, Type, Timer, [nisplus | Opts]) ->
872
 
    gethostbyname_tm_native(Name, Type, Timer, Opts);
873
 
gethostbyname_tm(Name, Type, Timer, [wins | Opts]) ->
874
 
    gethostbyname_tm_native(Name, Type, Timer, Opts);
875
 
gethostbyname_tm(Name, Type, Timer, [native | Opts]) ->
876
 
    gethostbyname_tm_native(Name, Type, Timer, Opts);
877
 
gethostbyname_tm(_, _, _, [no_default|_]) ->
878
 
    %% If the native resolver has failed, we should not bother
879
 
    %% to try to be smarter and parse the IP address here.
880
 
    {error,nxdomain};
881
 
gethostbyname_tm(Name, Type, Timer, [_ | Opts]) ->
 
864
gethostbyname_tm(Name, Type, Timer, [string|_]=Opts) ->
 
865
    Result = gethostbyname_string(Name, Type),
 
866
    gethostbyname_tm(Name, Type, Timer, Opts, Result);
 
867
gethostbyname_tm(Name, Type, Timer, [dns|_]=Opts) ->
 
868
    Result = inet_res:gethostbyname_tm(Name, Type, Timer),
 
869
    gethostbyname_tm(Name, Type, Timer, Opts, Result);
 
870
gethostbyname_tm(Name, Type, Timer, [file|_]=Opts) ->
 
871
    Result = inet_hosts:gethostbyname(Name, Type),
 
872
    gethostbyname_tm(Name, Type, Timer, Opts, Result);
 
873
gethostbyname_tm(Name, Type, Timer, [yp|_]=Opts) ->
 
874
    gethostbyname_tm_native(Name, Type, Timer, Opts);
 
875
gethostbyname_tm(Name, Type, Timer, [nis|_]=Opts) ->
 
876
    gethostbyname_tm_native(Name, Type, Timer, Opts);
 
877
gethostbyname_tm(Name, Type, Timer, [nisplus|_]=Opts) ->
 
878
    gethostbyname_tm_native(Name, Type, Timer, Opts);
 
879
gethostbyname_tm(Name, Type, Timer, [wins|_]=Opts) ->
 
880
    gethostbyname_tm_native(Name, Type, Timer, Opts);
 
881
gethostbyname_tm(Name, Type, Timer, [native|_]=Opts) ->
 
882
    gethostbyname_tm_native(Name, Type, Timer, Opts);
 
883
gethostbyname_tm(Name, Type, Timer, [_|_]=Opts) ->
882
884
    gethostbyname_tm(Name, Type, Timer, Opts);
883
 
%% Last resort - parse the hostname as address
884
 
gethostbyname_tm(Name, inet, _Timer, []) ->
885
 
    case inet_parse:ipv4_address(Name) of
886
 
        {ok,IP4} ->
887
 
            {ok,make_hostent(Name, [IP4], [], inet)};
888
 
        _ ->
889
 
            gethostbyname_self(Name)
890
 
    end;
891
 
gethostbyname_tm(Name, inet6, _Timer, []) ->
892
 
    case inet_parse:ipv6_address(Name) of
893
 
        {ok,IP6} ->
894
 
            {ok,make_hostent(Name, [IP6], [], inet6)};
895
 
        _ ->
896
 
            %% Even if Name is a valid IPv4 address, we can't
897
 
            %% assume it's correct to return it on a IPv6
898
 
            %% format ( {0,0,0,0,0,16#ffff,?u16(A,B),?u16(C,D)} ).
899
 
            %% This host might not support IPv6.
900
 
            gethostbyname_self(Name)
 
885
%% Make sure we always can look up our own hostname.
 
886
gethostbyname_tm(Name, Type, Timer, []) ->
 
887
    Result = gethostbyname_self(Name, Type),
 
888
    gethostbyname_tm(Name, Type, Timer, [], Result).
 
889
 
 
890
gethostbyname_tm(Name, Type, Timer, Opts, Result) ->
 
891
    case Result of
 
892
        {ok,_} ->
 
893
            Result;
 
894
        {error,formerr} ->
 
895
            {error,einval};
 
896
        {error,_} when Opts =:= [] ->
 
897
            {error,nxdomain};
 
898
        {error,_} ->
 
899
            gethostbyname_tm(Name, Type, Timer, tl(Opts))
901
900
    end.
902
901
 
903
902
gethostbyname_tm_native(Name, Type, Timer, Opts) ->
904
903
    %% Fixme: add (global) timeout to gethost_native
905
 
    case inet_gethost_native:gethostbyname(Name, Type) of
906
 
        {error,formerr} -> {error,einval};
907
 
        {error,timeout} -> {error,timeout};
908
 
        {error,_} -> gethostbyname_tm(Name, Type, Timer, Opts++[no_default]);
909
 
        Result -> Result
910
 
    end.
911
 
 
912
 
%% Make sure we always can look up our own hostname.
913
 
gethostbyname_self(Name) ->
914
 
    Type = case inet_db:res_option(inet6) of
915
 
               true -> inet6;
916
 
               false -> inet
917
 
           end,
 
904
    Result = inet_gethost_native:gethostbyname(Name, Type),
 
905
    gethostbyname_tm(Name, Type, Timer, Opts, Result).
 
906
 
 
907
 
 
908
 
 
909
gethostbyname_self(Name, Type) when is_atom(Name) ->
 
910
    gethostbyname_self(atom_to_list(Name), Type);
 
911
gethostbyname_self(Name, Type)
 
912
  when is_list(Name), Type =:= inet;
 
913
       is_list(Name), Type =:= inet6 ->
918
914
    case inet_db:gethostname() of
919
915
        Name ->
920
 
            {ok,make_hostent(Name, [translate_ip(loopback, Type)],
921
 
                         [], Type)};
 
916
            {ok,make_hostent(Name,
 
917
                             [translate_ip(loopback, Type)],
 
918
                             [], Type)};
922
919
        Self ->
923
920
            case inet_db:res_option(domain) of
924
921
                "" -> {error,nxdomain};
931
928
                        _ -> {error,nxdomain}
932
929
                    end
933
930
            end
934
 
    end.
 
931
    end;
 
932
gethostbyname_self(_, _) ->
 
933
    {error,formerr}.
 
934
 
 
935
gethostbyname_string(Name, Type) when is_atom(Name) ->
 
936
    gethostbyname_string(atom_to_list(Name), Type);
 
937
gethostbyname_string(Name, Type)
 
938
  when is_list(Name), Type =:= inet;
 
939
       is_list(Name), Type =:= inet6 ->
 
940
    case
 
941
        case Type of
 
942
            inet ->
 
943
                inet_parse:ipv4_address(Name);
 
944
            inet6 ->
 
945
                %% XXX should we really translate IPv4 addresses here
 
946
                %% even if we do not know if this host can do IPv6?
 
947
                inet_parse:ipv6_address(Name)
 
948
        end of
 
949
        {ok,IP} ->
 
950
            {ok,make_hostent(Name, [IP], [], Type)};
 
951
        {error,einval} ->
 
952
            {error,nxdomain}
 
953
    end;
 
954
gethostbyname_string(_, _) ->
 
955
    {error,formerr}.
935
956
 
936
957
make_hostent(Name, Addrs, Aliases, Type) ->
937
958
    #hostent{h_name = Name,