~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/shell.xml

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
<?xml version="1.0" encoding="latin1" ?>
 
2
<!DOCTYPE erlref SYSTEM "erlref.dtd">
 
3
 
 
4
<erlref>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>1996</year>
 
8
      <year>2007</year>
 
9
      <holder>Ericsson AB, All Rights Reserved</holder>
 
10
    </copyright>
 
11
    <legalnotice>
 
12
  The contents of this file are subject to the Erlang Public License,
 
13
  Version 1.1, (the "License"); you may not use this file except in
 
14
  compliance with the License. You should have received a copy of the
 
15
  Erlang Public License along with this software. If not, it can be
 
16
  retrieved online at http://www.erlang.org/.
 
17
 
 
18
  Software distributed under the License is distributed on an "AS IS"
 
19
  basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
20
  the License for the specific language governing rights and limitations
 
21
  under the License.
 
22
 
 
23
  The Initial Developer of the Original Code is Ericsson AB.
 
24
    </legalnotice>
 
25
 
 
26
    <title>shell</title>
 
27
    <prepared>Bjorn Gustavsson</prepared>
 
28
    <responsible>Bjarne Dacker</responsible>
 
29
    <docno>1</docno>
 
30
    <approved>Bjarne D&auml;cker</approved>
 
31
    <checked></checked>
 
32
    <date>97-01-24</date>
 
33
    <rev>A</rev>
 
34
    <file>shell.sgml</file>
 
35
  </header>
 
36
  <module>shell</module>
 
37
  <modulesummary>The Erlang Shell</modulesummary>
 
38
  <description>
 
39
    <p>The module <c>shell</c> implements an Erlang shell.
 
40
      </p>
 
41
    <p>The shell is a user interface program 
 
42
      for entering expression sequences. The expressions are
 
43
      evaluated and a value is returned. 
 
44
      A history mechanism saves previous commands and their
 
45
      values, which can then be incorporated in later commands.
 
46
      How many commands and results to save can be determined by the user,
 
47
      either interactively, by calling <c>shell:history/1</c> and
 
48
      <c>shell:results/1</c>, or by setting the application configuration
 
49
      parameters <c>shell_history_length</c> and
 
50
      <c>shell_saved_results</c> for the application STDLIB.
 
51
      </p>
 
52
    <p>The shell uses a helper process for evaluating commands in
 
53
      order to protect the history mechanism from exceptions. By
 
54
      default the evaluator process is killed when an exception
 
55
      occurs, but by calling <c>shell:catch_exception/1</c> or by
 
56
      setting the application configuration parameter
 
57
      <c>shell_catch_exception</c> for the application STDLIB
 
58
      this behavior can be changed. See also the example below.
 
59
      </p>
 
60
    <p>Variable bindings, and local process dictionary changes
 
61
      which are generated in user expressions are preserved, and the variables
 
62
      can be used in later commands to access their values. The
 
63
      bindings can also be forgotten so the variables can be re-used.
 
64
      </p>
 
65
    <p>The special shell commands all have the syntax of (local)
 
66
      function calls. They are evaluated as
 
67
      normal function calls and many commands can be used in one
 
68
      expression sequence.
 
69
      </p>
 
70
    <p>If a command (local function call) is not recognized by the
 
71
      shell, an attempt is first made to find the function in the
 
72
      module <c>user_default</c>, where customized local commands
 
73
      can be placed. If found, then the function is evaluated.
 
74
      Otherwise, an attempt is made to evaluate the function in the
 
75
      module <c>shell_default</c>. The module
 
76
      <c>user_default</c> must be explicitly loaded.
 
77
      </p>
 
78
    <p>The shell also permits the user to start multiple concurrent
 
79
      jobs. A job can be regarded as a set of processes which can
 
80
      communicate with the shell.
 
81
      </p>
 
82
    <p>There is some support for reading and printing records in
 
83
      the shell. During compilation record expressions are translated
 
84
      to tuple expressions. In runtime it is not known whether a tuple
 
85
      actually represents a record. Nor are the record definitions
 
86
      used by compiler available at runtime. So in order to read the
 
87
      record syntax and print tuples as records when possible, record
 
88
      definitions have to be maintained by the shell itself. The shell
 
89
      commands for reading, defining, forgetting, listing, and
 
90
      printing records are described below. Note that each job has its
 
91
      own set of record definitions. To facilitate matters record
 
92
      definitions in the modules <c>shell_default</c> and
 
93
      <c>user_default</c> (if loaded) are read each time a new job is
 
94
      started. For instance, adding the line</p>
 
95
    <code type="none">
 
96
\011  -include_lib("kernel/include/file.hrl").</code>
 
97
    <p>to <c>user_default</c> makes the definition of <c>file_info</c>
 
98
      readily available in the shell.
 
99
      </p>
 
100
    <p>The shell runs in two modes: </p>
 
