reshd

Tomas Abrahamsson tab@REDACTED
Fri May 4 12:44:04 CEST 2001


Here's a small program, that provides a telnet
interface to the erlang shell.  I called it reshd,
which is short for remote erlang shell daemon.

It is an alternative to run_erl/to_erl.  It opens a
tcp/ip port and listens for incoming connections.  Any
connection to this port drops right into an erlang
shell.

Example:

  First I make the erlang node execute reshd:start(5000).

  Then from a unix shell:
    prompt% telnet localhost 5000
    Trying 127.0.0.1...
    Connected to localhost.
    Escape character is '^]'.
    Eshell V5.0.1
    (node@REDACTED)1> io:format("Hello!~n").
    Hello!
    ok
    (node@REDACTED)2> l(my_module).
    {module,my_module}
    (node@REDACTED)3> exit().
    ** Terminating shell **
    Connection closed by foreign host.
    prompt%

The following is attached:

  - reshd.erl -- the remote erlang shell daemon.
  - resh.el   -- emacs extensions to the erlang mode,
                 for connecting to a reshd. It offers
                 the keybinding C-c s, which sets
                 the resh-buffer as current
                 compilation-buffer.

No efforts have been made regarding security, but I
guess it would be easy to add ssl and password
authentication or whatever is needed.

/Tomas
-------------- next part --------------
%%%----------------------------------------------------------------------
%%% Purpose : Remote erlang shell daemon -- a telnet interface to the shell
%%% File    : reshd.erl
%%% Author  : Tomas Abrahamsson <tab@REDACTED>
%%% Created : 12 Apr 2001 by Tomas Abrahamsson <tab@REDACTED>
%%%
%%% COPYRIGHT
%%%
%%% These programs are released into the public domain.  You may do
%%% anything you like with them, including modifying them and selling
%%% the binaries without source for ridiculous amounts of money without
%%% saying who made them originally.
%%% 
%%% However, I would be happy if you release your works with complete
%%% source for free use.
%%%----------------------------------------------------------------------
-module(reshd).
-author('tab@REDACTED').
-rcs('$Id: reshd.erl,v 1.5 2001/05/04 09:57:48 tab Exp $').	% '

%% API
-export([start/1, start/2]).
-export([stop/1, stop/2]).
-export([build_regname/1, build_regname/2]).

%% exports due to spawns
-export([server_init/3]).
-export([clienthandler_init/3]).

%% ----------------------------------------------------------------------
%% ----------------------------------------------------------------------
%% API
%% ----------------------------------------------------------------------
%% ----------------------------------------------------------------------

%% ----------------------------------------------------------------------
%% start(PortNumber) -> {ok, UsedPortNumber} | {error, Reason}
%% start(IP, PortNumber) -> {ok, UsedPortNumber} | {error, Reason}
%%   Portnumber = UsedPortNumber = integer(0..65535)
%%   IP = any | {Byte,Byte,Byte,Byte}
%%   Byte = integer(0..255)
%%
%% Start the reshd server to listen for connections on TCP/IP port PortNumber.
%%
%% The special port number 0 means "use any available TCP/IP port".
%% The port that is actually used is returned. If PortNumber != 0, then
%% UsedPortNumber == PortNumber.
%%
%% Optionally, an IP address to bind to can also be specified.
%% The default is that IP any, which means to bind to all ip addresses
%% on the machine.
%%
%% The process that listens for and handles incoming connections is
%% locally registred under the name reshd_<IP>_<UsedPortNumber>.
%% build_regname is used to build the name.
%% ----------------------------------------------------------------------

start(PortNumber) ->
    start(any, PortNumber).
start(IP, PortNumber) ->
    server_start(IP, PortNumber).

%% ----------------------------------------------------------------------
%% stop(PortNumber) -> void()
%% stop(IP, PortNumber) -> void()
%%   Portnumber = UsedPortNumber = integer(0..65535)
%%   IP = any | {Byte,Byte,Byte,Byte}
%%   Byte = integer(0..255)
%% 
%% Stops the reshd server and any open connections associated to it. 
%% ----------------------------------------------------------------------
stop(PortNumber) ->
    stop(any, PortNumber).
