Ease of deployment is one of the things I seriously consider when evaluating technology solutions. In this post, a modified version of the Elixir getting started echo server will be installed as a FreeBSD service. There are three goals.

  • The app needs to be able to be rebuilt and the service restarted to reflect changes on a development machine.
  • The service needs to automatically start when the machine is booted.
  • The service sould work like any other service.
service elixir_echo start
service elixir_echo stop
service elixir_echo restart
service elixir_echo status

The steps are a little involved, but ultimately straightforward.

Software Versions

$ date
January 17, 2016 at 07:37:31 PM JST
$ uname -a
FreeBSD mirage.sennue.com 11.0-CURRENT FreeBSD 11.0-CURRENT #0 r287598: Thu Sep 10 14:45:48 JST 2015     root@:/usr/obj/usr/src/sys/MIRAGE_KERNEL  amd64
$ elixir --version
Erlang/OTP 18 [erts-7.2.1] [source] [64-bit] [async-threads:10] [hipe] [kernel-poll:false]
Elixir 1.2.0

Instructions

elixir needs to be installed. The tooling to install dependencies for elixir apps comes with the port.

sudo portmaster lang/elixir

First, start a new project for the echo service.

mix new --sup elixir_echo
cd elixir_echo

Next, add a modified version of the echo server from the Elixir getting started section. This version loads the port from environment variables or the app configuration environment. The default fallback is port 4040. It also gracefully handles closed sockets. The code goes in lib/echo_elixir.ex.

defmodule ElixirEcho do
  use Application
  require Logger

  @default_port 4040

  @doc false
  def start(_type, _args) do
    import Supervisor.Spec

    port = "PORT" |> get_env(@default_port) |> to_integer(@default_port)

    children = [
      supervisor(Task.Supervisor, [[name: ElixirEcho.TaskSupervisor]]),
      worker(Task, [ElixirEcho, :accept, [port]])
    ]

    opts = [strategy: :one_for_one, name: ElixirEcho.Supervisor]
    Supervisor.start_link(children, opts)
  end

  @doc """
  Starts accepting connections on the given `port`.
  """
  def accept(port) do
    {:ok, socket} = :gen_tcp.listen(port,
                      [:binary, packet: :line, active: false, reuseaddr: true])
    Logger.info "Accepting connections on port #{port}"
    loop_acceptor(socket)
  end

  defp loop_acceptor(socket) do
    {:ok, client} = :gen_tcp.accept(socket)
    {:ok, pid} = Task.Supervisor.start_child(ElixirEcho.TaskSupervisor, fn -> serve(client) end)
    :ok = :gen_tcp.controlling_process(client, pid)
    Logger.info "Opened connection"
    loop_acceptor(socket)
  end

  defp serve(socket) do
    status = socket
    |> read_line()
    |> write_line(socket)

    case status do
      :ok ->
        serve(socket)
      :closed ->
        Logger.info "Closed connection"
        :gen_tcp.close(socket)
        :ok
    end
  end

  defp read_line(socket) do
    case :gen_tcp.recv(socket, 0) do
      {:ok, data} ->
        data
      {:error, :closed} ->
        :closed
    end
  end

  defp write_line(:closed, _socket), do: :closed
  defp write_line(line, socket) do
    :gen_tcp.send(socket, line)
    Logger.info "Echo: #{line |> String.strip}"
    :ok
  end

  # Utility Functions

  def get_env(name, default) do
    case (
      System.get_env(name) ||
      Application.get_env(:elixir_echo, name |> String.downcase |> String.to_atom)
    ) |> to_string
    do
      "" -> default |> to_string
      result -> result
    end
  end

  def to_integer(x, _default) when is_integer(x), do: x
  def to_integer(x, default) when is_binary(x) do
    case x |> Integer.parse do
      {result, _} -> result
      :error -> default
    end
  end
  def to_integer(_, default), do: default
end

Add the elixir release manager (exrm) to mix.exs as a project dependency.

  defp deps do
    [{:exrm, "~> 1.0.0-rc7"}]
  end

