From 4cb05a2b4d5e22a09286718d91d42e141b403e81 Mon Sep 17 00:00:00 2001 From: Jakob Pfender Date: Fri, 15 Oct 2010 10:22:26 +0200 Subject: documentation for server/client.erl --- server/client.erl | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/server/client.erl b/server/client.erl index c5beda7..6c81349 100644 --- a/server/client.erl +++ b/server/client.erl @@ -2,7 +2,7 @@ -export([start/2, loop/2, register/2, login/2]). start(Node, User) -> - %% start linked processes on client and server to get noticed if + %% 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), @@ -13,7 +13,7 @@ start(Node, User) -> Server = spawn_link(client, loop, [Client, User]), %% update the server process_id in the state of the client process, - %% so that the client process know directly its counterpart on the + %% so that the client process knows its direct counterpart on the %% server case server:rpc(Client, {change_state, Server}) of {ok} -> @@ -34,7 +34,7 @@ execute(Client, F) -> end. loop(Client, User) -> - %% mainloop for client modul in server, handle the commands form + %% main loop for client module in server, handle the commands from %% the logged_in client receive {register, Name, Password} -> @@ -50,14 +50,14 @@ loop(Client, User) -> execute(Client, fun() -> cldb:get_votes(User) end); {vote, Artist, Title} -> - %% only allow vote if user has vote to give away + %% 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 devote if user has vote to give away + %% 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} -- cgit v1.2.3 From 7b384b413741a90828a946c7e527f8b2847a17d5 Mon Sep 17 00:00:00 2001 From: Marco Ziener Date: Fri, 15 Oct 2010 10:27:31 +0200 Subject: Comments --- server/cldb.erl | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/server/cldb.erl b/server/cldb.erl index e6f414e..1d4aba0 100644 --- a/server/cldb.erl +++ b/server/cldb.erl @@ -4,12 +4,14 @@ -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) -> @@ -39,6 +41,8 @@ find_user_by_pid(Pid) -> _ -> {error} end. +%% Retrieve all the entrys + all() -> F = fun() -> mnesia:match_object({user, '_', '_', '_', '_', '_', '_'}) @@ -48,6 +52,7 @@ all() -> _ -> {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|_]} -> @@ -68,6 +73,7 @@ login(User, Pwd) when is_list(User) and is_list(Pwd) -> login(_, _) -> {error}. +%% Inorder to log out the client after his process died. set_client_pid(User, Pid) -> case find(User) of {atomic, [UserRow|_]} -> @@ -85,6 +91,7 @@ set_client_pid(User, Pid) -> {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|_]} -> -- cgit v1.2.3 From 0ab2e2a0a98304b28f326d3bad1ceb9a96d60402 Mon Sep 17 00:00:00 2001 From: Jakob Pfender Date: Fri, 15 Oct 2010 10:27:40 +0200 Subject: documentation for server/dispatcher.erl --- server/dispatcher.erl | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/server/dispatcher.erl b/server/dispatcher.erl index 27c2d4c..08b19ec 100644 --- a/server/dispatcher.erl +++ b/server/dispatcher.erl @@ -13,10 +13,10 @@ start() -> code:purge(server), code:load_abs("../common/server"), - %% initalize database + %% initalize client database cldb:init(), - %% spawn media backend in seperat process + %% spawn media backend in seperate process try spawn(media, init, []) of _ -> io:format("Media-Backend started!~n") @@ -26,11 +26,11 @@ start() -> exit(1) end, - %% start server (registered as dis, arriving messages will call + %% start server (registered as "dis", arriving messages will call %% the handle function to get the result) %% The state of the server is true if register is allowed (no user - %% exists) -> first created user is admit and after the first - %% registration only the admit could register the other user + %% exists) -> first created user is admin and after the first + %% registration only the admin can register other users UserExists = checkUserExists(cldb:all()), try server:start(dis, dispatcher, UserExists) of true -> @@ -47,12 +47,12 @@ handle({register, {User, Password}}, true) -> {cldb:register(User, Password, admin), false}; handle({register, _}, false) -> - %% if state of the server is false, no registration allowed, - %% because the admin user allready exists + %% if state of the server is false, registration is not allowed, + %% because the admin user already exists {{error, no_rights}, false}; handle({login, {Node, User, Password}}, State) -> - %% login user if Password match + %% login user if password correct case cldb:login(User, Password) of {ok, UserRow} -> case client:start(Node, UserRow) of @@ -67,10 +67,10 @@ handle({login, {Node, User, Password}}, State) -> handle({'EXIT', From, _}, State) -> %% handle the exit messages from the client, so that the client - %% logouts if the connection between server and client breaks + %% logs out if the connection between server and client breaks cldb:logout(From), State; handle(Cmd, State) -> - %% standard command, to find invalid commands and emit an error + %% standard command to find invalid commands and emit an error {{error, {unknown_command, Cmd}}, State}. -- cgit v1.2.3 From 770cd61fe93347933c957e8da6de499a5dcb64fd Mon Sep 17 00:00:00 2001 From: Jakob Pfender Date: Fri, 15 Oct 2010 10:39:58 +0200 Subject: documentation for media.erl --- server/media.erl | 69 ++++++++++++++++++++++++++------------------------------ 1 file changed, 32 insertions(+), 37 deletions(-) diff --git a/server/media.erl b/server/media.erl index 8c60f10..4710cac 100644 --- a/server/media.erl +++ b/server/media.erl @@ -3,23 +3,23 @@ -define(TESTPATTERN, "../ac/*.mp3"). -define(TIMEOUT, 100000000). -%This module is responsible for the management of the music database. -%It keeps track of playlist items with their current voting and locked/unlocked status -%and automatically selects the next song with the highest vote count to play back. +%% This module is responsible for the management of the music database. +%% It keeps track of playlist items with their current voting and locked/unlocked status +%% and automatically selects the next song with the highest vote count to play back. -% Since we are not willing to calculate and deliver all the id3 tags everytime they are requested, -% we try to get something persistent with mnesia. -% Concerning the parsing of id3tags we use the library id3v2 by Brendon Hogger. For detailed information take a -% look at the header of the library. +%% Since we are not willing to calculate and deliver all the id3 tags everytime they are requested, +%% we try to get something persistent with mnesia. +%% Concerning the parsing of id3tags we use the library id3v2 by Brendon Hogger. For detailed information take a +%% look at the header of the library. -% What is an entry in our database made of? By the way the filepath includes the filename. +%% What is an entry in our database made of? By the way the filepath includes the filename. -record(track, {title, artist, votes, locked, filepath }). -% Before this module becomes usable, we must initialize it with the following steps: -% 1. Initialize the mnesia database and create the table within it. -% 2. Parse the mp3s in the working directory and add them to the database -% 3. Get into a loop so the database can be queried and files can be played. +%% Before this module becomes usable, we must initialize it with the following steps: +%% 1. Initialize the mnesia database and create the table within it. +%% 2. Parse the mp3s in the working directory and add them to the database +%% 3. Get into a loop so the database can be queried and files can be played. init() -> mnesia:create_schema([node()]), @@ -30,8 +30,8 @@ init() -> io:format("Starting to play music~n"), start_playing(). -% uses the algorithm of Brendon Hogger to split the id3-tags and -% inserts the songs into the Database +%% uses the Brendon Hogger's algorithm to split the id3 tags and +%% inserts the songs into the Database read_files([FN|Rest],Total,Fail) -> case id3v2:read_file(FN) of @@ -44,14 +44,14 @@ read_files([FN|Rest],Total,Fail) -> end; read_files([],Total,Fail) -> io:format("Total: ~w, Failed: ~w~n", [Total, Fail]). -% Our loop to play music all the time, play waits on exit_status +%% Our loop to continuously play music, play waits on exit_status start_playing() -> {Artist, Title} = search_best(media:all(), 0,0), play(Artist, Title). -% Basic insertion of entries into the database. Some entries are left out because they are 0 or false. +%% Basic insertion of entries into the database, including vote count and lock status. Some entries are left out because they are 0 or false. insert(Artist, Title, Filepath) -> F = fun() -> @@ -59,10 +59,10 @@ insert(Artist, Title, Filepath) -> end, mnesia:transaction(F). -% Of course we need a query to find out whats actually the most wished for track. -% We will do it by requesting all the records from the database and then iteramte over just taking a look at the vote -% variable, so it is like list of integers. In case no tracks were voted for we just take the first track we find and play it. -% Of course it is locked afterwards so another will be choosen. +%% Of course we need a query to find out what the most requested track is. +%% We accomplish this by requesting all the records from the database and then iterating over them just taking a look at the vote +%% count, so it is like list of integers. In case several tracks share the highest vote count we just take the first track with the highest vote count +%% we found and play it. Of course the song is locked afterwards, so in case no one ever votes the playlist just cycles like a normal playlist. search_best([Head|Rest], Max_Votes, Track) -> @@ -74,14 +74,14 @@ search_best([Head|Rest], Max_Votes, Track) -> search_best([], 0, 0) -> reset_all(all()); search_best([], _, Track) -> {Track#track.artist, Track#track.title}. -% if nothing is playable anymore (because all songs are locked) just reset all songs and start playing again... +%% if nothing is playable anymore (because all songs are locked) just reset all songs and start from the beginning ... reset_all([Head|Rest]) -> unlock(Head#track.artist, Head#track.title), reset_all(Rest); reset_all([]) -> ok. -% We want to query in order to simplify the next calls. +%% We want to query in order to simplify the next calls. ask(Artist, Title) -> F = fun() -> @@ -90,7 +90,7 @@ ask(Artist, Title) -> {atomic, Results} = mnesia:transaction(F), Results. -% Just in case the client is interested in everything we have. +%% Just in case the client is interested in everything we have. all() -> F = fun() -> @@ -99,9 +99,8 @@ all() -> {atomic, Results} = mnesia:transaction(F), Results. -% We want to play mp3s from our database. After we play them they will be locked. -% In practice we are going to set their locked variable to true and spawn a process which will unlock them after a certain time. -% Well this could be considered abuse. +%% We want to play mp3s from our database. After we have played them they will be locked. +%% In practice we are going to set their locked variable to TRUE and spawn a process which will unlock them after a certain time. play(Artist, Title) -> [Head|_] = ask(Artist, Title), @@ -117,11 +116,7 @@ play(Artist, Title) -> end. -% Of course we need a query to find out what the highest voted track is. -% We accomplish this by requesting all the records from the database and then iterate over them, just taking a look at the vote -% variable, so it is like a list of integers. In case no tracks were voted for we just take the first track we found and play it. Of course this song is locked afterwards so a different one will be chosen. - -%votes for a track, i.e. increases its vote count by one. +%% votes for a track, i.e. increases its vote count by one. vote(Artist, Title) -> F = fun() -> [Head|_] = ask(Artist, Title), @@ -131,7 +126,7 @@ vote(Artist, Title) -> end, mnesia:transaction(F). -%votes against a track, i.e. decreases its vote count by one. +%% votes against a track, i.e. decreases its vote count by one. devote(Artist, Title) -> F = fun() -> [Head|_] = ask(Artist, Title), @@ -141,7 +136,7 @@ devote(Artist, Title) -> end, mnesia:transaction(F). -%resets the vote count of selected track to 0 (this is called when the song is played). +%% resets the vote count of selected track to 0 (this is called when the song is played). reset_votes(Artist, Title) -> F = fun() -> [Head|_] = ask(Artist, Title), @@ -150,7 +145,7 @@ reset_votes(Artist, Title) -> end, mnesia:transaction(F). -%locks a song so it can't be played again or voted for for that time. +%% locks a song so it can't be played again for a certain time. lock(Artist, Title) -> F = fun() -> [Head|_] = ask(Artist, Title), @@ -159,7 +154,7 @@ lock(Artist, Title) -> end, mnesia:transaction(F). -%unlocks a song so it can be played and voted for again. +%% unlocks a song so it can be played again. unlock(Artist, Title) -> F = fun() -> [Head|_] = ask(Artist, Title), @@ -168,8 +163,8 @@ unlock(Artist, Title) -> end, mnesia:transaction(F). -% Lock a song if it was just played, after a Timeout it will be unlocked automaticly -% If all songs are locked, all will be unlocked. +%% Lock a song if it was just played, after a timeout it will be unlocked automatically +%% If all songs are locked, they will all be unlocked. lock_process(Artist, Title) -> lock(Artist, Title), receive -- cgit v1.2.3 From 471ff16376d373ff54cbce563f70f01c01f91bba Mon Sep 17 00:00:00 2001 From: Michael Wittig Date: Fri, 15 Oct 2010 10:40:58 +0200 Subject: cldb commented from the bottom --- server/cldb.erl | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/server/cldb.erl b/server/cldb.erl index 1d4aba0..c294471 100644 --- a/server/cldb.erl +++ b/server/cldb.erl @@ -109,7 +109,9 @@ logout(Pid) -> _ -> {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, []} -> @@ -126,10 +128,10 @@ register(User, Pwd, Root) when is_list(User) and is_list(Pwd) -> _ -> {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 -> @@ -154,6 +156,7 @@ inc_vote(User) -> end, mnesia:transaction(F). +%% Return rights of User (admin or nan). check_rights(User) -> {atomic, [UserRow|_]} = find(User), UserRow#user.rights. @@ -166,11 +169,14 @@ update_votes() -> _ -> 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|_]} -> -- cgit v1.2.3 From ebbf2038b2e131cc43eae1d4c98fbd6efb548f0a Mon Sep 17 00:00:00 2001 From: Jakob Pfender Date: Fri, 15 Oct 2010 10:44:30 +0200 Subject: documentation for server/cldb.erl --- server/cldb.erl | 27 ++++++++++++++------------- 1 file changed, 14 insertions(+), 13 deletions(-) diff --git a/server/cldb.erl b/server/cldb.erl index c294471..8d58fb4 100644 --- a/server/cldb.erl +++ b/server/cldb.erl @@ -1,10 +1,10 @@ -% The clientdatabase +%% The client database -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 +%% Initialisation of the mnesia database init() -> mnesia:create_schema([node()]), mnesia:start(), @@ -41,7 +41,7 @@ find_user_by_pid(Pid) -> _ -> {error} end. -%% Retrieve all the entrys +%% Retrieve all entries all() -> F = fun() -> @@ -73,7 +73,7 @@ login(User, Pwd) when is_list(User) and is_list(Pwd) -> login(_, _) -> {error}. -%% Inorder to log out the client after his process died. +%% In order to log out the client after its process has died. set_client_pid(User, Pid) -> case find(User) of {atomic, [UserRow|_]} -> @@ -91,7 +91,7 @@ set_client_pid(User, Pid) -> {error, user_not_found} end. -%% Changing the database to log out a user by PID +%% Change the database to log out a user by PID logout(Pid) -> case find_user_by_pid(Pid) of {atomic, [UserRow|_]} -> @@ -109,9 +109,10 @@ logout(Pid) -> _ -> {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. + +%% Adds an entry into the database for this user. +%% If he is already registered, this will return an error. +%% In order to vote, users arer required to log in after registering. register(User, Pwd, Root) when is_list(User) and is_list(Pwd) -> case find(User) of {atomic, []} -> @@ -131,7 +132,7 @@ register(User, Pwd, Root) when is_list(User) and is_list(Pwd) -> register(_,_,_) -> {error, invalid_username}. -%% functions to de- and increment the amount of votes a user got left. +%% functions to de- and increment the amount of votes a user has left. dec_vote(User) when is_list(User) -> {atomic, [Head|_]} = find(User), if Head#user.votes > 0 -> @@ -156,13 +157,13 @@ inc_vote(User) -> end, mnesia:transaction(F). -%% Return rights of User (admin or nan). +%% Return rights of a 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 + %% after a song every logged in client gets one more vote to spend case find_logged_in_user() of {ok, List} -> give_votes(List); @@ -170,13 +171,13 @@ update_votes() -> end. %% Increment the votes of every user. -%% It will be called when a song has ended. +%% This is 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. +%% Returns the amount of votes a specific user has. get_votes(User) -> case find(User) of {atomic, [UserRow|_]} -> -- cgit v1.2.3