Posts tagged ‘erlang’

Releasing Erlang/OTP Code

I’m trying to understand how to build an OTP “release”.  The Erlang documentation leans more toward reference material than how-to (System Principles) and online references that I’ve found rely on various third party tools (Building An OTP Application).  I decided to walk through the steps manually to better understand how all the pieces fit together.  Ultimately, my goal is to experiment with OTP’s hot code swapping.

Definitions: Modules, Applications, Supervisors, Workers, Releases

Erlang code is organized into .erl files.  Each file is a Module.  An Application is some code with a defined entry point.  Once the application is running (and assuming your using the OTP framework), Supervisor processes manage Worker processes that are running code in your Modules.  Hence, an Application is a collection of Modules which are the code needed to run your application.  An Application has a version number.  Applications are grouped together into a Release.  A Release identifies the required versions of its component Applications.  A Release also has a version number which is more or less unrelated to the Applications’ version numbers.  You deploy a new Release in order to upgrade the software on a running system. You create a target system to run the first version.

Application File Structure

An Application has a particular file structure:

  • include – .hrl files (common includes)
  • ebin – .beam, .app files (objects)
  • src – .erl (and other) source files
  • priv – application specific files

Module: gen_server

Let’s start with simple OTP generic server so we have something useful to play with.  This server remembers a single value.

  • simpletest:set(10) – sets the value it remembers to 10.
  • simpletest:add(20) – adds 20 to the value.

The initial value is 0.
simpletest-1.0/src/simpletest.erl:

-module(simpletest).

-export([start_link/0]).
-export([set/1, add/1]).

-behaviour(gen_server).
-export([init/1, handle_call/3, handle_cast/2, handle_info/2, terminate/2, code_change/3]).

start_link() ->
    gen_server:start_link({local, ?MODULE}, ?MODULE, [], []).

set(Value) ->
    gen_server:call(?MODULE, {set, Value}).

add(Value) ->
    gen_server:call(?MODULE, {add, Value}).

init(_Args) ->
    {ok, 0}.

handle_call({set, Value}, _From, _Accumulator) ->
    {reply, {ok, Value}, Value};
handle_call({add, Value}, _From, Accumulator) ->
    Accumulator1 = Accumulator + Value,
    {reply, {ok, Accumulator1}, Accumulator1}.

handle_cast(_Request, Accumulator) ->
    {noreply, Accumulator}.

handle_info(_Request, Accmulator) ->
    {noreply, Accmulator}.

terminate(_Reason, _State) ->
    ok.

code_change(_OldVsn, State, _Extra) ->
    {ok, State}.

The generic server needs a supervisor.
simpletest-1.0/src/simpletest_sup.erl:

-module(simpletest_sup).

-export([start_link/0]).

-behaviour(supervisor).
-export([init/1]).

start_link() ->
    supervisor:start_link({local, ?MODULE}, ?MODULE, []).

init([]) ->
    SimpleTest = {
        id,
        { simpletest, start_link, [] },
        permanent, brutal_kill, worker, [simpletest]
    },
    {ok, {{one_for_one, 3, 1000}, [SimpleTest]}}.

Our supervisor needs an application.
simpletest-1.0/src/simpletest_app.erl:

-module(simpletest_app).

-behaviour(application).
-export([start/2, stop/1]).

start(normal, _StartArgs) ->
    simpletest_sup:start_link().

stop(_State) ->
    ok.

Build the .beam files into simpletest-1.0/ebin:

$ erlc -W -o ../ebin simpletest.erl simpletest_sup.erl simpletest_app.erl

The Application resource file (.app file) bundles the modules into the application and tells the application module how to launch our Application. vsn is the version of the application. This is the first place that we’ve identified the version. registered lists the named processes. applications are the applications that need to be running for our application to work. Most applications require at least kernel and stdlib. modules lists all of the modules in our application. Remember that the supervisor and application behaviors are also modules in our application. mod is the entry point to our application.
simpletest-1.0/ebin/simpletest.app:

