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

« back to all changes in this revision

Viewing changes to lib/kernel/src/auth.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
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(auth).
37
37
 
38
38
-define(COOKIE_ETS_PROTECTION, protected). 
39
39
 
 
40
-type cookie() :: atom().
40
41
-record(state, {
41
 
          our_cookie,       %% Our own cookie
42
 
          other_cookies     %% The send-cookies of other nodes
 
42
          our_cookie    :: cookie(),  %% Our own cookie
 
43
          other_cookies :: ets:tab()  %% The send-cookies of other nodes
43
44
         }).
 
45
-type state() :: #state{}.
44
46
 
45
47
-include("../include/file.hrl").
46
48
 
48
50
%% Exported functions
49
51
%%----------------------------------------------------------------------
50
52
 
 
53
-spec start_link() -> {'ok',pid()} | {'error', term()} | 'ignore'.
 
54
 
51
55
start_link() ->
52
56
    gen_server:start_link({local, auth}, auth, [], []).
53
57
 
61
65
        pang -> no
62
66
    end.
63
67
 
64
 
-spec cookie() -> atom().
 
68
-spec cookie() -> cookie().
65
69
 
66
70
cookie() ->
67
71
    get_cookie().
68
72
 
69
 
-spec cookie(Cookies :: [atom(),...] | atom()) -> 'true'.
 
73
-spec cookie(Cookies :: [cookie(),...] | cookie()) -> 'true'.
70
74
 
71
75
cookie([Cookie]) ->
72
76
    set_cookie(Cookie);
73
77
cookie(Cookie) ->
74
78
    set_cookie(Cookie).
75
79
 
76
 
-spec node_cookie(Cookies :: [atom(),...]) -> 'yes' | 'no'.
 
80
-spec node_cookie(Cookies :: [node() | cookie(),...]) -> 'yes' | 'no'.
77
81
 
78
82
node_cookie([Node, Cookie]) ->
79
83
    node_cookie(Node, Cookie).
80
84
 
81
 
-spec node_cookie(Node :: node(), Cookie :: atom()) -> 'yes' | 'no'.
 
85
-spec node_cookie(Node :: node(), Cookie :: cookie()) -> 'yes' | 'no'.
82
86
 
83
87
node_cookie(Node, Cookie) ->
84
88
    set_cookie(Node, Cookie),
86
90
 
87
91
%%--"New" interface-----------------------------------------------------
88
92
 
89
 
-spec get_cookie() -> atom().
 
93
-spec get_cookie() -> 'nocookie' | cookie().
90
94
 
91
95
get_cookie() ->
92
96
    get_cookie(node()).
93
97
 
94
 
-spec get_cookie(Node :: node()) -> atom().
 
98
-spec get_cookie(Node :: node()) -> 'nocookie' | cookie().
95
99
 
96
100
get_cookie(_Node) when node() =:= nonode@nohost ->
97
101
    nocookie;
98
102
get_cookie(Node) ->
99
103
    gen_server:call(auth, {get_cookie, Node}).
100
104
 
101
 
-spec set_cookie(Cookie :: atom()) -> 'true'.
 
105
-spec set_cookie(Cookie :: cookie()) -> 'true'.
102
106
 
103
107
set_cookie(Cookie) ->
104
108
    set_cookie(node(), Cookie).
105
109
 
106
 
-spec set_cookie(Node :: node(), Cookie :: atom()) -> 'true'.
 
110
-spec set_cookie(Node :: node(), Cookie :: cookie()) -> 'true'.
107
111
 
108
112
set_cookie(_Node, _Cookie) when node() =:= nonode@nohost ->
109
113
    erlang:error(distribution_not_started);
117
121
 
118
122
-spec print(Node :: node(), Format :: string(), Args :: [_]) -> 'ok'.
119
123
 
120
 
print(Node,Format,Args) ->
121
 
    (catch gen_server:cast({auth,Node},{print,Format,Args})).
 
124
print(Node, Format, Args) ->
 
125
    (catch gen_server:cast({auth, Node}, {print, Format, Args})).
122
126
 
123
127
%%--gen_server callbacks------------------------------------------------
124
128
 
 
129
-spec init([]) -> {'ok', state()}.
 
130
 
125
131
init([]) ->
126
132
    process_flag(trap_exit, true),
127
133
    {ok, init_cookie()}.
