Skip to content

Commit

Permalink
Add plugins in Observer
Browse files Browse the repository at this point in the history
	Add documentation
	Add simple example of plugin
  • Loading branch information
crownedgrouse committed Jan 26, 2019
1 parent d0252a3 commit 9619d43
Show file tree
Hide file tree
Showing 2 changed files with 204 additions and 10 deletions.
139 changes: 139 additions & 0 deletions lib/observer/doc/src/observer_ug.xml
Expand Up @@ -355,4 +355,143 @@
in application STDLIB.
</p>
</section>

<section>
<title>Plugins</title>
<p>Other third party graphical user interfaces can be added to Observer menu.
If any declared, a menu entry 'Plugins' is shown, otherwise not.
</p>
<p>Plugins have to be declared in <c>observer</c> application configuration,
as a list of tuple <c>{NameString, StartMFA}</c> under a key <c>plugins</c>.
Plugin names will be sorted in alphabetic order in menu, and a maximum of ten plugins
kept. If more are declared only first ten (sorted) ones will be available.
</p>
<p>
<c>NameString</c> is the name of application to display in Plugins menu.
<c>StartMFA</c> is the start command MFA , as a 3 or 4 elements tuple.
Atom 'node' as fourth tuple element will add the current node observed by Observer as last argument of start command.
</p>
<list type="bulleted">
<item><c>{M, F, []}</c> Start without any argument.</item>
<item><c>{M, F, A}</c> Start with argument list A.</item>
<item><c>{M, F, A, node}</c> Start with current observed node as last argument of list A.</item>
</list>
<p>
Start command must return a <c>wx_object()</c> like <c>wx:new/0</c>.
</p>
<p>Configuration example :</p>
<code type="none"><![CDATA[
[
{observer, [ {plugins, [
{ "My app", {myapp_gui, start, [], node}},
{ "Another app", {another, gui, []}},
{ "A third app", {acme, start, [debug, verbose]}},
{ "A funny app", {funny, ui, [{log_level, 3}], node}}
]}
]}
].]]></code>
<p>Example of a minimalist plugin restarting applications on observed node.
Note that <c>init:restart/0</c> on local node will close Observer,
so better using this on a remote observed node.
</p>
<warning>
<p>To prevent the observer from being closed, please do not call
<c>wx:destroy()</c> from your plugins.</p>
</warning>
<code type="none"><![CDATA[
-module(opdemo).
-include_lib("wx/include/wx.hrl").
-behaviour(wx_object).
-export([start/0, start/1, start_link/0, start_link/1]).
-export([init/1, handle_call/3, handle_event/2,
handle_info/2, handle_cast/2, code_change/3, terminate/2]).
-record(state,
{frame
,node
}).
start() ->
start([]).
start(Args) ->
wx_object:start(?MODULE, Args, []).
start_link() ->
start_link([]).
start_link(Args) ->
wx_object:start_link(?MODULE, Args, []).
init(Node) ->
TNode = case Node of
X when is_atom(X) -> X;
_ -> erlang:node() % default to current node
end,
Parent = wx:new(),
process_flag(trap_exit, true),
Text = atom_to_list(?MODULE),
MiniFrame = wxMiniFrame:new(Parent, ?wxID_ANY, Text, [{style,
?wxDEFAULT_FRAME_STYLE bor
?wxFRAME_FLOAT_ON_PARENT}]),
Panel = wxPanel:new(MiniFrame, []),
% Add a button to restart all application of given node
Sz = wxBoxSizer:new(?wxVERTICAL),
ButtSz = wxStaticBoxSizer:new(?wxHORIZONTAL, Panel,
[{label, atom_to_list(TNode)}]),
SzFlags = [{proportion, 0}, {border, 4}, {flag, ?wxALL}],
B = wxButton:new(Panel, 10, [{label,"Restart applications"}]),
wxSizer:add(ButtSz, B, SzFlags),
wxMiniFrame:setSize(MiniFrame, {150,100}),
wxMiniFrame:center(MiniFrame),
wxMiniFrame:show(MiniFrame),
wxWindow:connect(Panel, command_button_clicked),
wxWindow:setSizer(Panel, Sz),
wxSizer:layout(Sz),
wxWindow:refresh(Panel),
{MiniFrame, #state{frame=MiniFrame ,node = TNode}}.
%%%%%%%%%%%%
%% Callbacks
handle_info({'EXIT',_, wx_deleted}, State) ->
{noreply,State};
handle_info({'EXIT',_, shutdown}, State) ->
{noreply,State};
handle_info({'EXIT',_, normal}, State) ->
{noreply,State};
handle_info(_, State) ->
{noreply,State}.
handle_call(_, _From, State) ->
{reply,ok,State}.
handle_cast(_, State) ->
{noreply,State}.
handle_event({wx,10, _, _,
{wxCommand,command_button_clicked,_,_,_}}, State) ->
% Restart applications on node
Res = rpc:call(State#state.node, init, restart, []),
io:format("restarting application on ~p : ~p~n", [State#state.node, Res]),
{noreply,State};
handle_event(Ev,State) ->
io:format("~p Got uncaught event ~p ~n",[?MODULE, Ev]),
{noreply, State}.
code_change(_, _, State) ->
{stop, not_yet_implemented, State}.
terminate(_Reason, _State = #state{frame=Frame}) ->
wxMiniFrame:destroy(Frame),
ok.
.]]></code>
</section>
</chapter>
75 changes: 65 additions & 10 deletions lib/observer/src/observer_wx.erl
Expand Up @@ -39,6 +39,8 @@
-define(ID_NOTEBOOK, 3).
-define(ID_CDV, 4).
-define(ID_LOGVIEW, 5).
-define(FIRST_PLUGINS_MENU_ID, 10).
-define(LAST_PLUGINS_MENU_ID, 20).

-define(FIRST_NODES_MENU_ID, 1000).
-define(LAST_NODES_MENU_ID, 2000).
Expand All @@ -61,7 +63,8 @@
prev_node="",
log = false,
reply_to=false,
config
config,
plugins
}).

start() ->
Expand Down Expand Up @@ -119,7 +122,8 @@ setup(#state{frame = Frame} = State) ->
MenuBar = wxMenuBar:new(),

{Nodes, NodeMenus} = get_nodes(),
DefMenus = default_menus(NodeMenus),
{Plugins, PluginsMenus} = get_plugins(),
DefMenus = default_menus(NodeMenus, PluginsMenus),
observer_lib:create_menus(DefMenus, MenuBar, default),

wxFrame:setMenuBar(Frame, MenuBar),
Expand Down Expand Up @@ -209,7 +213,8 @@ setup(#state{frame = Frame} = State) ->
active_tab = SysPid,
panels = Panels,
node = node(),
nodes = Nodes
nodes = Nodes,
plugins = Plugins
},
%% Create resources which we don't want to duplicate
SysFont = wxSystemSettings:getFont(?wxSYS_SYSTEM_FIXED_FONT),
Expand Down Expand Up @@ -367,6 +372,37 @@ handle_event(#wx{id = Id, event = #wxCommand{type = command_menu_selected}},
end,
{noreply, change_node_view(Node, LState)};

handle_event(#wx{id = Id, event = #wxCommand{type = command_menu_selected}},
#state{plugins= Ns} = State)
when Id > ?FIRST_PLUGINS_MENU_ID, Id =< ?LAST_PLUGINS_MENU_ID ->
{N, {M, F, A}} = case lists:nth(Id - ?FIRST_PLUGINS_MENU_ID, Ns) of
{N0, {M0, F0, [], node}} -> {N0, {M0, F0, [State#state.node]}};
{N0, {M0, F0, A0, node}} -> {N0, {M0, F0, A0 ++ [State#state.node]}};
{N0, {M0, F0, A0}} -> {N0, {M0, F0, A0}}
end,
Env = wx:get_env(),
spawn(fun() ->
wx:set_env(Env),
WO = try
erlang:apply(M, F, A)
catch
throw:T1 -> T1
end,
Pid = try
wx_object:get_pid(WO)
catch
throw:T2 -> T2
end,
case Pid of
Pid when is_pid(Pid) ->
erlang:monitor(process, Pid),
set_status("Plugin started : " ++ N);
_ -> io:format("~ts : ~p~n", [N, WO]),
set_status(io_lib:format("Plugin ~ts : start error", [N]))
end
end),
{noreply, State};

handle_event(Event, #state{active_tab=Pid} = State) ->
Pid ! Event,
{noreply, State}.
Expand Down Expand Up @@ -656,7 +692,7 @@ create_connect_dialog(connect, #state{frame = Frame}) ->
cancel
end.

default_menus(NodesMenuItems) ->
default_menus(NodesMenuItems, PluginsMenu) ->
CDV = #create_menu{id = ?ID_CDV, text = "Examine Crashdump"},
Quit = #create_menu{id = ?wxID_EXIT, text = "Quit"},
About = #create_menu{id = ?wxID_ABOUT, text = "About"},
Expand All @@ -673,7 +709,7 @@ default_menus(NodesMenuItems) ->
false ->
FileMenu = {"File", [CDV, Quit]},
HelpMenu = {"Help", [About,Help]},
[FileMenu, NodeMenu, LogMenu, HelpMenu];
lists:flatten([FileMenu, NodeMenu, LogMenu, PluginsMenu, HelpMenu]);
true ->
%% On Mac quit and about will be moved to the "default' place
%% automagicly, so just add them to a menu that always exist.
Expand Down Expand Up @@ -702,7 +738,7 @@ remove_menu_items([{Tag, _Menus}|Rest], MenuBar) ->
case wxMenuBar:findMenu(MenuBar, Tag) of
?wxNOT_FOUND ->
remove_menu_items(Rest, MenuBar);
MenuId ->
MenuId ->
Menu = wxMenuBar:getMenu(MenuBar, MenuId),
wxMenuBar:remove(MenuBar, MenuId),
Items = wxMenu:getMenuItems(Menu),
Expand Down Expand Up @@ -738,7 +774,7 @@ epmd_nodes(Names) ->
update_node_list(State = #state{menubar=MenuBar}) ->
{Nodes, NodesMenuItems} = get_nodes(),
NodeMenu = case wxMenuBar:findMenu(MenuBar, "Nodes") of
?wxNOT_FOUND ->
?wxNOT_FOUND ->
Menu = wxMenu:new(),
wxMenuBar:append(MenuBar, Menu, "Nodes"),
Menu;
Expand All @@ -748,11 +784,11 @@ update_node_list(State = #state{menubar=MenuBar}) ->
wxMenu:getMenuItems(Menu)),
Menu
end,

Index = wx:foldl(fun(Record, Index) ->
observer_lib:create_menu_item(Record, NodeMenu, Index)
end, 0, NodesMenuItems),

Dist = case erlang:is_alive() of
true -> #create_menu{id = ?ID_PING, text = "Connect node"};
false -> #create_menu{id = ?ID_CONNECT, text = "Enable distribution"}
Expand Down Expand Up @@ -806,7 +842,7 @@ is_rb_compatible(Node) ->

is_rb_server_running(Node, LogState) ->
%% If already started, somebody else may use it.
%% We can not use it too, as far log file would be overriden. Not fair.
%% We cannot use it too, as far log file would be overriden. Not fair.
case rpc:block_call(Node, erlang, whereis, [rb_server]) of
Pid when is_pid(Pid), (LogState == false) ->
throw("Error: rb_server is already started and maybe used by someone.");
Expand All @@ -815,3 +851,22 @@ is_rb_server_running(Node, LogState) ->
undefined ->
ok
end.

get_plugins() ->
%% Returns optional plugins to add to menu, otherwise []
application:load(observer),
case application:get_env(observer, plugins) of
undefined -> {[], []};
{ok, P} -> % Add only valid parameters
F = lists:filter(fun(X) -> case X of
{_N, {_M, _F, _A}} -> true;
{_N, {_M, _F, _A, node}} -> true;
_ -> io:format("~p~n",[{invalid, X}]), false end end , P),
{Plugins, _} = lists:split((?LAST_PLUGINS_MENU_ID - ?FIRST_PLUGINS_MENU_ID), lists:usort(F)),
{_, PMenues} = lists:foldl(fun({N, _}, {Id, Acc}) when Id =< ?LAST_PLUGINS_MENU_ID ->
{Id + 1, [#create_menu{id=Id + ?FIRST_PLUGINS_MENU_ID,
text=N} | Acc]}
end, {1, []}, Plugins),
{Plugins, {"Plugins",lists:reverse(PMenues)}}
end.

0 comments on commit 9619d43

Please sign in to comment.