~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/reltool/test/reltool_server_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
 
 
19
-module(reltool_server_SUITE).
 
20
 
 
21
-export([all/0, init_per_suite/1, end_per_suite/1, 
 
22
         init_per_testcase/2, fin_per_testcase/2, end_per_testcase/2]).
 
23
 
 
24
-compile(export_all).
 
25
 
 
26
-include("reltool_test_lib.hrl").
 
27
 
 
28
-define(NODE_NAME, '__RELTOOL__TEMPORARY_TEST__NODE__').
 
29
 
 
30
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
31
%% Initialization functions.
 
32
 
 
33
init_per_suite(Config) ->
 
34
    reltool_test_lib:init_per_suite(Config).
 
35
 
 
36
end_per_suite(Config) ->
 
37
    reltool_test_lib:end_per_suite(Config).
 
38
 
 
39
init_per_testcase(Func,Config) ->
 
40
    reltool_test_lib:init_per_testcase(Func,Config).
 
41
end_per_testcase(Func,Config) -> 
 
42
    reltool_test_lib:end_per_testcase(Func,Config).
 
43
fin_per_testcase(Func,Config) -> %% For test_server
 
44
    reltool_test_lib:end_per_testcase(Func,Config).
 
45
 
 
46
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
47
%% SUITE specification
 
48
 
 
49
all() ->
 
50
    all(suite).
 
51
all(suite) ->
 
52
    [
 
53
     start_server,
 
54
     set_config,
 
55
     create_release,
 
56
     create_script,
 
57
     create_target,
 
58
     create_embedded,
 
59
     create_standalone,
 
60
     create_old_target
 
61
    ].
 
62
 
 
63
%% The test cases
 
64
 
 
65
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
66
%% Start a server process and check that it does not crash
 
67
 
 
68
start_server(TestInfo) when is_atom(TestInfo) -> 
 
69
    reltool_test_lib:tc_info(TestInfo);
 
70
start_server(_Config) ->
 
71
    {ok, Pid} = ?msym({ok, _}, reltool:start_server([])),
 
72
    Libs = lists:sort(erl_libs()),
 
73
    StrippedDefault =
 
74
        case Libs of
 
75
            [] -> {sys, []};
 
76
            _  -> {sys, [{lib_dirs, Libs}]}
 
77
        end,
 
78
    ?m({ok, StrippedDefault}, reltool:get_config(Pid)),
 
79
    ?m(ok, reltool:stop(Pid)),
 
80
    ok.
 
81
 
 
82
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
83
%% Start a server process and check that it does not crash
 
84
 
 
85
set_config(TestInfo) when is_atom(TestInfo) -> 
 
86
    reltool_test_lib:tc_info(TestInfo);
 
87
set_config(_Config) ->
 
88
    Libs = lists:sort(erl_libs()),
 
89
    Default =
 
90
        {sys,
 
91
         [
 
92
          {mod_cond, all},
 
93
          {incl_cond, derived},
 
94
          {root_dir, code:root_dir()},
 
95
          {lib_dirs, Libs}
 
96
         ]},
 
97
    {ok, Pid} = ?msym({ok, _}, reltool:start_server([{config, Default}])),
 
98
    StrippedDefault =
 
99
        case Libs of
 
100
            [] -> {sys, []};
 
101
            _  -> {sys, [{lib_dirs, Libs}]}
 
102
        end,
 
103
    ?m({ok, StrippedDefault}, reltool:get_config(Pid)),
 
104
 
 
105
    ?m(ok, reltool:stop(Pid)),
 
106
    ok.
 
107
 
 
108
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
109
%% Generate releases
 
110
 
 
111
create_release(TestInfo) when is_atom(TestInfo) -> 
 
112
    reltool_test_lib:tc_info(TestInfo);
 
113
create_release(_Config) ->
 
114
    %% Configure the server
 
115
    RelName = "Just testing...",
 
116
    RelVsn = "1.0",
 
117
    Config =
 
118
        {sys,
 
119
         [
 
120
          {lib_dirs, []},
 
121
          {boot_rel, RelName},
 
122
          {rel, RelName, RelVsn, [kernel, stdlib]}
 
123
         ]},
 
124
    %% Generate release 
 
125
    ErtsVsn = erlang:system_info(version),
 
126
    Apps = application:loaded_applications(),
 
127
    {value, {_, _, KernelVsn}} = lists:keysearch(kernel, 1, Apps),
 
