% The clientdatabase
-module(cldb).
-export([init/0, ask/2, login/2, decVote/1, incVote/1, register/3, check_rights/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).
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) ->
F = fun() ->
[Head|_] = ask(User, '_'),
Votes = Head#user.votes - 1,
New = Head#user{votes = Votes},
mnesia:write(New)
end,
mnesia:transaction(F).
incVote(User) ->
F = fun() ->
[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.