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



                                                                                       






                                                                                                               
                                                          
 
                                                                                    
                                                                   
                                                                         
                                                                            



                                   
                                                                           
                                                   





                                                                 
 
                                   


                                                          
                                                         





                                                                                 
                                                                
 
                  
                                                        
                            
 
 
                                                                                                      
 





                                                                                                                    




                                                                                                                               
 





                                                                              
                                          
                                                                     
 
                                                                                                               
 
                         


                                                    
 
                                                       
 
                     
                
                                                                          

                                              

            
                                                              


                
                                                                 



                                              
                                                                                 

                                                                                                                                
 
                      
                                  
                                        
                                                                                                 
                               
                                                
    
                                                            
           
                                                                                 
                                                                     
    
 
 


                                                                                                                                                                                                             
 
                                                         








                                                
                                                             








                                                
                                                                                       







                                              
                                                                     


                                              
                                                
                                 


                          
                                                        


                                              
                                                 
                                 


                          

                                                                                    
                              

                        



                                        

                
-module(media).
-export([init/0,insert/3, ask/2, all/0, play/2, vote/2, devote/2, lock_process/2]).
-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.

% 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.

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

init() ->
    mnesia:create_schema([node()]),
    mnesia:start(),
    mnesia:create_table(track, [{attributes, record_info(fields, track)}]),
    read_files(filelib:wildcard(?TESTPATTERN),0,0),
    io:format("Initialisation of mnesia successful.~n"),
    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

read_files([FN|Rest],Total,Fail) ->
	case id3v2:read_file(FN) of
	{ok, Props} -> % insert entry into mnesia DB
		Artist = proplists:get_value(tpe1, Props),
	   	Title = proplists:get_value(tit2, Props),
		insert(bitstring_to_list(Artist), bitstring_to_list(Title), FN),
		read_files(Rest, Total+1, Fail);
	not_found -> read_files(Rest, Total+1, Fail+1)
	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

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.

insert(Artist, Title, Filepath) ->
    F = fun() ->
                mnesia:write(#track{artist = Artist, title = Title, votes = 0, locked = false, filepath = 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.


search_best([Head|Rest], Max_Votes, Track) -> 
	if 
	((Max_Votes =<  Head#track.votes) and (Head#track.locked == false)) ->
		search_best(Rest, Head#track.votes, Head);
	true -> search_best(Rest, Max_Votes, Track)
	end;
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...

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.

ask(Artist, Title) ->
    F = fun() ->
		mnesia:match_object({track, Title, Artist, '_', '_', '_'})
	end,
    {atomic, Results} = mnesia:transaction(F),
    Results.

% Just in case the client is interested in everything we have.

all() ->
    F = fun() ->
                mnesia:match_object({track, '_','_','_','_','_'})
        end,
    {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.

play(Artist, Title) ->
    [Head|_] = ask(Artist, Title),
    {_, Title, Artist, _, _, Fp} = Head,
    Port = erlang:open_port({spawn_executable, "/usr/bin/mplayer"}, [{args, [Fp]}, exit_status]),
    reset_votes(Artist, Title),
    spawn(media, lock_process, [Artist, Title]),
    
    io:format("playing: ~s, Artist: ~s~n", [Title, Artist]),
    receive
		{Port, {exit_status, 0}} -> cldb:update_votes(), start_playing();
		{Port, {exit_status, S}} -> throw({commandfailed, S})
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.
vote(Artist, Title) ->
    F = fun() ->
                [Head|_] = ask(Artist, Title),
                Votes = Head#track.votes + 1,
                New = Head#track{votes = Votes},
                mnesia:write(New)
        end,
    mnesia:transaction(F).

%votes against a track, i.e. decreases its vote count by one.
devote(Artist, Title) ->
    F = fun() ->
                [Head|_] = ask(Artist, Title),
                Votes = Head#track.votes - 1,
                New = Head#track{votes = Votes},
                mnesia:write(New)
        end,
    mnesia:transaction(F).

%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),
                New = Head#track{votes = 0},
                mnesia:write(New)
        end,
    mnesia:transaction(F).
    
%locks a song so it can't be played again or voted for for that time.
lock(Artist, Title) ->
    F = fun() ->
                [Head|_] = ask(Artist, Title),
                New = Head#track{locked = true},
                mnesia:write(New)
        end,
    mnesia:transaction(F).

%unlocks a song so it can be played and voted for again.
unlock(Artist, Title) ->
    F = fun() ->
                [Head|_] = ask(Artist, Title),
                New = Head#track{locked = false},
                mnesia:write(New)
        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_process(Artist, Title) ->
    lock(Artist, Title),
    receive 

    after ?TIMEOUT ->
              unlock(Artist, Title) end.