aboutsummaryrefslogtreecommitdiffstats
path: root/server/media.erl
blob: 0a992755dc6b3960b00236afc940d3528e485e5e (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
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
-module(media).
-export([init/0,insert/3, ask/2, all/0, play/3, vote/2, devote/2]).
-define(TESTPATTERN, "../ac/*.mp3").

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

% With which application do we play mp3s?

player(path) ->
    {ok, ["/usr/bin/env", "mplayer", "-quiet", path]}.

% Before this module becomes usable, we must initialize it with the following steps:
% 1. Initialize the mnesiadatabase 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 actually queried and files can be played.

init() ->
    mnesia:create_schema([node()]),
    mnesia:start(),
    mnesia:create_table(track, [{index, [y]}, {attributes, record_info(fields, track)}]),
    read_files(filelib:wildcard(?TESTPATTERN),0,0),
    io:format("Initialisation of mnesia successful.\n"),
    start_playing().

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

% Basic insertion of entrys into the database. Some entries are left out because they are 0 or false.

% Our Runloop to play music all the time, play waits on exit_status
start_playing() ->
	{Artist, Title} = search_best(),
	play(Artist, Title, "muh").

insert(Artist, Title, Filepath) ->
    F = fun() ->
                mnesia:write(#track{artist = Artist, title = Title, votes = 0, locked = false, filepath = Filepath})
        end,
    mnesia:transaction(F).

search_best() -> {"Allison Crowe", "Northern Lights"}.


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

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 become 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, Callback) ->
    [Head|_] = ask(Artist, Title),
    {_, _, _, _, _, Fp} = Head,
    Port = erlang:open_port({spawn_executable, "/usr/bin/mplayer"}, [{args, [Fp]}, exit_status]),
    receive
		{Port, {exit_status, 0}} -> start_playing();
		{Port, {exit_status, S}} -> throw({commandfailed, S})
    end.


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

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

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

top() ->
    All = all().