blob: 971f983c264d07dfdeb0cdd86d06bcc37adc4599 [file] [log] [blame]
Harald Welte5882a9b2011-02-09 13:12:46 +01001%% -*- erlang -*-
2%% -------------------------------------------------------------------
3%%
4%% nodetool: Helper Script for interacting with live nodes
5%%
6%% -------------------------------------------------------------------
7
8main(Args) ->
9 %% Extract the args
10 {RestArgs, TargetNode} = process_args(Args, [], undefined),
11
12 %% See if the node is currently running -- if it's not, we'll bail
13 case {net_kernel:hidden_connect_node(TargetNode), net_adm:ping(TargetNode)} of
14 {true, pong} ->
15 ok;
16 {_, pang} ->
17 io:format("Node ~p not responding to pings.\n", [TargetNode]),
18 halt(1)
19 end,
20
21 case RestArgs of
22 ["ping"] ->
23 %% If we got this far, the node already responsed to a ping, so just dump
24 %% a "pong"
25 io:format("pong\n");
26 ["stop"] ->
27 io:format("~p\n", [rpc:call(TargetNode, init, stop, [], 60000)]);
28 ["restart"] ->
29 io:format("~p\n", [rpc:call(TargetNode, init, restart, [], 60000)]);
30 ["reboot"] ->
31 io:format("~p\n", [rpc:call(TargetNode, init, reboot, [], 60000)]);
32 ["rpc", Module, Function | RpcArgs] ->
33 case rpc:call(TargetNode, list_to_atom(Module), list_to_atom(Function), [RpcArgs], 60000) of
34 ok ->
35 ok;
36 {badrpc, Reason} ->
37 io:format("RPC to ~p failed: ~p\n", [TargetNode, Reason]),
38 halt(1);
39 _ ->
40 halt(1)
41 end;
42 Other ->
43 io:format("Other: ~p\n", [Other]),
44 io:format("Usage: nodetool {ping|stop|restart|reboot}\n")
45 end,
46 net_kernel:stop().
47
48process_args([], Acc, TargetNode) ->
49 {lists:reverse(Acc), TargetNode};
50process_args(["-setcookie", Cookie | Rest], Acc, TargetNode) ->
51 erlang:set_cookie(node(), list_to_atom(Cookie)),
52 process_args(Rest, Acc, TargetNode);
53process_args(["-name", TargetName | Rest], Acc, _) ->
54 ThisNode = append_node_suffix(TargetName, "_maint_"),
55 {ok, _} = net_kernel:start([ThisNode, longnames]),
56 process_args(Rest, Acc, nodename(TargetName));
57process_args(["-sname", TargetName | Rest], Acc, _) ->
58 ThisNode = append_node_suffix(TargetName, "_maint_"),
59 {ok, _} = net_kernel:start([ThisNode, shortnames]),
60 process_args(Rest, Acc, nodename(TargetName));
61process_args([Arg | Rest], Acc, Opts) ->
62 process_args(Rest, [Arg | Acc], Opts).
63
64
65nodename(Name) ->
66 case string:tokens(Name, "@") of
67 [_Node, _Host] ->
68 list_to_atom(Name);
69 [Node] ->
70 [_, Host] = string:tokens(atom_to_list(node()), "@"),
71 list_to_atom(lists:concat([Node, "@", Host]))
72 end.
73
74append_node_suffix(Name, Suffix) ->
75 case string:tokens(Name, "@") of
76 [Node, Host] ->
77 list_to_atom(lists:concat([Node, Suffix, os:getpid(), "@", Host]));
78 [Node] ->
79 list_to_atom(lists:concat([Node, Suffix, os:getpid()]))
80 end.