aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorAlexander Sulfrian <alexander@sulfrian.net>2010-10-15 09:18:48 +0200
committerAlexander Sulfrian <alexander@sulfrian.net>2010-10-15 09:18:48 +0200
commit4b73af956cd4e4a307720f9aeaa0d8d3a7ce4b45 (patch)
tree6a0aa5f15b3986c12c2547f71a869494a7753b39
parentf12f458f6a15704e1028445368e7d0a599279f97 (diff)
downloaderlang-4b73af956cd4e4a307720f9aeaa0d8d3a7ce4b45.tar.gz
erlang-4b73af956cd4e4a307720f9aeaa0d8d3a7ce4b45.tar.xz
erlang-4b73af956cd4e4a307720f9aeaa0d8d3a7ce4b45.zip
added that only logged_in clients get vote points, added comments
-rw-r--r--server/cldb.erl140
-rw-r--r--server/client.erl31
-rw-r--r--server/dispatcher.erl31
-rw-r--r--server/media.erl2
4 files changed, 156 insertions, 48 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.
-
diff --git a/server/client.erl b/server/client.erl
index 7cee336..421280b 100644
--- a/server/client.erl
+++ b/server/client.erl
@@ -2,11 +2,19 @@
-export([start/2, loop/2, register/2, login/2]).
start(Node, User) ->
+ %% start linked processes on client and server to get noticed if
+ %% client disconnects and properly handle the logged in status
process_flag(trap_exit, true),
Client = server:start_on_node(Node, client, undef),
link(Client),
+ %% store the client pid in the client database to find the correct
+ %% user on the exit message from the client
+ cldb:set_client_pid(User, Client),
Server = spawn_link(client, loop, [Client, User]),
+ %% update the server process_id in the state of the client process,
+ %% so that the client process know directly its counterpart on the
+ %% server
case server:rpc(Client, {change_state, Server}) of
{ok} ->
{ok, Client};
@@ -26,12 +34,12 @@ execute(Client, F) ->
end.
loop(Client, User) ->
- %% mainloop for client modul in server
+ %% mainloop for client modul in server, handle the commands form
+ %% the logged_in client
receive
{register, Name, Password} ->
- case User of
- {user, _, _, _, admin} ->
- execute(Client, fun() -> cldb:register(Name, Password, none) end);
+ case cldb:check_rights(User) of
+ admin -> execute(Client, fun() -> cldb:register(Name, Password, none) end);
_ -> Client ! {error, {no_rights}}
end;
@@ -42,21 +50,30 @@ loop(Client, User) ->
execute(Client, fun() -> media:getVotes(Client) end);
{vote, Artist, Title} ->
- case cldb:decVote(User) of
+ %% only allow vote if user has vote to give away
+ case cldb:dec_vote(User) of
{ok} -> execute(Client, fun() -> media:vote(Artist, Title) end);
_ -> Client ! {error, no_votes_available}
- end;
+ end;
{devote, Artist, Title} ->
- execute(Client, fun() -> media:devote(Artist, Title) end);
+ %% only allow devote if user has vote to give away
+ case cldb:dec_vote(User) of
+ {ok} -> execute(Client, fun() -> media:devote(Artist, Title) end);
+ _ -> Client ! {error, no_votes_available}
+ end;
Cmd ->
+ %% fallback for error messages
Client ! {error, {unknown_command, Cmd}}
end,
loop(Client, User).
register(Client, {Name, Password}) ->
+ %% forward the register messages to the dispatcher (if user is not
+ %% logged in)
dis ! {Client, {register, {Name, Password}}}.
login(Client, {Node, Name, Password}) ->
+ %% forward the login messages to the dispatcher
dis ! {Client, {login, {Node, Name, Password}}}.
diff --git a/server/dispatcher.erl b/server/dispatcher.erl
index 3806ef7..27c2d4c 100644
--- a/server/dispatcher.erl
+++ b/server/dispatcher.erl
@@ -1,7 +1,8 @@
-module(dispatcher).
--export([start/0, handle/2, checkUserExists/1]).
+-export([start/0, handle/2]).
checkUserExists([_|_]) ->
+ %% helper function to check if given array contains at least one element
false;
checkUserExists(_) ->
true.
@@ -12,6 +13,7 @@ start() ->
code:purge(server),
code:load_abs("../common/server"),
+ %% initalize database
cldb:init(),
%% spawn media backend in seperat process
@@ -24,13 +26,15 @@ start() ->
exit(1)
end,
- %% start server (registered as dis)
- %% server-module will call handle if message arrives and init to
- %% initialize the status
- UserExists = checkUserExists(cldb:ask('_', '_')),
+ %% start server (registered as dis, arriving messages will call
+ %% the handle function to get the result)
+ %% The state of the server is true if register is allowed (no user
+ %% exists) -> first created user is admit and after the first
+ %% registration only the admit could register the other user
+ UserExists = checkUserExists(cldb:all()),
try server:start(dis, dispatcher, UserExists) of
true ->
- io:format("Server started: ~w!~n", [UserExists]),
+ io:format("Server started!~n"),
true
catch
_ ->
@@ -39,14 +43,16 @@ start() ->
end.
handle({register, {User, Password}}, true) ->
- io:format("User created: ~s~n", [User]),
- cldb:register(User, Password, admin),
- {{ok, user_created}, false};
+ %% first registration
+ {cldb:register(User, Password, admin), false};
handle({register, _}, false) ->
+ %% if state of the server is false, no registration allowed,
+ %% because the admin user allready exists
{{error, no_rights}, false};
handle({login, {Node, User, Password}}, State) ->
+ %% login user if Password match
case cldb:login(User, Password) of
{ok, UserRow} ->
case client:start(Node, UserRow) of
@@ -59,9 +65,12 @@ handle({login, {Node, User, Password}}, State) ->
{{error, {user_or_password_invalid, Why}}, State}
end;
-handle({'EXIT', _, _}, State) ->
+handle({'EXIT', From, _}, State) ->
+ %% handle the exit messages from the client, so that the client
+ %% logouts if the connection between server and client breaks
+ cldb:logout(From),
State;
handle(Cmd, State) ->
- %% standard command, to find transmission errors
+ %% standard command, to find invalid commands and emit an error
{{error, {unknown_command, Cmd}}, State}.
diff --git a/server/media.erl b/server/media.erl
index 5148edc..14aa53e 100644
--- a/server/media.erl
+++ b/server/media.erl
@@ -112,7 +112,7 @@ play(Artist, Title) ->
io:format("playing: ~s, Artist: ~s~n", [Title, Artist]),
receive
- {Port, {exit_status, 0}} -> cldb:give_votes(cldb:all()), start_playing();
+ {Port, {exit_status, 0}} -> cldb:update_votes(), start_playing();
{Port, {exit_status, S}} -> throw({commandfailed, S})
end.