stop(IP, PortNumber) ->
    server_stop(IP, PortNumber).


%% ----------------------------------------------------------------------
%% build_regname(PortNumber) -> atom()
%% build_regname(IP, PortNumber) -> atom()
%%   Portnumber = UsedPortNumber = integer(0..65535)
%%   IP = any | {Byte,Byte,Byte,Byte}
%%   Byte = integer(0..255)
%% 
%% Build a name under which the reshd server may be registered.
%% ----------------------------------------------------------------------
build_regname(PortNumber) ->
    build_regname(any, PortNumber).

build_regname(any, PortNumber) ->
    Name = atom_to_list(?MODULE) ++ "_any_" ++ integer_to_list(PortNumber),
    list_to_atom(Name);
build_regname({IP1, IP2, IP3, IP4}, PortNumber) ->
    Name = atom_to_list(?MODULE) ++ "_" ++
	list_to_integer(IP1) ++ "_" ++
	list_to_integer(IP2) ++ "_" ++
	list_to_integer(IP3) ++ "_" ++
	list_to_integer(IP4) ++ "_" ++
	"_" ++ integer_to_list(PortNumber),
    list_to_atom(Name);
build_regname(HostNameOrIP, PortNumber) ->
    Name = atom_to_list(?MODULE) ++
	"_" ++ HostNameOrIP ++ "_" ++
	integer_to_list(PortNumber),
    list_to_atom(Name).


%% ----------------------------------------------------------------------
%% ----------------------------------------------------------------------
%% Internal functions: the server part
%% ----------------------------------------------------------------------
%% ----------------------------------------------------------------------
server_start(IP, PortNumber) ->
    Server = spawn(?MODULE, server_init, [self(), IP, PortNumber]),
    receive
	{ok, UsedPortNumber} ->
	    RegName = build_regname(IP, UsedPortNumber),
	    register(RegName, Server),
	    {ok, UsedPortNumber};
	{error, {Symptom, Diagnostics}} ->
	    {error, {Symptom, Diagnostics}}
    end.

server_stop(IP, PortNumber) ->
    RegName = build_regname(IP, PortNumber),
    case whereis(RegName) of
	undefined ->
	    do_nothing;
	Pid ->
	    Pid ! stop
    end.

server_init(From, IP, PortNumber) ->
    IPOpt = ip_to_opt(IP),
    ListenOpts = [list,
		  {packet, 0},
		  {active, true},		% this is the default
		  {nodelay, true},
		  {reuseaddr, true}] ++ IPOpt,
    case gen_tcp:listen(PortNumber, ListenOpts) of
	{ok, ServerSocket} ->
	    {ok, UsedPortNumber} = inet:port(ServerSocket),
	    From ! {ok, UsedPortNumber},
	    process_flag(trap_exit, true),
	    server_loop(From, ServerSocket);
	{error, Reason} ->
	    From ! {error, {listen_failed, Reason}}
    end.


ip_to_opt(any) ->
    [];
ip_to_opt({IP1, IP2, IP3, IP4}=IPNumber) ->
    [{ip, IPNumber}];
ip_to_opt(HostNameOrIPAsString) ->
    case inet:getaddr(HostNameOrIPAsString, inet) of
	{ok, IPNumber} ->
	    [{ip, IPNumber}];
	{error, Error} ->
	    loginfo("~p: IP lookup failed for ~p: ~p. Binding to any ip.",
		    [?MODULE, HostNameOrIPAsString, Error]),
	    []
    end.


server_loop(From, ServerSocket) ->
    server_loop(From, ServerSocket, []).

