-module(client).
-export([register/2, register/3, login/3, list/0, handle/2, getVotes/0, vote/2, devote/2]).
checkLogin(Value) ->
%% check if user meets the requirements to be logged in or not by
%% logging in to the registered processes and checking if the cli
%% process is registered
LoggedIn = lists:member(cli, registered()),
if LoggedIn == Value ->
true;
true -> throw({error, login_state})
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, Params) ->
%% shortcut for sending something to the dispatcher on the server
{dis, buildNode(Server)} ! {self(), Params}.
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, {Name, Password}})
catch
{error, login_state} ->
{error, logged_in}
end,
%% 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, {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};
{_, Msg} ->
Msg;
Msg ->
Msg
after 3000 ->
%% protect from waiting endless for server
%% response (maybe if used wrong hostname or
%% something like that)
{error, timeout}
end
catch
{error, login_state} ->
{error, 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} ->
{Msg, Server};
Msg ->
{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) ->
send_to_server(get_votes, Server);
handle({vote, Artist, Title}, Server) ->
send_to_server({vote, Artist, Title}, Server);
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) ->
%% 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)
catch
{error, login_state} ->
{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).
vote(Artist, Title) ->
%% positive vote, increments the votes for {Artist, Title} by one
try_logged_in_rpc({vote, Artist, Title}).
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}).