101
    <list type="bulleted">
 
102
      <item><c>Normal (possibly restricted)</c> mode, in which
 
103
       commands can be edited and expressions evaluated.
 
104
      </item>
 
105
      <item>Job Control Mode <c>JCL</c>, in which jobs can be
 
106
       started, killed, detached and connected.
 
107
      </item>
 
108
    </list>
 
109
    <p>Only the currently connected job can 'talk' to the shell.</p>
 
110
  </description>
 
111
 
 
112
  <section>
 
113
    <title>Shell Commands</title>
 
114
    <taglist>
 
115
      <tag><c>b()</c></tag>
 
116
      <item>
 
117
        <p>Prints the current variable bindings.</p>
 
118
      </item>
 
119
      <tag><c>f()</c></tag>
 
120
      <item>
 
121
        <p>Removes all variable bindings.
 
122
          </p>
 
123
      </item>
 
124
      <tag><c>f(X)</c></tag>
 
125
      <item>
 
126
        <p>Removes the binding of variable <c>X</c>.
 
127
          </p>
 
128
      </item>
 
129
      <tag><c>h()</c></tag>
 
130
      <item>
 
131
        <p>Prints the history list.
 
132
          </p>
 
133
      </item>
 
134
      <tag><c>history(N)</c></tag>
 
135
      <item>
 
136
        <p>Sets the number of previous commands to keep in the
 
137
          history list to <c>N</c>. The previous number is returned.
 
138
          The default number is 20.
 
139
          </p>
 
140
      </item>
 
141
      <tag><c>results(N)</c></tag>
 
142
      <item>
 
143
        <p>Sets the number of results from previous commands to keep in
 
144
          the history list to <c>N</c>. The previous number is returned.
 
145
          The default number is 20.
 
146
          </p>
 
147
      </item>
 
148
      <tag><c>e(N)</c></tag>
 
149
      <item>
 
150
        <p>Repeats the command <c>N</c>, if <c>N</c> is positive. If
 
151
          it is negative, the <c>N</c>th previous command is repeated
 
152
          (i.e., <c>e(-1)</c> repeats the previous command).
 
153
          </p>
 
154
      </item>
 
155
      <tag><c>v(N)</c></tag>
 
156
      <item>
 
157
        <p>Uses the return value of the command <c>N</c> in the
 
158
          current command, if <c>N</c> is positive. If it is negative,
 
159
          the return value of the <c>N</c>th previous command is used
 
160
          (i.e., <c>v(-1)</c> uses the value of the previous command).
 
161
          </p>
 
162
      </item>
 
163
      <tag><c>help()</c></tag>
 
164
      <item>
 
165
        <p>Evaluates <c>shell_default:help()</c>.
 
166
          </p>
 
167
      </item>
 
168
      <tag><c>c(File)</c></tag>
 
169
      <item>
 
170
        <p>Evaluates <c>shell_default:c(File)</c>. This compiles
 
171
          and loads code in <c>File</c> and purges old versions of
 
172
          code, if necessary. Assumes that the file and module names
 
173
          are the same.
 
174
          </p>
 
175
      </item>
 
176
      <tag><c>catch_exception(Bool)</c></tag>
 
177
      <item>
 
178
        <p>Sets the exception handling of the evaluator process. The
 
179
          previous exception handling is returned. The default
 
180
          (<c>false</c>) is to kill the evaluator process when an
 
181
          exception occurs, which causes the shell to create a new
 
182
          evaluator process. When the exception handling is set to
 
183
          <c>true</c> the evaluator process lives on which means that
 
184
          for instance ports and ETS tables as well as processes
 
185
          linked to the evaluator process survive the exception.
 
186
        </p>
 
187
      </item>
 
188
      <tag><c>rd(RecordName, RecordDefinition)</c></tag>
 
189
      <item>
 
190
        <p>Defines a record in the shell. <c>RecordName</c> is
 
191
          an atom and <c>RecordDefinition</c> lists the field names
 
192
          and the default values. Usually record definitions are made
 
193
          known to the shell by use of the <c>rr</c> commands
 
194
          described below, but sometimes it is handy to define records
 
195
          on the fly.
 
196
          </p>
 
197
      </item>
 
198
      <tag><c>rf()</c></tag>
 
199
      <item>
 
200
        <p>Removes all record definitions, then reads record
 
201
          definitions from the modules <c>shell_default</c> and
 
202
          <c>user_default</c> (if loaded). Returns the names of the
 
203
          records defined.
 
204
          </p>
 
205
      </item>
 
206
      <tag><c>rf(RecordNames)</c></tag>
 
207
      <item>
 
208
        <p>Removes selected record definitions.
 
209
          <c>RecordNames</c> is a record name or a list of record names.
 
210
          Use <c>'_'</c> to remove all record definitions.
 
211
          </p>
 
212
      </item>
 