server_loop(From, ServerSocket, Clients) ->
    case gen_tcp:accept(ServerSocket, 250) of
	{ok, ClientSocket} ->
	    ClientHandler = clienthandler_start(From, self(), ClientSocket),
	    gen_tcp:controlling_process(ClientSocket, ClientHandler),
	    server_loop(From, ServerSocket, [ClientHandler | Clients]);
	{error, timeout} ->
	    %% Check for signals now and then
	    receive
		stop ->
		    lists:foreach(fun(Client) -> Client ! stop end, Clients),
		    done;
		{client_stop, Client} ->
		    RemainingClients = [C || C <- Clients, C /= Client],
		    server_loop(From, ServerSocket, RemainingClients);
		{'EXIT', Client, Reason} ->
		    RemainingClients = [C || C <- Clients, C /= Client],
		    server_loop(From, ServerSocket, RemainingClients);
		Unexpected ->
		    loginfo("~p:server_loop: unexpected message:~p",
			    [?MODULE, Unexpected]),
		    server_loop(From, ServerSocket, Clients)
	    after 0 ->
		    server_loop(From, ServerSocket, Clients)
	    end;
	{error, Reason} ->
	    logerror("~p:server_loop: Error: accepting on ~p: ~p.",
		     [?MODULE, ServerSocket, Reason])
    end.


%% ----------------------------------------------------------------------
%% ----------------------------------------------------------------------
%% The client handler part -- handles a user of the reshd.
%% ----------------------------------------------------------------------
%% ----------------------------------------------------------------------
clienthandler_start(From, Server, ClientSocket) ->
    spawn_link(?MODULE, clienthandler_init, [From, Server, ClientSocket]).

-record(io_request,
	{
	  prompt,
	  mod, fn, args,
	  from, reply_as
	 }).
	  

clienthandler_init(From, Server, ClientSocket) ->
    %% Announce ourself as group leader.
    %% This causes all calls to io:format(...) and such alike
    %% to send their output to us.
    group_leader(self(), self()),

    %% Next, start the shell
    %% and link to it, so we know when it exits.
    process_flag(trap_exit, true),
    Reshd = shell:start(true),
    link(Reshd),

    %% Go ahead and take care of user input!
    R = (catch clienthandler_loop(idle, Reshd, Server, ClientSocket)),
    exit(Reshd, kill).

clienthandler_loop(State, Reshd, Server, ClientSocket) ->
    receive
	{tcp, _Socket, Input} ->
	    NativeInput = nl_network_to_native(Input),
	    case handle_input(ClientSocket, State, NativeInput) of
		{ok, NewState} ->
		    clienthandler_loop(NewState, Reshd, Server, ClientSocket);
		close ->
		    gen_tcp:close(ClientSocket)
	    end;

	{tcp_closed, Socket} ->
	    Server ! {client_stop, self()},
	    done;

	{tcp_error, Socket, Reason} ->
	    Server ! {client_stop, self()},
	    done;

	stop ->
	    gen_tcp:close(ClientSocket),
	    done;

	{io_request, From, ReplyAs, Req} ->
	    case handle_io_request(ClientSocket, State, From, ReplyAs, Req) of
		{ok, NewState} ->
		    clienthandler_loop(NewState, Reshd, Server, ClientSocket);
		close ->
		    gen_tcp:close(ClientSocket)
	    end;

	{'EXIT', Reshd, normal} ->
	    gen_tcp:close(ClientSocket);

	{'EXIT', Reshd, _OtherReason} ->
	    gen_tcp:close(ClientSocket);

	Other ->
	    clienthandler_loop(State, Reshd, Server, ClientSocket)
    end.


