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

« back to all changes in this revision

Viewing changes to system/doc/getting_started/records_macros.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>2003</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>Records and Macros</title>
 
25
    <prepared></prepared>
 
26
    <docno></docno>
 
27
    <date></date>
 
28
    <rev></rev>
 
29
    <file>record_macros.xml</file>
 
30
  </header>
 
31
  <p>Larger programs are usually written as a collection of files with
 
32
    a well defined interface between the various parts.</p>
 
33
 
 
34
  <section>
 
35
    <title>The Larger Example Divided into Several Files</title>
 
36
    <p>To illustrate this, we will divide the messenger example from
 
37
      the previous chapter into five files.</p>
 
38
    <taglist>
 
39
      <tag><c>mess_config.hrl</c></tag>
 
40
      <item>header file for configuration data</item>
 
41
      <tag><c>mess_interface.hrl</c></tag>
 
42
      <item>interface definitions between the client and the messenger</item>
 
43
      <tag><c>user_interface.erl</c></tag>
 
44
      <item>functions for the user interface</item>
 
45
      <tag><c>mess_client.erl</c></tag>
 
46
      <item>functions for the client side of the messenger</item>
 
47
      <tag><c>mess_server.erl</c></tag>
 
48
      <item>functions for the server side of the messenger</item>
 
49
    </taglist>
 
50
    <p>While doing this we will also clean up the message passing
 
51
      interface between the shell, the client and the server and define
 
52
      it using <em>records</em>, we will also introduce <em>macros</em>.</p>
 
53
    <code type="none">
 
54
%%%----FILE mess_config.hrl----
 
55
 
 
56
%%% Configure the location of the server node,
 
57
-define(server_node, messenger@super).
 
58
 
 
59
%%%----END FILE----</code>
 
60
    <code type="none">
 
61
%%%----FILE mess_interface.hrl----
 
62
 
 
63
%%% Message interface between client and server and client shell for
 
64
%%% messenger program 
 
65
 
 
66
%%%Messages from Client to server received in server/1 function.
 
67
-record(logon,{client_pid, username}).
 
68
-record(message,{client_pid, to_name, message}).
 
