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

« back to all changes in this revision

Viewing changes to lib/inets/src/mod_auth_plain.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

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,
2
 
%% Version 1.1, (the "License"); you may not use this file except in
3
 
%% compliance with the License. You should have received a copy of the
4
 
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
6
 
%% 
7
 
%% Software distributed under the License is distributed on an "AS IS"
8
 
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
 
%% the License for the specific language governing rights and limitations
10
 
%% under the License.
11
 
%% 
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
 
%%
18
 
-module(mod_auth_plain).
19
 
 
20
 
-include("httpd.hrl").
21
 
-include("mod_auth.hrl").
22
 
 
23
 
-define(VMODULE,"AUTH_PLAIN").
24
 
-include("httpd_verbosity.hrl").
25
 
 
26
 
 
27
 
%% Internal API
28
 
-export([store_directory_data/2]).
29
 
 
30
 
 
31
 
-export([get_user/2, 
32
 
         list_group_members/2, 
33
 
         add_user/2, 
34
 
         add_group_member/3, 
35
 
         list_users/1, 
36
 
         delete_user/2, 
37
 
         list_groups/1, 
38
 
         delete_group_member/3, 
39
 
         delete_group/2, 
40
 
         remove/1]).
41
 
 
42
 
%%
43
 
%% API
44
 
%%
45
 
 
46
 
%%
47
 
%% Storage format of users in the ets table:
48
 
%% {UserName, Password, UserData}
49
 
%%
50
 
 
51
 
