hop-2012/experiments/erlang/src/hop_factory.erl

81 lines
3.1 KiB
Erlang

%% Copyright 2010, 2011, 2012 Tony Garnock-Jones <tonygarnockjones@gmail.com>.
%%
%% This file is part of Hop.
%%
%% Hop is free software: you can redistribute it and/or modify it
%% under the terms of the GNU General Public License as published by
%% the Free Software Foundation, either version 3 of the License, or
%% (at your option) any later version.
%%
%% Hop is distributed in the hope that it will be useful, but WITHOUT
%% ANY WARRANTY; without even the implied warranty of MERCHANTABILITY
%% or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public
%% License for more details.
%%
%% You should have received a copy of the GNU General Public License
%% along with Hop. If not, see <http://www.gnu.org/licenses/>.
-module(hop_factory).
-behaviour(gen_server).
-export([init/1, terminate/2, code_change/3, handle_call/3, handle_cast/2, handle_info/2]).
-export([start_link/1, register_class/2]).
start_link(Args) ->
gen_server:start_link({local, ?MODULE}, ?MODULE, Args, []).
register_class(ClassName, ClassModule) ->
gen_server:call(?MODULE, {register_class, ClassName, ClassModule}).
%%---------------------------------------------------------------------------
-record(state, {classes}).
init([]) ->
yes = global:register_name(<<"factory">>, self()),
{ok, #state{classes = []}}.
terminate(_Reason, _State) ->
ok.
code_change(_OldVsn, State, _Extra) ->
{ok, State}.
handle_call({register_class, ClassName, ClassModule}, _From, State = #state{classes = Classes}) ->
{reply, ok, State#state{classes = [{ClassName, ClassModule} | Classes]}};
handle_call(_Request, _From, State) ->
{stop, {bad_call, _Request}, State}.
handle_cast(_Request, State) ->
{stop, {bad_cast, _Request}, State}.
handle_info({hop, Sexp}, State = #state{classes = Classes}) ->
case Sexp of
[<<"create">>, ClassName, Arg, ReplySink, ReplyName] ->
Reply =
case lists:keysearch(ClassName, 1, Classes) of
false ->
error_logger:warning_report({?MODULE, class_not_found, ClassName}),
[<<"create-failed">>, [<<"factory">>, <<"class-not-found">>]];
{value, {_, ClassModule}} ->
case catch ClassModule:hop_create(Arg) of
{ok, Info} ->
[<<"create-ok">>, Info];
{error, Info} ->
[<<"create-failed">>, [<<"constructor">>, Info]];
Otherwise ->
error_logger:warning_report({?MODULE, creation_failed,
Sexp, Otherwise}),
[<<"create-failed">>, [<<"constructor">>]]
end
end,
hop:post(ReplySink, ReplyName, Reply, <<>>),
{noreply, State};
_ ->
error_logger:warning_report({?MODULE, message_not_understood, Sexp}),
{noreply, State}
end;
handle_info(_Message, State) ->
{stop, {bad_info, _Message}, State}.