~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/ssh/src/ssh_userreg.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • mto: (3.3.1 squeeze)
  • mto: This revision was merged to the branch mainline in revision 17.
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%<copyright>
 
2
%% <year>2008-2008</year>
 
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
 
4
%%</copyright>
 
5
%%<legalnotice>
 
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
%% The Initial Developer of the Original Code is Ericsson AB.
 
18
%%</legalnotice>
 
19
%%
 
20
%% Description: User register for ssh_cli
 
21
 
 
22
-module(ssh_userreg).
 
23
 
 
24
-behaviour(gen_server).
 
25
 
 
26
%% API
 
27
-export([start_link/0, register_user/2, lookup_user/1]).
 
28
 
 
29
%% gen_server callbacks
 
30
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
 
31
         terminate/2, code_change/3]).
 
32
 
 
33
-record(state, {user_db = []}).
 
34
 
 
35
%%====================================================================
 
36
%% API
 
37
%%====================================================================
 
38
%%--------------------------------------------------------------------
 
39
%% Function: start_link() -> {ok,Pid} | ignore | {error,Error}
 
40
%% Description: Starts the server
 
41
%%--------------------------------------------------------------------
 
42
start_link() ->
 
43
    gen_server:start_link({local, ?MODULE}, ?MODULE, [], []).
 
44
 
 
45
register_user(User, Cm) ->
 
46
    gen_server:cast(?MODULE, {register, {User, Cm}}).
 
47
 
 
48
lookup_user(Cm) ->
 
49
    gen_server:call(?MODULE, {get_user, Cm}, infinity).
 
50
 
 
51
%%====================================================================
 
52
%% gen_server callbacks
 
53
%%====================================================================
 
54
 
 
55
%%--------------------------------------------------------------------
 
56
%% Function: init(Args) -> {ok, State} |
 
57
%%                         {ok, State, Timeout} |
 
58
%%                         ignore               |
 
59
%%                         {stop, Reason}
 
60
%% Description: Initiates the server
 
61
%%--------------------------------------------------------------------
 
62
init([]) ->
 
63
    {ok, #state{}}.
 
64
 
 
65
%%--------------------------------------------------------------------
 
66
%% Function: %% handle_call(Request, From, State) -> {reply, Reply, State} |
 
67
%%                                      {reply, Reply, State, Timeout} |
 
68
%%                                      {noreply, State} |
 
69
%%                                      {noreply, State, Timeout} |
 
70
%%                                      {stop, Reason, Reply, State} |
 
71
%%                                      {stop, Reason, State}
 
72
%% Description: Handling call messages
 
73
%%--------------------------------------------------------------------
 
74
handle_call({get_user, Cm}, _From, #state{user_db = Db} = State) ->
 
75
    User = lookup(Cm, Db),
 
76
    {reply, {ok, User}, State}.
 
77
 
 
78
%%--------------------------------------------------------------------
 
79
%% Function: handle_cast(Msg, State) -> {noreply, State} |
 
80
%%                                      {noreply, State, Timeout} |
 
81
%%                                      {stop, Reason, State}
 
82
%% Description: Handling cast messages
 
83
%%--------------------------------------------------------------------
 
84
handle_cast({register, UserCm}, State0) ->
 
85
    State = insert(UserCm, State0),
 
86
    {noreply, State}.
 
87
 
 
88
%%--------------------------------------------------------------------
 
89
%% Function: handle_info(Info, State) -> {noreply, State} |
 
90
%%                                       {noreply, State, Timeout} |
 
91
%%                                       {stop, Reason, State}
 
92
%% Description: Handling all non call/cast messages
 
93
%%--------------------------------------------------------------------
 
94
handle_info(_Info, State) ->
 
95
    {noreply, State}.
 
96
 
 
97
%%--------------------------------------------------------------------
 
98
%% Function: terminate(Reason, State) -> void()
 
99
%% Description: This function is called by a gen_server when it is about to
 
100
%% terminate. It should be the opposite of Module:init/1 and do any necessary
 
101
%% cleaning up. When it returns, the gen_server terminates with Reason.
 
102
%% The return value is ignored.
 
103
%%--------------------------------------------------------------------
 
104
terminate(_Reason, _State) ->
 
105
    ok.
 
106
 
 
107
%%--------------------------------------------------------------------
 
108
%% Func: code_change(OldVsn, State, Extra) -> {ok, NewState}
 
109
%% Description: Convert process state when code is changed
 
110
%%--------------------------------------------------------------------
 
111
code_change(_OldVsn, State, _Extra) ->
 
112
    {ok, State}.
 
113
 
 
114
%%--------------------------------------------------------------------
 
115
%%% Internal functions
 
116
%%--------------------------------------------------------------------
 
117
insert({User, Cm}, #state{user_db = Db} = State) ->
 
118
    State#state{user_db = [{User, Cm} | Db]}.
 
119
 
 
120
lookup(_, []) ->
 
121
    undefined;
 
122
lookup(Cm, [{User, Cm} | _Rest]) ->
 
123
    User;
 
124
lookup(Cm, [_ | Rest]) ->
 
125
    lookup(Cm, Rest).
 
126