add_user(DirData, #httpd_user{username = User} = UStruct) ->
52
 
    ?vtrace("add_user -> entry with:"
53
 
        "~n   User: ~p",[User]),
54
 
    PWDB = httpd_util:key1search(DirData, auth_user_file),
55
 
    Record = {User,
56
 
              UStruct#httpd_user.password, 
57
 
              UStruct#httpd_user.user_data}, 
58
 
    case ets:lookup(PWDB, User) of
59
 
        [{User, _SomePassword, _SomeData}] ->
60
 
            {error, user_already_in_db};
61
 
        _ ->
62
 
            ets:insert(PWDB, Record),
63
 
            true
64
 
    end.
65
 
 
66
 
get_user(DirData, User) ->
67
 
    ?vtrace("get_user -> entry with:"
68
 
        "~n   User: ~p",[User]),
69
 
    PWDB = httpd_util:key1search(DirData, auth_user_file),
70
 
    case ets:lookup(PWDB, User) of
71
 
        [{User, PassWd, Data}] ->
72
 
            {ok, #httpd_user{username=User, password=PassWd, user_data=Data}};
73
 
        _ ->
74
 
            {error, no_such_user}
75
 
    end.
76
 
 
77
 
list_users(DirData) ->
78
 
    PWDB = httpd_util:key1search(DirData, auth_user_file),
79
 
    case ets:match(PWDB, '$1') of
80
 
        Records when list(Records) ->
81
 
            {ok, lists:foldr(fun({User,PassWd,Data}, A) -> [User|A] end, 
82
 
                             [], lists:flatten(Records))};
83
 
        O ->
84
 
            {ok, []}
85
 
    end.
86
 
 
87
 
delete_user(DirData, UserName) ->
88
 
    ?vtrace("delete_user -> entry with:"
89
 
        "~n   UserName: ~p",[UserName]),
90
 
    PWDB = httpd_util:key1search(DirData, auth_user_file),
91
 
    case ets:lookup(PWDB, UserName) of
92
 
        [{UserName, SomePassword, SomeData}] ->
93
 
            ets:delete(PWDB, UserName),
94
 
            case list_groups(DirData) of
95
 
                {ok,Groups}->
96
 
                    lists:foreach(fun(Group) -> 
97
 
                                          delete_group_member(DirData, Group, UserName) 
98
 
                                  end,Groups),
99
 
                    true;
100
 
                _->
101
 
                    true
102
 
            end;
103
 
        _ ->
104
 
            {error, no_such_user}
105
 
    end.
106
 
 
107
 
%%
108
 
%% Storage of groups in the ets table:
109
 
%% {Group, UserList} where UserList is a list of strings.
110
 
%%
111
 
  
112
 
add_group_member(DirData, Group, UserName) ->
113
 
    ?DEBUG("add_group_members -> ~n"
114
 
           "    Group:    ~p~n"
115
 
           "    UserName: ~p",[Group,UserName]),
116
 
    GDB = httpd_util:key1search(DirData, auth_group_file),
117
 
    case ets:lookup(GDB, Group) of
118
 
        [{Group, Users}] ->
119
 
            case lists:member(UserName, Users) of
120
 
                true ->
121
 
                    ?DEBUG("add_group_members -> already member in group",[]),
122
 
                    true;
123
 
                false ->
124
 
                    ?DEBUG("add_group_members -> add",[]),
125
 
                    ets:insert(GDB, {Group, [UserName|Users]}),
126
 
                    true
127
 
            end;
128
 
        [] ->
129
 
            ?DEBUG("add_group_members -> create grouo",[]),
130
 
            ets:insert(GDB, {Group, [UserName]}),
131
 
            true;
132
 
        Other ->
133
 
            ?ERROR("add_group_members -> Other: ~p",[Other]),
134
 
            {error, Other}
135
 
    end.
136
 
 
137
 
list_group_members(DirData, Group) ->
138
 
    ?DEBUG("list_group_members -> Group: ~p",[Group]),
139
 
    GDB = httpd_util:key1search(DirData, auth_group_file),
140
 
    case ets:lookup(GDB, Group) of
141
 
        [{Group, Users}] ->
142
 
            ?DEBUG("list_group_members -> Users: ~p",[Users]),
143
 
            {ok, Users};
144
 
        _ ->
145
 
            {error, no_such_group}
146
 
    end.
147
 
 
148
 
list_groups(DirData) ->
149
 
    ?DEBUG("list_groups -> entry",[]),
150
 
    GDB = httpd_util:key1search(DirData, auth_group_file),
151
 
    case ets:match(GDB, '$1') of
152
 
        [] ->
153
 
            ?DEBUG("list_groups -> []",[]),
154
 
            {ok, []};
155
 
        Groups0 when list(Groups0) ->
156
 
            ?DEBUG("list_groups -> Groups0: ~p",[Groups0]),
157
 
            {ok, httpd_util:uniq(lists:foldr(fun({G, U}, A) -> [G|A] end,
158
 
                                             [], lists:flatten(Groups0)))};
159
 
        _ ->
160
 
            {ok, []}
161
 
    end.
162
 
 
163
 
delete_group_member(DirData, Group, User) ->
164
 
    ?DEBUG("list_group_members -> ~n"
165
 
           "     Group: ~p~n"
166
 
           "     User:  ~p",[Group,User]),
167
 
    GDB = httpd_util:key1search(DirData, auth_group_file),
168
 
    UDB = httpd_util:key1search(DirData, auth_user_file),
169
 
    case ets:lookup(GDB, Group) of
170
 
        [{Group, Users}] when list(Users) ->
171
 
            case lists:member(User, Users) of
172
 
                true ->
173
 
                    ?DEBUG("list_group_members -> deleted from group",[]),
174
 
                    ets:delete(GDB, Group),
175
 
                    ets:insert(GDB, {Group, lists:delete(User, Users)}),
176
 
                    true;
177
 
                false ->
178
 
                    ?DEBUG("list_group_members -> not member",[]),
179
 
                    {error, no_such_group_member}
180
 
            end;
181
 
        _ ->
182
 
            ?ERROR("list_group_members -> no such group",[]),
183
 
            {error, no_such_group}
184
 
    end.
185
 
 
186
 
delete_group(DirData, Group) ->
187
 
    ?DEBUG("list_group_members -> Group: ~p",[Group]),
188
 
    GDB = httpd_util:key1search(DirData, auth_group_file),
189
 
    case ets:lookup(GDB, Group) of
190
 
        [{Group, Users}] ->
191
 
            ?DEBUG("list_group_members -> delete",[]),
192
 
            ets:delete(GDB, Group),
193
 
            true;
194
 
        _ ->
195
 
            ?ERROR("delete_group -> no such group",[]),
196
 
            {error, no_such_group}
197
 
    end.
198
 
 
199
 
 
200
 
store_directory_data(Directory, DirData) ->
201
 
    PWFile = httpd_util:key1search(DirData, auth_user_file),
202
 
    GroupFile = httpd_util:key1search(DirData, auth_group_file),
203
 
    case load_passwd(PWFile) of
204
 
        {ok, PWDB} ->
205
 
            case load_group(GroupFile) of
206
 
                {ok, GRDB} ->
207
 
                    %% Address and port is included in the file names...
208
 
                    Addr = httpd_util:key1search(DirData, bind_address),
209
 
                    Port = httpd_util:key1search(DirData, port),
210
 
                    {ok, PasswdDB} = store_passwd(Addr,Port,PWDB),
211
 
                    {ok, GroupDB}  = store_group(Addr,Port,GRDB),
212
 
                    NDD1 = lists:keyreplace(auth_user_file, 1, DirData, 
213
 
                                            {auth_user_file, PasswdDB}),
214
 
                    NDD2 = lists:keyreplace(auth_group_file, 1, NDD1, 
215
 
                                            {auth_group_file, GroupDB}),
216
 
                    {ok, NDD2};
217
 
                Err ->
218
 
                    ?ERROR("failed storing directory data: "
219
 
                           "load group error: ~p",[Err]),
220
 
                    {error, Err}
221
 
            end;
222
 
        Err2 ->
223
 
            ?ERROR("failed storing directory data: "
224
 
                   "load passwd error: ~p",[Err2]),
225
 
            {error, Err2}
226
 
    end.
227
 
 
228
 
 
229
 
 
230
 
%% load_passwd
231
 
 
232
 
load_passwd(AuthUserFile) ->
233
 
    case file:open(AuthUserFile, read) of
234
 
        {ok,Stream} ->
235
 
            parse_passwd(Stream, []);
236
 
        {error, _} ->
237
 
            {error, ?NICE("Can't open "++AuthUserFile)}
238
 
    end.
239
 
 
240
 
parse_passwd(Stream,PasswdList) ->
241
 
    Line =
242
 
        case io:get_line(Stream, '') of
243
 
            eof ->
244
 
                eof;
245
 
            String ->
246
 
                httpd_conf:clean(String)
247
 
        end,
248
 
    parse_passwd(Stream, PasswdList, Line).
249
 
 
250
 
parse_passwd(Stream, PasswdList, eof) ->
251
 
    file:close(Stream),
252
 
    {ok, PasswdList};
253
 
parse_passwd(Stream, PasswdList, "") ->
254
 
    parse_passwd(Stream, PasswdList);
255
 
parse_passwd(Stream, PasswdList, [$#|_]) ->
256
 
    parse_passwd(Stream, PasswdList);
257
 
parse_passwd(Stream, PasswdList, Line) ->      
258
 
    case regexp:split(Line,":") of
259
 
        {ok, [User,Password]} ->
260
 
            parse_passwd(Stream, [{User,Password, []}|PasswdList]);
261
 
        {ok,_} ->
262
 
            {error, ?NICE(Line)}
263
 
    end.
264
 
 
265
 
%% load_group
266
 
 
267
 
load_group(AuthGroupFile) ->
268
 
    case file:open(AuthGroupFile, read) of
269
 
        {ok, Stream} ->
270
 
            parse_group(Stream,[]);
271
 
        {error, _} ->
272
 
            {error, ?NICE("Can't open "++AuthGroupFile)}
273
 
    end.
274
 
 
275
 
parse_group(Stream, GroupList) ->
276
 
    Line=
277
 
        case io:get_line(Stream,'') of
278
 
            eof ->
279
 
                eof;
280
 
            String ->
281
 
                httpd_conf:clean(String)
282
 
        end,
283
 
    parse_group(Stream, GroupList, Line).
284
 
 
285
 
parse_group(Stream, GroupList, eof) ->
286
 
    file:close(Stream),
287
 
    {ok, GroupList};
288
 
parse_group(Stream, GroupList, "") ->
289
 
    parse_group(Stream, GroupList);
290
 
parse_group(Stream, GroupList, [$#|_]) ->
291
 
    parse_group(Stream, GroupList);
292
 
parse_group(Stream, GroupList, Line) ->      
293
 
    case regexp:split(Line, ":") of
294
 
        {ok, [Group,Users]} ->
295
 
            {ok, UserList} = regexp:split(Users," "),
296
 
            parse_group(Stream, [{Group,UserList}|GroupList]);
297
 
        {ok, _} ->
298
 
            {error, ?NICE(Line)}
299
 
    end.
300
 
 
301
 
 
302
 
%% store_passwd
303
 
 
304
 
store_passwd(Addr,Port,PasswdList) ->
305
 
    Name = httpd_util:make_name("httpd_passwd",Addr,Port),
306
 
    PasswdDB = ets:new(Name, [set, public]),
307
 
    store_passwd(PasswdDB, PasswdList).
308
 
 
309
 
store_passwd(PasswdDB, []) ->
310
 
    {ok, PasswdDB};
311
 
store_passwd(PasswdDB, [User|Rest]) ->
312
 
    ets:insert(PasswdDB, User),
313
 
    store_passwd(PasswdDB, Rest).
314
 
 
315
 
%% store_group
316
 
 
317
 
store_group(Addr,Port,GroupList) ->
318
 
    Name = httpd_util:make_name("httpd_group",Addr,Port),
319
 
    GroupDB = ets:new(Name, [set, public]),
320
 
    store_group(GroupDB, GroupList).
321
 
 
322
 
 
323
 
store_group(GroupDB,[]) ->
324
 
    {ok, GroupDB};
325
 
store_group(GroupDB,[User|Rest]) ->
326
 
    ets:insert(GroupDB, User),
327
 
    store_group(GroupDB, Rest).
328
 
 
329
 
 
330
 
%% remove/1
331
 
%%
332
 
%% Deletes ets tables used by this auth mod.
333
 
%%
334
 
remove(DirData) ->
335
 
    PWDB = httpd_util:key1search(DirData, auth_user_file),
336
 
    GDB = httpd_util:key1search(DirData, auth_group_file),
337
 
    ets:delete(PWDB),
338
 
    ets:delete(GDB).
339
 
 
340
 
 
341
 
 
342
 
 
343
 
 
344