213
      <tag><c>rl()</c></tag>
 
214
      <item>
 
215
        <p>Prints all record definitions.
 
216
          </p>
 
217
      </item>
 
218
      <tag><c>rl(RecordNames)</c></tag>
 
219
      <item>
 
220
        <p>Prints selected record definitions.
 
221
          <c>RecordNames</c> is a record name or a list of record names.
 
222
          </p>
 
223
      </item>
 
224
      <tag><c>rp(Term)</c></tag>
 
225
      <item>
 
226
        <p>Prints a term using the record definitions known to the
 
227
          shell. All of <c>Term</c> is printed; the depth is not
 
228
          limited as is the case when a return value is printed.
 
229
          </p>
 
230
      </item>
 
231
      <tag><c>rr(Module)</c></tag>
 
232
      <item>
 
233
        <p>Reads record definitions from a module's BEAM file. If
 
234
          there are no record definitions in the BEAM file, the
 
235
          source file is located and read instead. Returns the names
 
236
          of the record definitions read. <c>Module</c> is an atom.
 
237
          </p>
 
238
      </item>
 
239
      <tag><c>rr(Wildcard)</c></tag>
 
240
      <item>
 
241
        <p>Reads record definitions from files. Existing
 
242
          definitions of any of the record names read are replaced.
 
243
          <c>Wildcard</c> is a wildcard string as defined in
 
244
          <c>filelib(3)</c> but not an atom.
 
245
          </p>
 
246
      </item>
 
247
      <tag><c>rr(WildcardOrModule, RecordNames)</c></tag>
 
248
      <item>
 
249
        <p>Reads record definitions from files but
 
250
          discards record names not mentioned in <c>RecordNames</c> (a
 
251
          record name or a list of record names).
 
252
          </p>
 
253
      </item>
 
254
      <tag><c>rr(WildcardOrModule, RecordNames, Options)</c></tag>
 
255
      <item>
 
256
        <p>Reads record definitions from files. The compiler
 
257
          options <c>{i,&nbsp;Dir}</c>, <c>{d,&nbsp;Macro}</c>, and
 
258
          <c>{d,&nbsp;Macro,&nbsp;Value}</c> are recognized and used
 
259
          for setting up the include path and macro definitions. Use
 
260
          <c>'_'</c> as value of <c>RecordNames</c> to read all record
 
261
          definitions.
 
262
          </p>
 
263
      </item>
 
264
    </taglist>
 
265
  </section>
 
266
 
 
267
  <section>
 
268
    <title>Example</title>
 
269
    <p>The following example is a long dialogue with the shell. Commands
 
270
      starting with <c>></c> are inputs to the shell. All other lines
 
271
      are output from the shell. All commands in this example are explained at the end of the dialogue.
 
272
      .</p>
 
273
    <pre>
 
274
strider 1> <input>erl</input>
 
275
Erlang (BEAM) emulator version 5.3 [hipe] [threads:0]
 
276
 
 
277
Eshell V5.3  (abort with ^G)
 
278
1><input>Str = "abcd".</input>
 
279
"abcd"
 
280
2> <input>L = length(Str).</input>
 
281
4
 
282
3> <input>Descriptor = {L, list_to_atom(Str)}.</input>
 
283
{4,abcd}
 
284
4> <input>L.</input> 
 
285
4
 
286
5> <input>b().</input>
 
287
Descriptor = {4,abcd}
 
288
L = 4
 
289
Str = "abcd"
 
290
ok
 
291
6> <input>f(L).</input> 
 
292
ok
 
293
7> <input>b().</input>
 
294
Descriptor = {4,abcd}
 
295
Str = "abcd"
 
296
ok
 
297
8> <input>f(L).</input>
 
298
ok
 
299
9> <input>{L, _} = Descriptor.</input>
 
300
{4,abcd}
 
301
10> <input>L.</input>
 
302
4
 
303
11> <input>{P, Q, R} = Descriptor.</input>
 
304
** exception error: no match of right hand side value {4,abcd}
 
305
12> <input>P.</input>
 
306
* 1: variable 'P' is unbound **
 
307
13> <input>Descriptor.</input>
 
308
{4,abcd}
 
309
14><input>{P, Q} = Descriptor.</input>
 
310
{4,abcd}
 
311
15> <input>P.</input>
 
312
4
 
313
16> <input>f().</input>
 
314
ok
 
315
17> <input>put(aa, hello).</input>
 
316
undefined
 
317
18> <input>get(aa).</input>
 
318
hello
 
319
19> <input>Y = test1:demo(1).</input>
 
320
11
 
321
20> <input>get().</input>
 
322
[{aa,worked}]
 
323
21> <input>put(aa, hello).</input>
 
324
worked
 
325
22> <input>Z = test1:demo(2).</input>
 
326
** exception error: no match of right hand side value 1
 
327
     in function  test1:demo/1
 