128
    {value, {_, _, StdlibVsn}} = lists:keysearch(stdlib, 1, Apps),
 
129
    Rel = {release, {RelName, RelVsn}, 
 
130
           {erts, ErtsVsn}, 
 
131
           [{kernel, KernelVsn}, 
 
132
            {stdlib, StdlibVsn}]},
 
133
    ?m({ok, Rel}, reltool:get_rel([{config, Config}], RelName)),
 
134
    ok.
 
135
 
 
136
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
137
%% Generate boot scripts
 
138
 
 
139
create_script(TestInfo) when is_atom(TestInfo) -> 
 
140
    reltool_test_lib:tc_info(TestInfo);
 
141
create_script(_Config) ->
 
142
    %% Configure the server
 
143
    RelName = "Just testing",
 
144
    RelVsn = "1.0",
 
145
    Config =
 
146
        {sys,
 
147
         [
 
148
          {lib_dirs, []},
 
149
          {boot_rel, RelName},
 
150
          {rel, RelName, RelVsn, [stdlib, kernel]}
 
151
         ]},
 
152
    {ok, Pid} = ?msym({ok, _}, reltool:start_server([{config, Config}])),
 
153
 
 
154
    %% Generate release file
 
155
    ErtsVsn = erlang:system_info(version),
 
156
    Apps = application:loaded_applications(),
 
157
    {value, {_, _, KernelVsn}} = lists:keysearch(kernel, 1, Apps),
 
158
    {value, {_, _, StdlibVsn}} = lists:keysearch(stdlib, 1, Apps),
 
159
    Rel = {release, 
 
160
           {RelName, RelVsn}, 
 
161
           {erts, ErtsVsn},
 
162
           [{stdlib, StdlibVsn}, {kernel, KernelVsn}]},
 
163
    ?m({ok, Rel}, reltool:get_rel(Pid, RelName)),
 
164
    RelFile = RelName ++ ".rel",
 
165
    ?m(ok, file:write_file(RelFile, io_lib:format("~p.\n", [Rel]))),
 
166
 
 
167
    %% Generate script file
 
168
    ?m(ok, systools:make_script(RelName, [])),
 
169
    ScriptFile = RelName ++ ".script",
 
170
    {ok, [OrigScript]} = ?msym({ok, [_]}, file:consult(ScriptFile)),
 
171
    {ok, Script} = ?msym({ok, _}, reltool:get_script(Pid, RelName)),
 
172
    %% OrigScript2 = sort_script(OrigScript),
 
173
    %% Script2 = sort_script(Script),
 
174
    %% ?m(OrigScript2, Script2),
 
175
    
 
176
    ?m(equal, diff_script(OrigScript, Script)),
 
177
    
 
178
    %% Stop server
 
179
    ?m(ok, reltool:stop(Pid)),
 
180
    ok.
 
181
 
 
182
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
183
%% Generate target system
 
184
 
 
185
create_target(TestInfo) when is_atom(TestInfo) -> 
 
186
    reltool_test_lib:tc_info(TestInfo);
 
187
create_target(_Config) ->
 
188
    %% Configure the server
 
189
    RelName1 = "Just testing",
 
190
    RelName2 = "Just testing with SASL",
 
191
    RelVsn = "1.0",
 
192
    Config =
 
193
        {sys,
 
194
         [
 
195
          {root_dir, code:root_dir()},
 
196
          {lib_dirs, []},
 
197
          {boot_rel, RelName2},
 
198
          {rel, RelName1, RelVsn, [stdlib, kernel]},
 
199
          {rel, RelName2, RelVsn, [sasl, stdlib, kernel]},
 
200
          {app, sasl, [{incl_cond, include}]}
 
201
         ]},
 
202
 
 
203
    %% Generate target file
 
204
    TargetDir = "reltool_target_dir_development",
 
205
    ?m(ok, reltool_utils:recursive_delete(TargetDir)),
 
206
    ?m(ok, file:make_dir(TargetDir)),
 
207
    ?m(ok, reltool:create_target([{config, Config}], TargetDir)),
 
208
    
 
209
    Erl = filename:join([TargetDir, "bin", "erl"]),
 
210
    {ok, Node} = ?msym({ok, _}, start_node(?NODE_NAME, Erl)),
 
211
    ?msym(ok, stop_node(Node)),
 
212
    
 
213
    ok.
 
