aboutsummaryrefslogtreecommitdiffstats
path: root/server
diff options
context:
space:
mode:
authorMichael Wittig <michael.wittig@fu-berlin.de>2010-10-14 14:35:44 +0200
committerMichael Wittig <michael.wittig@fu-berlin.de>2010-10-14 14:35:44 +0200
commitc840d5e566dfe3d1c24e183ba558e02a7075a36d (patch)
treeed4c9b31b0f055064219012e70b1902e15bc82aa /server
parent1f3f1443259937eb08de6c001791b28514ba67d9 (diff)
parent6c2aac98c6647ed3bec434788c18370e12fff117 (diff)
downloaderlang-c840d5e566dfe3d1c24e183ba558e02a7075a36d.tar.gz
erlang-c840d5e566dfe3d1c24e183ba558e02a7075a36d.tar.xz
erlang-c840d5e566dfe3d1c24e183ba558e02a7075a36d.zip
Merge branch 'master' of ssh://git.animux.de/erlang
Diffstat (limited to 'server')
-rw-r--r--server/client.erl46
-rw-r--r--server/dispatcher.erl2
-rw-r--r--server/media.erl45
3 files changed, 72 insertions, 21 deletions
diff --git a/server/client.erl b/server/client.erl
index ce7c99b..333df4a 100644
--- a/server/client.erl
+++ b/server/client.erl
@@ -10,32 +10,52 @@ start(Node) ->
case server:rpc(Client, {change_state, Server}) of
{ok} ->
{ok, Client};
- _ ->
- {error, unknown_error}
+ Why ->
+ {error, {unknown_error, Why}}
end.
loop(Client) ->
receive
list ->
- Client ! {ok, {foo}},
- loop(Client);
+ try media:all() of
+ Result ->
+ Client ! {ok, Result}
+ catch
+ _: Why ->
+ Client ! {error, Why}
+ end;
get_votes ->
- Client ! {ok, media:getVotes(Client)},
- loop(Client);
+ try media:getVotes(Client) of
+ Result ->
+ Client ! {ok, Result}
+ catch
+ _: Why ->
+ Client ! {error, Why}
+ end;
{vote, Artist, Title} ->
- Client ! media:vote(Artist, Title),
- loop(Client);
+ try media:vote(Artist, Title) of
+ Result ->
+ Client ! {ok, Result}
+ catch
+ _: Why ->
+ Client ! {error, Why}
+ end;
{devote, Artist, Title} ->
- Client ! media:devote(Artist, Title),
- loop(Client);
+ try media:devote(Artist, Title) of
+ Result ->
+ Client ! {ok, Result}
+ catch
+ _: Why ->
+ Client ! {error, Why}
+ end;
Cmd ->
- Client ! {error, {unknown_command, Cmd}},
- loop(Client)
- end.
+ Client ! {error, {unknown_command, Cmd}}
+ end,
+ loop(Client).
register(Client, {Name, Password}) ->
dis ! {Client, {register, {Name, Password}}}.
diff --git a/server/dispatcher.erl b/server/dispatcher.erl
index 4f1f58b..9b4c61b 100644
--- a/server/dispatcher.erl
+++ b/server/dispatcher.erl
@@ -5,6 +5,8 @@ start() ->
code:purge(server),
code:load_abs("../common/server"),
+ spawn(media, init, []),
+
case server:start(dis, dispatcher) of
true ->
io:format("Server started... ~n"),
diff --git a/server/media.erl b/server/media.erl
index 8921724..d20c8e9 100644
--- a/server/media.erl
+++ b/server/media.erl
@@ -1,6 +1,7 @@
-module(media).
-export([init/0,insert/3, ask/2, all/0, play/3, vote/2, devote/2]).
-define(TESTPATTERN, "../ac/*.mp3").
+-define(TIMEOUT, 10000).
% 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.
@@ -22,28 +23,31 @@ init() ->
mnesia:create_table(track, [{attributes, record_info(fields, track)}]),
read_files(filelib:wildcard(?TESTPATTERN),0,0),
io:format("Initialisation of mnesia successful.\n"),
- start_playing().
+ start_playing(),
+ io:format("Starting to play music\n").
-read_files([FN|Rest],Total,Fail) ->
+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),
+ 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(media:all(), 0,0),
play(Artist, Title, "muh").
-%insert The Track into the database
+% Basic insertion of entrys 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})
@@ -104,7 +108,7 @@ play(Artist, Title, Callback) ->
% 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.
+% 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() ->
@@ -124,5 +128,30 @@ devote(Artist, Title) ->
end,
mnesia:transaction(F).
-top() ->
- All = all().
+lock(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).
+
+unlock(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).
+
+lock_prozess(Artist, Title) ->
+ lock(Artist, Title),
+ receive
+
+ after ?TIMEOUT ->
+ unlock(Artist, Title) end.
+
+
+