aboutsummaryrefslogtreecommitdiffstats
path: root/client/client.erl
blob: b72b5eeb45b51f88e175ba32170a9333352a2e3f (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
-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) ->
    list_to_atom("distributed_music_system_main_node@" ++ Server).

rpc(Server, Function, Params) ->
    rpc:call(buildNode(Server), client, 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) ->
    try checkLogin(false) of
	_ ->
	    rpc(Server, register, [self(), {Name, Password}])
    catch
	{error, login_state} ->
	    {error, logged_in}
    end,
    wait_for_reply().

%login to the server
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}}} ->
		    erlang:register(cli, Pid),
		    {ok, logged_in};
		{_, Msg} ->
		    Msg;
		Msg ->
		    Msg
	    after 3000 ->
		    {error, timeout}
	    end
    catch
	{error, login_state} ->
	    {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) ->
    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({register, Name, Password}, Server) ->
    send_to_server({register, Name, Password}, Server);
handle({change_state, NewState}, _) ->
    {{ok}, NewState};

handle(Cmd, Server) ->
    {{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
    try checkLogin(true) of
	_ ->
	    server:rpc(cli, Rpc)
    catch
	{error, login_state} ->
	    {error, not_logged_in}
    end.

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}).