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

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_tests_SUITE_data/src/inets/mod_auth_mnesia.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
%% ``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: mod_auth_mnesia.erl,v 1.2 2010/03/04 13:54:19 maria Exp $
 
17
%%
 
18
-module(mod_auth_mnesia).
 
19
-export([get_user/2,
 
20
         list_group_members/2,
 
21
         add_user/2,
 
22
         add_group_member/3,
 
23
         list_users/1,
 
24
         delete_user/2,
 
25
         list_groups/1,
 
26
         delete_group_member/3,
 
27
         delete_group/2]).
 
28
 
 
29
-export([store_user/5, store_user/6, 
 
30
         store_group_member/5, store_group_member/6, 
 
31
         list_group_members/3, list_group_members/4, 
 
32
         list_groups/2, list_groups/3,
 
33
         list_users/2, list_users/3, 
 
34
         remove_user/4, remove_user/5, 
 
35
         remove_group_member/5, remove_group_member/6, 
 
36
         remove_group/4, remove_group/5]).
 
37
 
 
38
-export([store_directory_data/2]).
 
39
 
 
40
-include("httpd.hrl").
 
41
-include("mod_auth.hrl").
 
42
 
 
43
 
 
44
 
 
45
store_directory_data(Directory, DirData) ->
 
46
    %% We don't need to do anything here, we could ofcourse check that the appropriate
 
47
    %% mnesia tables has been created prior to starting the http server.
 
48
    ok.
 
49
 
 
50
 
 
51
%%
 
52
%% API
 
53
%%
 
54
 
 
55
%% Compability API
 
56
 
 
57
 
 
58
store_user(UserName, Password, Port, Dir, AccessPassword) ->
 
59
   %% AccessPassword is ignored - was not used in previous version
 
60
   DirData = [{path,Dir},{port,Port}],
 
61
   UStruct = #httpd_user{username = UserName,
 
62
                         password = Password},
 
63
   add_user(DirData, UStruct).
 
64
 
 
65
store_user(UserName, Password, Addr, Port, Dir, AccessPassword) ->
 
66
   %% AccessPassword is ignored - was not used in previous version
 
67
   DirData = [{path,Dir},{bind_address,Addr},{port,Port}],
 
68
   UStruct = #httpd_user{username = UserName,
 
69
                         password = Password},
 
70
   add_user(DirData, UStruct).
 
71
 
 
72
store_group_member(GroupName, UserName, Port, Dir, AccessPassword) ->
 
73
   DirData = [{path,Dir},{port,Port}],
 
74
   add_group_member(DirData, GroupName, UserName).
 
75
 
 
76
store_group_member(GroupName, UserName, Addr, Port, Dir, AccessPassword) ->
 
77
   DirData = [{path,Dir},{bind_address,Addr},{port,Port}],
 
78
   add_group_member(DirData, GroupName, UserName).
 
79
 
 
80
list_group_members(GroupName, Port, Dir) ->
 
81
   DirData = [{path,Dir},{port,Port}],
 
82
   list_group_members(DirData, GroupName).
 
83
 
 
84
list_group_members(GroupName, Addr, Port, Dir) ->
 
85
   DirData = [{path,Dir},{bind_address,Addr},{port,Port}],
 
86
   list_group_members(DirData, GroupName).
 
87
 
 
88
list_groups(Port, Dir) ->
 
89
   DirData = [{path,Dir},{port,Port}],
 
90
   list_groups(DirData).
 
91
 
 
92
list_groups(Addr, Port, Dir) ->
 
93
   DirData = [{path,Dir},{bind_address,Addr},{port,Port}],
 
94
   list_groups(DirData).
 
95
 
 
96
list_users(Port, Dir) ->
 
97
   DirData = [{path,Dir},{port,Port}],
 
98
   list_users(DirData).
 
99
    
 
100
list_users(Addr, Port, Dir) ->
 
101
   DirData = [{path,Dir},{bind_address,Addr},{port,Port}],
 
102
   list_users(DirData).
 