Install exrm and build a release. This will create the rel/ directory.

mix deps.get
mix deps.compile
mix release

The rc script will use environment variable knobs to configure the app. Note that the RELX_REPLACE_OS_VARS=true environment variable needs to be defined to use environment variables for dynamic configuration.

The vm.args file is primarily used to configure the erlang VM. It can also be used to define application configure parameters. Application configuration parameters defined in this file can be passed into the program as atoms or integers. Add the following to rel/vm.args.

## Name of the node
-name ${NODE_NAME}

## Cookie for distributed erlang
-setcookie ${COOKIE}

## App Settings
-elixir_echo port ${PORT}

Alternatively, sys.config can be used to pass in application configuration parameters. In this file, application configuration parameters defined with environment variables must be strings. Pass the port setting in as above or add the following to rel/sys.config. The app module was written to work with either solution. Adding both files will not break anything.

[
  {elixir_echo, [
    {port, "${PORT}"}
  ]}
].

Build a release with the configuration files and do the initial install.

mix release
su
sh
PROJECT=elixir_echo
INSTALL_DIR=/usr/local/opt
VERSION=$(cat rel/${PROJECT}/releases/start_erl.data | cut -d' ' -f2)
INSTALL_TAR=`pwd`/rel/$PROJECT/releases/$VERSION/$PROJECT.tar.gz
mkdir -p $INSTALL_DIR/$PROJECT
(cd $INSTALL_DIR/$PROJECT; \
tar -xf $INSTALL_TAR)
pw adduser $PROJECT -d $INSTALL_DIR/$PROJECT -s /usr/sbin/nologin -c "$PROJECT system service user"
chown -R $PROJECT:$PROJECT $INSTALL_DIR/$PROJECT

An rc script defines the the service. elixir_echo_run() is called from the other functions. It configures and calls the release. HOME is set to the installation directory to force the erlang cookie file to be written there regardless of elixir_echo_user setting. elixir_echo_status() echoes a user friendly message if the release can be pinged. Add shutdown to the keyword list if the service needs to gracefull shutdown when the machine restarts. The rest is standard rc configuration. Add the rc script to /usr/local/etc/rc.d/elixir_echo

#!/bin/sh
#
# PROVIDE: elixir_echo
# REQUIRE: networking
# KEYWORD:
 
. /etc/rc.subr
 
name="elixir_echo"
rcvar="${name}_enable"
install_dir="/usr/local/opt/${name}"
version=$(cat ${install_dir}/releases/start_erl.data | cut -d' ' -f2)
command="${install_dir}/bin/${name}"
 
start_cmd="${name}_start"
stop_cmd="${name}_stop"
status_cmd="${name}_status"

load_rc_config $name
: ${elixir_echo_enable:="no"}
: ${elixir_echo_port:="4040"}
: ${elixir_echo_user:=${name}}
: ${elixir_echo_node_name:="${name}@127.0.0.1"}
: ${elixir_echo_cookie:="${name}"}
: ${elixir_echo_config_dir:="${install_dir}/releases/${version}/${name} start"}

elixir_echo_run()
{
  RELX_REPLACE_OS_VARS=true \
  HOME="${install_dir}" \
  RELEASE_CONFIG_DIR="${elixir_echo_config}" \
  NODE_NAME="${elixir_echo_node_name}" \
  COOKIE="${elixir_echo_cookie}" \
  PORT="${elixir_echo_port}" \
  su -m "$elixir_echo_user" -c "$command $1"
}

elixir_echo_start()
{
  elixir_echo_run start
}

elixir_echo_stop()
{
  elixir_echo_run stop
}

elixir_echo_status()
{
  ping_result=`elixir_echo_run ping`
  echo "${ping_result}"
  case "${ping_result}" in
    *pong*)
      echo "${name} is running."
      ;;
  esac
}

load_rc_config $name
run_rc_command "$1"

Enable and configure the service in /etc/rc.conf

elixir_echo_enable="YES"
elixir_echo_port=8255
elixir_echo_node_name="parrot"
elixir_echo_cookie="cracker"

