aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--client/client.erl82
-rw-r--r--server/client.erl11
-rw-r--r--server/dispatcher.erl12
3 files changed, 60 insertions, 45 deletions
diff --git a/client/client.erl b/client/client.erl
index b72b5ee..43dbfc6 100644
--- a/client/client.erl
+++ b/client/client.erl
@@ -12,49 +12,53 @@ checkLogin(Value) ->
end.
buildNode(Server) ->
+ %% build the node string of the server by using the hostname
list_to_atom("distributed_music_system_main_node@" ++ Server).
rpc(Server, Function, Params) ->
- rpc:call(buildNode(Server), client, Function, Params).
+ %% shortcut for calling a function from the server
+ rpc:call(buildNode(Server), dispatcher, Function, Params).
-wait_for_reply() ->
- receive
- {_, Msg} ->
- Msg;
- Why -> Why
- after 3000 ->
- {error, timeout}
- end.
-
-register(Name, Password) ->
- try checkLogin(true) of
- _ ->
- server:rpc(cli, {register, Name, Password})
- catch
- {error, login_state} ->
- {error, not_logged_in}
- end.
-
-%register the client with the server
register(Server, Name, Password) ->
+ %% check if client is not logged in (if client is logged in,
+ %% register/2 should be used)
try checkLogin(false) of
_ ->
+ %% register a new user account on the server
rpc(Server, register, [self(), {Name, Password}])
catch
{error, login_state} ->
{error, logged_in}
end,
- wait_for_reply().
-%login to the server
+ %% wait for response
+ receive
+ {_, Msg} ->
+ Msg;
+ Why -> Why
+ after 3000 ->
+ %% protect from waiting endless for server response (maybe
+ %% if used wrong hostname or something like that)
+ {error, timeout}
+ end.
+
login(Server, Name, Password) ->
+ %% load common/server (used by server and client)
code:purge(server),
code:load_abs("../common/server"),
+ %% check if client is not logged in (if client is logged in, it
+ %% would make no sense to login again)
try checkLogin(false) of
_ ->
+ %% login to the server
rpc(Server, login, [self(), {node(), Name, Password}]),
receive
+ %% the server returns the Pid of the process on the
+ %% client, that should handle the communication
+ %% between server and client, the process is started
+ %% by the server on the client node and registered
+ %% here as cli process
{ok, {ok, {logged_in, Pid}}} ->
erlang:register(cli, Pid),
{ok, logged_in};
@@ -63,6 +67,9 @@ login(Server, Name, Password) ->
Msg ->
Msg
after 3000 ->
+ %% protect from waiting endless for server
+ %% response (maybe if used wrong hostname or
+ %% something like that)
{error, timeout}
end
catch
@@ -70,17 +77,10 @@ login(Server, Name, Password) ->
{error, logged_in}
end.
-%request the playlist from the server
-list() ->
- try checkLogin(true) of
- _ ->
- server:rpc(cli, list)
- catch
- {error, login_state} ->
- {error, not_logged_in}
- end.
-
send_to_server(Cmd, Server) ->
+ %% generic helper function for sending a message to the given
+ %% server and wait for a response from the server (the function
+ %% returns a tupel of the reponse and the server)
Server ! Cmd,
receive
{ok, Msg} ->
@@ -89,6 +89,8 @@ send_to_server(Cmd, Server) ->
{Msg, Server}
end.
+%% the handle functions are called from the process started by the
+%% process started by the server on login and registered as cli
handle(list, Server) ->
send_to_server(list, Server);
handle(get_votes, Server) ->
@@ -99,15 +101,20 @@ handle({devote, Artist, Title}, Server) ->
send_to_server({devote, Artist, Title}, Server);
handle({register, Name, Password}, Server) ->
send_to_server({register, Name, Password}, Server);
+
handle({change_state, NewState}, _) ->
+ %% change the state of the server (used from the client process on
+ %% the server to set the process id, so that the client could send
+ %% messages directly to the server
{{ok}, NewState};
handle(Cmd, Server) ->
+ %% fallback to return a error message for not existing commands
{{error, {unknown_command, Cmd}}, Server}.
try_logged_in_rpc(Rpc) ->
- %% tries to execute an rpc for logged in user and returns error
- %% message if user is not logged in
+ %% helper function that tries to execute an rpc for logged in user
+ %% and returns error message if user is not logged in
try checkLogin(true) of
_ ->
server:rpc(cli, Rpc)
@@ -116,6 +123,10 @@ try_logged_in_rpc(Rpc) ->
{error, not_logged_in}
end.
+list() ->
+ %% request the playlist from the server
+ try_logged_in_rpc(list).
+
getVotes() ->
%% queries the server for the current votes this client possesses
try_logged_in_rpc(get_votes).
@@ -128,3 +139,6 @@ devote(Artist, Title) ->
%% negative vote, decrements the votes for {Artist, Title} by one
try_logged_in_rpc({devote, Artist, Title}).
+register(Name, Password) ->
+ %% register a new user (used by the admin)
+ try_logged_in_rpc({register, Name, Password}).
diff --git a/server/client.erl b/server/client.erl
index 6c81349..03f6276 100644
--- a/server/client.erl
+++ b/server/client.erl
@@ -1,5 +1,5 @@
-module(client).
--export([start/2, loop/2, register/2, login/2]).
+-export([start/2, loop/2]).
start(Node, User) ->
%% start linked processes on client and server to get notice if
@@ -68,12 +68,3 @@ loop(Client, User) ->
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 08b19ec..a0a0459 100644
--- a/server/dispatcher.erl
+++ b/server/dispatcher.erl
@@ -1,5 +1,5 @@
-module(dispatcher).
--export([start/0, handle/2]).
+-export([start/0, handle/2, register/2, login/2]).
checkUserExists([_|_]) ->
%% helper function to check if given array contains at least one element
@@ -74,3 +74,13 @@ handle({'EXIT', From, _}, State) ->
handle(Cmd, State) ->
%% standard command to find invalid commands and emit an error
{{error, {unknown_command, Cmd}}, State}.
+
+register(Client, {Name, Password}) ->
+ %% forward the register messages to the dispatcher (called form
+ %% the client)
+ dis ! {Client, {register, {Name, Password}}}.
+
+login(Client, {Node, Name, Password}) ->
+ %% forward the login messages to the dispatcher (called form the
+ %% client)
+ dis ! {Client, {login, {Node, Name, Password}}}.