69
%%% {'EXIT', ClientPid, Reason}  (client terminated or unreachable.
 
70
 
 
71
%%% Messages from Server to Client, received in await_result/0 function 
 
72
-record(abort_client,{message}).
 
73
%%% Messages are: user_exists_at_other_node, 
 
74
%%%               you_are_not_logged_on
 
75
-record(server_reply,{message}).
 
76
%%% Messages are: logged_on
 
77
%%%               receiver_not_found
 
78
%%%               sent  (Message has been sent (no guarantee)
 
79
%%% Messages from Server to Client received in client/1 function
 
80
-record(message_from,{from_name, message}).
 
81
 
 
82
%%% Messages from shell to Client received in client/1 function
 
83
%%% spawn(mess_client, client, [server_node(), Name])
 
84
-record(message_to,{to_name, message}).
 
85
%%% logoff
 
86
 
 
87
%%%----END FILE----</code>
 
88
    <code type="none">
 
89
%%%----FILE user_interface.erl----
 
90
 
 
91
%%% User interface to the messenger program
 
92
%%% login(Name)
 
93
%%%     One user at a time can log in from each Erlang node in the
 
94
%%%     system messenger: and choose a suitable Name. If the Name
 
95
%%%     is already logged in at another node or if someone else is
 
96
%%%     already logged in at the same node, login will be rejected
 
97
%%%     with a suitable error message.
 
98
 
 
99
%%% logoff()
 
100
%%%     Logs off anybody at at node
 
101
 
 
102
%%% message(ToName, Message)
 
103
%%%     sends Message to ToName. Error messages if the user of this 
 
104
%%%     function is not logged on or if ToName is not logged on at
 
105
%%%     any node.
 
106
 
 
107
-module(user_interface).
 
108
-export([logon/1, logoff/0, message/2]).
 
109
-include("mess_interface.hrl").
 
110
-include("mess_config.hrl").
 
111
 
 
112
logon(Name) ->
 
113
    case whereis(mess_client) of 
 
114
        undefined ->
 
115
            register(mess_client, 
 
116
                     spawn(mess_client, client, [?server_node, Name]));
 
117
        _ -> already_logged_on
 
118
    end.
 
119
 
 
120
logoff() ->
 
121
    mess_client ! logoff.
 
122
 
 
123
message(ToName, Message) ->
 
124
    case whereis(mess_client) of % Test if the client is running
 
125
        undefined ->
 
126
            not_logged_on;
 
127
        _ -> mess_client ! #message_to{to_name=ToName, message=Message},
 
128
             ok
 
129
end.
 
130
 
 
131
%%%----END FILE----</code>
 
132
    <code type="none">
 
133
%%%----FILE mess_client.erl----
 
134
 
 
135
%%% The client process which runs on each user node
 
136
 
 
137
-module(mess_client).
 
138
-export([client/2]).
 
139
-include("mess_interface.hrl").
 
140
 
 
141
client(Server_Node, Name) ->
 
142
    {messenger, Server_Node} ! #logon{client_pid=self(), username=Name},
 
143
    await_result(),
 
144
    client(Server_Node).
 
145
 
 
146
client(Server_Node) ->
 
147
    receive
 
148
        logoff ->
 
149
            exit(normal);
 
150
        #message_to{to_name=ToName, message=Message} ->
 
151
            {messenger, Server_Node} ! 
 
152
                #message{client_pid=self(), to_name=ToName, message=Message},
 
153
            await_result();
 
154
        {message_from, FromName, Message} ->
 
155
            io:format("Message from ~p: ~p~n", [FromName, Message])
 
156
    end,
 
157
    client(Server_Node).
 
158
 
 
159
%%% wait for a response from the server
 
160
await_result() ->
 
161
    receive
 
162
        #abort_client{message=Why} ->
 
163
            io:format("~p~n", [Why]),
 
164
            exit(normal);
 
165
        #server_reply{message=What} ->
 
166
            io:format("~p~n", [What])
 
167
    after 5000 ->
 
168
            io:format("No response from server~n", []),
 
169
            exit(timeout)
 
170
    end.
 
171
 
 
172
%%%----END FILE---</code>
 
173
    <code type="none">
 
174
%%%----FILE mess_server.erl----
 
175
 
 
176
%%% This is the server process of the messenger service
 
177
 
 
178
-module(mess_server).
 
179
-export([start_server/0, server/0]).
 
180
-include("mess_interface.hrl").
 
181
 
 
182
server() ->
 
183
    process_flag(trap_exit, true),
 
184
    server([]).
 
185
 
 
186
%%% the user list has the format [{ClientPid1, Name1},{ClientPid22, Name2},...]
 
187
server(User_List) ->
 
188
    io:format("User list = ~p~n", [User_List]),
 
189
    receive
 
190
        #logon{client_pid=From, username=Name} ->
 
191
            New_User_List = server_logon(From, Name, User_List),
 
192
            server(New_User_List);
 
193
        {'EXIT', From, _} ->
 
194
            New_User_List = server_logoff(From, User_List),
 
195
            server(New_User_List);
 
196
        #message{client_pid=From, to_name=To, message=Message} ->
 
197
            server_transfer(From, To, Message, User_List),
 
198
            server(User_List)
 
199
    end.
 
200
 
 
201
%%% Start the server
 
202
start_server() ->
 
203
    register(messenger, spawn(?MODULE, server, [])).
 
204
 
 
205
%%% Server adds a new user to the user list
 
206
server_logon(From, Name, User_List) ->
 
207
    %% check if logged on anywhere else
 
208
    case lists:keymember(Name, 2, User_List) of
 
209
        true ->
 
210
            From ! #abort_client{message=user_exists_at_other_node},
 
211
            User_List;
 
212
        false ->
 
213
            From ! #server_reply{message=logged_on},
 
214
            link(From),
 
215
            [{From, Name} | User_List]        %add user to the list
 
216
    end.
 
217
 
 
218
%%% Server deletes a user from the user list
 
219
server_logoff(From, User_List) ->
 
220
    lists:keydelete(From, 1, User_List).
 
221
 
 
222
%%% Server transfers a message between user
 
223
server_transfer(From, To, Message, User_List) ->
 
224
    %% check that the user is logged on and who he is
 
225
    case lists:keysearch(From, 1, User_List) of
 
226
        false ->
 
227
            From ! #abort_client{message=you_are_not_logged_on};
 
228
        {value, {_, Name}} ->
 
229
            server_transfer(From, Name, To, Message, User_List)
 
230
    end.
 
231
%%% If the user exists, send the message
 
232
server_transfer(From, Name, To, Message, User_List) ->
 
233
    %% Find the receiver and send the message
 
234
    case lists:keysearch(To, 2, User_List) of
 
235
        false ->
 
236
            From ! #server_reply{message=receiver_not_found};
 
237
        {value, {ToPid, To}} ->
 
238
            ToPid ! #message_from{from_name=Name, message=Message}, 
 
239
            From !  #server_reply{message=sent} 
 
240
    end.
 
241
 
 
242
%%%----END FILE---</code>
 
243
  </section>
 
244
 
 
245
  <section>
 
246
    <title>Header Files</title>
 
247
    <p>You will see some files above with extension <c>.hrl</c>. These
 
248
      are header files which are included in the <c>.erl</c> files by:</p>
 
249
    <code type="none">
 
250
-include("File_Name").</code>
 
251
    <p>for example:</p>
 
252
    <code type="none">
 
253
-include("mess_interface.hrl").</code>
 
254
    <p>In our case above the file is fetched from the same directory as
 
255
      all the other files in the messenger example. (*manual*).</p>
 
256
    <p>.hrl files can contain any valid Erlang code but are most often
 
257
      used for record and macro definitions.</p>
 
258
  </section>
 
259
 
 
260
  <section>
 
261
    <title>Records</title>
 
262
    <p>A record is defined as:</p>
 
263
    <code type="none">
 
264
-record(name_of_record,{field_name1, field_name2, field_name3, ......}).</code>
 
265
    <p>For example:</p>
 
266
    <code type="none">
 
267
-record(message_to,{to_name, message}).</code>
 
268
    <p>This is exactly equivalent to:</p>
 
269
    <code type="none">
 
270
{message_to, To_Name, Message}</code>
 
271
    <p>Creating record, is best illustrated by an example:</p>
 
272
    <code type="none">
 
273
#message_to{message="hello", to_name=fred)</code>
 
274
    <p>This will create:</p>
 
275
    <code type="none">
 
276
{message_to, fred, "hello"}</code>
 
277
    <p>Note that you don't have to worry about the order you assign
 
278
      values to the various parts of the records when you create it.
 
279
      The advantage of using records is that by placing their
 
280
      definitions in header files you can conveniently define
 
281
      interfaces which are easy to change. For example, if you want to
 
282
      add a new field to the record, you will only have to change
 
283
      the code where the new field is used and not at every place
 
284
      the record is referred to. If you leave out a field when creating
 
285
      a record, it will get the value of the atom undefined. (*manual*)</p>
 
286
    <p>Pattern matching with records is very similar to creating
 
287
      records. For example inside a <c>case</c> or <c>receive</c>:</p>
 
288
    <code type="none">
 
289
#message_to{to_name=ToName, message=Message} -></code>
 
290
    <p>is the same as:</p>
 
291
    <code type="none">
 
292
{message_to, ToName, Message}</code>
 
293
  </section>
 
294
 
 
295
  <section>
 
296
    <title>Macros</title>
 
297
    <p>The other thing we have added to the messenger is a macro.
 
298
      The file <c>mess_config.hrl</c> contains the definition:</p>
 
299
    <code type="none">
 
300
%%% Configure the location of the server node,
 
301
-define(server_node, messenger@super).</code>
 
302
    <p>We include this file in mess_server.erl:</p>
 
303
    <code type="none">
 
304
-include("mess_config.hrl").</code>
 
305
    <p>Every occurrence of <c>?server_node</c> in <c>mess_server.erl</c>
 
306
      will now be replaced by <c>messenger@super</c>.</p>
 
307
    <p>The other place a macro is used is when we spawn the server
 
308
      process:</p>
 
309
    <code type="none">
 
310
spawn(?MODULE, server, [])</code>
 
311
    <p>This is a standard macro (i.e. defined by the system, not
 
312
      the user). <c>?MODULE</c> is always replaced by the name of
 
313
      current module (i.e. the <c>-module</c> definition near the start
 
314
      of the file). There are more advanced ways of using macros with,
 
315
      for example parameters (*manual*).</p>
 
316
    <p>The three Erlang (<c>.erl</c>) files in the messenger example are
 
317
      individually compiled into object code file (<c>.beam</c>).
 
318
      The Erlang system loads and links these files into the system
 
319
      when they are referred to during execution of the code. In our
 
320
      case we simply have put them in the same directory which is our
 
321
      current working directory (i.e. the place we have done "cd" to).
 
322
      There are ways of putting the <c>.beam</c> files in other
 
323
      directories.</p>
 
324
    <p>In the messenger example, no assumptions have been made about
 
325
      what the message being sent is. It could be any valid Erlang term.</p>
 
326
  </section>
 
327
</chapter>
 
328