aboutsummaryrefslogblamecommitdiffstats
path: root/server/client.erl
blob: 03f627651dbcdc54a721f0180eb11e75f627b536 (plain) (tree)
1
2
3
4
5
6
7
8
9
                
                           
 
                    
                                                                   
                                                                  
                                  
                                                       
                 


                                                                      
                                                      
 
                                                                       
                                                                     
             
                                                      
               
                         

                                         
        
 










                                         
                     
                                                                      
                           
           
                                     

                                                                                           


                                                  
               
                                                      
 
                    
                                                               

                                
                                                              
                                       

                                                                                
                

                                  
                                                                



                                                                                  
 
              
                                          

                                                    
                       
-module(client).
-export([start/2, loop/2]).

start(Node, User) ->
    %% start linked processes on client and server to get notice if
    %% client disconnects and properly handle the logged in status
    process_flag(trap_exit, true),
    Client = server:start_on_node(Node, client, undef),
    link(Client),
    %% store the client pid in the client database to find the correct
    %% user on the exit message from the client
    cldb:set_client_pid(User, Client),
    Server = spawn_link(client, loop, [Client, User]),

    %% update the server process_id in the state of the client process,
    %% so that the client process knows its direct counterpart on the
    %% server
    case server:rpc(Client, {change_state, Server}) of
	{ok} ->
	    {ok, Client};
	Why ->
	    {error, {unknown_error, Why}}
    end.

execute(Client, F) ->
    %% execute F() with error handling
    %% (sends error message on exception)
    try F() of
	Result ->
	    Client ! {ok, Result}
    catch
	_: Why ->
	    Client ! {error, Why}
    end.

loop(Client, User) ->
    %% main loop for client module in server, handle the commands from
    %% the logged_in client
    receive
	{register, Name, Password} ->
	    case cldb:check_rights(User) of
		admin -> execute(Client, fun() -> cldb:register(Name, Password, none) end);
		_ -> Client ! {error, {no_rights}}
	    end;

	list ->
	    execute(Client, fun() -> media:all() end);

	get_votes ->
	    execute(Client, fun() -> cldb:get_votes(User) end);

	{vote, Artist, Title} ->
	    %% only allow voting if user has at least one vote
	    case cldb:dec_vote(User) of
	        {ok} -> execute(Client, fun() -> media:vote(Artist, Title) end);
	        _ -> Client ! {error, no_votes_available}
	    end;

	{devote, Artist, Title} ->
	    %% only allow devoting if user has at least one vote
	    case cldb:dec_vote(User) of
	        {ok} -> execute(Client, fun() -> media:devote(Artist, Title) end);
	        _ -> Client ! {error, no_votes_available}
	    end;

	Cmd ->
	    %% fallback for error messages
	    Client ! {error, {unknown_command, Cmd}}
    end,
    loop(Client, User).