328
23> <input>Z.</input>
 
329
* 1: variable 'Z' is unbound **
 
330
24> <input>get(aa).</input>
 
331
hello
 
332
25> <input>erase(), put(aa, hello).</input>
 
333
undefined
 
334
26> <input>spawn(test1, demo, [1]).</input>
 
335
&lt;0.57.0>
 
336
27> <input>get(aa).</input>
 
337
hello
 
338
28> <input>io:format("hello hello\ ").</input>
 
339
hello hello ok
 
340
29> <input>e(28).</input>
 
341
hello hello ok
 
342
30> <input>v(28).</input>
 
343
ok
 
344
31> <input>c(ex).</input>
 
345
{ok,ex}
 
346
32> <input>rr(ex).</input>
 
347
[rec]
 
348
33> <input>rl(rec).</input>
 
349
-record(rec,{a,b = val()}).
 
350
ok
 
351
34> <input>#rec{}.</input>
 
352
** exception error: undefined shell command val/0
 
353
35> <input>#rec{b = 3}.</input>
 
354
#rec{a = undefined,b = 3}
 
355
36> <input>rp(v(-1)).</input>
 
356
#rec{a = undefined,b = 3}
 
357
ok
 
358
37> <input>rd(rec, {f = orddict:new()}).</input>
 
359
rec
 
360
38> <input>#rec{}.</input>
 
361
#rec{f = []}
 
362
ok
 
363
39> <input>rd(rec, {c}), A.</input>
 
364
* 1: variable 'A' is unbound **
 
365
40> <input>#rec{}.</input>
 
366
#rec{c = undefined}
 
367
ok
 
368
41> <input>test1:loop(0).</input>
 
369
Hello Number: 0
 
370
Hello Number: 1
 
371
Hello Number: 2
 
372
Hello Number: 3
 
373
 
 
374
User switch command
 
375
 --> i
 
376
 --> c
 
377
.
 
378
.
 
379
.
 
380
Hello Number: 3374
 
381
Hello Number: 3375
 
382
Hello Number: 3376
 
383
Hello Number: 3377
 
384
Hello Number: 3378
 
385
** exception exit: killed
 
386
42> <input>E = ets:new(t, []).</input>
 
387
17
 
388
43> <input>ets:insert({d,1,2}).</input>
 
389
** exception error: undefined function ets:insert/1
 
390
44> <input>ets:insert(E, {d,1,2}).</input>
 
391
** exception error: argument is of wrong type
 
392
     in function  ets:insert/2
 
393
        called as ets:insert(16,{d,1,2})
 
394
45> <input>f(E).</input>
 
395
ok
 
396
46> <input>catch_exception(true).</input>
 
397
false
 
398
47> <input>E = ets:new(t, []).</input>
 
399
18
 
400
48> <input>ets:insert({d,1,2}).</input>
 
401
* exception error: undefined function ets:insert/1
 
402
49> <input>ets:insert(E, {d,1,2}).</input>
 
403
true
 
404
50> <input>halt().</input>
 
405
strider 2></pre>
 
406
  </section>
 
407
 
 
408
  <section>
 
409
    <title>Comments</title>
 
410
    <p>Command 1 sets the variable <c>Str</c> to the string
 
411
      <c>"abcd"</c>.
 
412
      </p>
 
413
    <p>Command 2 sets <c>L</c> to the length of the string evaluating
 
414
      the BIF <c>atom_to_list</c>.
 
415
      </p>
 
416
    <p>Command 3 builds the tuple <c>Descriptor</c>.
 
417
      </p>
 
418
    <p>Command 4 prints the value of the variable <c>L</c>.
 
419
      </p>
 
420
    <p>Command 5 evaluates the internal shell command <c>b()</c>, which
 
421
      is an abbreviation of "bindings". This prints 
 
422
      the current shell variables and their bindings. The <c>ok</c> at
 
423
      the end is the return value of the <c>b()</c> function.
 
424
      </p>
 
425
    <p>Command 6 <c>f(L)</c> evaluates the internal shell command
 
426
      <c>f(L)</c> (abbreviation of "forget"). The value of the variable
 
427
      <c>L</c> is removed.
 
428
      </p>
 
429
    <p>Command 7 prints the new bindings.
 
430
      </p>
 
431
    <p>Command 8 has no effect since <c>L</c> has no value.</p>
 
432
    <p>Command 9 performs a pattern matching operation on
 
433
      <c>Descriptor</c>, binding a new value to <c>L</c>.
 
434
      </p>
 
435
    <p>Command 10 prints the current value of <c>L</c>.
 
436
      </p>
 
437
    <p>Command 11 tries to match <c>{P, Q, R}</c> against
 
438
      <c>Descriptor</c> which is <c>{4, abc}</c>. The match fails and
 
439
      none of the new variables become bound. The printout starting
 
440
      with "<c>** exception error:</c>" is not the value of the
 