%% Returns:
%%   {ok, NewState} |
%%   close
handle_input(ClientSocket, State, Input) ->
    case State of
	idle ->
	    {ok, {pending_input, Input}};
	{pending_input, PendingInput} ->
	    NewInput = PendingInput ++ Input,
	    {ok, {pending_input, NewInput}};
	{pending_request, Cont, [FirstReq | RestReqs] = Requests} ->
	    #io_request{prompt = Prompt,
			mod = Mod,
			fn = Fun,
			args = Args} = FirstReq,
	    case catch apply(Mod, Fun, [Cont, Input|Args]) of
		{more, NewCont} ->
		    print_prompt(ClientSocket, Prompt),
		    {ok, {pending_request, NewCont, Requests}};
		{done, Result, []} ->
		    #io_request{from = From,
				reply_as = ReplyAs} = FirstReq,
		    From ! {io_reply, ReplyAs, Result},
		    case length(RestReqs) of
			0 ->
			    {ok, idle};
			N ->
			    [#io_request{prompt = NextPrompt}|_] = RestReqs,
			    print_prompt(ClientSocket, NextPrompt),
			    InitCont = init_cont(),
			    {ok, {pending_request, InitCont, RestReqs}}
		    end;
		{done, Result, RestChars} ->
		    #io_request{from = From,
				reply_as = ReplyAs} = FirstReq,
		    From ! {io_reply, ReplyAs, Result},
		    case length(RestReqs) of
			0 ->
			    {ok, {pending_input, RestChars}};
			N ->
			    InitCont = init_cont(),
			    TmpState = {pending_request, InitCont, RestReqs},
			    handle_input(ClientSocket, RestChars, TmpState)
		    end;
		Other ->
		    logerror("~p:handle_input: Unexpected result: ~p~n",
			     [?MODULE, Other]),
		    close
	    end
    end.


%% Returns:
%%   {ok, NewState} |
%%   close
handle_io_request(ClientSocket, State, From, ReplyAs, IoRequest) ->
    case IoRequest of
	{put_chars, Mod, Fun, Args} ->
	    Text = case catch apply(Mod, Fun, Args) of
		      {'EXIT', Reason} -> "";
		      Txt -> Txt
		   end,
	    NWText = nl_native_to_network(lists:flatten(Text)),
	    gen_tcp:send(ClientSocket, NWText),
	    From ! {io_reply, ReplyAs, ok},
	    {ok, State};

	{put_chars, Text} ->
	    NWText = nl_native_to_network(lists:flatten(Text)),
	    gen_tcp:send(ClientSocket, Text),
	    From ! {io_reply, ReplyAs, ok},
	    {ok, State};

	{get_until, Prompt, Mod, Fun, Args} ->
	    NewReq = #io_request{prompt = Prompt,
				 mod = Mod,
				 fn = Fun,
				 args = Args,
				 from = From,
				 reply_as = ReplyAs},
	    case State of
		{pending_request, Cont, PendingReqs} ->
		    NewState = {pending_request, Cont, PendingReqs++[NewReq]},
		    {ok, NewState};

		idle ->
		    print_prompt(ClientSocket, Prompt),
		    InitContinuation = init_cont(),
		    NewState = {pending_request, InitContinuation, [NewReq]},
		    {ok, NewState};

		{pending_input, Input} ->
		    InitContinuation = init_cont(),
		    TmpState = {pending_request, InitContinuation, [NewReq]},
		    handle_input(ClientSocket, TmpState, Input)
	    end;

	UnexpectedIORequest ->
	    loginfo("~p:handle_io_request: Unexpected IORequest:~p~n",
		    [?MODULE, UnexpectedIORequest]),
	    From ! {io_reply, ReplyAs, ok},
	    {ok, State}
    end.
    

init_cont() ->
    [].

print_prompt(ClientSocket, Prompt) ->
    PromptText = case Prompt of
		     {IoFun, PromptFmtStr, PromptArgs} ->
			 io_lib:IoFun(PromptFmtStr, PromptArgs);
		     {IoFun, PromptFmtStr} ->
			 io_lib:IoFun(PromptFmtStr, [])
		 end,
    NWPromptText = nl_native_to_network(lists:flatten(PromptText)),
    gen_tcp:send(ClientSocket, NWPromptText).

%% Convert network newline (cr,lf) to native (\n)
nl_network_to_native(Input) ->
    nl_network_to_native(Input, "").


nl_network_to_native("\r\n" ++ Rest, Acc) ->
    nl_network_to_native(Rest, [$\n | Acc]);
