-module(client).
-export([register/3, login/3, list/0, handle/2, getVotes/0, vote/2, devote/2]).
contains([], _) ->
false;
contains([H|_], H) ->
true;
contains([_|T], Search) ->
contains(T, Search).
checkLogin(Value) ->
checkLogin(Value, contains(registered(), cli)).
checkLogin(Value, Value) ->
true;
checkLogin(_, _) ->
throw({error, login_state}).
buildNode(Server) ->
list_to_atom("distributed_music_system_main_node@" ++ Server).
rpc(Server, Function, Params) ->
rpc:call(buildNode(Server), client, Function, Params).
register(Server, Name, Password) ->
rpc(Server, register, [self(), {Name, Password}]),
receive
{_, Msg} ->
Msg
end.
login(Server, Name, Password) ->
code:purge(server),
code:load_abs("../common/server"),
try checkLogin(false) of
_ ->
rpc(Server, login, [self(), {node(), Name, Password}]),
receive
{ok, {ok, {logged_in, Pid}}} ->
register(cli, Pid),
{ok, logged_in};
{_, Msg} ->
Msg;
Msg ->
Msg
end
catch
{error, login_state} ->
{error, logged_in}
end.
list() ->
try checkLogin(true) of
_ ->
server:rpc(cli, list)
catch
{error, login_state} ->
{error, not_logged_in}
end.
send_to_server(Cmd, Server) ->
Server ! Cmd,
receive
{ok, Msg} ->
{Msg, Server};
Msg ->
{Msg, Server}
end.
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({change_state, NewState}, _) ->
{{ok}, NewState};
handle(Cmd, Server) ->
{{error, {unknown_command, Cmd}}, Server}.
%queries the server for the current votes this client possesses
getVotes() ->
try checkLogin(true) of
_ ->
server:rpc(cli, get_votes)
catch
{error, login_state} ->
{error, not_logged_in}
end.
%positive vote, increments the votes for {Artist, Title} by one
vote(Artist, Title) ->
try checkLogin(true) of
_ ->
server:rpc(cli, {vote, Artist, Title})
catch
{error, login_state} ->
{error, not_logged_in}
end.
%negative vote, decrements the votes for {Artist, Title} by one
devote(Artist, Title) ->
try checkLogin(true) of
_ ->
server:rpc(cli, {devote, Artist, Title})
catch
{error, login_state} ->
{error, not_logged_in}
end.