~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to system/doc/design_principles/des_princ.xml

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
<?xml version="1.0" encoding="latin1" ?>
 
2
<!DOCTYPE chapter SYSTEM "chapter.dtd">
 
3
 
 
4
<chapter>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>1997</year><year>2009</year>
 
8
      <holder>Ericsson AB. All Rights Reserved.</holder>
 
9
    </copyright>
 
10
    <legalnotice>
 
11
      The contents of this file are subject to the Erlang Public License,
 
12
      Version 1.1, (the "License"); you may not use this file except in
 
13
      compliance with the License. You should have received a copy of the
 
14
      Erlang Public License along with this software. If not, it can be
 
15
      retrieved online at http://www.erlang.org/.
 
16
    
 
17
      Software distributed under the License is distributed on an "AS IS"
 
18
      basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
19
      the License for the specific language governing rights and limitations
 
20
      under the License.
 
21
    
 
22
    </legalnotice>
 
23
 
 
24
    <title>Overview</title>
 
25
    <prepared></prepared>
 
26
    <docno></docno>
 
27
    <date></date>
 
28
    <rev></rev>
 
29
    <file>des_princ.xml</file>
 
30
  </header>
 
31
  <p>The <em>OTP Design Principles</em> is a set of principles for how
 
32
    to structure Erlang code in terms of processes, modules and
 
33
    directories.</p>
 
34
 
 
35
  <section>
 
36
    <title>Supervision Trees</title>
 
37
    <p>A basic concept in Erlang/OTP is the <em>supervision tree</em>.
 
38
      This is a process structuring model based on the idea of
 
39
      <em>workers</em> and <em>supervisors</em>.</p>
 
40
    <list type="bulleted">
 
41
      <item>Workers are processes which perform computations, that is,
 
42
       they do the actual work.</item>
 
43
      <item>Supervisors are processes which monitor the behaviour of
 
44
       workers. A supervisor can restart a worker if something goes
 
45
       wrong.</item>
 
46
      <item>The supervision tree is a hierarchical arrangement of
 
47
       code into supervisors and workers, making it possible to
 
48
       design and program fault-tolerant software.</item>
 
49
    </list>
 
50
    <marker id="sup6"></marker>
 
51
    <image file="../design_principles/sup6.gif">
 
52
      <icaption>Supervision Tree</icaption>
 
53
    </image>
 
54
    <p>In the figure above, square boxes represents supervisors and
 
55
      circles represent workers.</p>
 
56
  </section>
 
57
 
 
58
  <section>
 
59
    <title>Behaviours</title>
 
60
    <p>In a supervision tree, many of the processes have similar
 
61
      structures, they follow similar patterns. For example,
 
62
      the supervisors are very similar in structure. The only difference
 
63
      between them is which child processes they supervise. Also, many
 
64
      of the workers are servers in a server-client relation, finite
 
65
      state machines, or event handlers such as error loggers.</p>
 
66
    <p><em>Behaviours</em> are formalizations of these common patterns.
 
67
      The idea is to divide the code for a process in a generic part
 
68
      (a behaviour module) and a specific part (a <em>callback module</em>).</p>
 
69
    <p>The behaviour module is part of Erlang/OTP. To implement a
 
70
      process such as a supervisor, the user only has to implement
 
71
      the callback module which should export a pre-defined set of
 
72
      functions, the <em>callback functions</em>.</p>
 
73
    <p>An example to illustrate how code can be divided into a generic
 
74
      and a specific part: Consider the following code (written in
 
75
      plain Erlang) for a simple server, which keeps track of a number
 
76
      of "channels". Other processes can allocate and free the channels
 
77
      by calling the functions <c>alloc/0</c> and <c>free/1</c>,
 
78
      respectively.</p>
 
79
    <marker id="ch1"></marker>
 
80
    <code type="none">
 
81
-module(ch1).
 
82
-export([start/0]).
 
83
-export([alloc/0, free/1]).
 
84
-export([init/0]).
 
85
 
 
86
start() ->
 
87
    spawn(ch1, init, []).
 
88
 
 
89
alloc() ->
 
90
    ch1 ! {self(), alloc},
 
91
    receive
 
92
        {ch1, Res} ->
 
93
            Res
 