nl_network_to_native([C | Rest], Acc) ->
    nl_network_to_native(Rest, [C | Acc]);
nl_network_to_native("", Acc) ->
    lists:reverse(Acc).

				    

%% Convert native newline \n to network (cr,lf)
nl_native_to_network(Input) ->
    nl_native_to_network(Input, "").


nl_native_to_network("\n" ++ Rest, Acc) ->
    %% Here we put \r\n in reversed order.
    %% It'll be put in correct order by the lists:reverse() call
    %% in the last clause.
    nl_native_to_network(Rest, [$\n, $\r | Acc]);
nl_native_to_network([C | Rest], Acc) ->
    nl_native_to_network(Rest, [C | Acc]);
nl_native_to_network("", Acc) ->
    lists:reverse(Acc).


loginfo(FmtStr, Args) ->
    %% FIXME: Invent a way to log errors.
    %% Can't use the error_log module since someone may
    %% add a log handler that does io:format. Then there
    %% will be a deadlock, I think, if this is function
    %% is called from within code that handles the client.
    fixme.
logerror(FmtStr, Args) ->
    %% See loginfo/2.
    fixme.
-------------- next part --------------
;;; resh.el -- emacs support for connecting to a reshd
;;;            (remote erlang shell daemon)
;;
;; $Id: resh.el,v 1.5 2001/05/04 09:57:34 tab Exp $
;;
;; Author: Tomas Abrahamsson <tab@REDACTED>

;;; COPYRIGHT

;; These programs are released into the public domain.  You may do
;; anything you like with them, including modifying them and selling
;; the binaries without source for ridiculous amounts of money without
;; saying who made them originally.
;; 
;; However, I would be happy if you release your works with complete
;; source for free use.

;;; Installation:

