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

« back to all changes in this revision

Viewing changes to lib/inets/src/http_server/mod_browser.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id$
 
17
%%
 
18
%% ----------------------------------------------------------------------
 
19
%%
 
20
%% Browsers sends a string to the webbserver
 
21
%% to identify themsevles. They are a bit nasty
 
22
%% since the only thing that the specification really 
 
23
%% is strict about is that they shall be short
 
24
%% some axamples:
 
25
%%
 
26
%% Netscape Mozilla/4.75 [en] (X11; U; SunOS 5.8 sun4u)
 
27
%%          Mozilla/5.0 (X11; U; Linux i686; en-US; rv:1.0.1) Gecko/20020823 Netscape/7.0
 
28
%% Mozilla  Mozilla/5.0 (X11; U; Linux i686; en-US; rv:1.1) Gecko/20020827
 
29
%% Safari   Mozilla/5.0 (Macintosh; U; PPC Mac OS X; en-us) AppleWebKit/85 (KHTML, like Gecko) Safari/85
 
30
%% IE5      Mozilla/4.0 (compatible; MSIE 5.0; SP1B; SunOS 5.8 sun4u; X11)
 
31
%% Lynx     Lynx/2.8.3rel.1 libwww-FM/2.142
 
32
%%
 
33
%% ----------------------------------------------------------------------
 
34
 
 
35
-module(mod_browser).
 
36
 
 
37
-export([do/1, test/0, getBrowser/1]).
 
38
 
 
39
%% Remember that the order of the mozilla browsers are 
 
40
%% important since some browsers include others to behave 
 
41
%% as they were something else  
 
42
-define(MOZILLA_BROWSERS,[{netscape, "netscape"},
 
43
                          {opera,    "opera"}, 
 
44
                          {msie,     "msie"}, 
 
45
                          {safari,   "safari"},
 
46
                          {mozilla,  "rv:"}]). % fallback, must be last
 
47
 
 
48
 
 
49
%% If your operatingsystem is not recognized add it to this list.
 
50
-define(OPERATIVE_SYSTEMS,[{win3x,  ["win16", "windows 3", "windows 16-bit"]},
 
51
                           {win95,  ["win95", "windows 95"]},
 
52
                           {win98,  ["win98", "windows 98"]},
 
53
                           {winnt,  ["winnt", "windows nt"]},
 
54
                           {win2k,  ["nt 5"]},
 
55
                           {sunos4, ["sunos 4"]},
 
56
                           {sunos5, ["sunos 5"]},
 
57
                           {sun,    ["sunos"]},
 
58
                           {aix,    ["aix"]},
 
59
                           {linux,  ["linux"]},
 
60
                           {sco,    ["sco", "unix_sv"]},
 
61
                           {freebsd,["freebsd"]},
 
62
                           {bsd,    ["bsd"]},
 
63
                           {macosx, ["mac os x"]}]).
 
64
 
 
65
-define(LYNX,       lynx).
 
66
-define(MOZILLA,    mozilla).
 
67
-define(EMACS,      emacs).
 
68
-define(STAROFFICE, soffice).
 
69
-define(MOSAIC,     mosaic).
 
70
-define(NETSCAPE,   netscape).
 
71
-define(SAFARU,     safari).
 
72
-define(UNKOWN,     unknown).
 
73
 
 
74
-include("httpd.hrl").
 
75
 
 
76
-define(VMODULE,"BROWSER").
 
77
 
 
78
do(Info) ->
 
