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

« back to all changes in this revision

Viewing changes to lib/erl_interface/test/ei_accept_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 2001-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
 
 
20
%%
 
21
-module(ei_accept_SUITE).
 
22
 
 
23
-include("test_server.hrl").
 
24
-include("ei_accept_SUITE_data/ei_accept_test_cases.hrl").
 
25
 
 
26
-export([all/1, init_per_testcase/2, fin_per_testcase/2,
 
27
         ei_accept/1, ei_threaded_accept/1]).
 
28
 
 
29
-import(runner, [get_term/1,send_term/2]).
 
30
 
 
31
all(suite) -> [ei_accept, ei_threaded_accept].
 
32
 
 
33
init_per_testcase(_Case, Config) ->
 
34
    Dog = ?t:timetrap(?t:minutes(0.25)),
 
35
    [{watchdog, Dog}|Config].
 
36
 
 
37
fin_per_testcase(_Case, Config) ->
 
38
    Dog = ?config(watchdog, Config),
 
39
    test_server:timetrap_cancel(Dog),
 
40
    ok.
 
41
 
 
42
ei_accept(Config) when is_list(Config) ->
 
43
    ?line P = runner:start(?interpret),
 
44
    ?line 0 = ei_connect_init(P, 42, erlang:get_cookie(), 0),
 
45
 
 
46
%    ?line AMsg={a,[message, with], " strings in it!", [-12, -23], 1.001},
 
47
    %% shouldn't this be a bif or function or something?
 
48
    ?line Myname= hd(tl(string:tokens(atom_to_list(node()), "@"))),
 
49
    ?line io:format("Myname ~p ~n",  [Myname]),
 
50
    ?line EINode= list_to_atom("c42@"++Myname),
 
51
    ?line io:format("EINode ~p ~n",  [EINode]),
 
52
    ?line Self= self(),
 
53
    ?line TermToSend= {call, Self, "Test"},
 
54
    ?line F= fun() ->
 
55
                     timer:sleep(500),
 
56
                     {any, EINode} ! TermToSend,
 
57
                     Self ! sent_ok,
 
58
                     ok
 
59
             end,
 
60
 
 
61
    ?line spawn(F),
 
62
    ?line Port  = 6543,
 
63
    ?line {ok, Fd, _Node} = ei_accept(P, Port),
 
64
    ?line TermReceived= ei_receive(P, Fd),
 
65
    ?line io:format("Sent ~p received ~p ~n", [TermToSend, TermReceived]),
 
66
    ?line TermToSend= TermReceived,
 
67
    ?line receive
 
68
              sent_ok ->
 
69
                  ok;
 
70
              Unknown ->
 
71
                  io:format("~p ~n", [Unknown])
 
72
          after 1000 ->
 
73
                  io:format("timeout ~n")
 
74
          end,
 
75
    ?line ok= ei_unpublish(P),
 
76
    ok.
 
77
 
 
78
ei_threaded_accept(Config) when is_list(Config) ->
 
79
    ?line Einode = filename:join(?config(data_dir, Config), "eiaccnode"),
 
80
    ?line N = 1, % 3,
 
81
    ?line Host = atom_to_list(node()),
 
82
    ?line Port = 6767,
 
83
    ?line start_einode(Einode, N, Host, Port),
 
84
    ?line io:format("started eiaccnode"),
 
85
    %%?line spawn_link(fun() -> start_einode(Einode, N, Host, Port) end),
 
86
    ?line TestServerPid = self(),
 
87
    ?line [ spawn_link(fun() -> send_rec_einode(I, TestServerPid) end)
 
88
            || I <- lists:seq(0, N-1) ],
 
89
    ?line [ receive I -> ok end
 
90
            || I <- lists:seq(0, N-1) ],
 
91
    ok.
 
92
 
 
93
send_rec_einode(N, TestServerPid) ->
 
94
    ?line Myname= hd(tl(string:tokens(atom_to_list(node()), "@"))),
 
95
    ?line EINode= list_to_atom("eiacc" ++ integer_to_list(N) ++ "@" ++ Myname),
 
96
    ?line io:format("EINode ~p ~n",  [EINode]),
 
97
    ?line Self= self(),
 
98
    ?line timer:sleep(10*1000),
 
99
    ?line {any, EINode} ! Self,
 
100
    ?line receive
 
101
              {N,_}=X ->
 
102
                  ?line io:format("Received by ~s ~p~n", [EINode, X]),
 
103
                  ?line TestServerPid ! N,
 
104
                  ?line X
 
105
          after 10000 ->
 
106
                  ?line test_server:fail(EINode)
 
107
          end.
 
108
 
 
109
start_einode(Einode, N, Host, Port) ->
 
110
    Einodecmd = Einode ++ " " ++ atom_to_list(erlang:get_cookie())
 
111
        ++ " " ++ integer_to_list(N) ++ " " ++ Host ++ " "
 
112
        ++ integer_to_list(Port) ++ " nothreads",
 
113
    io:format("Einodecmd  ~p ~n", [Einodecmd]),      
 
114
    ?line open_port({spawn, Einodecmd}, []),
 
115
    ok.
 
116
 
 
117
 
 
118
 
 
119
%%% Interface functions for ei (erl_interface) functions.
 
120
 
 
121
ei_connect_init(P, Num, Cookie, Creation) ->
 
122
    send_command(P, ei_connect_init, [Num,Cookie,Creation]),
 
123
    case get_term(P) of
 
124
        {term,Int} when is_integer(Int) -> Int
 
125
    end.
 
126
 
 
127
ei_accept(P, PortNo) ->
 
128
    send_command(P, ei_accept, [PortNo]),
 
129
    case get_term(P) of
 
130
        {term,{Fd, _, Node}} when Fd >= 0 -> {ok, Fd, Node};
 
131
        {term,{_Fd, Errno, _Node}} -> {error,Errno}
 
132
    end.
 
133
 
 
134
ei_receive(P, Fd) ->
 
135
    send_command(P, ei_receive, [Fd]),
 
136
    {term, T}= get_term(P),
 
137
    T.
 
138
 
 
139
ei_unpublish(P) ->
 
140
    send_command(P, ei_unpublish, []),
 
141
    case get_term(P) of
 
142
        {term,{0, _}} -> ok;
 
143
        {term,{_X, Errno}} -> {error,Errno}
 
144
    end.
 
145
 
 
146
send_command(P, Name, Args) ->
 
147
    runner:send_term(P, {Name,list_to_tuple(Args)}).
 
148
 
 
149
    
 
150
 
 
151