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

« back to all changes in this revision

Viewing changes to lib/inets/src/http_client/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-2009. 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]).
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
 
%%%========================================================================
42
 
%%% Internal functions
43
 
%%%========================================================================
44
 
parse_scheme(AbsURI) ->
45
 
    case split_uri(AbsURI, ":", {error, no_scheme}, 1, 1) of
46
 
        {error, no_scheme} ->
47
 
            {error, no_scheme};
48
 
        {StrScheme, Rest} ->
49
 
            case list_to_atom(http_util:to_lower(StrScheme)) of
50
 
                Scheme when Scheme == http; Scheme == https ->
51
 
                    {Scheme, Rest};
52
 
                Scheme ->
53
 
                    {error, {not_supported_scheme, Scheme}}
54
 
            end
55
 
    end.
56
 
 
57
 
parse_uri_rest(Scheme, "//" ++ URIPart) ->
58
 
 
59
 
    {Authority, PathQuery} = 
60
 
        case split_uri(URIPart, "/", URIPart, 1, 0) of
61
 
            Split = {_, _} ->
62
 
                Split;
63
 
            URIPart ->
64
 
                case split_uri(URIPart, "\\?", URIPart, 1, 0) of
65
 
                    Split = {_, _} ->
66
 
                        Split;
67
 
                    URIPart ->
68
 
                        {URIPart,""}
69
 
                end
70
 
        end,
71
 
    
72
 
    {UserInfo, HostPort} = split_uri(Authority, "@", {"", Authority}, 1, 1),
73
 
    {Host, Port} = parse_host_port(Scheme, HostPort),
74
 
    {Path, Query} = parse_path_query(PathQuery),
75
 
    {UserInfo, Host, Port, Path, Query}.
76
 
 
77
 
 
78
 
parse_path_query(PathQuery) ->
79
 
    {Path, Query} =  split_uri(PathQuery, "\\?", {PathQuery, ""}, 1, 0),
80
 
    {path(Path), Query}.
81
 
    
82
 
 
83
 
parse_host_port(Scheme,"[" ++ HostPort) -> %ipv6
84
 
    DefaultPort = default_port(Scheme),
85
 
    {Host, ColonPort} = split_uri(HostPort, "\\]", {HostPort, ""}, 1, 1),
86
 
    {_, Port} = split_uri(ColonPort, ":", {"", DefaultPort}, 0, 1),
87
 
    {Host, int_port(Port)};
88
 
 
89
 
parse_host_port(Scheme, HostPort) ->
90
 
    DefaultPort = default_port(Scheme),
91
 
    {Host, Port} = split_uri(HostPort, ":", {HostPort, DefaultPort}, 1, 1),
92
 
    {Host, int_port(Port)}.
93
 
    
94
 
split_uri(UriPart, SplitChar, NoMatchResult, SkipLeft, SkipRight) ->
95
 
    case inets_regexp:first_match(UriPart, SplitChar) of
96
 
        {match, Match, _} ->
97
 
            {string:substr(UriPart, 1, Match - SkipLeft),
98
 
             string:substr(UriPart, Match + SkipRight, length(UriPart))}; 
99
 
        nomatch ->
100
 
            NoMatchResult
101
 
    end.
102
 
 
103
 
default_port(http) ->
104
 
    80;
105
 
default_port(https) ->
106
 
    443.
107
 
 
108
 
int_port(Port) when is_integer(Port) ->
109
 
    Port;
110
 
int_port(Port) when is_list(Port) ->
111
 
    list_to_integer(Port).
112
 
 
113
 
path("") ->
114
 
    "/";
115
 
path(Path) ->
116
 
    Path.