The service can now be started. If the service is enabled, it will automatically start when the machine boots.

service elixir_echo start
telnet 127.0.0.1 8255 # make sure it works

Optional: Adding a Release to the Systemwide Path

Adding a release to the systemwide path is not necessary, but it can be convenient. The pass through script can be pointed at the development install instead of the service install if you want to build with exrm mix release –dev.

Create a directory for the convenience pass through script.

mkdir -p $INSTALL_DIR/bin

NODE_NAME and COOKIE need default values because vm.args has no useful default fallbacks. PORT has a fallback. Add the script to /usr/local/opt/bin/elixir_echo

#!/bin/sh
SCRIPT=$(realpath $0)
BASENAME=$(basename $SCRIPT)
BASEDIR=$(dirname $SCRIPT)
COMMAND=$(realpath $BASEDIR/../$BASENAME/bin/$BASENAME)

: ${NODE_NAME:=${BASENAME}}
: ${COOKIE:=${BASENAME}}
NODE_NAME=$NODE_NAME COOKIE=$COOKIE RELX_REPLACE_OS_VARS=true $COMMAND "$@"

Make the script executable.

chmod +x $INSTALL_DIR/bin/$PROJECT

Add /usr/local/opt/bin to the global path in /etc/profile for sh.

PATH=/usr/local/opt/bin:$PATH
export PATH

Add /usr/local/opt/bin to the global path in /etc/csh.cshrc for csh. Consider updating the root path in /root/.cshrc.

set path=(/usr/local/opt/bin $path)

Update the path in the current shell if necessary.

# sh bash
source /etc/csh.cshrc
# csh tcsh
. /etc/profile

Fix permissions if you want to be able to run as any user. This has security implications. It may make more sense to point the script at the development release if it is being used as a development convenience.

chmod 755 $INSTALL_DIR/$PROJECT/bin/$PROJECT
chmod 755 $INSTALL_DIR/$PROJECT/bin/nodetool
chmod 755 $INSTALL_DIR/$PROJECT/releases/$VERSION/$PROJECT.sh
mkdir -p $INSTALL_DIR/$PROJECT/log
chmod 777 $INSTALL_DIR/$PROJECT/log
chmod 777 $INSTALL_DIR/$PROJECT/log/*.*
mkdir -p $INSTALL_DIR/$PROJECT/tmp/erl_pipes/$PROJECT
chmod 777 $INSTALL_DIR/$PROJECT/tmp/erl_pipes/$PROJECT
mkdir -p $INSTALL_DIR/$PROJECT/running-config/
chmod 777 $INSTALL_DIR/$PROJECT/running-config/
chmod 666 $INSTALL_DIR/$PROJECT/running-config/*.*
chown -R $PROJECT:$PROJECT $INSTALL_DIR/$PROJECT

The release can now be conveniently controlled.

NODE_NAME=canary COOKIE=sesame PORT=5678 elixir_echo start
telnet 127.0.0.1 5678 # make sure it works

Setup Complete

Switch from root to a normal user.

exit # sh
exit # su

Updating

Casual updates on a development machine can be performed as follows.

mix release
su
sh
PROJECT=elixir_echo
INSTALL_DIR=/usr/local/opt
VERSION=$(cat rel/${PROJECT}/releases/start_erl.data | cut -d' ' -f2)
INSTALL_TAR=`pwd`/rel/$PROJECT/releases/$VERSION/$PROJECT.tar.gz
(cd $INSTALL_DIR/$PROJECT; \
tar -xf $INSTALL_TAR)
chown -R $PROJECT:$PROJECT $INSTALL_DIR/$PROJECT
service $PROJECT restart
exit # sh
exit # su

Troubleshooting

If configuration looks like it should be working, but nothing changes, try deleting the running-config directory. Sometimes rebooting fixes problems, like killing zombie nodes with strange default names and cookie values.

What Next?

Consider looking into edeliver for deployment. “edeliver is based on deliver and provides a bash script to build and deploy Elixir and Erlang applications and perform hot-code upgrades.”

References: