aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorMarco Ziener <mziener@lavabit.com>2010-10-14 11:44:48 +0200
committerMarco Ziener <mziener@lavabit.com>2010-10-14 11:44:48 +0200
commit7f7862efc17932637234f54e4faa503ed356b4ce (patch)
tree2e13e53a6fdfcb2c42de26a35e37e3dc67f08819
parent45c0805771f78696727741b190787d48f4f0f462 (diff)
parent8bd7f77de295d1d89edb95d6f9f869f1fedfdffc (diff)
downloaderlang-7f7862efc17932637234f54e4faa503ed356b4ce.tar.gz
erlang-7f7862efc17932637234f54e4faa503ed356b4ce.tar.xz
erlang-7f7862efc17932637234f54e4faa503ed356b4ce.zip
Merge branch 'master' of ssh://git.animux.de/erlang
-rw-r--r--client/client.erl60
-rw-r--r--media.erl63
-rw-r--r--server/client.erl25
3 files changed, 47 insertions, 101 deletions
diff --git a/client/client.erl b/client/client.erl
index 67be4ee..46ef59f 100644
--- a/client/client.erl
+++ b/client/client.erl
@@ -1,5 +1,5 @@
-module(client).
--export([register/3, login/3, list/0, handle/2]).
+-export([register/3, login/3, list/0, handle/2, getVotes/0, vote/2, devote/2]).
contains([], _) ->
false;
@@ -58,14 +58,23 @@ list() ->
{error, not_logged_in}
end.
-handle(list, Server) ->
- Server ! list,
+send_to_server(Cmd, Server) ->
+ Server ! Cmd,
receive
{ok, Msg} ->
{Msg, Server};
Msg ->
{Msg, Server}
- end;
+ end.
+
+handle(list, Server) ->
+ send_to_server(list, Server);
+handle(get_votes, Server) ->
+ send_to_server(get_votes, Server);
+handle({vote, Artist, Title}, Server) ->
+ send_to_server({vote, Artist, Title}, Server);
+handle({devote, Artist, Title}, Server) ->
+ send_to_server({devote, Artist, Title}, Server);
handle({change_state, NewState}, _) ->
{{ok}, NewState};
@@ -74,31 +83,32 @@ handle(Cmd, Server) ->
{{error, {unknown_command, Cmd}}, Server}.
%queries the server for the current votes this client possesses
-getVotes(Server) ->
- rpc(Server, getVotes, self()),
- receive
- Msg ->
- Msg
- end.
+getVotes() ->
+ try checkLogin(true) of
+ _ ->
+ server:rpc(cli, get_votes)
+ catch
+ {error, login_state} ->
+ {error, not_logged_in}
+ end.
%positive vote, increments the votes for {Artist, Title} by one
vote(Artist, Title) ->
- rpc(Server, vote, [Artist, Title]),
- receive
- {_, ok, Msg} ->
- Msg;
- {_, error, Msg} ->
- {error, Msg}
- end.
+ try checkLogin(true) of
+ _ ->
+ server:rpc(cli, {vote, Artist, Title})
+ catch
+ {error, login_state} ->
+ {error, not_logged_in}
+ end.
%negative vote, decrements the votes for {Artist, Title} by one
devote(Artist, Title) ->
- rpc(Server, devote, [Artist, Title]),
- receive
- {_, ok, Msg} ->
- Msg;
- {_, error, Msg} ->
- {error, Msg}
- end.
-
+ try checkLogin(true) of
+ _ ->
+ server:rpc(cli, {devote, Artist, Title})
+ catch
+ {error, login_state} ->
+ {error, not_logged_in}
+ end.
diff --git a/media.erl b/media.erl
deleted file mode 100644
index 1ff2f23..0000000
--- a/media.erl
+++ /dev/null
@@ -1,63 +0,0 @@
--module(media).
--export([init/0,insert/3, ask/2, all/0]).
-
-% 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, {artist, title, 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, [{attributes, record_info(fields, track)}]),
- io:format("Initialisation of mnesia successful.\n").
-
-% 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})
- end,
- mnesia:transaction(F).
-
-% We want to query in order to simplify the next calls.
-ask(Artist, Title) ->
- F = fun() ->
- mnesia:match_object({track, Artist, Title, '_', '_', '_'})
- end,
- {atomic, Results} = mnesia:transaction(F),
- Results.
-
-% Just in case the client is interested in everything we got.
-
-all() ->
- F = fun() ->
- mnesia:match({track, '_','_','_','_','_'})
- end,
- {atomic, Results} = mnesia:transaction(F),
- Results.
-
-% We want to play mp3s from our database.
-
-play(Artist, Title, Callback) ->
- [Head|_] = ask(Artist, Title),
- {_, artist, title, _, _, fp} = Head,
- Cmd = "mplayer -quiet " ++ fp,
- Port = erlang:open_port({spawn, Cmd}, [exit_status]).
-
-% We want to execute commands locally
-
diff --git a/server/client.erl b/server/client.erl
index bf8bc22..ce7c99b 100644
--- a/server/client.erl
+++ b/server/client.erl
@@ -20,6 +20,18 @@ loop(Client) ->
Client ! {ok, {foo}},
loop(Client);
+ get_votes ->
+ Client ! {ok, media:getVotes(Client)},
+ loop(Client);
+
+ {vote, Artist, Title} ->
+ Client ! media:vote(Artist, Title),
+ loop(Client);
+
+ {devote, Artist, Title} ->
+ Client ! media:devote(Artist, Title),
+ loop(Client);
+
Cmd ->
Client ! {error, {unknown_command, Cmd}},
loop(Client)
@@ -30,16 +42,3 @@ register(Client, {Name, Password}) ->
login(Client, {Node, Name, Password}) ->
dis ! {Client, {login, {Node, Name, Password}}}.
-
-getVotes() ->
- media:getVotes(self()),
- receive
- Msg ->
- Client ! Msg
- end.
-
-vote(Artist,Title) ->
- media:vote(Artist, Title).
-
-devote(Artist,Title) ->
- media:devote(Artist, Title).