~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_dets.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_dets.erl,v 1.1 2008/12/17 09:53:35 mikpe Exp $
 
17
%%
 
18
-module(mod_auth_dets).
 
19
 
 
20
%% dets authentication storage
 
21
 
 
22
-export([get_user/2,
 
23
         list_group_members/2,
 
24
         add_user/2,
 
25
         add_group_member/3,
 
26
         list_users/1,
 
27
         delete_user/2,
 
28
         list_groups/1,
 
29
         delete_group_member/3,
 
30
         delete_group/2,
 
31
         remove/1]).
 
32
 
 
33
-export([store_directory_data/2]).
 
34
 
 
35
-include("httpd.hrl").
 
36
-include("mod_auth.hrl").
 
37
 
 
38
store_directory_data(Directory, DirData) ->
 
39
    ?CDEBUG("store_directory_data -> ~n"
 
40
            "     Directory: ~p~n"
 
41
            "     DirData:   ~p",
 
42
            [Directory, DirData]),
 
43
 
 
44
    PWFile = httpd_util:key1search(DirData, auth_user_file),
 
45
    GroupFile = httpd_util:key1search(DirData, auth_group_file),
 
46
    Addr = httpd_util:key1search(DirData, bind_address),
 
47
    Port = httpd_util:key1search(DirData, port),
 
48
 
 
49
    PWName  = httpd_util:make_name("httpd_dets_pwdb",Addr,Port),
 
50
    case dets:open_file(PWName,[{type,set},{file,PWFile},{repair,true}]) of
 
51
        {ok, PWDB} ->
 
52
            GDBName = httpd_util:make_name("httpd_dets_groupdb",Addr,Port),
 
53
            case dets:open_file(GDBName,[{type,set},{file,GroupFile},{repair,true}]) of
 
54
                {ok, GDB} ->
 
55
                    NDD1 = lists:keyreplace(auth_user_file, 1, DirData, 
 
56
                                            {auth_user_file, PWDB}),
 
57
                    NDD2 = lists:keyreplace(auth_group_file, 1, NDD1, 
 
58
                                            {auth_group_file, GDB}),
 
59
                    {ok, NDD2};
 
60
                {error, Err}->
 
61
                    {error, {{file, GroupFile},Err}}
 
62
            end;
 
63
        {error, Err2} ->
 
64
            {error, {{file, PWFile},Err2}} 
 
65
    end.
 
66
 
 
67
%%
 
68
%% Storage format of users in the dets table:
 
69
%% {{UserName, Addr, Port, Dir}, Password, UserData}
 
70
%%
 
71
 
 
72
add_user(DirData, UStruct) ->
 
73
    {Addr, Port, Dir} = lookup_common(DirData),
 
74
    PWDB = httpd_util:key1search(DirData, auth_user_file),
 
