~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

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_dns).
129
129
           RA:1,PR:1,_:2,Rcode:4,
130
130
           QdCount:16,AnCount:16,NsCount:16,ArCount:16,
131
131
           QdBuf/binary>>=Buffer) ->
132
 
    {AnBuf,QdList} = decode_query_section(QdBuf,QdCount,Buffer),
133
 
    {NsBuf,AnList} = decode_rr_section(AnBuf,AnCount,Buffer),
134
 
    {ArBuf,NsList} = decode_rr_section(NsBuf,NsCount,Buffer),
135
 
    {Rest,ArList} = decode_rr_section(ArBuf,ArCount,Buffer),
 
132
    {AnBuf,QdList,QdTC} = decode_query_section(QdBuf,QdCount,Buffer),
 
133
    {NsBuf,AnList,AnTC} = decode_rr_section(AnBuf,AnCount,Buffer),
 
134
    {ArBuf,NsList,NsTC} = decode_rr_section(NsBuf,NsCount,Buffer),
 
135
    {Rest,ArList,ArTC} = decode_rr_section(ArBuf,ArCount,Buffer),
136
136
        case Rest of
137
137
            <<>> ->
 
138
                HdrTC = decode_boolean(TC),
138
139
                DnsHdr =
139
140
                    #dns_header{id=Id,
140
141
                                qr=decode_boolean(QR),
141
142
                                opcode=decode_opcode(Opcode),
142
143
                                aa=decode_boolean(AA),
143
 
                                tc=decode_boolean(TC),
 
144
                                tc=HdrTC,
144
145
                                rd=decode_boolean(RD),
145
146
                                ra=decode_boolean(RA),
146
147
                                pr=decode_boolean(PR),
147
148
                                rcode=Rcode},
148
 
                #dns_rec{header=DnsHdr,
149
 
                         qdlist=QdList,
150
 
                         anlist=AnList,
151
 
                         nslist=NsList,
152
 
                         arlist=ArList};
 
149
                case QdTC or AnTC or NsTC or ArTC of
 
150
                    true when not HdrTC ->
 
151
                        throw(?DECODE_ERROR);
 
152
                    _ ->
 
153
                        #dns_rec{header=DnsHdr,
 
154
                                 qdlist=QdList,
 
155
                                 anlist=AnList,
 
156
                                 nslist=NsList,
 
157
                                 arlist=ArList}
 
158
                end;
153
159
            _ ->
154
160
                %% Garbage data after DNS message
155
161
                throw(?DECODE_ERROR)
161
167
decode_query_section(Bin, N, Buffer) ->
162
168
    decode_query_section(Bin, N, Buffer, []).
163
169
 
 
170
decode_query_section(<<>>=Rest, N, _Buffer, Qs) ->
 
171
    {Rest,reverse(Qs),N =/= 0};
164
172
decode_query_section(Rest, 0, _Buffer, Qs) ->
165
 
    {Rest,reverse(Qs)};
 
173
    {Rest,reverse(Qs),false};
166
174
decode_query_section(Bin, N, Buffer, Qs) ->
167
175
    case decode_name(Bin, Buffer) of
168
176
        {<<Type:16,Class:16,Rest/binary>>,Name} ->
179
187
decode_rr_section(Bin, N, Buffer) ->
180
188
    decode_rr_section(Bin, N, Buffer, []).
181
189
 
 
190
decode_rr_section(<<>>=Rest, N, _Buffer, RRs) ->
 
191
    {Rest,reverse(RRs),N =/= 0};
182
192
decode_rr_section(Rest, 0, _Buffer, RRs) ->
183
 
    {Rest,reverse(RRs)};
 
193
    {Rest,reverse(RRs),false};
184
194
decode_rr_section(Bin, N, Buffer, RRs) ->
185
195
    case decode_name(Bin, Buffer) of
186
196
        {<<T:16/unsigned,C:16/unsigned,TTL:4/binary,