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

« back to all changes in this revision

Viewing changes to lib/inets/src/http_lib/http_uri.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
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2006-2010. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%%
 
20
 
 
21
-module(http_uri).
 
22
 
 
23
-export([parse/1, encode/1, decode/1]).
 
24
 
 
25
%%%=========================================================================
 
26
%%%  API
 
27
%%%=========================================================================
 
28
parse(AbsURI) ->
 
29
    case parse_scheme(AbsURI) of
 
30
        {error, Reason} ->
 
31
            {error, Reason};
 
32
        {Scheme, Rest} ->
 
33
            case (catch parse_uri_rest(Scheme, Rest)) of
 
34
                {UserInfo, Host, Port, Path, Query} ->
 
35
                    {Scheme, UserInfo, Host, Port, Path, Query};
 
36
                _  ->
 
37
                    {error, {malformed_url, AbsURI}}
 
38
            end
 
39
    end.
 
40
 
 
41
encode(URI) ->
 
42
    Reserved = sets:from_list([$;, $:, $@, $&, $=, $+, $,, $/, $?,
 
43
                               $#, $[, $], $<, $>, $\", ${, $}, $|,
 
44
                               $\\, $', $^, $%, $ ]),
 
45
    lists:append(lists:map(fun(Char) ->
 
46
                                   uri_encode(Char, Reserved)
 
47
                           end, URI)).
 
48
 
 
49
decode([$%,Hex1,Hex2|Rest]) ->
 
50
    [hex2dec(Hex1)*16+hex2dec(Hex2)|decode(Rest)];
 
51
decode([First|Rest]) ->
 
52
    [First|decode(Rest)];
 
53
decode([]) ->
 
54
    [].
 
55
 
 
56
%%%========================================================================
 
57
%%% Internal functions
 
58
%%%========================================================================
 
59
parse_scheme(AbsURI) ->
 
60
    case split_uri(AbsURI, ":", {error, no_scheme}, 1, 1) of
 
61
        {error, no_scheme} ->
 
62
            {error, no_scheme};
 
63
        {StrScheme, Rest} ->
 
64
            case list_to_atom(http_util:to_lower(StrScheme)) of
 
65
                Scheme when Scheme == http; Scheme == https ->
 
66
                    {Scheme, Rest};
 
67
                Scheme ->
 
68
                    {error, {not_supported_scheme, Scheme}}
 
69
            end
 
70
    end.
 
71
 
 
72
parse_uri_rest(Scheme, "//" ++ URIPart) ->
 
73
 
 
74
    {Authority, PathQuery} =
 
75
        case split_uri(URIPart, "/", URIPart, 1, 0) of
 
76
            Split = {_, _} ->
 
77
                Split;
 
78
            URIPart ->
 
79
                case split_uri(URIPart, "\\?", URIPart, 1, 0) of
 
80
                    Split = {_, _} ->
 
81
                        Split;
 
82
                    URIPart ->
 
83
                        {URIPart,""}
 
84
                end
 
85
        end,
 
86
 
 
87
    {UserInfo, HostPort} = split_uri(Authority, "@", {"", Authority}, 1, 1),
 
88
    {Host, Port} = parse_host_port(Scheme, HostPort),
 
89
    {Path, Query} = parse_path_query(PathQuery),
 
90
    {UserInfo, Host, Port, Path, Query}.
 
91
 
 
92
 
 
93
parse_path_query(PathQuery) ->
 
94
    {Path, Query} =  split_uri(PathQuery, "\\?", {PathQuery, ""}, 1, 0),
 
95
    {path(Path), Query}.
 
96
 
 
97
parse_host_port(Scheme,"[" ++ HostPort) -> %ipv6
 
98
    DefaultPort = default_port(Scheme),
 
99
    {Host, ColonPort} = split_uri(HostPort, "\\]", {HostPort, ""}, 1, 1),
 
100
    {_, Port} = split_uri(ColonPort, ":", {"", DefaultPort}, 0, 1),
 
101
    {Host, int_port(Port)};
 
102
 
 
103
parse_host_port(Scheme, HostPort) ->
 
104
    DefaultPort = default_port(Scheme),
 
105
    {Host, Port} = split_uri(HostPort, ":", {HostPort, DefaultPort}, 1, 1),
 
106
    {Host, int_port(Port)}.
 
107
 
 
108
split_uri(UriPart, SplitChar, NoMatchResult, SkipLeft, SkipRight) ->
 
109
    case inets_regexp:first_match(UriPart, SplitChar) of
 
110
        {match, Match, _} ->
 
111
            {string:substr(UriPart, 1, Match - SkipLeft),
 
112
             string:substr(UriPart, Match + SkipRight, length(UriPart))};
 
113
        nomatch ->
 
114
            NoMatchResult
 
115
    end.
 
116
 
 
117
default_port(http) ->
 
118
    80;
 
119
default_port(https) ->
 
120
    443.
 
121
 
 
122
int_port(Port) when is_integer(Port) ->
 
123
    Port;
 
124
int_port(Port) when is_list(Port) ->
 
125
    list_to_integer(Port).
 
126
 
 
127
path("") ->
 
128
    "/";
 
129
path(Path) ->
 
130
    Path.
 
131
 
 
132
uri_encode(Char, Reserved) ->
 
133
    case sets:is_element(Char, Reserved) of
 
134
        true ->
 
135
            [ $% | http_util:integer_to_hexlist(Char)];
 
136
        false ->
 
137
            [Char]
 
138
    end.
 
139
 
 
140
hex2dec(X) when (X>=$0) andalso (X=<$9) -> X-$0;
 
141
hex2dec(X) when (X>=$A) andalso (X=<$F) -> X-$A+10;
 
142
hex2dec(X) when (X>=$a) andalso (X=<$f) -> X-$a+10.