79
    case httpd_util:key1search(Info#mod.data,status) of
 
80
        {_StatusCode, _PhraseArgs, _Reason} ->
 
81
            {proceed,Info#mod.data};
 
82
        undefined ->
 
83
            Browser = getBrowser1(Info),
 
84
            {proceed,[{'user-agent', Browser}|Info#mod.data]}
 
85
    end.
 
86
 
 
87
getBrowser1(Info) ->
 
88
    PHead = Info#mod.parsed_header,
 
89
    case httpd_util:key1search(PHead,"user-agent") of
 
90
        undefined ->
 
91
            undefined;
 
92
        AgentString ->
 
93
            getBrowser(AgentString)
 
94
    end.
 
95
 
 
96
getBrowser(AgentString) ->
 
97
    LAgentString = httpd_util:to_lower(AgentString),
 
98
    case regexp:first_match(LAgentString,"^[^ ]*") of
 
99
        {match,Start,Length} ->
 
100
            Browser = lists:sublist(LAgentString,Start,Length),
 
101
            case browserType(Browser) of
 
102
                {mozilla,Vsn} ->
 
103
                    {getMozilla(LAgentString,
 
104
                                ?MOZILLA_BROWSERS,{?NETSCAPE,Vsn}),
 
105
                     operativeSystem(LAgentString)};
 
106
                AnyBrowser ->
 
107
                      {AnyBrowser,operativeSystem(LAgentString)}
 
108
            end;
 
109
        nomatch ->
 
110
            browserType(LAgentString)
 
111
    end.
 
112
 
 
113
browserType([$l,$y,$n,$x|Version]) ->
 
114
    {?LYNX,browserVersion(Version)};
 
115
browserType([$m,$o,$z,$i,$l,$l,$a|Version]) ->
 
116
    {?MOZILLA,browserVersion(Version)};
 
117
browserType([$e,$m,$a,$c,$s|Version]) ->
 
118
    {?EMACS,browserVersion(Version)};
 
119
browserType([$s,$t,$a,$r,$o,$f,$f,$i,$c,$e|Version]) ->
 
120
    {?STAROFFICE,browserVersion(Version)};
 
121
browserType([$m,$o,$s,$a,$i,$c|Version]) ->
 
122
    {?MOSAIC,browserVersion(Version)};
 
123
browserType(_Unknown) ->
 
124
    unknown.
 
125
 
 
126
 
 
127
browserVersion([$/|VsnString]) ->
 
128
    case catch list_to_float(VsnString) of
 
129
        Number when float(Number) ->
 
130
            Number;
 
131
        _Whatever ->
 
132
            case string:span(VsnString,"1234567890.") of
 
133
                0 ->
 
134
                    unknown;
 
135
                VLength ->
 
136
                    Vsn = string:substr(VsnString,1,VLength),
 
137
                    case string:tokens(Vsn,".") of
 
138
                        [Number] ->
 
139
                           list_to_float(Number++".0");
 
140
                        [Major,Minor|_MinorMinor] ->
 
141
                            list_to_float(Major++"."++Minor)
 
142
                    end
 
143
            end
 
144
    end;
 
145
browserVersion(VsnString) ->
 
146
    browserVersion([$/|VsnString]).
 
147
 
 
148
operativeSystem(OpString) ->
 
149
  operativeSystem(OpString, ?OPERATIVE_SYSTEMS).
 
150
 
 
151
operativeSystem(_OpString,[]) ->
 
152
    unknown;
 
153
operativeSystem(OpString,[{RetVal,RegExps}|Rest]) ->
 
154
    case controlOperativeSystem(OpString,RegExps) of
 
155
        true ->
 
156
            RetVal;
 
157
        _ ->
 
158
            operativeSystem(OpString,Rest)
 
159
    end.
 
160
 
 
161
controlOperativeSystem(_OpString,[]) ->
 
162
    false;
 
163
controlOperativeSystem(OpString,[Regexp|Regexps]) ->
 
164
    case regexp:match(OpString,Regexp) of
 
165
        {match,_,_} ->
 
166
            true;
 
167
        nomatch ->
 
168
            controlOperativeSystem(OpString,Regexps)
 
169
    end.
 
170
 
 
171
 
 
172
%% OK this is ugly but thats the only way since 
 
173
%% all browsers dont conform to the name/vsn standard
 
174
%% First we check if it is one of the browsers that 
 
175
%% are not the default mozillaborwser against the regexp 
 
176
%% for the different browsers. if no match, it is a mozilla 
 
177
%% browser i.e opera, netscape, ie or safari
 
178
 
 
179
getMozilla(_AgentString,[],Default) ->
 
180
    Default;
 
181
getMozilla(AgentString,[{Agent,AgentRegExp}|Rest],Default) ->
 
182
    case regexp:match(AgentString,AgentRegExp) of
 
183
        {match,_,_} ->
 
184
            {Agent,getMozVersion(AgentString,AgentRegExp)};
 
185
        nomatch ->
 
186
            getMozilla(AgentString,Rest,Default)
 
187
    end.
 
188
 
 
189
getMozVersion(AgentString, AgentRegExp) ->
 
190
    case regexp:match(AgentString,AgentRegExp++"[0-9\.\ \/]*") of
 
191
        {match,Start,Length} when length(AgentRegExp) < Length ->
 
192
            %% Ok we got the number split it out
 
193
            RealStart  = Start+length(AgentRegExp),
 
194
            RealLength = Length-length(AgentRegExp),
 
195
            VsnString  = string:substr(AgentString,RealStart,RealLength),
 
196
            %% case string:strip(VsnString,both,$\ ) of
 
197
            case strip(VsnString) of
 
198
                [] ->
 
199
                    unknown;
 
200
                [Y1,Y2,Y3,Y4,M1,M2,D1,D2] = DateVsn when
 
201
                      Y1 =< $9, Y1 >= $0,
 
202
                      Y2 =< $9, Y2 >= $0,
 
203
                      Y3 =< $9, Y3 >= $0,
 
204
                      Y4 =< $9, Y4 >= $0,
 
205
                      M1 =< $9, M1 >= $0,
 
206
                      M2 =< $9, M2 >= $0,
 
207
                      D1 =< $9, D1 >= $0,
 
208
                      D2 =< $9, D2 >= $0 ->
 
209
                    list_to_integer(DateVsn);
 
210
                Vsn ->
 
211
                    case string:tokens(Vsn,".") of
 
212
                        [Number]->
 
213
                            list_to_float(Number++".0");
 
214
                        [Major,Minor|Rev] ->
 
215
                            V = lists:flatten([Major,".",Minor,Rev]),
 
216
                            list_to_float(V)
 
217
                    end
 
218
            end;
 
219
        nomatch ->
 
220
            unknown
 
221
    end.
 
222
 
 
223
strip(VsnString) ->
 
224
    strip2(strip1(VsnString)).
 
225
 
 
226
strip1(VsnString) ->    
 
227
    string:strip(VsnString,both,$\ ).
 
228
 
 
229
strip2(VsnString) ->    
 
230
    string:strip(VsnString,both,$/ ).
 
231
 
 
232
test()->
 
233
    test("Mozilla/4.75 [en] (X11; U; SunOS 5.8 sun4u)"),
 
234
    test("Mozilla/5.0 (X11; U; Linux i686; en-US; rv:1.0.1) Gecko/20020823 Netscape/7.0"),
 
235
    test("Mozilla/5.0 (X11; U; Linux i686; en-US; rv:1.1) Gecko/20020827"),
 
236
    test("Mozilla/5.0 (Macintosh; U; PPC Mac OS X Mach-O; en-US; rv:1.4) Gecko/20020827"),
 
237
    test("Mozilla/5.0 (Macintosh; U; PPC Mac OS X; en-us) AppleWebKit/85 (KHTML, like Gecko) Safari/85"),
 
238
    test("Mozilla/4.0 (compatible; MSIE 5.0; SP1B; SunOS 5.8 sun4u; X11)"),
 
239
    test("Lynx/2.8.3rel.1 libwww-FM/2.142"),
 
240
    ok.
 
241
 
 
242
test(Str) ->
 
243
    Browser = getBrowser(Str),
 
244
    io:format("~n--------------------------------------------------------~n"),
 
245
    io:format("~p",[Browser]),
 
246
    io:format("~n--------------------------------------------------------~n").
 
247