103
    
 
104
remove_user(UserName, Port, Dir, _AccessPassword) ->
 
105
   DirData = [{path,Dir},{port,Port}],
 
106
   delete_user(DirData, UserName).
 
107
 
 
108
remove_user(UserName, Addr, Port, Dir, _AccessPassword) ->
 
109
   DirData = [{path,Dir},{bind_address,Addr},{port,Port}],
 
110
   delete_user(DirData, UserName).
 
111
 
 
112
remove_group_member(GroupName,UserName,Port,Dir,_AccessPassword) ->
 
113
   DirData = [{path,Dir},{port,Port}],
 
114
   delete_group_member(DirData, GroupName, UserName).
 
115
 
 
116
remove_group_member(GroupName,UserName,Addr,Port,Dir,_AccessPassword) ->
 
117
   DirData = [{path,Dir},{bind_address,Addr},{port,Port}],
 
118
   delete_group_member(DirData, GroupName, UserName).
 
119
 
 
120
remove_group(GroupName,Port,Dir,_AccessPassword) ->
 
121
   DirData = [{path,Dir},{port,Port}],
 
122
   delete_group(DirData, GroupName).
 
123
 
 
124
remove_group(GroupName,Addr,Port,Dir,_AccessPassword) ->
 
125
   DirData = [{path,Dir},{bind_address,Addr},{port,Port}],
 
126
   delete_group(DirData, GroupName).
 
127
 
 
128
%%
 
129
%% Storage format of users in the mnesia table:
 
130
%% httpd_user records
 
131
%%
 
132
 
 
133
add_user(DirData, UStruct) ->
 
134
    {Addr, Port, Dir} = lookup_common(DirData),
 
135
    UserName = UStruct#httpd_user.username,
 
136
    Password = UStruct#httpd_user.password,
 
137
    Data     = UStruct#httpd_user.user_data,
 
138
    User=#httpd_user{username={UserName,Addr,Port,Dir},
 
139
                     password=Password,
 
140
                     user_data=Data},
 
141
    case mnesia:transaction(fun() -> mnesia:write(User) end) of
 
142
        {aborted,Reason} ->
 
143
            {error,Reason};
 
144
        _ ->
 
145
            true
 
146
    end.
 
147
 
 
148
get_user(DirData, UserName) ->
 
149
    {Addr, Port, Dir} = lookup_common(DirData),
 
150
    case mnesia:transaction(fun() ->
 
151
                                    mnesia:read({httpd_user, 
 
152
                                                 {UserName,Addr,Port,Dir}})
 
153
                            end) of
 
154
        {aborted,Reason} ->
 
155
            {error, Reason};
 
156
        {'atomic',[]} ->
 
157
            {error, no_such_user};
 
158
        {'atomic', [Record]} when record(Record, httpd_user) ->
 
