aboutsummaryrefslogtreecommitdiffstats
path: root/server/cldb.erl
diff options
context:
space:
mode:
Diffstat (limited to 'server/cldb.erl')
-rw-r--r--server/cldb.erl140
1 files changed, 111 insertions, 29 deletions
diff --git a/server/cldb.erl b/server/cldb.erl
index d1daaa9..28815a6 100644
--- a/server/cldb.erl
+++ b/server/cldb.erl
@@ -1,8 +1,8 @@
% 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}).
+-export([init/0, all/0, find/1, login/2, dec_vote/1, inc_vote/1, register/3, check_rights/1, update_votes/0, logout/1, set_client_pid/2]).
+-record(user, {name, passwd, votes, logged_in, pid, rights}).
init() ->
mnesia:create_schema([node()]),
@@ -10,44 +10,121 @@ init() ->
mnesia:create_table(user, [{attributes, record_info(fields, user)}]),
io:format("Userdb up and running \n").
-ask(User, Pwd) ->
+find(User) when is_list(User) ->
+ find(User, '_');
+find(User) ->
+ find(User#user.name, '_').
+
+find(User, Pwd) ->
F = fun() ->
- mnesia:match_object({user, User, Pwd, '_', '_'})
+ mnesia:match_object({user, User, Pwd, '_', '_', '_', '_'})
end,
mnesia:transaction(F).
+find_logged_in_user() ->
+ F = fun() ->
+ mnesia:match_object({user, '_', '_', '_', true, '_', '_'})
+ end,
+ case mnesia:transaction(F) of
+ {atomic, List} -> {ok, List};
+ _ -> {error}
+ end.
+
+find_user_by_pid(Pid) ->
+ F = fun() ->
+ mnesia:match_object({user, '_', '_', '_', '_', Pid, '_'})
+ end,
+ case mnesia:transaction(F) of
+ {atomic, List} -> {ok, List};
+ _ -> {error}
+ end.
+
all() ->
- F = fun() ->
- mnesia:match_object({user, '_', '_', '_', '_'})
+ F = fun() ->
+ mnesia:match_object({user, '_', '_', '_', '_', '_', '_'})
end,
- {atomic, List} = mnesia:transaction(F),
- List.
-
+ case mnesia:transaction(F) of
+ {atomic, List} -> {ok, List};
+ _ -> {error}
+ end.
+
+login(User, Pwd) when is_list(User) and is_list(Pwd) ->
+ case find(User, Pwd) of
+ {atomic, [UserRow|_]} ->
+ NewUserRow = UserRow#user{logged_in = true},
+ F = fun() ->
+ mnesia:write(NewUserRow)
+ end,
+ case mnesia:transaction(F) of
+ {atomic, ok} ->
+ {ok, NewUserRow};
+ {atomic, Why} ->
+ {error, Why}
+ end;
-login(User, Pwd) ->
- case ask(User, Pwd) of
- {atomic, [UserRow|_]} -> {ok, UserRow};
_-> {error}
+ end;
+
+login(_, _) ->
+ {error}.
+
+set_client_pid(User, Pid) ->
+ case find(User) of
+ {atomic, [UserRow|_]} ->
+ NewUserRow = UserRow#user{pid = Pid},
+ F = fun() ->
+ mnesia:write(NewUserRow)
+ end,
+ case mnesia:transaction(F) of
+ {atomic, ok} ->
+ {ok, pid_updated};
+ {atomic, Why} ->
+ {error, Why}
+ end;
+ _ ->
+ {error, user_not_found}
end.
-register(User, Pwd, Root) ->
- case ask(User, '_') of
+logout(Pid) ->
+ case find_user_by_pid(Pid) of
+ {atomic, [UserRow|_]} ->
+ F = fun() ->
+ New = UserRow#user{logged_in = false},
+ mnesia:write(New)
+ end,
+ case mnesia:transaction(F) of
+ {atomic, ok} ->
+ {ok, logged_out};
+ {atomic, Why} ->
+ {error, Why}
+ end;
+
+ _ ->
+ {error, invalid_user}
+ end.
+
+register(User, Pwd, Root) when is_list(User) and is_list(Pwd) ->
+ case find(User) of
{atomic, []} ->
F = fun() ->
- mnesia:write(#user{name = User, passwd = Pwd, votes = 5, rights = Root})
+ mnesia:write(#user{name = User, passwd = Pwd, votes = 5, logged_in = false, pid = undef, rights = Root})
end,
case mnesia:transaction(F) of
{atomic, ok} ->
+ io:format("User created: ~s~n", [User]),
{ok, user_created};
{atomic, Why} ->
{error, Why}
end;
_ ->
{error, duplicated_user}
- end.
+ end;
+
+register(_,_,_) ->
+ {error, invalid_username}.
-decVote(User) when is_list(User) ->
- {atomic, [Head|_]} = ask(User, '_'),
+dec_vote(User) when is_list(User) ->
+ {atomic, [Head|_]} = find(User),
if Head#user.votes > 0 ->
F = fun() ->
Votes = Head#user.votes - 1,
@@ -58,12 +135,12 @@ decVote(User) when is_list(User) ->
{ok};
true -> {error}
end;
-decVote(User) ->
- decVote(User#user.name).
+dec_vote(User) ->
+ dec_vote(User#user.name).
-incVote(User) ->
+inc_vote(User) ->
F = fun() ->
- {atomic, [Head|_]} = ask(User, '_'),
+ {atomic, [Head|_]} = find(User),
Votes = Head#user.votes + 1,
New = Head#user{votes = Votes},
mnesia:write(New)
@@ -71,13 +148,18 @@ incVote(User) ->
mnesia:transaction(F).
check_rights(User) ->
- {_, _, Rights} = ask(User, '_'),
- Rights.
+ {atomic, [UserRow|_]} = find(User),
+ UserRow#user.rights.
-% after a song every client gets on more vote
-give_votes([Head|Rest]) ->
- User = Head#user.name,
- incVote(User),
+update_votes() ->
+ %% after a song every logged_in client gets on more vote
+ case find_logged_in_user() of
+ {ok, List} ->
+ give_votes(List);
+ _ -> error
+ end.
+
+give_votes([User|Rest]) ->
+ inc_vote(User#user.name),
give_votes(Rest);
give_votes([]) -> ok.
-