214
 
 
215
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
216
%% Generate embedded target system
 
217
 
 
218
create_embedded(TestInfo) when is_atom(TestInfo) -> 
 
219
    reltool_test_lib:tc_info(TestInfo);
 
220
create_embedded(_Config) ->
 
221
    %% Configure the server
 
222
    RelName1 = "Just testing",
 
223
    RelName2 = "Just testing with SASL",
 
224
    RelVsn = "1.0",
 
225
    Config =
 
226
        {sys,
 
227
         [
 
228
          {lib_dirs, []},
 
229
          {profile, embedded},
 
230
          {boot_rel, RelName2},
 
231
          {rel, RelName1, RelVsn, [stdlib, kernel]},
 
232
          {rel, RelName2, RelVsn, [sasl, stdlib, kernel]},
 
233
          {app, sasl, [{incl_cond, include}]}
 
234
         ]},
 
235
 
 
236
    %% Generate target file
 
237
    TargetDir = "reltool_target_dir_embedded",
 
238
    ?m(ok, reltool_utils:recursive_delete(TargetDir)),
 
239
    ?m(ok, file:make_dir(TargetDir)),
 
240
    ?m(ok, reltool:create_target([{config, Config}], TargetDir)),
 
241
 
 
242
    Erl = filename:join([TargetDir, "bin", "erl"]),
 
243
    {ok, Node} = ?msym({ok, _}, start_node(?NODE_NAME, Erl)),
 
244
    ?msym(ok, stop_node(Node)),
 
245
        
 
246
    ok.
 
247
 
 
248
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
249
%% Generate standalone system
 
250
 
 
251
create_standalone(TestInfo) when is_atom(TestInfo) -> 
 
252
    reltool_test_lib:tc_info(TestInfo);
 
253
create_standalone(_Config) ->
 
254
    %% Configure the server
 
255
    ExDir = code:lib_dir(reltool, examples),
 
256
    EscriptName = "display_args",
 
257
    Escript = filename:join([ExDir, EscriptName]),
 
258
    Config =
 
259
        {sys,
 
260
         [
 
261
          {lib_dirs, []},
 
262
          {escript, Escript, [{incl_cond, include}]},
 
263
          {profile, standalone}
 
264
         ]},
 
265
 
 
266
    %% Generate target file
 
267
    TargetDir = "reltool_target_dir_standalone",
 
268
    ?m(ok, reltool_utils:recursive_delete(TargetDir)),
 
269
    ?m(ok, file:make_dir(TargetDir)),
 
270
    ?m(ok, reltool:create_target([{config, Config}], TargetDir)),
 
271
 
 
272
    BinDir = filename:join([TargetDir, "bin"]),
 
273
    Erl = filename:join([BinDir, "erl"]),
 
274
    {ok, Node} = ?msym({ok, _}, start_node(?NODE_NAME, Erl)), 
 
275
    RootDir = ?ignore(rpc:call(Node, code, root_dir, [])),
 
276
    ?msym(ok, stop_node(Node)),
 
277
    
 
278
    Expected =  iolist_to_binary(["Root dir: ", RootDir, "\n"
 
279
                                  "Script args: [\"-arg1\",\"arg2\",\"arg3\"]\n",
 
280
                                  "Smp: false\n",
 
281
                                  "ExitCode:0"]),
 
282
    io:format("Expected: ~s\n", [Expected]),
 
283
    ?m(Expected, run(BinDir, EscriptName ++ " -arg1 arg2 arg3")),
 
284
    
 
285
    ok.
 
286
 
 
287
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
288
%% Generate old type of target system
 
289
 
 
290
create_old_target(TestInfo) when is_atom(TestInfo) -> 
 
291
    reltool_test_lib:tc_info(TestInfo);
 
292
create_old_target(_Config) ->
 
293
    %% Configure the server
 
294
    RelName1 = "Just testing",
 
295
    RelName2 = "Just testing with SASL",
 
296
    RelVsn = "1.0",
 
297
    Config =
 
298
        {sys,
 
299
         [
 
300
          {lib_dirs, []},
 
301
          {boot_rel, RelName2},
 
302
          {rel, RelName1, RelVsn, [stdlib, kernel]},
 
303
          {rel, RelName2, RelVsn, [sasl, stdlib, kernel]},
 
304
          {relocatable, false}, % Implies explicit old style installation
 
305
          {app, sasl, [{incl_cond, include}]}
 
306
         ]},
 
