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

« back to all changes in this revision

Viewing changes to lib/inets/src/http_client/httpc_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-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
%% Description: Cookie handling according to RFC 2109
 
20
 
 
21
-module(httpc_cookie).
 
22
 
 
23
-include("httpc_internal.hrl").
 
24
 
 
25
-export([open_db/3, close_db/1, insert/2, header/4, cookies/3]). 
 
26
-export([reset_db/1, which_cookies/1]). 
 
27
 
 
28
-record(cookie_db, {db, session_db}).
 
29
 
 
30
 
 
31
%%%=========================================================================
 
32
%%%  API
 
33
%%%=========================================================================
 
34
 
 
35
%%--------------------------------------------------------------------
 
36
%% Func: open_db(DbName, DbDir, SessionDbName) -> #cookie_db{}
 
37
%% Purpose: Create the cookie db
 
38
%%--------------------------------------------------------------------
 
39
 
 
40
open_db(_, only_session_cookies, SessionDbName) ->
 
41
    ?hcrt("open (session cookies only) db", 
 
42
          [{session_db_name, SessionDbName}]),
 
43
    SessionDb = ets:new(SessionDbName, 
 
44
                        [protected, bag, {keypos, #http_cookie.domain}]),
 
45
    #cookie_db{session_db = SessionDb};
 
46
 
 
47
open_db(Name, Dir, SessionDbName) ->
 
48
    ?hcrt("open db", 
 
49
          [{name, Name}, {dir, Dir}, {session_db_name, SessionDbName}]),
 
50
    File = filename:join(Dir, atom_to_list(Name)),
 
51
    case dets:open_file(Name, [{keypos, #http_cookie.domain},
 
52
                               {type, bag},
 
53
                               {file, File},
 
54
                               {ram_file, true}]) of
 
55
        {ok, Db} ->
 
56
            SessionDb = ets:new(SessionDbName, 
 
57
                                [protected, bag, 
 
58
                                 {keypos, #http_cookie.domain}]),
 
59
            #cookie_db{db = Db, session_db = SessionDb};
 
60
        {error, Reason} ->
 
61
            throw({error, {failed_open_file, Name, File, Reason}})
 
62
    end.
 
63
 
 
64
 
 
65
%%--------------------------------------------------------------------
 
66
%% Func: reset_db(CookieDb) -> void()
 
67
%% Purpose: Reset (empty) the cookie database
 
68
%% 
 
69
%%--------------------------------------------------------------------
 
70
 
 
71
reset_db(#cookie_db{db = undefined, session_db = SessionDb}) ->
 
72
    ets:delete_all_objects(SessionDb),
 
73
    ok;
 
74
reset_db(#cookie_db{db = Db, session_db = SessionDb}) ->
 
75
    dets:delete_all_objects(Db),
 
76
    ets:delete_all_objects(SessionDb),
 
77
    ok.
 
78
 
 
79
 
 
80
%%--------------------------------------------------------------------
 
81
%% Func: close_db(CookieDb) -> ok
 
82
%% Purpose: Close the cookie db
 
83
%%--------------------------------------------------------------------
 
84
 
 
85
close_db(#cookie_db{db = Db, session_db = SessionDb}) ->
 
86
    ?hcrt("close db", []),
 
87
    maybe_dets_close(Db), 
 
88
    ets:delete(SessionDb),
 
89
    ok.
 
90
 
 
91
maybe_dets_close(undefined) ->
 
92
    ok;
 
93
maybe_dets_close(Db) ->
 
94
    dets:close(Db).
 
95
    
 
96
 
 
97
%%--------------------------------------------------------------------
 
98
%% Func: insert(CookieDb) -> ok
 
99
%% Purpose: Close the cookie db
 
100
%%--------------------------------------------------------------------
 
101
 
 
102
%% If no persistent cookie database is defined we
 
103
%% treat all cookies as if they where session cookies. 
 
104
insert(#cookie_db{db = undefined} = CookieDb,
 
105
       #http_cookie{max_age = Int} = Cookie) when is_integer(Int) ->
 
106
    insert(CookieDb, Cookie#http_cookie{max_age = session});
 
107
 
 
108
insert(#cookie_db{session_db = SessionDb} = CookieDb, 
 
109
       #http_cookie{domain  = Key, 
 
110
                    name    = Name, 
 
111
                    path    = Path, 
 
112
                    max_age = session} = Cookie) ->
 
113
    ?hcrt("insert session cookie", [{cookie, Cookie}]),
 
114
    Pattern = #http_cookie{domain = Key, name = Name, path = Path, _ = '_'}, 
 
115
    case ets:match_object(SessionDb, Pattern) of
 
116
        [] ->
 
117
            ets:insert(SessionDb, Cookie);
 
118
        [NewCookie] ->
 
119
            delete(CookieDb, NewCookie),
 
120
            ets:insert(SessionDb, Cookie)
 
121
    end,
 
122
    ok;
 
123
insert(#cookie_db{db = Db} = CookieDb,
 
124
       #http_cookie{domain  = Key, 
 
125
                    name    = Name, 
 
126
                    path    = Path, 
 
127
                    max_age = 0}) ->
 
128
    ?hcrt("insert", [{domain, Key}, {name, Name}, {path, Path}]),
 
129
    Pattern = #http_cookie{domain = Key, name = Name, path = Path, _ = '_'}, 
 
130
    case dets:match_object(Db, Pattern) of
 
131
        [] ->
 
132
            ok;
 
133
        [NewCookie] ->
 
134
            delete(CookieDb, NewCookie)
 
135
    end,
 
136
    ok;
 
137
insert(#cookie_db{db = Db} = CookieDb,
 
138
       #http_cookie{domain = Key, name = Name, path = Path} = Cookie) ->
 
139
    ?hcrt("insert", [{cookie, Cookie}]),
 
140
    Pattern = #http_cookie{domain = Key,
 
141
                           name = Name, 
 
142
                           path = Path,
 
143
                           _ = '_'}, 
 
144
    case dets:match_object(Db, Pattern) of
 
145
        [] ->
 
146
            dets:insert(Db, Cookie);
 
147
        [OldCookie] ->
 
148
            delete(CookieDb, OldCookie),
 
149
            dets:insert(Db, Cookie)
 
150
    end,
 
151
    ok.
 
152
 
 
153
 
 
154
 
 
155
%%--------------------------------------------------------------------
 
156
%% Func: header(CookieDb) -> ok
 
157
%% Purpose: Cookies
 
158
%%--------------------------------------------------------------------
 
159
 
 
160
header(CookieDb, Scheme, {Host, _}, Path) ->
 
161
    ?hcrd("header", [{scheme, Scheme}, {host, Host}, {path, Path}]),
 
162
    case lookup_cookies(CookieDb, Host, Path) of
 
163
        [] ->
 
164
            {"cookie", ""};
 
165
        Cookies ->
 
166
            {"cookie", cookies_to_string(Scheme, Cookies)}
 
167
    end.
 
168
 
 
169
 
 
170
%%--------------------------------------------------------------------
 
171
%% Func: cookies(Headers, RequestPath, RequestHost) -> [cookie()]
 
172
%% Purpose: Which cookies are stored
 
173
%%--------------------------------------------------------------------
 
174
 
 
175
cookies(Headers, RequestPath, RequestHost) ->
 
176
    ?hcrt("cookies", [{headers,      Headers}, 
 
177
                      {request_path, RequestPath}, 
 
178
                      {request_host, RequestHost}]),
 
179
    Cookies = parse_set_cookies(Headers, {RequestPath, RequestHost}),
 
180
    accept_cookies(Cookies, RequestPath, RequestHost).
 
181
        
 
182
 
 
183
%%--------------------------------------------------------------------
 
184
%% Func: which_cookies(CookieDb) -> [cookie()]
 
185
%% Purpose: For test and debug purpose, 
 
186
%%          dump the entire cookie database
 
187
%%--------------------------------------------------------------------
 
188
 
 
189
which_cookies(#cookie_db{db = undefined, session_db = SessionDb}) ->
 
190
    SessionCookies = ets:tab2list(SessionDb),
 
191
    [{session_cookies, SessionCookies}];
 
192
which_cookies(#cookie_db{db = Db, session_db = SessionDb}) ->
 
193
    Cookies        = dets:match_object(Db, '_'), 
 
194
    SessionCookies = ets:tab2list(SessionDb),
 
195
    [{cookies, Cookies}, {session_cookies, SessionCookies}].
 
196
 
 
197
 
 
198
%%%========================================================================
 
199
%%% Internal functions
 
200
%%%========================================================================
 
201
 
 
202
delete(#cookie_db{session_db = SessionDb}, 
 
203
       #http_cookie{max_age = session} = Cookie) ->
 
204
    ets:delete_object(SessionDb, Cookie);
 
205
delete(#cookie_db{db = Db}, Cookie) ->
 
206
    dets:delete_object(Db, Cookie).
 
207
 
 
208
 
 
209
lookup_cookies(#cookie_db{db = undefined, session_db = SessionDb}, Key) ->
 
210
    Pattern = #http_cookie{domain = Key, _ = '_'}, 
 
211
    Cookies = ets:match_object(SessionDb, Pattern),
 
212
    ?hcrt("lookup cookies", [{cookies, Cookies}]),    
 
213
    Cookies;
 
214
 
 
215
lookup_cookies(#cookie_db{db = Db, session_db = SessionDb}, Key) ->
 
216
    Pattern = #http_cookie{domain = Key, _ = '_'}, 
 
217
    SessionCookies = ets:match_object(SessionDb, Pattern),
 
218
    ?hcrt("lookup cookies", [{session_cookies, SessionCookies}]),    
 
219
    Cookies = dets:match_object(Db, Pattern),
 
220
    ?hcrt("lookup cookies", [{cookies, Cookies}]),    
 
221
    Cookies ++ SessionCookies.
 
222
 
 
223
 
 
224
lookup_cookies(CookieDb, Host, Path) ->
 
225
    Cookies = 
 
226
        case http_util:is_hostname(Host) of 
 
227
            true ->  
 
228
                HostCookies = lookup_cookies(CookieDb, Host),
 
229
                [_| DomainParts] = string:tokens(Host, "."),
 
230
                lookup_domain_cookies(CookieDb, DomainParts, HostCookies);
 
231
            false -> % IP-adress
 
232
                lookup_cookies(CookieDb, Host)
 
233
        end,
 
234
    ValidCookies = valid_cookies(CookieDb, Cookies),
 
235
    lists:filter(fun(Cookie) -> 
 
236
                         lists:prefix(Cookie#http_cookie.path, Path) 
 
237
                 end, ValidCookies).
 
238
 
 
239
%% For instance if Host=localhost 
 
240
lookup_domain_cookies(_CookieDb, [], AccCookies) ->
 
241
    lists:flatten(AccCookies);
 
242
 
 
243
%% Top domains can not have cookies
 
244
lookup_domain_cookies(_CookieDb, [_], AccCookies) ->
 
245
    lists:flatten(AccCookies);
 
246
 
 
247
lookup_domain_cookies(CookieDb, [Next | DomainParts], AccCookies) ->    
 
248
    Domain = merge_domain_parts(DomainParts, [Next ++ "."]),
 
249
    lookup_domain_cookies(CookieDb, DomainParts, 
 
250
                          [lookup_cookies(CookieDb, Domain) | AccCookies]).
 
251
 
 
252
merge_domain_parts([Part], Merged) ->
 
253
    lists:flatten(["." | lists:reverse([Part | Merged])]);
 
254
merge_domain_parts([Part| Rest], Merged) ->
 
255
    merge_domain_parts(Rest, [".", Part | Merged]).
 
256
 
 
257
cookies_to_string(Scheme, [Cookie | _] = Cookies) ->
 
258
    Version = "$Version=" ++ Cookie#http_cookie.version ++ "; ", 
 
259
    cookies_to_string(Scheme, path_sort(Cookies), [Version]).
 
260
 
 
261
cookies_to_string(_, [], CookieStrs) ->
 
262
    case length(CookieStrs) of
 
263
        1 ->
 
264
            "";
 
265
        _ ->
 
266
            lists:flatten(lists:reverse(CookieStrs))
 
267
    end;
 
268
 
 
269
cookies_to_string(https, [#http_cookie{secure = true} = Cookie| Cookies], 
 
270
                  CookieStrs) ->
 
271
    Str = case Cookies of
 
272
              [] ->
 
273
                  cookie_to_string(Cookie);
 
274
              _ ->
 
275
                  cookie_to_string(Cookie) ++ "; "
 
276
          end,
 
277
    cookies_to_string(https, Cookies, [Str | CookieStrs]);
 
278
 
 
279
cookies_to_string(Scheme, [#http_cookie{secure = true}| Cookies],  
 
280
                  CookieStrs) ->
 
281
    cookies_to_string(Scheme, Cookies, CookieStrs);
 
282
 
 
283
cookies_to_string(Scheme, [Cookie | Cookies], CookieStrs) ->
 
284
    Str = case Cookies of
 
285
              [] ->
 
286
                  cookie_to_string(Cookie);
 
287
              _ ->
 
288
                  cookie_to_string(Cookie) ++ "; "
 
289
          end,
 
290
    cookies_to_string(Scheme, Cookies, [Str | CookieStrs]).
 
291
 
 
292
cookie_to_string(#http_cookie{name = Name, value = Value} = Cookie) ->
 
293
    Str = Name ++ "=" ++ Value,
 
294
    add_domain(add_path(Str, Cookie), Cookie).
 
295
    
 
296
add_path(Str, #http_cookie{path_default = true}) ->
 
297
    Str;
 
298
add_path(Str, #http_cookie{path = Path}) ->
 
299
    Str ++ "; $Path=" ++  Path.
 
300
 
 
301
add_domain(Str, #http_cookie{domain_default = true}) ->
 
302
    Str;
 
303
add_domain(Str, #http_cookie{domain = Domain}) ->
 
304
    Str ++ "; $Domain=" ++  Domain.
 
305
 
 
306
parse_set_cookies(OtherHeaders, DefaultPathDomain) ->
 
307
    SetCookieHeaders = 
 
308
        lists:foldl(fun({"set-cookie", Value}, Acc) ->  
 
309
                            [string:tokens(Value, ",")| Acc];
 
310
                       (_, Acc) ->
 
311
                            Acc
 
312
                    end, [], OtherHeaders),
 
313
    
 
314
    lists:flatten(
 
315
      lists:map(fun(CookieHeader) ->
 
316
                        NewHeader = fix_netscape_cookie(CookieHeader, []),
 
317
                        parse_set_cookie(NewHeader, [], DefaultPathDomain) 
 
318
                end,
 
319
                SetCookieHeaders)).
 
320
 
 
321
parse_set_cookie([], AccCookies, _) ->    
 
322
    AccCookies;
 
323
parse_set_cookie([CookieHeader | CookieHeaders], AccCookies, 
 
324
                 Defaults = {DefaultPath, DefaultDomain}) -> 
 
325
    [CookieStr | Attributes] = case string:tokens(CookieHeader, ";") of
 
326
                                   [CStr] ->
 
327
                                       [CStr, ""];
 
328
                                   [CStr | Attr] ->
 
329
                                       [CStr, Attr]
 
330
                               end,
 
331
    Pos = string:chr(CookieStr, $=),
 
332
    Name = string:substr(CookieStr, 1, Pos - 1),
 
333
    Value = string:substr(CookieStr, Pos + 1),
 
334
    Cookie = #http_cookie{name = string:strip(Name), 
 
335
                          value = string:strip(Value)},
 
336
    NewAttributes = parse_set_cookie_attributes(Attributes),
 
337
    TmpCookie = cookie_attributes(NewAttributes, Cookie),
 
338
    %% Add runtime defult values if necessary
 
339
    NewCookie = domain_default(path_default(TmpCookie, DefaultPath), 
 
340
                               DefaultDomain),
 
341
    parse_set_cookie(CookieHeaders, [NewCookie | AccCookies], Defaults).
 
342
 
 
343
parse_set_cookie_attributes([]) ->
 
344
    [];
 
345
parse_set_cookie_attributes([Attributes]) ->
 
346
    lists:map(fun(Attr) -> 
 
347
                      [AttrName, AttrValue] = 
 
348
                          case string:tokens(Attr, "=") of
 
349
                              %% All attributes have the form
 
350
                              %% Name=Value except "secure"!
 
351
                              [Name] -> 
 
352
                                  [Name, ""];
 
353
                              [Name, Value] ->
 
354
                                  [Name, Value];
 
355
                              %% Anything not expected will be
 
356
                              %% disregarded
 
357
                              _ -> 
 
358
                                  ["Dummy",""]
 
359
                          end,
 
360
                      {http_util:to_lower(string:strip(AttrName)), 
 
361
                       string:strip(AttrValue)}
 
362
              end, Attributes).
 
363
 
 
364
cookie_attributes([], Cookie) ->
 
365
    Cookie;
 
366
cookie_attributes([{"comment", Value}| Attributes], Cookie) ->
 
367
    cookie_attributes(Attributes, 
 
368
                                Cookie#http_cookie{comment = Value});
 
369
cookie_attributes([{"domain", Value}| Attributes], Cookie) ->
 
370
    cookie_attributes(Attributes, 
 
371
                                Cookie#http_cookie{domain = Value});
 
372
cookie_attributes([{"max-age", Value}| Attributes], Cookie) ->
 
373
    ExpireTime = cookie_expires(list_to_integer(Value)),
 
374
    cookie_attributes(Attributes, 
 
375
                                Cookie#http_cookie{max_age = ExpireTime});
 
376
%% Backwards compatibility with netscape cookies
 
377
cookie_attributes([{"expires", Value}| Attributes], Cookie) ->
 
378
    Time = http_util:convert_netscapecookie_date(Value),
 
379
    ExpireTime = calendar:datetime_to_gregorian_seconds(Time),
 
380
    cookie_attributes(Attributes, 
 
381
                      Cookie#http_cookie{max_age = ExpireTime});
 
382
cookie_attributes([{"path", Value}| Attributes], Cookie) ->
 
383
    cookie_attributes(Attributes, 
 
384
                      Cookie#http_cookie{path = Value});
 
385
cookie_attributes([{"secure", _}| Attributes], Cookie) ->
 
386
    cookie_attributes(Attributes, 
 
387
                      Cookie#http_cookie{secure = true});
 
388
cookie_attributes([{"version", Value}| Attributes], Cookie) ->
 
389
    cookie_attributes(Attributes, 
 
390
                      Cookie#http_cookie{version = Value});
 
391
%% Disregard unknown attributes.
 
392
cookie_attributes([_| Attributes], Cookie) ->
 
393
    cookie_attributes(Attributes, Cookie).
 
394
   
 
395
domain_default(Cookie = #http_cookie{domain = undefined}, 
 
396
               DefaultDomain) ->
 
397
    Cookie#http_cookie{domain = DefaultDomain, domain_default = true};
 
398
domain_default(Cookie, _) ->
 
399
    Cookie.
 
400
 
 
401
path_default(#http_cookie{path = undefined} = Cookie, DefaultPath) ->
 
402
    Cookie#http_cookie{path = skip_right_most_slash(DefaultPath),
 
403
                       path_default = true};
 
404
path_default(Cookie, _) ->
 
405
    Cookie.
 
406
 
 
407
%% Note: if the path is only / that / will be keept
 
408
skip_right_most_slash("/") ->
 
409
    "/";
 
410
skip_right_most_slash(Str) ->
 
411
    string:strip(Str, right, $/).
 
412
 
 
413
accept_cookies(Cookies, RequestPath, RequestHost) ->
 
414
    lists:filter(fun(Cookie) ->
 
415
                         accept_cookie(Cookie, RequestPath, RequestHost)
 
416
                 end, Cookies).
 
417
 
 
418
accept_cookie(Cookie, RequestPath, RequestHost) ->
 
419
    Accepted = 
 
420
        accept_path(Cookie, RequestPath) andalso 
 
421
        accept_domain(Cookie, RequestHost),
 
422
    Accepted.
 
423
 
 
424
accept_path(#http_cookie{path = Path}, RequestPath) ->
 
425
    lists:prefix(Path, RequestPath).
 
426
 
 
427
accept_domain(#http_cookie{domain = RequestHost}, RequestHost) ->
 
428
    true;
 
429
 
 
430
accept_domain(#http_cookie{domain = Domain}, RequestHost) ->
 
431
    HostCheck = 
 
432
        case http_util:is_hostname(RequestHost) of 
 
433
            true ->             
 
434
                (lists:suffix(Domain, RequestHost) andalso
 
435
                 (not 
 
436
                  lists:member($., 
 
437
                               string:substr(RequestHost, 1,
 
438
                                             (length(RequestHost) -
 
439
                                              length(Domain))))));
 
440
            false -> 
 
441
                false
 
442
        end,
 
443
    HostCheck 
 
444
        andalso (hd(Domain) =:= $.) 
 
445
        andalso (length(string:tokens(Domain, ".")) > 1).
 
446
 
 
447
cookie_expires(0) ->
 
448
    0;
 
449
cookie_expires(DeltaSec) ->
 
450
    NowSec = calendar:datetime_to_gregorian_seconds({date(), time()}),
 
451
    NowSec + DeltaSec.
 
452
 
 
453
is_cookie_expired(#http_cookie{max_age = session}) ->
 
454
    false;
 
455
is_cookie_expired(#http_cookie{max_age = ExpireTime}) ->
 
456
    NowSec = calendar:datetime_to_gregorian_seconds({date(), time()}),
 
457
    ExpireTime - NowSec =< 0.
 
458
 
 
459
 
 
460
valid_cookies(Db, Cookies) ->
 
461
    valid_cookies(Db, Cookies, []).
 
462
 
 
463
valid_cookies(_Db, [], Valid) ->
 
464
    Valid;
 
465
 
 
466
valid_cookies(Db, [Cookie | Cookies], Valid) ->
 
467
    case is_cookie_expired(Cookie) of
 
468
        true ->
 
469
            delete(Db, Cookie),
 
470
            valid_cookies(Db, Cookies, Valid);
 
471
        false ->
 
472
            valid_cookies(Db, Cookies, [Cookie | Valid])
 
473
    end.
 
474
    
 
475
path_sort(Cookies)->
 
476
    lists:reverse(lists:keysort(#http_cookie.path, Cookies)).
 
477
 
 
478
 
 
479
%%  Informally, the Set-Cookie response header comprises the token
 
480
%%  Set-Cookie:, followed by a comma-separated list of one or more
 
481
%%  cookies. Netscape cookies expires attribute may also have a
 
482
%% , in this case the header list will have been incorrectly split
 
483
%% in parse_set_cookies/2 this functions fixs that problem.
 
484
fix_netscape_cookie([Cookie1, Cookie2 | Rest], Acc) ->
 
485
    case inets_regexp:match(Cookie1, "expires=") of
 
486
        {_, _, _} ->
 
487
            fix_netscape_cookie(Rest, [Cookie1 ++ Cookie2 | Acc]);
 
488
        nomatch ->
 
489
            fix_netscape_cookie([Cookie2 |Rest], [Cookie1| Acc])
 
490
    end;
 
491
fix_netscape_cookie([Cookie | Rest], Acc) ->
 
492
    fix_netscape_cookie(Rest, [Cookie | Acc]);
 
493
 
 
494
fix_netscape_cookie([], Acc) ->
 
495
    Acc.