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

« back to all changes in this revision

Viewing changes to lib/inets/src/http_client/http_cookie.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
 
%%
2
 
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2004-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
 
%% Description: Cookie handling according to RFC 2109
20
 
 
21
 
-module(http_cookie).
22
 
 
23
 
-include("httpc_internal.hrl").
24
 
 
25
 
-export([header/4, cookies/3, open_cookie_db/1, close_cookie_db/1, insert/2]). 
26
 
 
27
 
%%%=========================================================================
28
 
%%%  API
29
 
%%%=========================================================================
30
 
header(Scheme, {Host, _}, Path, CookieDb) ->
31
 
    case lookup_cookies(Host, Path, CookieDb) of
32
 
        [] ->
33
 
            {"cookie", ""};
34
 
        Cookies ->
35
 
            {"cookie", cookies_to_string(Scheme, Cookies)}
36
 
    end.
37
 
 
38
 
cookies(Headers, RequestPath, RequestHost) ->
39
 
    Cookies = parse_set_cookies(Headers, {RequestPath, RequestHost}),
40
 
    accept_cookies(Cookies, RequestPath, RequestHost).
41
 
        
42
 
open_cookie_db({{_, only_session_cookies}, SessionDbName}) ->
43
 
    EtsDb = ets:new(SessionDbName, [protected, bag,
44
 
                                    {keypos, #http_cookie.domain}]),
45
 
    {undefined, EtsDb};
46
 
 
47
 
open_cookie_db({{DbName, Dbdir}, SessionDbName}) ->
48
 
    File = filename:join(Dbdir, atom_to_list(DbName)),
49
 
    {ok, DetsDb} = dets:open_file(DbName, [{keypos, #http_cookie.domain},
50
 
                                           {type, bag},
51
 
                                           {file, File},
52
 
                                           {ram_file, true}]),
53
 
    EtsDb = ets:new(SessionDbName, [protected, bag,
54
 
                                    {keypos, #http_cookie.domain}]),
55
 
    {DetsDb, EtsDb}.
56
 
 
57
 
close_cookie_db({undefined, EtsDb}) ->
58
 
    ets:delete(EtsDb);
59
 
 
60
 
close_cookie_db({DetsDb, EtsDb}) ->
61
 
    dets:close(DetsDb),
62
 
    ets:delete(EtsDb).
63
 
 
64
 
%% If no persistent cookie database is defined we
65
 
%% treat all cookies as if they where session cookies. 
66
 
insert(Cookie = #http_cookie{max_age = Int}, 
67
 
       Dbs = {undefined, _}) when is_integer(Int) ->
68
 
    insert(Cookie#http_cookie{max_age = session}, Dbs);
69
 
 
70
 
insert(Cookie = #http_cookie{domain = Key, name = Name, 
71
 
                    path = Path, max_age = session},
72
 
       Db = {_, CookieDb}) ->
73
 
    case ets:match_object(CookieDb, #http_cookie{domain = Key,
74
 
                                                 name = Name, 
75
 
                                                 path = Path,
76
 
                                                 _ = '_'}) of
77
 
        [] ->
78
 
            ets:insert(CookieDb, Cookie);
79
 
        [NewCookie] ->
80
 
            delete(NewCookie, Db),
81
 
            ets:insert(CookieDb, Cookie)
82
 
    end,
83
 
    ok;
84
 
insert(#http_cookie{domain = Key, name = Name, 
85
 
                    path = Path, max_age = 0},
86
 
       Db = {CookieDb, _}) ->
87
 
    case dets:match_object(CookieDb, #http_cookie{domain = Key,
88
 
                                                  name = Name, 
89
 
                                                  path = Path,
90
 
                                                  _ = '_'}) of
91
 
        [] ->
92
 
            ok;
93
 
        [NewCookie] ->
94
 
            delete(NewCookie, Db)
95
 
    end,
96
 
    ok;
97
 
insert(Cookie = #http_cookie{domain = Key, name = Name, path = Path},
98
 
       Db = {CookieDb, _}) ->
99
 
    case dets:match_object(CookieDb, #http_cookie{domain = Key,
100
 
                                                  name = Name, 
101
 
                                                  path = Path,
102
 
                                                  _ = '_'}) of
103
 
        [] ->
104
 
            dets:insert(CookieDb, Cookie);
105
 
        [NewCookie] ->
106
 
            delete(NewCookie, Db),
107
 
            dets:insert(CookieDb, Cookie)
108
 
    end,
109
 
    ok.
110
 
 
111
 
%%%========================================================================
112
 
%%% Internal functions
113
 
%%%========================================================================
114
 
lookup_cookies(Key, {undefined, Ets}) ->
115
 
    ets:match_object(Ets, #http_cookie{domain = Key,
116
 
                                       _ = '_'});
117
 
lookup_cookies(Key, {Dets,Ets}) ->
118
 
    SessionCookies = ets:match_object(Ets, #http_cookie{domain = Key,
119
 
                                                        _ = '_'}),
120
 
    Cookies = dets:match_object(Dets, #http_cookie{domain = Key,
121
 
                                                   _ = '_'}),