307
 
 
308
    %% Generate target file
 
309
    TargetDir = "reltool_target_dir_old",
 
310
    ?m(ok, reltool_utils:recursive_delete(TargetDir)),
 
311
    ?m(ok, file:make_dir(TargetDir)),
 
312
    ?m(ok, reltool:create_target([{config, Config}], TargetDir)),
 
313
    
 
314
    %% io:format("Will fail on Windows (should patch erl.ini)\n", []),
 
315
    ?m(ok, reltool:install(RelName2, TargetDir)),
 
316
 
 
317
    Erl = filename:join([TargetDir, "bin", "erl"]),
 
318
    {ok, Node} = ?msym({ok, _}, start_node(?NODE_NAME, Erl)),
 
319
    ?msym(ok, stop_node(Node)),
 
320
    
 
321
    ok.
 
322
 
 
323
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
324
%% Library functions
 
325
 
 
326
erl_libs() ->
 
327
    case os:getenv("ERL_LIBS") of
 
328
        false  -> [];
 
329
        LibStr -> string:tokens(LibStr, ":;")
 
330
    end.
 
331
 
 
332
diff_script(Script, Script) ->
 
333
    equal;
 
334
diff_script({script, Rel, Commands1}, {script, Rel, Commands2}) ->
 
335
    diff_cmds(Commands1, Commands2);
 
336
diff_script({script, Rel1, _}, {script, Rel2, _}) ->
 
337
    {error, {Rel1, Rel2}}.
 
338
 
 
339
diff_cmds([Cmd | Commands1], [Cmd | Commands2]) ->
 
340
    diff_cmds(Commands1, Commands2);
 
341
diff_cmds([Cmd1 | _Commands1], [Cmd2 | _Commands2]) ->
 
342
    {diff, {expected, Cmd1}, {actual, Cmd2}};
 
343
diff_cmds([], []) ->
 
344
    equal.
 
345
 
 
346
os_cmd(Cmd) when is_list(Cmd) ->
 
347
    %% Call the plain os:cmd with an echo command appended to print command status
 
348
    %% io:format("os:cmd(~p).\n", [Cmd]),
 
349
    case os:cmd(Cmd++";echo \"#$?\"") of
 
350
        %% There is (as far as I can tell) only one thing that will match this
 
351
        %% and that is too silly to ever be used, but...
 
352
        []->
 
353
            {99, []};
 
354
        Return->
 
355
            %% Find the position of the status code wich is last in the string
 
356
            %% prepended with #
 