441
      expression (the expression had no value because its evaluation
 
442
      failed), but rather a warning printed by the system to inform
 
443
      the user that an error has occurred. The values of the other
 
444
      variables (<c>L</c>, <c>Str</c>, etc.) are unchanged.
 
445
      </p>
 
446
    <p>Commands 12 and 13 show that <c>P</c> is unbound because the
 
447
      previous command failed, and that <c>Descriptor</c> has not
 
448
      changed.
 
449
      </p>
 
450
    <p>Commands 14 and 15 show a correct match where <c>P</c> and
 
451
      <c>Q</c> are bound.
 
452
      </p>
 
453
    <p>Command 16 clears all bindings.
 
454
      </p>
 
455
    <p>The next few commands assume that <c>test1:demo(X)</c> is
 
456
      defined in the following way:</p>
 
457
    <pre>
 
458
demo(X) ->
 
459
    put(aa, worked),
 
460
    X = 1,
 
461
    X + 10.    </pre>
 
462
    <p>Commands 17 and 18 set and inspect the value of the item
 
463
      <c>aa</c> in the process dictionary.
 
464
      </p>
 
465
    <p>Command 19 evaluates <c>test1:demo(1)</c>. The evaluation
 
466
      succeeds and the changes made in the process dictionary become
 
467
      visible to the shell. The new value of the dictionary item
 
468
      <c>aa</c> can be seen in command 20.
 
469
      </p>
 
470
    <p>Commands 21 and 22 change the value of the dictionary item
 
471
      <c>aa</c> to <c>hello</c> and call <c>test1:demo(2)</c>. Evaluation
 
472
      fails and the changes made to the dictionary in
 
473
      <c>test1:demo(2)</c>, before the error occurred, are discarded.
 
474
      </p>
 
475
    <p>Commands 23 and 24 show that <c>Z</c> was not bound and that the
 
476
      dictionary item <c>aa</c> has retained its original value.
 
477
      </p>
 
478
    <p>Commands 25, 26 and 27 show the effect of evaluating
 
479
      <c>test1:demo(1)</c> in the background. In this case, the
 
480
      expression is evaluated in a newly spawned process. Any
 
481
      changes made in the process dictionary are local to the newly
 
482
      spawned process and therefore not visible to the shell.
 
483
      </p>
 
484
    <p>Commands 28, 29 and 30 use the history facilities of the shell.
 
485
      </p>
 
486
    <p>Command 29 is <c>e(28)</c>. This re-evaluates command
 
487
      28. Command 30 is <c>v(28)</c>. This uses the value (result) of
 
488
      command 28. In the cases of a pure function (a function
 
489
      with no side effects), the result is the same. For a function
 
490
      with side effects, the result can be different.
 
491
      </p>
 
492
    <p>The next few commands show some record manipulation. It is 
 
493
      assumed that <c>ex.erl</c> defines a record like this:</p>
 
494
    <pre>
 
495
-record(rec, {a, b = val()}).
 
496
 
 
497
val() ->
 
498
    3.    </pre>
 
499
    <p>Commands 31 and 32 compiles the file <c>ex.erl</c> and reads
 
500
      the record definitions in <c>ex.beam</c>. If the compiler did not
 
501
      output any record definitions on the BEAM file, <c>rr(ex)</c>
 
502
      tries to read record definitions from the source file instead.
 
503
      </p>
 
504
    <p>Command 33 prints the definition of the record named
 
505
      <c>rec</c>. 
 
506
      </p>
 
507
    <p>Command 34 tries to create a <c>rec</c> record, but fails
 
508
      since the function <c>val/0</c> is undefined. Command 35 shows
 
509
      the workaround: explicitly assign values to record fields that
 
510
      cannot otherwise be initialized.
 
511
      </p>
 
512
    <p>Command 36 prints the newly created record using record
 
513
      definitions maintained by the shell.
 
514
      </p>
 
515
    <p>Command 37 defines a record directly in the shell. The 
 
516
      definition replaces the one read from the file <c>ex.beam</c>.
 
517
      </p>
 
518
    <p>Command 38 creates a record using the new definition, and
 
519
      prints the result.
 
520
      </p>
 
521
    <p>Command 39 and 40 show that record definitions are updated
 
522
      as side effects. The evaluation of the command fails but
 
523
      the definition of <c>rec</c> has been carried out.
 
524
      </p>
 
525
    <p>For the next command, it is assumed that <c>test1:loop(N)</c> is
 
526
      defined in the following way:</p>
 
527
    <pre>
 
528
loop(N) ->
 
529
    io:format("Hello Number: ~w~n", [N]), 
 
530
    loop(N+1).</pre>
 
531
    <p>Command 41 evaluates <c>test1:loop(0)</c>, which puts the
 
532
      system into an infinite loop. At this point the user types
 
