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

« back to all changes in this revision

Viewing changes to lib/kernel/src/auth.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

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,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
10
%% retrieved online at http://www.erlang.org/.
6
11
%% 
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
16
%% 
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
%% %CopyrightEnd%
17
18
%%
18
19
-module(auth).
19
20
-behaviour(gen_server).
43
44
 
44
45
-include("../include/file.hrl").
45
46
 
46
 
 
47
 
%%----------------------------------------------------------------------
48
 
%% Contract specifications 
49
 
%%----------------------------------------------------------------------
50
 
 
51
 
-type(node() :: atom()).
52
 
 
53
47
%%----------------------------------------------------------------------
54
48
%% Exported functions
55
49
%%----------------------------------------------------------------------
59
53
 
60
54
%%--Deprecated interface------------------------------------------------
61
55
 
62
 
-spec(is_auth/1 :: (Node :: node()) -> 'yes' | 'no').
 
56
-spec is_auth(Node :: node()) -> 'yes' | 'no'.
63
57
 
64
58
is_auth(Node) ->
65
59
    case net_adm:ping(Node) of
67
61
        pang -> no
68
62
    end.
69
63
 
70
 
-spec(cookie/0 :: () -> atom()).
 
64
-spec cookie() -> atom().
71
65
 
72
66
cookie() ->
73
67
    get_cookie().
74
68
 
75
 
-spec(cookie/1 :: (Cookies :: [atom(),...] | atom()) -> 'true').
 
69
-spec cookie(Cookies :: [atom(),...] | atom()) -> 'true'.
76
70
 
77
71
cookie([Cookie]) ->
78
72
    set_cookie(Cookie);
79
73
cookie(Cookie) ->
80
74
    set_cookie(Cookie).
81
75
 
82
 
-spec(node_cookie/1 :: (Cookies :: [atom(),...]) -> 'yes' | 'no').
 
76
-spec node_cookie(Cookies :: [atom(),...]) -> 'yes' | 'no'.
83
77
 
84
78
node_cookie([Node, Cookie]) ->
85
79
    node_cookie(Node, Cookie).
86
80
 
87
 
-spec(node_cookie/2 :: (Node :: node(), Cookie :: atom()) -> 'yes' | 'no').
 
81
-spec node_cookie(Node :: node(), Cookie :: atom()) -> 'yes' | 'no'.
88
82
 
89
83
node_cookie(Node, Cookie) ->
90
84
    set_cookie(Node, Cookie),
92
86
 
93
87
%%--"New" interface-----------------------------------------------------
94
88
 
95
 
-spec(get_cookie/0 :: () -> atom()).
 
89
-spec get_cookie() -> atom().
96
90
 
97
91
get_cookie() ->
98
92
    get_cookie(node()).
99
93
 
100
 
-spec(get_cookie/1 :: (Node :: node()) -> atom()).
 
94
-spec get_cookie(Node :: node()) -> atom().
101
95
 
102
96
get_cookie(_Node) when node() =:= nonode@nohost ->
103
97
    nocookie;
104
98
get_cookie(Node) ->
105
99
    gen_server:call(auth, {get_cookie, Node}).
106
100
 
107
 
-spec(set_cookie/1 :: (Cookie :: atom()) -> 'true').
 
101
-spec set_cookie(Cookie :: atom()) -> 'true'.
108
102
 
109
103
set_cookie(Cookie) ->
110
104
    set_cookie(node(), Cookie).
111
105
 
112
 
-spec(set_cookie/2 :: (Node :: node(), Cookie :: atom()) -> 'true').
 
106
-spec set_cookie(Node :: node(), Cookie :: atom()) -> 'true'.
113
107
 
114
108
set_cookie(_Node, _Cookie) when node() =:= nonode@nohost ->
115
109
    erlang:error(distribution_not_started);
116
110
set_cookie(Node, Cookie) ->
117
111
    gen_server:call(auth, {set_cookie, Node, Cookie}).
118
112
 
119
 
-spec(sync_cookie/0 :: () -> any()).
 
113
-spec sync_cookie() -> any().
120
114
 
121
115
sync_cookie() ->
122
116
    gen_server:call(auth, sync_cookie).
123
117
 
124
 
-spec(print/3 :: (Node :: node(), Format :: string(), Args :: [_]) -> 'ok').
 
118
-spec print(Node :: node(), Format :: string(), Args :: [_]) -> 'ok'.
125
119
 
126
120
print(Node,Format,Args) ->
127
121
    (catch gen_server:cast({auth,Node},{print,Format,Args})).