159
            {ok, Record#httpd_user{username=UserName}};
 
160
        Other ->
 
161
            {error, no_such_user}
 
162
    end.
 
163
 
 
164
list_users(DirData) ->
 
165
    {Addr, Port, Dir} = lookup_common(DirData),
 
166
    case mnesia:transaction(fun() ->
 
167
                                    mnesia:match_object({httpd_user,
 
168
                                                         {'_',Addr,Port,Dir},'_','_'})
 
169
                            end) of
 
170
        {aborted,Reason} ->
 
171
            {error,Reason};
 
172
        {'atomic',Users} ->
 
173
            {ok, 
 
174
             lists:foldr(fun({httpd_user, {UserName, AnyAddr, AnyPort, AnyDir}, 
 
175
                              Password, Data}, Acc) ->
 
176
                                 [UserName|Acc]
 
177
                         end,
 
178
                         [], Users)}
 
179
    end.
 
180
 
 
181
delete_user(DirData, UserName) ->
 
182
    {Addr, Port, Dir} = lookup_common(DirData),
 
183
    case mnesia:transaction(fun() ->
 
184
                                    mnesia:delete({httpd_user,
 
185
                                                   {UserName,Addr,Port,Dir}})
 
186
                            end) of
 
187
        {aborted,Reason} ->
 
188
            {error,Reason};
 
189
        _ ->
 
190
            true
 
191
    end.
 
192
 
 
193
%%
 
194
%% Storage of groups in the mnesia table:
 
195
%% Multiple instances of {#httpd_group, User}
 
196
%%
 
197
 
 
198
add_group_member(DirData, GroupName, User) ->
 
199
    {Addr, Port, Dir} = lookup_common(DirData),
 
200
    Group=#httpd_group{name={GroupName, Addr, Port, Dir}, userlist=User},
 
201
    case mnesia:transaction(fun() -> mnesia:write(Group) end) of
 
202
        {aborted,Reason} ->
 
203
            {error,Reason};
 
204
        _ ->
 
205
            true
 
206
    end.
 
207
 
 
208
list_group_members(DirData, GroupName) ->
 
209
    {Addr, Port, Dir} = lookup_common(DirData),
 
210
    case mnesia:transaction(fun() ->
 
211
                                    mnesia:read({httpd_group,
 
212
                                                 {GroupName,Addr,Port,Dir}})
 
213
                            end) of
 
214
        {aborted, Reason} ->
 
215
            {error,Reason};
 
216
        {'atomic', Members} ->
 
217
            {ok,[UserName || {httpd_group,{AnyGroupName,AnyAddr,AnyPort,AnyDir},UserName} <- Members,
 
218
                             AnyGroupName == GroupName, AnyAddr == Addr,
 
219
                             AnyPort == Port, AnyDir == Dir]}
 
220
  end.
 
221
 
 
222
list_groups(DirData) -> 
 
223
    {Addr, Port, Dir} = lookup_common(DirData),
 
224
    case mnesia:transaction(fun() ->
 
225
                                    mnesia:match_object({httpd_group,
 
226
                                                         {'_',Addr,Port,Dir},'_'}) 
 
227
                            end) of
 
228
        {aborted, Reason} ->
 
229
            {error, Reason};
 
230
        {'atomic', Groups} ->
 
231
            GroupNames=
 
232
                [GroupName || {httpd_group,{GroupName,AnyAddr,AnyPort,AnyDir}, UserName} <- Groups,
 
233
                              AnyAddr == Addr, AnyPort == AnyPort, AnyDir == Dir],
 
234
            {ok, httpd_util:uniq(lists:sort(GroupNames))}
 
235
    end.
 
236
 
 
237
delete_group_member(DirData, GroupName, UserName) ->
 
238
    {Addr, Port, Dir} = lookup_common(DirData),
 
239
    Group = #httpd_group{name={GroupName, Addr, Port, Dir}, userlist=UserName},
 
240
    case mnesia:transaction(fun() -> mnesia:delete_object(Group) end) of
 
241
        {aborted,Reason} ->
 
242
            {error,Reason};
 
243
        _ ->
 
244
            true
 
245
    end.
 
246
 
 
247
%% THIS IS WRONG (?) !
 
248
%% Should first match out all httpd_group records for this group and then
 
249
%% do mnesia:delete on those. Or ?
 
250
 
 
251
delete_group(DirData, GroupName) ->
 
252
    {Addr, Port, Dir} = lookup_common(DirData),
 
253
    case mnesia:transaction(fun() ->
 
254
                                    mnesia:delete({httpd_group, 
 
255
                                                   {GroupName,Addr,Port,Dir}})
 
256
                            end) of
 
257
        {aborted,Reason} ->
 
258
            {error,Reason};
 
259
        _ ->
 
260
            true
 
261
    end.
 
262
 
 
263
%% Utility functions.
 
264
 
 
265
lookup_common(DirData) ->
 
266
    Dir = httpd_util:key1search(DirData, path),
 
267
    Port = httpd_util:key1search(DirData, port),
 
268
    Addr = httpd_util:key1search(DirData, bind_address),
 
269
    {Addr, Port, Dir}.
 
270
 
 
271
 
 
272
 
 
273
 
 
274
 
 
275
 
 
276