94
    end.
 
95
 
 
96
free(Ch) ->
 
97
    ch1 ! {free, Ch},
 
98
    ok.
 
99
 
 
100
init() ->
 
101
    register(ch1, self()),
 
102
    Chs = channels(),
 
103
    loop(Chs).
 
104
 
 
105
loop(Chs) ->
 
106
    receive
 
107
        {From, alloc} ->
 
108
            {Ch, Chs2} = alloc(Chs),
 
109
            From ! {ch1, Ch},
 
110
            loop(Chs2);
 
111
        {free, Ch} ->
 
112
            Chs2 = free(Ch, Chs),
 
113
            loop(Chs2)
 
114
    end.</code>
 
115
    <p>The code for the server can be rewritten into a generic part
 
116
      <c>server.erl</c>:</p>
 
117
    <code type="none">
 
118
-module(server).
 
119
-export([start/1]).
 
120
-export([call/2, cast/2]).
 
121
-export([init/1]).
 
122
 
 
123
start(Mod) ->
 
124
    spawn(server, init, [Mod]).
 
125
 
 
126
call(Name, Req) ->
 
127
    Name ! {call, self(), Req},
 
128
    receive
 
129
        {Name, Res} ->
 
130
            Res
 
131
    end.
 
132
 
 
133
cast(Name, Req) ->
 
134
    Name ! {cast, Req},
 
135
    ok.
 
136
 
 
137
init(Mod) ->
 
138
    register(Mod, self()),
 
139
    State = Mod:init(),
 
140
    loop(Mod, State).
 
141
 
 
142
loop(Mod, State) ->
 
143
    receive
 
144
        {call, From, Req} ->
 
145
            {Res, State2} = Mod:handle_call(Req, State),
 
146
            From ! {Mod, Res},
 
147
            loop(Mod, State2);
 
148
        {cast, Req} ->
 
149
            State2 = Mod:handle_cast(Req, State),
 
150
            loop(Mod, State2)
 
151
    end.</code>
 
152
    <p>and a callback module <c>ch2.erl</c>:</p>
 
153
    <code type="none">
 
154
-module(ch2).
 
155
-export([start/0]).
 
156
-export([alloc/0, free/1]).
 
157
-export([init/0, handle_call/2, handle_cast/2]).
 
158
 
 
159
start() ->
 
160
    server:start(ch2).
 
161
 
 
162
alloc() ->
 
163
    server:call(ch2, alloc).
 
164
 
 
165
free(Ch) ->
 
166
    server:cast(ch2, {free, Ch}).
 
167
 
 
168
init() ->
 
169
    channels().
 
170
 
 
171
handle_call(alloc, Chs) ->
 
172
    alloc(Chs). % => {Ch,Chs2}
 
173
 
 
174
handle_cast({free, Ch}, Chs) ->
 
175
    free(Ch, Chs). % => Chs2</code>
 
176
    <p>Note the following:</p>
 
177
    <list type="bulleted">
 
178
      <item>The code in <c>server</c> can be re-used to build many
 
179
       different servers.</item>
 
180
      <item>The name of the server, in this example the atom
 
181
      <c>ch2</c>, is hidden from the users of the client functions.
 
182
       This means the name can be changed without affecting them.</item>
 
183
      <item>The protcol (messages sent to and received from the server)
 
184
       is hidden as well. This is good programming practice and allows
 
185
       us to change the protocol without making changes to code using
 
186
       the interface functions.</item>
 
187
      <item>We can extend the functionality of <c>server</c>, without
 
188
       having to change <c>ch2</c> or any other callback module.</item>
 
189
    </list>
 
190
    <p>(In <c>ch1.erl</c> and <c>ch2.erl</c> above, the implementation
 
191
      of <c>channels/0</c>, <c>alloc/1</c> and <c>free/2</c> has been
 
192
      intentionally left out, as it is not relevant to the example.
 
193
      For completeness, one way to write these functions are given
 
194
      below. Note that this is an example only, a realistic
 
195
      implementation must be able to handle situations like running out
 
196
      of channels to allocate etc.)</p>
 
197
    <code type="none">
 
198
channels() ->
 
199
   {_Allocated = [], _Free = lists:seq(1,100)}.
 