357
            case string:rchr(Return, $#) of
 
358
                
 
359
                %% This happens only if the sh command pipe is somehow interrupted
 
360
                0->
 
361
                {98, Return};
 
362
                
 
363
                Position->
 
364
                Result = string:left(Return,Position - 1),
 
365
                Status = string:substr(Return,Position + 1, length(Return) - Position - 1),
 
366
                {list_to_integer(Status), Result}
 
367
            end
 
368
    end.
 
369
 
 
370
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
371
%% Node handling
 
372
 
 
373
start_node(Name, ErlPath) ->
 
374
    FullName = full_node_name(Name),
 
375
    CmdLine = mk_node_cmdline(Name, ErlPath),
 
376
    io:format("Starting node ~p: ~s~n", [FullName, CmdLine]),
 
377
    case open_port({spawn, CmdLine}, []) of
 
378
        Port when is_port(Port) ->
 
379
            unlink(Port),
 
380
            erlang:port_close(Port),
 
381
            case ping_node(FullName, 50) of
 
382
                ok -> {ok, FullName};
 
383
                Other -> exit({failed_to_start_node, FullName, Other})
 
384
            end;
 
385
        Error ->
 
386
            exit({failed_to_start_node, FullName, Error})
 
387
    end.
 
388
 
 
389
stop_node(Node) ->
 
390
    monitor_node(Node, true),
 
391
    spawn(Node, fun () -> halt() end),
 
392
    receive {nodedown, Node} -> ok end.
 
393
 
 
394
mk_node_cmdline(Name) ->
 
395
    Prog = case catch init:get_argument(progname) of
 
396
               {ok,[[P]]} -> P;
 
397
               _ -> exit(no_progname_argument_found)
 
398
           end,
 
399
    mk_node_cmdline(Name, Prog).
 
400
 
 
401
mk_node_cmdline(Name, Prog) ->
 
402
    Static = "-detached -noinput",
 
403
    Pa = filename:dirname(code:which(?MODULE)),
 
404
    NameSw = case net_kernel:longnames() of
 
405
                 false -> "-sname ";
 
406
                 true -> "-name ";
 
407
                 _ -> exit(not_distributed_node)
 
408
             end,
 
409
    {ok, Pwd} = file:get_cwd(),
 
410
    NameStr = atom_to_list(Name),
 
411
    Prog ++ " "
 
412
        ++ Static ++ " "
 
413
        ++ NameSw ++ " " ++ NameStr ++ " "
 
414
        ++ "-pa " ++ Pa ++ " "
 
415
        ++ "-env ERL_CRASH_DUMP " ++ Pwd ++ "/erl_crash_dump." ++ NameStr ++ " "
 
416
        ++ "-setcookie " ++ atom_to_list(erlang:get_cookie()).
 
417
 
 
418
full_node_name(PreName) ->
 
419
    HostSuffix = lists:dropwhile(fun ($@) -> false; (_) -> true end,
 
420
                                 atom_to_list(node())),
 
421
    list_to_atom(atom_to_list(PreName) ++ HostSuffix).
 
422
 
 
423
ping_node(_Node, 0) ->
 
424
    {error, net_adm};
 
425
ping_node(Node, N) when is_integer(N), N > 0 ->
 
426
    case catch net_adm:ping(Node) of
 
427
        pong -> 
 
428
            wait_for_process(Node, code_server, 50);
 
429
        _ ->
 
430
            timer:sleep(1000),
 
431
            ping_node(Node, N-1)
 
432
    end.
 
433
 
 
434
wait_for_process(_Node, Name, 0) ->
 
435
    {error, Name};
 
436
wait_for_process(Node, Name, N) when is_integer(N), N > 0 ->
 
437
    case rpc:call(Node, erlang, whereis, [Name]) of
 
438
        undefined ->
 
439
            timer:sleep(1000),
 
440
            wait_for_process(Node, Name, N-1);
 
441
        {badrpc, _} = Reason ->
 
442
            erlang:error({Reason, Node});
 
443
        Pid when is_pid(Pid) ->
 
444
            ok
 
445
    end.
 
446
 
 
447
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
448
%% Run escript
 
449
 
 
450
run(Dir, Cmd0) ->
 
451
    Cmd = case os:type() of
 
452
              {win32,_} -> filename:nativename(Dir) ++ "\\" ++ Cmd0;
 
453
              _ -> Cmd0
 
454
          end,
 
455
    do_run(Dir, Cmd).
 
456
 
 
457
run(Dir, Opts, Cmd0) ->
 
458
    Cmd = case os:type() of
 
459
              {win32,_} -> Opts ++ " " ++ filename:nativename(Dir) ++ "\\" ++ Cmd0;
 
460
              _ -> Opts ++ " " ++ Dir ++ "/" ++ Cmd0
 
461
          end,
 
462
    do_run(Dir, Cmd).
 
463
 
 
464
do_run(Dir, Cmd) ->
 
465
    io:format("Run: ~p\n", [Cmd]),
 
466
    Env = [{"PATH",Dir++":"++os:getenv("PATH")}],
 
467
    Port = open_port({spawn,Cmd}, [exit_status,eof,in,{env,Env}]),
 
468
    Res = get_data(Port, []),
 
469
    receive
 
470
        {Port,{exit_status,ExitCode}} ->
 
471
            iolist_to_binary([Res,"ExitCode:"++integer_to_list(ExitCode)])
 
472
    end.
 
473
 
 
474
get_data(Port, SoFar) ->
 
475
    receive
 
476
        {Port,{data,Bytes}} ->
 
477
            get_data(Port, [SoFar|Bytes]);
 
478
        {Port,eof} ->
 
479
            erlang:port_close(Port),
 
480
            SoFar
 
481
    end.
 
482
 
 
483
expected_output([data_dir|T], Data) ->
 
484
    Slash = case os:type() of
 
485
                {win32,_} -> "\\";
 
486
                _ -> "/"
 
487
            end,
 
488
    [filename:nativename(Data)++Slash|expected_output(T, Data)];
 
489
expected_output([H|T], Data) ->
 
490
    [H|expected_output(T, Data)];
 
491
expected_output([], _) -> 
 
492
    [];
 
493
expected_output(Bin, _) when is_binary(Bin) -> 
 
494
    Bin.