130
136
%% The net kernel will let all message to the auth server 
131
137
%% through as is
132
138
 
 
139
-type calls() :: 'echo' | 'sync_cookie'
 
140
               | {'get_cookie', node()}
 
141
               | {'set_cookie', node(), term()}.
 
142
 
 
143
-spec handle_call(calls(), {pid(), term()}, state()) ->
 
144
        {'reply', 'hello' | 'true' | 'nocookie' | cookie(), state()}.
 
145
 
133
146
handle_call({get_cookie, Node}, {_From,_Tag}, State) when Node =:= node() ->
134
147
    {reply, State#state.our_cookie, State};
135
148
handle_call({get_cookie, Node}, {_From,_Tag}, State) ->
145
158
 
146
159
%%
147
160
%% Happens when the distribution is brought up and 
148
 
%% Someone wight have set up the cookie for our new nodename.
 
161
%% someone might have set up the cookie for our new node name.
149
162
%%
150
163
 
151
164
handle_call({set_cookie, Node, Cookie}, {_From,_Tag}, State)  ->
153
166
    {reply, true, State};
154
167
    
155
168
handle_call(sync_cookie, _From, State) ->
156
 
    case ets:lookup(State#state.other_cookies,node()) of
 
169
    case ets:lookup(State#state.other_cookies, node()) of
157
170
        [{_N,C}] ->
158
 
            ets:delete(State#state.other_cookies,node()),
 
171
            ets:delete(State#state.other_cookies, node()),
159
172
            {reply, true, State#state{our_cookie = C}};
160
173
        [] ->
161
174
            {reply, true, State}
164
177
handle_call(echo, _From, O) -> 
165
178
    {reply, hello, O}.
166
179
 
 
180
%%
 
181
%% handle_cast/2
 
182
%%
 
183
 
 
184
-spec handle_cast({'print', string(), [term()]}, state()) ->
 
185
        {'noreply', state()}.
 
186
 
167
187
handle_cast({print,What,Args}, O) ->
168
188
  %% always allow print outs
169
 
  error_logger:error_msg(What,Args), 
 
189
  error_logger:error_msg(What, Args),
170
190
  {noreply, O}.
171
191
 
172
192
%% A series of bad messages that may come (from older distribution versions).
173
193
 
 
194
-spec handle_info(term(), state()) -> {'noreply', state()}.
 
195
 
174
196
handle_info({From,badcookie,net_kernel,{From,spawn,_M,_F,_A,_Gleader}}, O) ->
175
197
    auth:print(node(From) ,"~n** Unauthorized spawn attempt to ~w **~n",
176
198
              [node()]),
188
210
    {noreply, O};
189
211
handle_info({From,badcookie,rex,_Msg}, O) ->
190
212
    auth:print(getnode(From), 
191
 
               "~n** Unauthorized rpc attempt to ~w **~n",[node()]),
 
213
               "~n** Unauthorized rpc attempt to ~w **~n", [node()]),
192
214
    disconnect_node(node(From)), 
193
215
    {noreply, O};
194
 
%% These two messages has to do with the old auth:is_auth() call (net_adm:ping)
 
216
%% These two messages have to do with the old auth:is_auth() call (net_adm:ping)
195
217
handle_info({From,badcookie,net_kernel,{'$gen_call',{From,Tag},{is_auth,_Node}}}, O) -> %% ho ho
196
218
    From ! {Tag, no},
197
219
    {noreply, O};
215
237
            end
216
238
    end, 
217
239
    {noreply, Opened};
218
 
handle_info(_, O)->   % Ignore anything else especially EXIT signals
 
240
handle_info(_, O) ->   % Ignore anything else especially EXIT signals
219
241
    {noreply, O}.
220
242
 
 
243
-spec code_change(term(), state(), term()) -> {'ok', state()}.
 
244
 
221
245
code_change(_OldVsn, State, _Extra) ->
222
246
    {ok, State}.
223
247
 
 
248
-spec terminate(term(), state()) -> 'ok'.
 
249
 
224
250
terminate(_Reason, _State) ->
225
251
    ok.
226
252
 
260
286
            end;
261
287
        _Other ->
262
288
            #state{our_cookie = nocookie,
263
 
                   other_cookies = ets:new(cookies,[?COOKIE_ETS_PROTECTION])}
 
289
                   other_cookies = ets:new(cookies, [?COOKIE_ETS_PROTECTION])}
264
290
    end.
265
291
 
266
292
read_cookie() ->