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


                    
                                                                                                                                                       
                                                             
 
                                             
         
                                   
                   
                                                                         
                                          
 
                                              





                                
                
                                                                          
            
                          
 

















                                                                          

                          
        

                                                                         
            




                                     
                                                           












                                                        
 
                   




              
                                                        














                                                 
        
 
                                                 
















                                                              


                                                        

                                                                

                        
                                                                                                                                


                                         
                                                            





                                       
        

                              
 
                                                                      

                                    









                                                   

                             
 
                 
                
                                                





                                               
                                        
                     

                                       
 







                                                            

                                           

                                 

                         
 
                                         






                                     
% The clientdatabase

-module(cldb).
-export([init/0, all/0, find/1, login/2, dec_vote/1, inc_vote/1, register/3, check_rights/1, update_votes/0, logout/1, set_client_pid/2, get_votes/1]).
-record(user, {name, passwd, votes, logged_in, pid, rights}).

%% The initialisations of the mnesia database
init() ->
    mnesia:create_schema([node()]),
    mnesia:start(),
    mnesia:create_table(user, [{attributes, record_info(fields, user)}]),
    io:format("Userdb up and running \n").

%% The basic search operations on the database
find(User) when is_list(User) ->
    find(User, '_');
find(User) ->
    find(User#user.name, '_').

find(User, Pwd) ->
    F = fun() ->
		mnesia:match_object({user, User, Pwd, '_', '_', '_', '_'})
        end,
    mnesia:transaction(F).

find_logged_in_user() ->
    F = fun() ->
		mnesia:match_object({user, '_', '_', '_', true, '_', '_'})
        end,
    case mnesia:transaction(F) of
	{atomic, List} -> {ok, List};
	_ -> {error}
    end.

find_user_by_pid(Pid) ->
    F = fun() ->
		mnesia:match_object({user, '_', '_', '_', '_', Pid, '_'})
        end,
    case mnesia:transaction(F) of
	{atomic, List} -> {ok, List};
	_ -> {error}
    end.

%% Retrieve all the entrys

all() ->
    F = fun() ->
		mnesia:match_object({user, '_', '_', '_', '_', '_', '_'})
        end,
    case mnesia:transaction(F) of
	{atomic, List} -> {ok, List};
	_ -> {error}
    end.

%% Perform the login operation of a user into the database.
login(User, Pwd) when is_list(User) and is_list(Pwd) ->
    case find(User, Pwd) of
	{atomic, [UserRow|_]} ->
	    NewUserRow = UserRow#user{logged_in = true},
	    F = fun() ->
			mnesia:write(NewUserRow)
		end,
	    case mnesia:transaction(F) of
		{atomic, ok} ->
		    {ok, NewUserRow};
		{atomic, Why} ->
		    {error, Why}
	    end;

	_-> {error}
    end;

login(_, _) ->
    {error}.

%% Inorder to log out the client after his process died.
set_client_pid(User, Pid) ->
    case find(User) of
	{atomic, [UserRow|_]} ->
	    NewUserRow = UserRow#user{pid = Pid},
	    F = fun() ->
			mnesia:write(NewUserRow)
		end,
	    case mnesia:transaction(F) of
		{atomic, ok} ->
		    {ok, pid_updated};
		{atomic, Why} ->
		    {error, Why}
	    end;
	_ ->
	    {error, user_not_found}
    end.

%% Changing the database to log out a user by PID
logout(Pid) ->
    case find_user_by_pid(Pid) of
	{atomic, [UserRow|_]} ->
	    F = fun() ->
			New = UserRow#user{logged_in = false},
			mnesia:write(New)
		end,
	    case mnesia:transaction(F) of
		{atomic, ok} ->
		    {ok, logged_out};
		{atomic, Why} ->
		    {error, Why}
	    end;

	_ ->
	    {error, invalid_user}
    end.
%% Makes an entry into the database for this user.
%% If he is already registerd an error will be returned.
%% In order to vote it is needed to login afterwards.
register(User, Pwd, Root) when is_list(User) and is_list(Pwd) ->
    case find(User) of
	{atomic, []} ->
	    F = fun() ->
			mnesia:write(#user{name = User, passwd = Pwd, votes = 5, logged_in = false, pid = undef, rights = Root})
		end,
	    case mnesia:transaction(F) of
		{atomic, ok} ->
		    io:format("User created: ~s~n", [User]),
		    {ok, user_created};
		{atomic, Why} ->
		    {error, Why}
	    end;
	_ ->
	    {error, duplicated_user}
    end;
register(_,_,_) ->
    {error, invalid_username}.

%% functions to de- and increment the amount of votes a user got left.
dec_vote(User) when is_list(User) ->
    {atomic, [Head|_]} = find(User),
    if Head#user.votes > 0 ->
        F = fun() ->
                    Votes = Head#user.votes - 1,
                    New = Head#user{votes = Votes},
                    mnesia:write(New)
            end,
        mnesia:transaction(F),
        {ok};
        true -> {error}
    end;
dec_vote(User) ->
    dec_vote(User#user.name).

inc_vote(User) ->
    F = fun() ->
                {atomic, [Head|_]} = find(User),
                Votes = Head#user.votes + 1,
                New = Head#user{votes = Votes},
                mnesia:write(New)
        end,
    mnesia:transaction(F).

%% Return rights of User (admin or nan).
check_rights(User) ->
    {atomic, [UserRow|_]} = find(User),
    UserRow#user.rights.

update_votes() ->
    %% after a song every logged_in client gets on more vote
    case find_logged_in_user() of
	{ok, List} ->
	    give_votes(List);
	_ -> error
    end.

%% Increment the votes of every user. 
%% It will be called when a song has ended.
give_votes([User|Rest]) ->
	inc_vote(User#user.name),
	give_votes(Rest);
give_votes([]) -> ok.

%% Returns the amount of votes from User.
get_votes(User) ->
    case find(User) of
	{atomic, [UserRow|_]} ->
	    {ok, UserRow#user.votes};
	_ ->
	    {error, user_not_found}
    end.