add osmo nodes 'files' directory
diff --git a/rel/files/app.config b/rel/files/app.config
new file mode 100644
index 0000000..bba388b
--- /dev/null
+++ b/rel/files/app.config
@@ -0,0 +1,11 @@
+[
+ %% SASL config
+ {sasl, [
+         {sasl_error_logger, {file, "log/sasl-error.log"}},
+         {errlog_type, error},
+         {error_logger_mf_dir, "log/sasl"},      % Log directory
+         {error_logger_mf_maxbytes, 10485760},   % 10 MB max file size
+         {error_logger_mf_maxfiles, 5}           % 5 files max
+         ]}
+].
+
diff --git a/rel/files/erl b/rel/files/erl
new file mode 100755
index 0000000..e500626
--- /dev/null
+++ b/rel/files/erl
@@ -0,0 +1,34 @@
+#!/bin/bash
+
+## This script replaces the default "erl" in erts-VSN/bin. This is necessary
+## as escript depends on erl and in turn, erl depends on having access to a
+## bootscript (start.boot). Note that this script is ONLY invoked as a side-effect
+## of running escript -- the embedded node bypasses erl and uses erlexec directly
+## (as it should). 
+##
+## Note that this script makes the assumption that there is a start_clean.boot
+## file available in $ROOTDIR/release/VSN.
+
+# Determine the abspath of where this script is executing from.
+ERTS_BIN_DIR=$(cd ${0%/*} && pwd)
+
+# Now determine the root directory -- this script runs from erts-VSN/bin,
+# so we simply need to strip off two dirs from the end of the ERTS_BIN_DIR
+# path.
+ROOTDIR=${ERTS_BIN_DIR%/*/*}
+
+# Parse out release and erts info
+START_ERL=`cat $ROOTDIR/releases/start_erl.data`
+ERTS_VSN=${START_ERL% *}
+APP_VSN=${START_ERL#* }
+
+BINDIR=$ROOTDIR/erts-$ERTS_VSN/bin
+EMU=beam
+PROGNAME=`echo $0 | sed 's/.*\\///'`
+CMD="$BINDIR/erlexec"
+export EMU
+export ROOTDIR
+export BINDIR
+export PROGNAME
+
+exec $CMD -boot $ROOTDIR/releases/$APP_VSN/start_clean ${1+"$@"}
\ No newline at end of file
diff --git a/rel/files/nodetool b/rel/files/nodetool
new file mode 100755
index 0000000..971f983
--- /dev/null
+++ b/rel/files/nodetool
@@ -0,0 +1,80 @@
+%% -*- erlang -*-
+%% -------------------------------------------------------------------
+%%
+%% nodetool: Helper Script for interacting with live nodes
+%%
+%% -------------------------------------------------------------------
+
+main(Args) ->
+    %% Extract the args
+    {RestArgs, TargetNode} = process_args(Args, [], undefined),
+
+    %% See if the node is currently running  -- if it's not, we'll bail
+    case {net_kernel:hidden_connect_node(TargetNode), net_adm:ping(TargetNode)} of
+        {true, pong} ->
+            ok;
+        {_, pang} ->
+            io:format("Node ~p not responding to pings.\n", [TargetNode]),
+            halt(1)
+    end,
+
+    case RestArgs of
+        ["ping"] ->
+            %% If we got this far, the node already responsed to a ping, so just dump
+            %% a "pong"
+            io:format("pong\n");
+        ["stop"] ->
+            io:format("~p\n", [rpc:call(TargetNode, init, stop, [], 60000)]);
+        ["restart"] ->
+            io:format("~p\n", [rpc:call(TargetNode, init, restart, [], 60000)]);
+        ["reboot"] ->
+            io:format("~p\n", [rpc:call(TargetNode, init, reboot, [], 60000)]);
+        ["rpc", Module, Function | RpcArgs] ->
+            case rpc:call(TargetNode, list_to_atom(Module), list_to_atom(Function), [RpcArgs], 60000) of
+                ok ->
+                    ok;
+                {badrpc, Reason} ->
+                    io:format("RPC to ~p failed: ~p\n", [TargetNode, Reason]),
+                    halt(1);
+                _ ->
+                    halt(1)
+            end;
+        Other ->
+            io:format("Other: ~p\n", [Other]),
+            io:format("Usage: nodetool {ping|stop|restart|reboot}\n")
+    end,
+    net_kernel:stop().
+
+process_args([], Acc, TargetNode) ->
+    {lists:reverse(Acc), TargetNode};
+process_args(["-setcookie", Cookie | Rest], Acc, TargetNode) ->
+    erlang:set_cookie(node(), list_to_atom(Cookie)),
+    process_args(Rest, Acc, TargetNode);
+process_args(["-name", TargetName | Rest], Acc, _) ->
+    ThisNode = append_node_suffix(TargetName, "_maint_"),
+    {ok, _} = net_kernel:start([ThisNode, longnames]),
+    process_args(Rest, Acc, nodename(TargetName));
+process_args(["-sname", TargetName | Rest], Acc, _) ->
+    ThisNode = append_node_suffix(TargetName, "_maint_"),
+    {ok, _} = net_kernel:start([ThisNode, shortnames]),
+    process_args(Rest, Acc, nodename(TargetName));
+process_args([Arg | Rest], Acc, Opts) ->
+    process_args(Rest, [Arg | Acc], Opts).
+
+
+nodename(Name) ->
+    case string:tokens(Name, "@") of
+        [_Node, _Host] ->
+            list_to_atom(Name);
+        [Node] ->
+            [_, Host] = string:tokens(atom_to_list(node()), "@"),
+            list_to_atom(lists:concat([Node, "@", Host]))
+    end.
+
+append_node_suffix(Name, Suffix) ->
+    case string:tokens(Name, "@") of
+        [Node, Host] ->
+            list_to_atom(lists:concat([Node, Suffix, os:getpid(), "@", Host]));
+        [Node] ->
+            list_to_atom(lists:concat([Node, Suffix, os:getpid()]))
+    end.
diff --git a/rel/files/osmo b/rel/files/osmo
new file mode 100755
index 0000000..10c233b
--- /dev/null
+++ b/rel/files/osmo
@@ -0,0 +1,149 @@
+#!/bin/bash
+# -*- tab-width:4;indent-tabs-mode:nil -*-
+# ex: ts=4 sw=4 et
+
+RUNNER_SCRIPT_DIR=$(cd ${0%/*} && pwd)
+
+RUNNER_BASE_DIR=${RUNNER_SCRIPT_DIR%/*}
+RUNNER_ETC_DIR=$RUNNER_BASE_DIR/etc
+RUNNER_LOG_DIR=$RUNNER_BASE_DIR/log
+PIPE_DIR=/tmp/$RUNNER_BASE_DIR/
+RUNNER_USER=
+
+# Make sure this script is running as the appropriate user
+if [ ! -z "$RUNNER_USER" ] && [ `whoami` != "$RUNNER_USER" ]; then
+    exec sudo -u $RUNNER_USER -i $0 $@
+fi
+
+# Make sure CWD is set to runner base dir
+cd $RUNNER_BASE_DIR
+
+# Make sure log directory exists
+mkdir -p $RUNNER_LOG_DIR
+
+# Extract the target node name from node.args
+NAME_ARG=`grep -e '-[s]*name' $RUNNER_ETC_DIR/vm.args`
+if [ -z "$NAME_ARG" ]; then
+    echo "vm.args needs to have either -name or -sname parameter."
+    exit 1
+fi
+
+# Extract the target cookie
+COOKIE_ARG=`grep -e '-setcookie' $RUNNER_ETC_DIR/vm.args`
+if [ -z "$COOKIE_ARG" ]; then
+    echo "vm.args needs to have a -setcookie parameter."
+    exit 1
+fi
+
+# Identify the script name
+SCRIPT=`basename $0`
+
+# Parse out release and erts info
+START_ERL=`cat $RUNNER_BASE_DIR/releases/start_erl.data`
+ERTS_VSN=${START_ERL% *}
+APP_VSN=${START_ERL#* }
+
+# Add ERTS bin dir to our path
+ERTS_PATH=$RUNNER_BASE_DIR/erts-$ERTS_VSN/bin
+
+# Setup command to control the node
+NODETOOL="$ERTS_PATH/escript $ERTS_PATH/nodetool $NAME_ARG $COOKIE_ARG"
+
+# Check the first argument for instructions
+case "$1" in
+    start)
+        # Make sure there is not already a node running
+        RES=`$NODETOOL ping`
+        if [ "$RES" = "pong" ]; then
+            echo "Node is already running!"
+            exit 1
+        fi
+        HEART_COMMAND="$RUNNER_BASE_DIR/bin/$SCRIPT start"
+        export HEART_COMMAND
+        mkdir -p $PIPE_DIR
+        # Note the trailing slash on $PIPE_DIR/
+        $ERTS_PATH/run_erl -daemon $PIPE_DIR/ $RUNNER_LOG_DIR "exec $RUNNER_BASE_DIR/bin/$SCRIPT console" 2>&1
+        ;;
+
+    stop)
+        # Wait for the node to completely stop...
+        case `uname -s` in
+            Linux|Darwin|FreeBSD|DragonFly|NetBSD|OpenBSD)
+                # PID COMMAND
+                PID=`ps ax -o pid= -o command=|\
+                    grep "$RUNNER_BASE_DIR/.*/[b]eam"|awk '{print $1}'`
+                ;;
+            SunOS)
+                # PID COMMAND
+                PID=`ps -ef -o pid= -o args=|\
+                    grep "$RUNNER_BASE_DIR/.*/[b]eam"|awk '{print $1}'`
+                ;;
+            CYGWIN*)
+                # UID PID PPID TTY STIME COMMAND
+                PID=`ps -efW|grep "$RUNNER_BASE_DIR/.*/[b]eam"|awk '{print $2}'`
+                ;;
+        esac
+        $NODETOOL stop
+        while `kill -0 $PID 2>/dev/null`;
+        do
+            sleep 1
+        done
+        ;;
+
+    restart)
+        ## Restart the VM without exiting the process
+        $NODETOOL restart
+        ;;
+
+    reboot)
+        ## Restart the VM completely (uses heart to restart it)
+        $NODETOOL reboot
+        ;;
+
+    ping)
+        ## See if the VM is alive
+        $NODETOOL ping
+        ;;
+
+    attach)
+        # Make sure a node IS running
+        RES=`$NODETOOL ping`
+        if [ "$RES" != "pong" ]; then
+            echo "Node is not running!"
+            exit 1
+        fi
+
+        shift
+        $ERTS_PATH/to_erl $PIPE_DIR
+        ;;
+
+    console)
+        # Setup beam-required vars
+        ROOTDIR=$RUNNER_BASE_DIR
+        BINDIR=$ROOTDIR/erts-$ERTS_VSN/bin
+        EMU=beam
+        PROGNAME=`echo $0 | sed 's/.*\\///'`
+        CMD="$BINDIR/erlexec -boot $RUNNER_BASE_DIR/releases/$APP_VSN/$SCRIPT -embedded -config $RUNNER_ETC_DIR/app.config -args_file $RUNNER_ETC_DIR/vm.args -- ${1+"$@"}"
+        export EMU
+        export ROOTDIR
+        export BINDIR
+        export PROGNAME
+
+        # Dump environment info for logging purposes
+        echo "Exec: $CMD"
+        echo "Root: $ROOTDIR"
+
+        # Log the startup
+        logger -t "$SCRIPT[$$]" "Starting up"
+
+        # Start the VM
+        exec $CMD
+        ;;
+
+    *)
+        echo "Usage: $SCRIPT {start|stop|restart|reboot|ping|console|attach}"
+        exit 1
+        ;;
+esac
+
+exit 0
diff --git a/rel/files/vm.args b/rel/files/vm.args
new file mode 100644
index 0000000..a2ec28a
--- /dev/null
+++ b/rel/files/vm.args
@@ -0,0 +1,21 @@
+
+## Name of the node
+-name osmo@127.0.0.1
+
+## Cookie for distributed erlang
+-setcookie osmo
+
+## Heartbeat management; auto-restarts VM if it dies or becomes unresponsive
+## (Disabled by default..use with caution!)
+##-heart
+
+## Enable kernel poll and a few async threads
++K true
++A 5
+
+## Increase number of concurrent ports/sockets
+-env ERL_MAX_PORTS 4096
+
+## Tweak GC to run more often
+-env ERL_FULLSWEEP_AFTER 10
+