75
    Record = {{UStruct#httpd_user.username, Addr, Port, Dir},
 
76
              UStruct#httpd_user.password, UStruct#httpd_user.user_data}, 
 
77
    case dets:lookup(PWDB, UStruct#httpd_user.username) of
 
78
        [Record] ->
 
79
            {error, user_already_in_db};
 
80
        _ ->
 
81
            dets:insert(PWDB, Record),
 
82
            true
 
83
    end.
 
84
 
 
85
get_user(DirData, UserName) ->
 
86
    {Addr, Port, Dir} = lookup_common(DirData),
 
87
    PWDB = httpd_util:key1search(DirData, auth_user_file),
 
88
    User = {UserName, Addr, Port, Dir},
 
89
    case dets:lookup(PWDB, User) of
 
90
        [{User, Password, UserData}] ->
 
91
            {ok, #httpd_user{username=UserName, password=Password, user_data=UserData}};
 
92
        Other ->
 
93
            {error, no_such_user}
 
94
    end.
 
95
 
 
96
list_users(DirData) ->
 
97
    ?DEBUG("list_users -> ~n"
 
98
           "     DirData: ~p", [DirData]),
 
99
    {Addr, Port, Dir} = lookup_common(DirData),
 
100
    PWDB = httpd_util:key1search(DirData, auth_user_file),
 
101
    case dets:traverse(PWDB, fun(X) -> {continue, X} end) of    %% SOOOO Ugly !
 
102
        Records when list(Records) ->
 
103
            ?DEBUG("list_users -> ~n"
 
104
                   "     Records: ~p", [Records]),
 
105
            {ok, [UserName || {{UserName, AnyAddr, AnyPort, AnyDir}, Password, _Data} <- Records,
 
106
                              AnyAddr == Addr, AnyPort == Port, AnyDir == Dir]};
 
107
        O ->
 
108
            ?DEBUG("list_users -> ~n"
 
109
                   "     O: ~p", [O]),
 
110
            {ok, []}
 
111
    end.
 
112
 
 
113
delete_user(DirData, UserName) ->
 
114
    {Addr, Port, Dir} = lookup_common(DirData),
 
115
    PWDB = httpd_util:key1search(DirData, auth_user_file),
 
116
    User = {UserName, Addr, Port, Dir},
 
117
    case dets:lookup(PWDB, User) of
 
118
        [{User, SomePassword, UserData}] ->
 
119
            dets:delete(PWDB, User),
 
120
            lists:foreach(fun(Group) -> delete_group_member(DirData, Group, UserName) end, 
 
121
                          list_groups(DirData)),
 
122
            true;
 
123
        _ ->
 
124
            {error, no_such_user}
 
125
    end.
 
126
 
 
127
%%
 
128
%% Storage of groups in the dets table:
 
129
%% {Group, UserList} where UserList is a list of strings.
 
130
%%
 
131
add_group_member(DirData, GroupName, UserName) ->
 
132
    {Addr, Port, Dir} = lookup_common(DirData),
 
133
    GDB = httpd_util:key1search(DirData, auth_group_file),
 
134
    Group = {GroupName, Addr, Port, Dir},
 
135
    case dets:lookup(GDB, Group) of
 
136
        [{Group, Users}] ->
 
137
            case lists:member(UserName, Users) of
 
138
                true ->
 
139
                    true;
 
140
                false ->
 
141
                    dets:insert(GDB, {Group, [UserName|Users]}),
 
142
                    true
 
143
            end;
 
144
        [] ->
 
145
            dets:insert(GDB, {Group, [UserName]}),
 
146
            true;
 
147
        Other ->
 
148
            {error, Other}
 
149
    end.
 
150
 
 
151
list_group_members(DirData, GroupName) ->
 
152
    {Addr, Port, Dir} = lookup_common(DirData),
 
153
    GDB = httpd_util:key1search(DirData, auth_group_file),
 
154
    Group = {GroupName, Addr, Port, Dir},
 
155
    case dets:lookup(GDB, Group) of
 
156
        [{Group, Users}] ->
 
157
            {ok, Users};
 
158
        Other ->
 
159
            {error, no_such_group}
 
160
    end.
 
161
 
 
162
list_groups(DirData) ->
 
163
    {Addr, Port, Dir} = lookup_common(DirData),
 
164
    GDB  = httpd_util:key1search(DirData, auth_group_file),
 
165
    case dets:match(GDB, {'$1', '_'}) of
 
166
        [] ->
 
167
            {ok, []};
 
168
        List when list(List) ->
 
169
            Groups = lists:flatten(List),
 
170
            {ok, [GroupName || {GroupName, AnyAddr, AnyPort, AnyDir} <- Groups,
 
171
                           AnyAddr == Addr, AnyPort == Port, AnyDir == Dir]};
 
172
        _ ->
 
173
            {ok, []}
 
174
    end.
 
175
 
 
176
delete_group_member(DirData, GroupName, UserName) ->
 
177
    {Addr, Port, Dir} = lookup_common(DirData),
 
178
    GDB = httpd_util:key1search(DirData, auth_group_file),
 
179
    Group = {GroupName, Addr, Port, Dir},
 
180
    case dets:lookup(GDB, GroupName) of
 
181
        [{Group, Users}] ->
 
182
            case lists:member(UserName, Users) of
 
183
                true ->
 
184
                    dets:delete(GDB, Group),
 
185
                    dets:insert(GDB, {Group,
 
186
                                      lists:delete(UserName, Users)}),
 
187
                    true;
 
188
                false ->
 
189
                    {error, no_such_group_member}
 
190
            end;
 
191
        _ ->
 
192
            {error, no_such_group}
 
193
    end.
 
194
 
 
195
delete_group(DirData, GroupName) ->
 
196
    {Addr, Port, Dir} = lookup_common(DirData),
 
197
    GDB = httpd_util:key1search(DirData, auth_group_file),
 
198
    Group = {GroupName, Addr, Port, Dir},
 
199
    case dets:lookup(GDB, Group) of
 
200
        [{Group, Users}] ->
 
201
            dets:delete(GDB, Group),
 
202
            true;
 
203
        _ ->
 
204
            {error, no_such_group}
 
205
    end.
 
206
 
 
207
lookup_common(DirData) ->
 
208
    Dir  = httpd_util:key1search(DirData, path),
 
209
    Port = httpd_util:key1search(DirData, port),
 
210
    Addr = httpd_util:key1search(DirData, bind_address),
 
211
    {Addr, Port, Dir}.
 
212
 
 
213
%% remove/1
 
214
%%
 
215
%% Closes dets tables used by this auth mod.
 
216
%%
 
217
remove(DirData) ->
 
218
    PWDB = httpd_util:key1search(DirData, auth_user_file),
 
219
    GDB = httpd_util:key1search(DirData, auth_group_file),
 
220
    dets:close(GDB),
 
221
    dets:close(PWDB),
 
222
    ok.