aboutsummaryrefslogtreecommitdiffstats
path: root/server/cldb.erl
blob: d1daaa949f8d1c316ee27ed43b08f8fcb47b62ed (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
% The clientdatabase

-module(cldb).
-export([init/0,all/0, ask/2, login/2, decVote/1, incVote/1, register/3, check_rights/1, give_votes/1]).
-record(user, {name, passwd, votes, rights}).

init() ->
    mnesia:create_schema([node()]),
    mnesia:start(),
    mnesia:create_table(user, [{attributes, record_info(fields, user)}]),
    io:format("Userdb up and running \n").

ask(User, Pwd) ->
    F = fun() ->
        mnesia:match_object({user, User, Pwd, '_', '_'})
        end,
    mnesia:transaction(F).

all() ->
	F = fun() ->
        mnesia:match_object({user, '_', '_', '_', '_'})
        end,
    {atomic, List} =  mnesia:transaction(F),
	List.
	

login(User, Pwd) ->
    case ask(User, Pwd) of
	{atomic, [UserRow|_]} -> {ok, UserRow};
	_-> {error}
    end.

register(User, Pwd, Root) ->
    case ask(User, '_') of
	{atomic, []} ->
	    F = fun() ->
			mnesia:write(#user{name = User, passwd = Pwd, votes = 5, rights = Root})
		end,
	    case mnesia:transaction(F) of
		{atomic, ok} ->
		    {ok, user_created};
		{atomic, Why} ->
		    {error, Why}
	    end;
	_ ->
	    {error, duplicated_user}
    end.

decVote(User) when is_list(User) ->
    {atomic, [Head|_]} = ask(User, '_'),
    if Head#user.votes > 0 ->
        F = fun() ->
                    Votes = Head#user.votes - 1,
                    New = Head#user{votes = Votes},
                    mnesia:write(New)
            end,
        mnesia:transaction(F),
        {ok};
        true -> {error}
    end;
decVote(User) ->
    decVote(User#user.name).

incVote(User) ->
    F = fun() ->
                {atomic, [Head|_]} = ask(User, '_'),
                Votes = Head#user.votes + 1,
                New = Head#user{votes = Votes},
                mnesia:write(New)
        end,
    mnesia:transaction(F).

check_rights(User) ->
    {_, _, Rights} = ask(User, '_'),
    Rights.

% after a song every client gets on more vote
give_votes([Head|Rest]) -> 
	User = Head#user.name,
	incVote(User),
	give_votes(Rest);
give_votes([]) -> ok.