{application, simpletest,
    [
        {description, "Simple Test"},
        {id, "simpletest"},
        {vsn, "1.0"},
        {registered, [simpletest_sup, simpletest]},
        {applications, [kernel, stdlib]},
        {modules, [simpletest, simpletest_sup, simpletest_app]},
        {mod, {simpletest_app, []}}
    ]
}.

In a separate directory, create a Release resource file (.rel) to bundle the Application into a Release. “Alpha1” is the name of our release and “1.0” is the version of our release. {simpletest, “1.0”} is our application. You can find the other application versions with application:loaded_applications().
releasetest.rel:

{release,
    {"Alpha1", "1.0"},
    {erts, "5.6.2"},
    [
        {kernel, "2.12.2"},
        {stdlib, "1.15.2"},
        {sasl, "2.1.5.2"},
        {simpletest, "1.0"}
    ]
}.

Creating the initial target system

A target system is a self-contained .tar.gz file for running a Release. The initial target system is the first version of the Release.

Create a stripped down Release resource file called plain.rel that has only kernel and stdlib.
plain.rel:

{release,
    {"Alpha1", "1.0"},
    {erts, "5.6.2"},
    [
        {kernel, "2.12.2"},
        {stdlib, "1.15.2"}
    ]
}.

Create the boot scripts for plain.rel and releasetest.rel. no_module_tests skips checking that module .beam files have corresponding .erl files and the .beam file is newer than the corresponding .erl file.

$ erl -pa .../simpletest-1.0/ebin
1> systools:make_script("plain", [no_module_tests]).
ok
2> systools:make_script("releasetest", [no_module_tests]).
ok

Wrap everything into a .tar.gz file. erts makes systools:make_tar include the Erlang Runtime System in the .tar.gz file.

3> systools:make_tar("releasetest", [{erts, code:root_dir()}]).
ok

In a temporary directory, extract the files from the testrelease.tar.gz file and rearrange the files:

$ mkdir tmp
$ cd tmp
$ tar zxf ../releasetest.tar.gz
$ rm ../releasetest.tar.gz
$ rm erts-5.6.2/bin/erl
$ rm erts-5.6.2/bin/start
$ mkdir bin
$ cp .../plain.boot bin/start.boot
$ cp -p erts-5.6.2/bin/empd bin
$ cp -p erts-5.6.2/bin/run_erl bin
$ cp -p erts-5.6.2/bin/to_erl bin

Create releases/start_erl.data with the erts version and the version of our release:

5.6.2 1.0

Rebuild the tar file.

$ tar czf ../releasetest.tar.gz bin erts-5.6.2 releases lib
$ cd ..
$ rm -fr tmp

Installing the Target System

Create a directory for the target system, untar the release and fix up the root dir in some of the start scripts.

$ mkdir .../target
$ cd .../target
$ tar zxf .../releasetest.tar.gz
$ cp erts-5.6.2/bin/erl.src bin/erl
$ cp erts-5.6.2/bin/start.src bin/start
$ cp erts-5.6.2/bin/start_erl.src bin/start_erl

In bin/erl and bin/start, replace %FINAL_ROOTDIR% with …/target.
Finish creating the release:

1> release_handler:create_RELEASES(".../target", ".../target/releases/releasetest.rel").

To launching the target system without booting the application use:

$ .../target/bin/erl

To boot the application on the target system:

$ .../target/bin/erl -boot .../target/releases/1.0/start

Now we have a self-contained Erlang runtime system for our release.

Loading new code

The next trick is to swap out the code in the running system. There are several flavors of code replacement. We’ll start with the simplest where replacing the code does not require anything more than reloading the module.

To experiment with this, let’s create a new version of simpletest.erl that includes a reset() function.
Revised simpletest-2.0/src/simpletest.erl (new lines marked with |):

-module(simpletest).

-export([start_link/0]).
-export([reset/0, set/1, add/1]).
-behaviour(gen_server).
-export([init/1, handle_call/3, handle_cast/2, handle_info/2, terminate/2, code_
change/3]).

start_link() ->
    gen_server:start_link({local, ?MODULE}, ?MODULE, [], []).

| reset() ->
|     gen_server:call(?MODULE, reset).

set(Value) ->
    gen_server:call(?MODULE, {set, Value}).

