aboutsummaryrefslogtreecommitdiffstats
path: root/common/server.erl
blob: 713a4436968e835c28ae1d911f936d430c09fa4a (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
%%  Inspired by  "Programming Erlang",
%%  published by The Pragmatic Bookshelf.
%%  Copyrights apply to this code.
%%  We make no guarantees that this code is fit for any purpose.
%%  Visit http://www.pragmaticprogrammer.com/titles/jaerlang for more book information.

-module(server).
-export([start/2, start/3, start_on_node/3, rpc/2]).

start(Name, Mod) ->
    %% like start/3 but call Mod:init() for getting the initial state
    start(Name, Mod, Mod:init()).

start(Name, Mod, State) ->
    %% start a server with the given initial State and register it as
    %% Name
    register(Name, spawn(fun() -> loop(Mod, State) end)).

start_on_node(Node, Mod, State) ->
    %% link start/3 but start the process on the given Node and not
    %% register it (only local processes could be registered)
    spawn(Node, fun() -> loop(Mod, State) end).

wait_response(_, Ref) ->
    %% wait for a specific reponse form the server
    receive
	{Ref, crash} -> exit(rpc);
        {Ref, ok, Response} -> Response
    end.

rpc(Client, Request) ->
    %% make a call to the given client (make a reference to find the
    %% corresponding response)
    Ref = make_ref(),
    Client ! {Ref, self(), Request},
    wait_response(Client, Ref).

loop(Mod, OldState) ->
    %% main lopp
    receive
	%% pattern, that is matched if a message is directly sended to
	%% a server (like register and login called form the client
	%% over the dispatcher)
        {From, Request} ->
            try Mod:handle(Request, OldState) of
                {Response, NewState} ->
                    From ! {ok, Response},
                    loop(Mod, NewState)
            catch
		%% log error if handle function is not working
		%% correctly and report the crash to the sender
		_: Why ->
                    log_the_error(Request, Why),
                    From ! {crash},
                    loop(Mod, OldState)
            end;

	%% pattern is matched if rpc/2 is used, response is send with
	%% the received reference to match the correct response
        {Ref, From, Request} when is_reference(Ref) ->
            try Mod:handle(Request, OldState) of
                {Response, NewState} ->
                    From ! {Ref, ok, Response},
                    loop(Mod, NewState)
            catch
		%% log error if handle function is not working
		%% correctly and report the crash to the sender
                _: Why ->
                    log_the_error(Request, Why),
                    From ! {Ref, crash},
                    loop(Mod, OldState)
            end;

	%% handle messages if a linked process emits an error (no
	%% response to sender nessessary, sender is dead)
	{'EXIT', From, Why} ->
            try Mod:handle({'EXIT', From, Why}, OldState) of
                NewState ->
		    loop(Mod, NewState)
            catch
		%% log error if handle function is not working
		%% correctly and report the crash to the sender
                _: Why ->
                    log_the_error('EXIT', Why),
                    loop(Mod, OldState)
            end
    end.

log_the_error(Request, Why) ->
    %% helper function to log an error
    io:format("Server request ~p caused exception ~p~n", [Request, Why]).