aboutsummaryrefslogtreecommitdiffstats
path: root/client/client.erl
blob: f8d5de2924cac82c72f38ca2aa5489839c130fae (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
-module(client).
-export([register/3, login/3, list/0, handle/3]).

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
	{_, ok, Msg} ->
	    Msg;
	{_, error, Msg} ->
	    Msg
    end.

login(Server, Name, Password) ->
    try checkLogin(false) of
	_ ->
	    rpc(Server, login, [self(), {Name, Password}]),
	    receive
		{_, ok, {ok, {logged_in, Client}}} ->
		    code:purge(server),
		    code:load_abs("../common/server"),
		    case server:start(cli, client, Client) of
			true ->
			    {ok, logged_in};
			_ ->
			    {error, unable_to_login}
		    end;
		{_, error, Msg} ->
		    Msg;
		Msg ->
		    Msg
	    end
    catch
	{error, login_state} ->
	    {error, logged_in}
    end.

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

list() ->
    try checkLogin(true) of
	_ ->
	    cli ! {self(), list},
	    receive
		{_, ok, Msg} ->
		    Msg;
		{_, error, Msg} ->
		    {error, Msg};
		Msg ->
		    {error, Msg}
	    end
    catch
	{error, login_state} ->
	    {error, not_logged_in}
    end.

handle(Cli, list, Client) ->
    Client ! {list},
    receive
	{_, {ok, List}} ->
	    io:format("List: ~w~n", List),
	    {{ok}, Client}
    end;

handle(Cli, {test, X}, Client) ->
    Client ! {X},
    receive
	Msg ->
	    io:format("Test: ~w~n~n", [Msg]),
	    {{ok}, Client}
    end;

handle(_, Cmd, Client) ->
    {{error, {unknown_command, Cmd}}, Client}.