200
 
 
201
alloc({Allocated, [H|T] = _Free}) ->
 
202
   {H, {[H|Allocated], T}}.
 
203
 
 
204
free(Ch, {Alloc, Free} = Channels) ->
 
205
   case lists:member(Ch, Alloc) of
 
206
      true ->
 
207
         {lists:delete(Ch, Alloc), [Ch|Free]};
 
208
      false ->
 
209
         Channels
 
210
   end.        </code>
 
211
    <p>Code written without making use of behaviours may be more
 
212
      efficient, but the increased efficiency will be at the expense of
 
213
      generality. The ability to manage all applications in the system
 
214
      in a consistent manner is very important.</p>
 
215
    <p>Using behaviours also makes it easier to read and understand
 
216
      code written by other programmers. Ad hoc programming structures,
 
217
      while possibly more efficient, are always more difficult to
 
218
      understand.</p>
 
219
    <p>The module <c>server</c> corresponds, greatly simplified,
 
220
      to the Erlang/OTP behaviour <c>gen_server</c>.</p>
 
221
    <p>The standard Erlang/OTP behaviours are:</p>
 
222
    <taglist>
 
223
      <tag><seealso marker="gen_server_concepts">gen_server</seealso></tag>
 
224
      <item>For implementing the server of a client-server relation.</item>
 
225
      <tag><seealso marker="fsm">gen_fsm</seealso></tag>
 
226
      <item>For implementing finite state machines.</item>
 
227
      <tag><seealso marker="events">gen_event</seealso></tag>
 
228
      <item>For implementing event handling functionality.</item>
 
229
      <tag><seealso marker="sup_princ">supervisor</seealso></tag>
 
230
      <item>For implementing a supervisor in a supervision tree.</item>
 
231
    </taglist>
 
232
    <p>The compiler understands the module attribute
 
233
      <c>-behaviour(Behaviour)</c> and issues warnings about
 
234
      missing callback functions. Example:</p>
 
235
    <code type="none">
 
236
-module(chs3).
 
237
-behaviour(gen_server).
 
238
...
 
239
 
 
240
3> c(chs3).
 
241
./chs3.erl:10: Warning: undefined call-back function handle_call/3
 
242
{ok,chs3}</code>
 
243
  </section>
 
244
 
 
245
  <section>
 
246
    <title>Applications</title>
 
247
    <p>Erlang/OTP comes with a number of components, each implementing
 
248
      some specific functionality. Components are with Erlang/OTP
 
249
      terminology called <em>applications</em>. Examples of Erlang/OTP
 
250
      applications are Mnesia, which has everything needed for
 
251
      programming database services, and Debugger which is used to
 
252
      debug Erlang programs. The minimal system based on Erlang/OTP
 
253
      consists of the applications Kernel and STDLIB.</p>
 
254
    <p>The application concept applies both to program structure
 
255
      (processes) and directory structure (modules).</p>
 
256
    <p>The simplest kind of application does not have any processes,
 
257
      but consists of a collection of functional modules. Such an
 
258
      application is called a <em>library application</em>. An example
 
259
      of a library application is STDLIB.</p>
 
260
    <p>An application with processes is easiest implemented as a
 
261
      supervision tree using the standard behaviours.</p>
 
262
    <p>How to program applications is described in
 
263
      <seealso marker="applications">Applications</seealso>.</p>
 
264
  </section>
 
265
 
 
266
  <section>
 
267
    <title>Releases</title>
 
268
    <p>A <em>release</em> is a complete system made out from a subset of
 
269
      the Erlang/OTP applications and a set of user-specific
 
270
      applications.</p>
 
271
    <p>How to program releases is described in
 
272
      <seealso marker="release_structure">Releases</seealso>.</p>
 
273
    <p>How to install a release in a target environment is described
 
274
      in the chapter about Target Systems in System Principles.</p>
 
275
  </section>
 
276
 
 
277
  <section>
 
278
    <title>Release Handling</title>
 
279
    <p><em>Release handling</em> is upgrading and downgrading between
 
280
      different versions of a release, in a (possibly) running system.
 
281
      How to do this is described in
 
282
      <seealso marker="release_handling">Release Handling</seealso>.</p>
 
283
  </section>
 
284
</chapter>
 
285