;; Either:
;;
;;   (autoload 'resh "resh" "Start a connection to an erlang reshd" t)
;; 
;; or:
;;
;;   (load-library "resh")
;;   (resh-install)		; installs keymaps
;;
;; The difference is that in the second case, the resh is bound to
;; C-c c immediately, while in the first case no key bindings are
;; installed until you have typed M-x resh for the first time.

;;; Code

(require 'erlang)

;; User definable variables
;; vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv
(defvar resh-default-host "localhost"
  "*Default hostname for `resh'.")

(defvar resh-default-port nil
  "*Default port (an integer) for `resh'.")
;; ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
;; End of user definable variables


(defvar resh-host-history nil
  "Host history for `resh'")

(defvar resh-port-history nil
  "Port history for `resh'")

(defvar resh-buff-history nil
  "Buffer name history for `resh'")

(defvar resh-current-host nil
  "Buffer-local variable, used for reconnection.")

(defvar resh-current-port nil
  "Buffer-local variable, used for reconnection.")

(defvar resh-is-installed nil
  "Whether resh is installed or not")

(defvar resh-auto-install-enabled t
  "Whether resh should autoinstall upon call to resh")


;;;###autoload
(defun resh (host port &optional reconnecting wanted-buffer-name)
  "Run an inferior remote Erlang shell.

The command line history can be accessed with  M-p  and  M-n.
The history is saved between sessions.

Entry to this mode calls the functions in the variables
`comint-mode-hook' and `erlang-shell-mode-hook' with no arguments.

The following commands imitate the usual Unix interrupt and
editing control characters:
\\{erlang-shell-mode-map}"
  (interactive
   ;; Handling of interactive calling
   (let* ((init-prompt "Remote erlang shell to")
	  (host-hist 'resh-host-history)
	  (port-hist 'resh-port-history)
	  (buff-hist 'resh-buff-history)
	  (host-prompt (concat init-prompt ": "))
	  (remote-host (read-string host-prompt resh-default-host host-hist))
	  (port-prompt (concat init-prompt " " remote-host " port: "))
	  (default-port (cond ((null resh-default-port) nil)
			      ((stringp resh-default-port) resh-default-port)
			      ((numberp resh-default-port)
			       (int-to-string resh-default-port))
			      (t nil)))
	  (remote-port-str (read-string port-prompt default-port port-hist))
	  (remote-port (cond ((string= "" remote-port-str)
			      (error "Not port number \"%s\"" remote-port-str))
			     (t (string-to-int remote-port-str))))
	  (buffer-prompt (concat init-prompt " "
				 remote-host ":" remote-port-str
				 ", buffer name: "))
	  (buffer-name (if current-prefix-arg
			   (read-string buffer-prompt nil buff-hist)
			 nil)))
     (list remote-host remote-port nil buffer-name)))

  (if (and (not resh-is-installed) resh-auto-install-enabled)
      (resh-install))

  (require 'comint)

  (let* ((proc-name (resh-buffer-name inferior-erlang-process-name host port))
	 (erl-buffer (make-comint proc-name (cons host port)))
	 (erl-process (get-buffer-process erl-buffer))
	 (erl-buffer-name (if wanted-buffer-name
			      wanted-buffer-name
			    (resh-buffer-name inferior-erlang-buffer-name
					      host port))))

    ;; Say no query needed if erl-process is running when Emacs is exited.
    (process-kill-without-query erl-process)

    ;; Switch to buffer in other or this window
    ;; the `erlang-inferior-shell-split-window' is a local extension
    ;; to the erlang mode.
    (if (and (boundp 'erlang-inferior-shell-split-window)
	     erlang-inferior-shell-split-window)
	(switch-to-buffer-other-window erl-buffer)
      (switch-to-buffer erl-buffer))

    ;; comint settings
    (if (and (not (eq system-type 'windows-nt))
	     (eq inferior-erlang-shell-type 'newshell))
	(setq comint-process-echoes nil))

    ;; Set buffer name and run erlang-shell-mode unless we are reconnecting
    (if reconnecting
	nil
      (condition-case nil
	  ;; `rename-buffer' takes only one argument in Emacs 18.
	  (rename-buffer erl-buffer-name t)
	(error (rename-buffer erl-buffer-name)))
      ;; remember the host/port so we can reconnect.
      (make-variable-buffer-local 'resh-current-host)
      (make-variable-buffer-local 'resh-current-port)
      (setq resh-current-host host)
      (setq resh-current-port port)
      (erlang-shell-mode))))

(defun resh-buffer-name (base host port)
  (let* ((host-port (concat host ":" (int-to-string port))))
    (if (string= (substring base -1) "*")
	(concat (substring base 0 -1) "-" host-port "*")
      (concat base "-" host-port))))

(defun resh-reconnect ()
  "Try to reconnect to a remote Erlang shell daemon."
  (interactive)
  (resh resh-current-host resh-current-port t))

(defun resh-set-inferior-erlang-buffer ()
  "Set current buffer to the inferior erlang buffer."
  (interactive)
  (setq inferior-erlang-buffer (current-buffer))
  (message "This buffer is now set to the current inferior erlang buffer"))


;;;###autoload
(defun resh-install ()
  (interactive)
  (if (not resh-is-installed)
      (progn
	(if (not (member 'resh-install-erl-keys erlang-mode-hook))
	    (add-hook 'erlang-mode-hook 'resh-install-erl-keys))
	(if (not (member 'resh-install-erl-shell-keys erlang-shell-mode-hook))
	    (add-hook 'erlang-shell-mode-hook 'resh-install-erl-shell-keys))
	(setq resh-is-installed t))))

(defun resh-install-erl-keys ()
  (local-set-key "\C-cc" 'resh-erlang))

(defun resh-install-erl-shell-keys ()
  (local-set-key "\C-cc" 'resh-erlang)
  (local-set-key "\C-cs" 'resh-set-inferior-erlang-buffer)
  ;; The reconnection is not fully working...
  ;;(local-set-key "\C-cr" 'resh-reconnect)
  )


(provide 'resh)


More information about the erlang-questions mailing list