122
 
    Cookies ++ SessionCookies.
123
 
 
124
 
delete(Cookie = #http_cookie{max_age = session}, {_, CookieDb}) ->
125
 
    ets:delete_object(CookieDb, Cookie);
126
 
delete(Cookie, {CookieDb, _}) ->
127
 
    dets:delete_object(CookieDb, Cookie).
128
 
 
129
 
lookup_cookies(Host, Path, Db) ->
130
 
    Cookies = 
131
 
        case http_util:is_hostname(Host) of 
132
 
            true ->  
133
 
                HostCookies = lookup_cookies(Host, Db),
134
 
                [_| DomainParts] = string:tokens(Host, "."),
135
 
                lookup_domain_cookies(DomainParts, Db, HostCookies);
136
 
            false -> % IP-adress
137
 
                lookup_cookies(Host, Db)
138
 
        end,
139
 
    ValidCookies = valid_cookies(Cookies, [], Db),
140
 
    lists:filter(fun(Cookie) -> 
141
 
                         lists:prefix(Cookie#http_cookie.path, Path) 
142
 
                 end, ValidCookies).
143
 
 
144
 
%% For instance if Host=localhost 
145
 
lookup_domain_cookies([], _, AccCookies) ->
146
 
    lists:flatten(AccCookies);
147
 
%% Top domains can not have cookies
148
 
lookup_domain_cookies([_], _, AccCookies) ->
149
 
    lists:flatten(AccCookies);
150
 
lookup_domain_cookies([Next | DomainParts], CookieDb, AccCookies) ->    
151
 
    Domain = merge_domain_parts(DomainParts, [Next ++ "."]),
152
 
    lookup_domain_cookies(DomainParts, CookieDb,
153
 
                          [lookup_cookies(Domain, CookieDb) 
154
 
                           | AccCookies]).
155
 
 
156
 
merge_domain_parts([Part], Merged) ->
157
 
    lists:flatten(["." | lists:reverse([Part | Merged])]);
158
 
merge_domain_parts([Part| Rest], Merged) ->
159
 
    merge_domain_parts(Rest, [".", Part | Merged]).
160
 
 
161
 
cookies_to_string(Scheme, Cookies = [Cookie | _]) ->
162
 
    Version = "$Version=" ++ Cookie#http_cookie.version ++ "; ", 
163
 
    cookies_to_string(Scheme, path_sort(Cookies), [Version]).
164
 
 
165
 
cookies_to_string(_, [], CookieStrs) ->
166
 
    case length(CookieStrs) of
167
 
        1 ->
168
 
            "";
169
 
        _ ->
170
 
            lists:flatten(lists:reverse(CookieStrs))
171
 
    end;
172
 
 
173
 
cookies_to_string(https, [Cookie = #http_cookie{secure = true}| Cookies], 
174
 
                  CookieStrs) ->
175
 
    Str = case Cookies of
176
 
              [] ->
177
 
                  cookie_to_string(Cookie);
178
 
              _ ->
179
 
                  cookie_to_string(Cookie) ++ "; "
180
 
          end,
181
 
    cookies_to_string(https, Cookies, [Str | CookieStrs]);
182
 
 
183
 
cookies_to_string(Scheme, [#http_cookie{secure = true}| Cookies],  
184
 
                  CookieStrs) ->
185
 
    cookies_to_string(Scheme, Cookies, CookieStrs);
186
 
 
187
 
cookies_to_string(Scheme, [Cookie | Cookies], CookieStrs) ->
188
 
    Str = case Cookies of
189
 
              [] ->
190
 
                  cookie_to_string(Cookie);
191
 
              _ ->
192
 
                  cookie_to_string(Cookie) ++ "; "
193
 
          end,
194
 
    cookies_to_string(Scheme, Cookies, [Str | CookieStrs]).
195
 
 
196
 
cookie_to_string(Cookie = #http_cookie{name = Name, value = Value}) ->
197
 
    Str = Name ++ "=" ++ Value,
198
 
    add_domain(add_path(Str, Cookie), Cookie).
199
 
    
200
 
add_path(Str, #http_cookie{path_default = true}) ->
201
 
    Str;
202
 
add_path(Str, #http_cookie{path = Path}) ->
203
 
    Str ++ "; $Path=" ++  Path.
204
 
 
205
 
add_domain(Str, #http_cookie{domain_default = true}) ->
206
 
    Str;
207
 
add_domain(Str, #http_cookie{domain = Domain}) ->
208
 
    Str ++ "; $Domain=" ++  Domain.
209
 
 
210
 
parse_set_cookies(OtherHeaders, DefaultPathDomain) ->
211
 
    SetCookieHeaders = lists:foldl(fun({"set-cookie", Value}, Acc) ->  
212
 
                                           [string:tokens(Value, ",")| Acc];
213
 
                                      (_, Acc) ->
214
 
                                           Acc
215
 
                                   end, [], OtherHeaders),
216
 
    
217
 
    lists:flatten(lists:map(fun(CookieHeader) ->
218
 
                                    NewHeader = 
219
 
                                        fix_netscape_cookie(CookieHeader, 
220
 
                                                            []),
221
 
                                    parse_set_cookie(NewHeader, [], 
222
 
                                                     DefaultPathDomain) end,
223
 
                            SetCookieHeaders)).
224
 
 
225
 
parse_set_cookie([], AccCookies, _) ->    
226
 
    AccCookies;
227
 
parse_set_cookie([CookieHeader | CookieHeaders], AccCookies, 
228
 
                 Defaults = {DefaultPath, DefaultDomain}) -> 
229
 
    [CookieStr | Attributes] = case string:tokens(CookieHeader, ";") of
230
 
                                   [CStr] ->
231
 
                                       [CStr, ""];
232
 
                                   [CStr | Attr] ->
233
 
                                       [CStr, Attr]
234
 
                               end,
235
 
    Pos = string:chr(CookieStr, $=),
236
 
    Name = string:substr(CookieStr, 1, Pos - 1),
237
 
    Value = string:substr(CookieStr, Pos + 1),
238
 
    Cookie = #http_cookie{name = string:strip(Name), 
239
 
                          value = string:strip(Value)},
240
 
    NewAttributes = parse_set_cookie_attributes(Attributes),
241
 
    TmpCookie = cookie_attributes(NewAttributes, Cookie),
242
 
    %% Add runtime defult values if necessary
243
 
    NewCookie = domain_default(path_default(TmpCookie, DefaultPath), 
244
 
                               DefaultDomain),
245
 
    parse_set_cookie(CookieHeaders, [NewCookie | AccCookies], Defaults).
246
 
 
247
 
parse_set_cookie_attributes([]) ->
248
 
    [];
249
 
parse_set_cookie_attributes([Attributes]) ->
250
 
    lists:map(fun(Attr) -> 
251
 
                      [AttrName, AttrValue] = 
252
 
                          case string:tokens(Attr, "=") of
253
 
                              %% All attributes have the form
254
 
                              %% Name=Value except "secure"!
255
 
                              [Name] -> 
256
 
                                  [Name, ""];
257
 
                              [Name, Value] ->
258
 
                                  [Name, Value];
259
 
                              %% Anything not expected will be
260
 
                              %% disregarded
261
 
                              _ -> 
262
 
                                  ["Dummy",""]
263
 
                          end,
264
 
                      {http_util:to_lower(string:strip(AttrName)), 
265
 
                       string:strip(AttrValue)}
266
 
              end, Attributes).
267
 
 
268
 
cookie_attributes([], Cookie) ->
269
 
    Cookie;
270
 
cookie_attributes([{"comment", Value}| Attributes], Cookie) ->
271
 
    cookie_attributes(Attributes, 
272
 
                                Cookie#http_cookie{comment = Value});
273
 
cookie_attributes([{"domain", Value}| Attributes], Cookie) ->
274
 
    cookie_attributes(Attributes, 
275
 
                                Cookie#http_cookie{domain = Value});
276
 
cookie_attributes([{"max-age", Value}| Attributes], Cookie) ->
277
 
    ExpireTime = cookie_expires(list_to_integer(Value)),
278
 
    cookie_attributes(Attributes, 
279
 
                                Cookie#http_cookie{max_age = ExpireTime});
280
 
%% Backwards compatibility with netscape cookies
281
 
cookie_attributes([{"expires", Value}| Attributes], Cookie) ->
282
 
    Time = http_util:convert_netscapecookie_date(Value),
283
 
    ExpireTime = calendar:datetime_to_gregorian_seconds(Time),
284
 
    cookie_attributes(Attributes, 
285
 
                                Cookie#http_cookie{max_age = ExpireTime});
286
 
cookie_attributes([{"path", Value}| Attributes], Cookie) ->
287
 
    cookie_attributes(Attributes, 
288
 
                                Cookie#http_cookie{path = Value});
289
 
cookie_attributes([{"secure", _}| Attributes], Cookie) ->
290
 
    cookie_attributes(Attributes, 
291
 
                                Cookie#http_cookie{secure = true});
292
 
cookie_attributes([{"version", Value}| Attributes], Cookie) ->
293
 
    cookie_attributes(Attributes, 
294
 
                                Cookie#http_cookie{version = Value});
295
 
%% Disregard unknown attributes.
296
 
cookie_attributes([_| Attributes], Cookie) ->
297
 
    cookie_attributes(Attributes, Cookie).
298
 
   
299
 
domain_default(Cookie = #http_cookie{domain = undefined}, 
300
 
               DefaultDomain) ->
301
 
    Cookie#http_cookie{domain = DefaultDomain, domain_default = true};
302
 
domain_default(Cookie, _) ->
303
 
    Cookie.
304
 
 
305
 
path_default(Cookie = #http_cookie{path = undefined}, 
306
 
             DefaultPath) ->
307
 
    Cookie#http_cookie{path = skip_right_most_slash(DefaultPath),
308
 
                       path_default = true};
309
 
path_default(Cookie, _) ->
310
 
    Cookie.
311
 
 
312
 
%% Note: if the path is only / that / will be keept
313
 
skip_right_most_slash("/") ->
314
 
    "/";
315
 
skip_right_most_slash(Str) ->
316
 
    string:strip(Str, right, $/).
317
 
 
318
 
accept_cookies(Cookies, RequestPath, RequestHost) ->
319
 
    lists:filter(fun(Cookie) ->
320
 
                         accept_cookie(Cookie, RequestPath, RequestHost)
321
 
                 end, Cookies).
322
 
 
323
 
accept_cookie(Cookie, RequestPath, RequestHost) ->
324
 
    accept_path(Cookie, RequestPath) and accept_domain(Cookie, RequestHost).
325
 
 
326
 
accept_path(#http_cookie{path = Path}, RequestPath) ->
327
 
    lists:prefix(Path, RequestPath).
328
 
 
329
 
accept_domain(#http_cookie{domain = RequestHost}, RequestHost) ->
330
 
    true;
331
 
 
332
 
accept_domain(#http_cookie{domain = Domain}, RequestHost) ->
333
 
    HostCheck = case http_util:is_hostname(RequestHost) of 
334
 
                    true ->             
335
 
                        (lists:suffix(Domain, RequestHost) andalso
336
 
                         (not 
337
 
                          lists:member($., 
338
 
                                       string:substr(RequestHost, 1,
339
 
                                                     (length(RequestHost) -
340
 
                                                      length(Domain))))));
341
 
                    false -> 
342
 
                        false
343
 
                end,
344
 
    HostCheck andalso (hd(Domain) == $.) 
345
 
        andalso (length(string:tokens(Domain, ".")) > 1).
346
 
 
347
 
cookie_expires(0) ->
348
 
    0;
349
 
cookie_expires(DeltaSec) ->
350
 
    NowSec = calendar:datetime_to_gregorian_seconds({date(), time()}),
351
 
    NowSec + DeltaSec.
352
 
 
353
 
is_cookie_expired(#http_cookie{max_age = session}) ->
354
 
    false;
355
 
is_cookie_expired(#http_cookie{max_age = ExpireTime}) ->
356
 
    NowSec = calendar:datetime_to_gregorian_seconds({date(), time()}),
357
 
    ExpireTime - NowSec =< 0.
358
 
 
359
 
valid_cookies([], Valid, _) ->
360
 
    Valid;
361
 
 
362
 
valid_cookies([Cookie | Cookies], Valid, Db) ->
363
 
    case is_cookie_expired(Cookie) of
364
 
        true ->
365
 
            delete(Cookie, Db),
366
 
            valid_cookies(Cookies, Valid, Db);
367
 
        false ->
368
 
            valid_cookies(Cookies, [Cookie | Valid], Db)
369
 
    end.
370
 
    
371
 
path_sort(Cookies)->
372
 
    lists:reverse(lists:keysort(#http_cookie.path, Cookies)).
373
 
 
374
 
 
375
 
%%  Informally, the Set-Cookie response header comprises the token
376
 
%%  Set-Cookie:, followed by a comma-separated list of one or more
377
 
%%  cookies. Netscape cookies expires attribute may also have a
378
 
%% , in this case the header list will have been incorrectly split
379
 
%% in parse_set_cookies/2 this functions fixs that problem.
380
 
fix_netscape_cookie([Cookie1, Cookie2 | Rest], Acc) ->
381
 
    case inets_regexp:match(Cookie1, "expires=") of
382
 
        {_, _, _} ->
383
 
            fix_netscape_cookie(Rest, [Cookie1 ++ Cookie2 | Acc]);
384
 
        nomatch ->
385
 
            fix_netscape_cookie([Cookie2 |Rest], [Cookie1| Acc])
386
 
    end;
387
 
fix_netscape_cookie([Cookie | Rest], Acc) ->
388
 
    fix_netscape_cookie(Rest, [Cookie | Acc]);
389
 
 
390
 
fix_netscape_cookie([], Acc) ->
391
 
    Acc.