533
      <c>Control G</c>, which suspends output from the current process,
 
534
      which is stuck in a loop, and activates <c>JCL</c> mode. In <c>JCL</c>
 
535
      mode the user can start and stop jobs.
 
536
      </p>
 
537
    <p>In this particular case, the <c>i</c> command ("interrupt") is
 
538
      used to terminate the looping program, and the <c>c</c> command
 
539
      is used to connect to the shell again. Since the process was
 
540
      running in the background before we killed it, there will be
 
541
      more printouts before the "<c>** exception exit: killed</c>"
 
542
      message is shown.
 
543
      </p>
 
544
    <p>Command 42 creates an ETS table.</p>
 
545
    <p>Command 43 tries to insert a tuple into the ETS table but the
 
546
      first argument (the table) is missing. The exception kills the
 
547
      evaluator process.</p>
 
548
    <p>Command 44 corrects the mistake, but the ETS table has been
 
549
      destroyed since it was owned by the killed evaluator process.</p>
 
550
    <p>Command 46 sets the exception handling of the evaluator process
 
551
      to <c>true</c>. The exception handling can also be set when
 
552
      starting Erlang, like this: <c>erl -stdlib shell_catch_exception
 
553
      true</c>.</p>
 
554
    <p>Command 48 makes the same mistake as in command 43, but this time
 
555
      the evaluator process lives on. The single star at the beginning
 
556
      of the printout signals that the exception has been caught.</p>
 
557
    <p>Command 49 successfully inserts the tuple into the ETS table.</p>
 
558
    <p>The <c>halt()</c> command exits the Erlang runtime system.
 
559
      </p>
 
560
  </section>
 
561
 
 
562
  <section>
 
563
    <title>JCL Mode</title>
 
564
    <p>When the shell starts, it starts a single evaluator
 
565
      process. This process, together with any local processes which
 
566
      it spawns, is referred to as a <c>job</c>. Only the current job,
 
567
      which is said to be <c>connected</c>, can perform operations
 
568
      with standard IO. All other jobs, which are said to be <c>detached</c>, are
 
569
      <c>blocked</c> if they attempt to use standard IO.
 
570
      </p>
 
571
    <p>All jobs which do not use standard IO run in the normal way.
 
572
      </p>
 
573
    <p>The shell escape key <em><c>^G</c></em> (Control G) detaches the current job 
 
574
      and activates <c>JCL</c> mode. The <c>JCL</c> mode prompt is <c>"-->"</c>. If <c>"?"</c> is entered at the prompt, the following help message is
 
575
      displayed:</p>
 
576
    <pre>
 
577
          --> ?
 
578
          c [nn]            - connect to job
 
579
          i [nn]            - interrupt job
 
580
          k [nn]            - kill job
 
581
          j                 - list all jobs
 
582
          s [shell]         - start local shell
 
583
          r [node [shell]]  - start remote shell
 
584
          q        - quit erlang
 
585
          ? | h             - this message    </pre>
 
586
    <p>The <c>JCL</c> commands have the following meaning:</p>
 
587
    <taglist>
 
588
      <tag><c>c [nn]</c></tag>
 
589
      <item>
 
590
        <p>Connects to job number <c><![CDATA[<nn>]]></c> or the current
 
591
          job. The standard shell is resumed. Operations which use
 
592
          standard IO by the current job will be interleaved with
 
593
          user inputs to the shell.
 
594
          </p>
 
595
      </item>
 
596
      <tag><c>i [nn]</c></tag>
 
597
      <item>
 
598
        <p>Stops the current evaluator process for job number
 
599
          <c>nn</c> or the current job, but does not kill the shell
 
600
          process. Accordingly, any variable bindings and the process dictionary
 
601
          will be preserved and the job can be connected again.
 
602
          This command can be used to interrupt an endless loop.
 
603
          </p>
 
604
      </item>
 
605
      <tag><c>k [nn]</c></tag>
 
606
      <item>
 
607
        <p>Kills job number <c>nn</c> or the current
 
608
          job. All spawned processes in the job are
 
609
          killed, provided they have not evaluated the
 
610
          <c>group_leader/1</c> BIF and are located on
 
611
          the local machine. Processes spawned on remote nodes will
 
612
          not be killed.
 
613
          </p>
 
614
      </item>
 
615
      <tag><c>j</c></tag>
 
616
      <item>
 
617
        <p>Lists all jobs. A list of all known jobs is
 
618
          printed. The current job name is prefixed with '*'.
 
619
          </p>
 
620
      </item>
 
621
      <tag><c>s</c></tag>
 
622
      <item>
 
623
        <p>Starts a new job. This will be assigned the new index
 
624
          <c>[nn]</c> which can be used in references.
 
625
          </p>
 
626
      </item>
 
627
      <tag><c>s [shell]</c></tag>
 
628
      <item>
 
629
        <p>Starts a new job. This will be assigned the new index
 