add(Value) ->
    gen_server:call(?MODULE, {add, Value}).

init(_Args) ->
    {ok, 0}.

| handle_call(reset, _From, _Accumulator) ->
|     Value = 0,
|     {reply, {ok, Value}, Value};
handle_call({set, Value}, _From, _Accumulator) ->
    {reply, {ok, Value}, Value};
handle_call({add, Value}, _From, Accumulator) ->
    Accumulator1 = Accumulator + Value,
    {reply, {ok, Accumulator1}, Accumulator1}.

handle_cast(_Request, Accumulator) ->
    {noreply, Accumulator}.

handle_info(_Request, Accmulator) ->
    {noreply, Accmulator}.

terminate(_Reason, _State) ->
    ok.

code_change(_OldVsn, State, _Extra) ->
    {ok, State}.

Update the version (vsn) in the .app file to 2.0.
simpletest-2.0/ebin/simpletest.app:

{application, simpletest,
    [
        {description, "Simple Test"},
        {id, "simpletest"},
        {vsn, "2.0"},
        {registered, [simpletest_sup, simpletest]},
        {applications, [kernel, stdlib]},
        {modules, [simpletest, simpletest_sup, simpletest_app]},
        {mod, {simpletest_app, []}}
    ]
}.

An application upgrade file (.appup) describes how to upgrade the application. For upgrading (and downgrading) from simpletest-1.0 to simpletest-2.0 all we need to do is reload the simpletest module.
simpletest-2.0/ebin/simpletest.appup:

{
    "2.0",
    [{"1.0", [{load_module, simpletest}]}],
    [{"1.0", [{load_module, simpletest}]}]
}.

Make a 2.0 Release file. I changed the release version to 2.0 and the version of our simpletest application to 2.0.
releasetest-2.0:

{release,
    {"Alpha1", "2.0"},
    {erts, "5.6.2"},
    [
        {kernel, "2.12.2"},
        {stdlib, "1.15.2"},
        {sasl, "2.1.5.2"},
        {simpletest, "2.0"}
    ]
}.

Next we need a relup file that describes the upgrade from release 1.0 to release 2.0. We make a relup file from the .rel files. systools:make_relup() needs to see the .app and .beam files for both versions. (You can also specify the paths to these files with systools:make_relup().)

$ erl -pa simpletest-2.0/ebin -pa simpletest-1.0/ebin
1> systools:make_relup("releasetest-2.0", ["releasetest"], ["releasetest"]).
ok

Create the release tar file.

$ erl -pa simpletest-2.0/ebin
1> systools:make_script("releasetest-2.0", [no_module_tests]).
ok
2> systools:make_tar("releasetest-2.0").
ok

To deploy the upgrade, copy releasetest-2.0.tar.gz into …target/releases.

Use release_handler:unpack_release() to unpack the .tar.gz file. release_handler:install_release() installs the release and switches the running code to the new version. release_handler:make_permanent() sets the boot version.

Unpack and install new version and demonstrate that the new code is installed and the state of the server is preserved:

1> release_handler:unpack_release("releasetest-2.0").
{ok,"2.0"}

% old server does not have the 2.0 feature
2> simpletest:reset()
** exception error: undefined function simpletest:reset/0

% set some state
3> simpletest:set(100)
{ok,100}

% install release 2.0
4> release_handler:install_release("2.0").
{ok,"1.0",[]}

% make release 2.0 permanent
5> release_handler:make_permanent("2.0").
ok

% demonstrate the state is preserved
6> simpletest:add(100).
{ok,200}

% we now have 2.0 features
7> simpletest:reset()
{ok,0}

If we decide we don’t like 2.0, we can downgrade with release_handler:install_release(“1.0”).

Conclusion

A Release is a set of Applications.  An Application is a set of Modules.  A Module is a .erl file.  An Application launches supervisors.  Supervisors launch Workers.

So, there you have it. All the gory details to building a release into a target system, launching the release on the target system, and pushing a code update.

August 22, 2008 at 5:03 pm Leave a comment


Calendar

April 2024
S M T W T F S
 123456
78910111213
14151617181920
21222324252627
282930  

Posts by Month

Posts by Category