630
          <c>[nn]</c> which can be used in references.
 
631
          If the optional argument <c>shell</c> is given, it is assumed
 
632
          to be a module that implements an alternative shell.
 
633
          </p>
 
634
      </item>
 
635
      <tag><c>r [node]</c></tag>
 
636
      <item>
 
637
        <p>Starts a remote job on <c>node</c>. This is used in
 
638
          distributed Erlang to allow a shell running on one node to
 
639
          control a number of applications running on a network of
 
640
          nodes.
 
641
          If the optional argument <c>shell</c> is given, it is assumed
 
642
          to be a module that implements an alternative shell.
 
643
          </p>
 
644
      </item>
 
645
      <tag><c>q</c></tag>
 
646
      <item>
 
647
        <p>Quits Erlang. Note that this option is disabled if
 
648
          Erlang is started with the ignore break, <c>+Bi</c>, 
 
649
          system flag (which may be useful e.g. when running
 
650
          a restricted shell, see below).
 
651
          </p>
 
652
      </item>
 
653
      <tag><c>?</c></tag>
 
654
      <item>
 
655
        <p>Displays this message.</p>
 
656
      </item>
 
657
    </taglist>
 
658
    <p>It is possible to alter the behavior of shell escape by means 
 
659
      of the STDLIB application variable <c>shell_esc</c>. The value of
 
660
      the variable can be either <c>jcl</c> (<c>erl -stdlib shell_esc jcl</c>) 
 
661
      or <c>abort</c> (<c>erl -stdlib shell_esc abort</c>). The 
 
662
      first option sets ^G to activate <c>JCL</c> mode (which is also 
 
663
      default behavior). The latter sets ^G to terminate the current 
 
664
      shell and start a new one. <c>JCL</c> mode cannot be invoked when 
 
665
      <c>shell_esc</c> is set to <c>abort</c>. </p>
 
666
    <p>If you want an Erlang node to have a remote job active from the start 
 
667
      (rather than the default local job), you start Erlang with the 
 
668
      <c>-remsh</c> flag. Example: <c>erl -sname this_node -remsh other_node@other_host</c></p>
 
669
  </section>
 
670
 
 
671
  <section>
 
672
    <title>Restricted Shell</title>
 
673
    <p>The shell may be started in a
 
674
      restricted mode. In this mode, the shell evaluates a function call
 
675
      only if allowed. This feature makes it possible to, for example,
 
676
      prevent a user from accidentally calling a function from the
 
677
      prompt that could harm a running system (useful in combination
 
678
      with the the system flag <em><c>+Bi</c></em>).</p>
 
679
    <p>When the restricted shell evaluates an expression and
 
680
      encounters a function call or an operator application, 
 
681
      it calls a callback function (with
 
682
      information about the function call in question). This callback
 
683
      function returns <c>true</c> to let the shell go ahead with the
 
684
      evaluation, or <c>false</c> to abort it. There are two possible
 
685
      callback functions for the user to implement:</p>
 
686
    <p><em><c>local_allowed(Func, ArgList, State) -> {true,NewState} | {false,NewState}</c></em></p>
 
687
    <p>to determine if the call to the local function <c>Func</c>
 
688
      with arguments <c>ArgList</c> should be allowed.</p>
 
689
    <p><em><c>non_local_allowed(FuncSpec, ArgList, State) -> {true,NewState} | {false,NewState} |  {{redirect,NewFuncSpec,NewArgList},NewState}</c></em></p>
 
690
    <p>to determine if the call to non-local function
 
691
      <c>FuncSpec</c> (<c>{Module,Func}</c> or a fun) with arguments
 
692
      <c>ArgList</c> should be allowed. The return value 
 
693
      <c>{redirect,NewFuncSpec,NewArgList}</c> can be used to let 
 
694
      the shell evaluate some other function than the one specified by 
 
695
      <c>FuncSpec</c> and <c>ArgList</c>.</p>
 
696
    <p>These callback functions are in fact called from local and
 
697
      non-local evaluation function handlers, described in the
 
698
      <seealso marker="erl_eval">erl_eval</seealso> 
 
699
      manual page. (Arguments in <c>ArgList</c> are evaluated before the
 
700
      callback functions are called.)</p>
 
701
    <p>The <c>State</c> argument is a tuple
 
702
      <c>{ShellState,ExprState}</c>. The return value <c>NewState</c>
 
703
      has the same form. This may be used to carry a state between calls
 
704
      to the callback functions. Data saved in <c>ShellState</c> lives
 
705
      through an entire shell session. Data saved in <c>ExprState</c>
 
706
      lives only through the evaluation of the current expression.</p>
 
707
    <p>There are two ways to start a restricted shell session:</p>
 
708
    <list type="bulleted">
 
709
      <item>Use the STDLIB application variable <c>restricted_shell</c>
 
710
       and specify, as its value, the name of the callback
 
711
       module. Example (with callback functions implemented in
 
712
       callback_mod.erl): <c>$ erl -stdlib restricted_shell callback_mod</c></item>
 
713
      <item>From a normal shell session, call function
 
714
      <c>shell:start_restricted/1</c>. This exits the current evaluator
 
715
       and starts a new one in restricted mode.</item>
 
716
    </list>
 
717
    <p><em>Notes:</em></p>
 
718
    <list type="bulleted">
 
719
      <item>When restricted shell mode is activated or
 
720
       deactivated, new jobs started on the node will run in restricted
 
721
       or normal mode respectively.</item>
 
722
      <item>If restricted mode has been enabled on a
 
723
       particular node, remote shells connecting to this node will also
 
724
       run in restricted mode.</item>
 
725
      <item>The callback functions cannot be used to allow or disallow
 
726
       execution of functions called from compiled code (only functions
 
727
       called from expressions entered at the shell prompt).</item>
 
728
    </list>
 
729
    <p>Errors when loading the callback module is handled in different
 
730
      ways depending on how the restricted shell is activated:</p>
 
731
    <list type="bulleted">
 
732
      <item>If the restricted shell is activated by setting the kernel
 
733
       variable during emulator startup and the callback module cannot be
 
734
       loaded, a default restricted shell allowing only the commands
 
735
      <c>q()</c> and <c>init:stop()</c> is used as fallback.</item>
 
736
      <item>If the restricted shell is activated using
 
737
      <c>shell:start_restricted/1</c> and the callback module cannot be
 
738
       loaded, an error report is sent to the error logger and the call
 
739
       returns <c>{error,Reason}</c>.</item>
 
740
    </list>
 
741
  </section>
 
742
  <funcs>
 
743
    <func>
 
744
      <name>history(N) -> integer()</name>
 
745
      <fsummary>Sets the number of previous commands to keep</fsummary>
 
746
      <type>
 
747
        <v>N = integer()</v>
 
748
      </type>
 
749
      <desc>
 
750
        <p>Sets the number of previous commands to keep in the
 
751
          history list to <c>N</c>. The previous number is returned.
 
752
          The default number is 20.</p>
 
753
      </desc>
 
754
    </func>
 
755
    <func>
 
756
      <name>results(N) -> integer()</name>
 
757
      <fsummary>Sets the number of previous results to keep</fsummary>
 
758
      <type>
 
759
        <v>N = integer()</v>
 
760
      </type>
 
761
      <desc>
 
762
        <p>Sets the number of results from previous commands to keep in
 
763
          the history list to <c>N</c>. The previous number is returned.
 
764
          The default number is 20.</p>
 
765
      </desc>
 
766
    </func>
 
767
    <func>
 
768
      <name>catch_exception(Bool) -> Bool</name>
 
769
      <fsummary>Sets the exception handling of the shell</fsummary>
 
770
      <type>
 
771
        <v>Bool = bool()</v>
 
772
      </type>
 
773
      <desc>
 
774
        <p>Sets the exception handling of the evaluator process. The
 
775
          previous exception handling is returned. The default
 
776
          (<c>false</c>) is to kill the evaluator process when an
 
777
          exception occurs, which causes the shell to create a new
 
778
          evaluator process. When the exception handling is set to
 
779
          <c>true</c> the evaluator process lives on which means that
 
780
          for instance ports and ETS tables as well as processes
 
781
          linked to the evaluator process survive the exception.</p>
 
782
      </desc>
 
783
    </func>
 
784
    <func>
 
785
      <name>start_restricted(Module) -> ok | {error, Reason}</name>
 
786
      <fsummary>Exits a normal shell and starts a restricted shell.</fsummary>
 
787
      <type>
 
788
        <v>Module = atom()</v>
 
789
        <v>Reason = atom()</v>
 
790
      </type>
 
791
      <desc>
 
792
        <p>Exits a normal shell and starts a restricted
 
793
          shell. <c>Module</c> specifies the callback module for the
 
794
          functions <c>local_allowed/3</c> and <c>non_local_allowed/3</c>.
 
795
          The function is meant to be called from the shell.</p>
 
796
        <p>If the callback module cannot be loaded, an error tuple is
 
797
          returned. The <c>Reason</c> in the error tuple is the one
 
798
          returned by the code loader when trying to load the code of the callback
 
799
          module.</p>
 
800
      </desc>
 
801
    </func>
 
802
    <func>
 
803
      <name>stop_restricted() -> ok</name>
 
804
      <fsummary>Exits a restricted shell and starts a normal shell.</fsummary>
 
805
      <desc>
 
806
        <p>Exits a restricted shell and starts a normal shell. The function
 
807
          is meant to be called from the shell.</p>
 
808
      </desc>
 
809
    </func>
 
810
  </funcs>
 
811
</erlref>
 
812