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

« back to all changes in this revision

Viewing changes to lib/asn1/test/asn1_bin_v2_particular_SUITE.erl.src

  • 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
particular() -> [smp, ticket7904].
 
3
 
 
4
 
 
5
smp(suite) -> [];
 
6
smp(Config)  ->
 
7
    case erlang:system_info(smp_support) of
 
8
        true ->
 
9
            NumOfProcs = erlang:system_info(schedulers),
 
10
            io:format("smp starting ~p workers\n",[NumOfProcs]),
 
11
 
 
12
            ?line Msg = {initiatingMessage, testNBAPsystem:cell_setup_req_msg()},
 
13
            ?line ok = testNBAPsystem:compile(Config,per_bin,[optimize]),
 
14
 
 
15
            Parent = self(),
 
16
            
 
17
            ?line ok = asn1rt:load_driver(),
 
18
        
 
19
            smp2(Parent,NumOfProcs,Msg,2),
 
20
 
 
21
            N = 10000,
 
22
 
 
23
            ?line {Time1,ok} = timer:tc(?MODULE,smp2,[Parent,NumOfProcs,Msg, N]),
 
24
            ?line {Time1S,ok} = timer:tc(?MODULE,sequential,[NumOfProcs * N,Msg]),
 
25
 
 
26
            ?line ok = testNBAPsystem:compile(Config,ber_bin,[optimize,driver]),
 
27
            ?line {Time2,ok} = timer:tc(?MODULE,smp2,[Parent,NumOfProcs,Msg, N]),
 
28
 
 
29
            ?line {Time2S,ok} = timer:tc(?MODULE,sequential,[NumOfProcs * N,Msg]),
 
30
 
 
31
            {comment,lists:flatten(io_lib:format("Encode/decode time parallell with ~p cores: ~p [microsecs]~nEncode/decode time sequential: ~p [microsecs]",[NumOfProcs,Time1+Time2,Time1S+Time2S]))};
 
32
        false ->
 
33
            {skipped,"No smp support"}
 
34
    end.
 
35
 
 
36
smp2(Parent,NumOfProcs,Msg, N) ->
 
37
    Pids = [spawn_link(fun() -> worker(Msg,Parent, N) end)
 
38
                    || _ <- lists:seq(1,NumOfProcs)],
 
39
    ?line ok = wait_pids(Pids).
 
40
 
 
41
worker(Msg, Parent, N) ->
 
42
    %% io:format("smp worker ~p with ~p worker loops.~n",[self(), N]),
 
43
    worker_loop(N, Msg),
 
44
    Parent ! self().
 
45
 
 
46
worker_loop(0, _Msg) ->
 
47
    ok;
 
48
worker_loop(N, Msg) ->
 
49
    ?line {ok,B}=asn1_wrapper:encode('NBAP-PDU-Discriptions',
 
50
                                     'NBAP-PDU',
 
51
                                     Msg),
 
52
    ?line {ok,_Msg}=asn1_wrapper:decode('NBAP-PDU-Discriptions',
 
53
                                     'NBAP-PDU',
 
54
                                     B),
 
55
    worker_loop(N - 1, Msg).
 
56
 
 
57
 
 
58
wait_pids([]) -> 
 
59
    ok;
 
60
wait_pids(Pids) ->
 
61
    receive
 
62
        Pid when is_pid(Pid) ->
 
63
            ?line true = lists:member(Pid,Pids),
 
64
            Others = lists:delete(Pid,Pids),
 
65
            io:format("wait_pid got ~p, still waiting for ~p\n",[Pid,Others]),
 
66
            wait_pids(Others);
 
67
        Err ->
 
68
            io:format("Err: ~p~n",[Err]),
 
69
            ?line exit(Err)
 
70
    end.
 
71
 
 
72
sequential(N,Msg) ->
 
73
     %%io:format("sequential encode/decode with N = ~p~n",[N]),
 
74
     worker_loop(N,Msg).
 
75
    
 
76
-record('InitiatingMessage',{procedureCode,criticality,value}).
 
77
-record('Iu-ReleaseCommand',{first,second}).
 
78
 
 
79
ticket7904(suite) -> [];
 
80
ticket7904(Config) ->
 
81
    ?line DataDir = ?config(data_dir,Config),
 
82
    ?line OutDir = ?config(priv_dir,Config),
 
83
 
 
84
    ?line ok = asn1ct:compile(DataDir ++ 
 
85
                      "RANAPextract1",[per_bin,optimize,{outdir,OutDir}]),
 
86
 
 
87
    Val1 = #'InitiatingMessage'{procedureCode=1,
 
88
                                criticality=ignore,
 
89
                                value=#'Iu-ReleaseCommand'{
 
90
                                  first=13,
 
91
                                  second=true}},
 
92
 
 
93
    ?line {ok,_} = 'RANAPextract1':encode('InitiatingMessage', Val1),
 
94
    asn1rt:unload_driver(),
 
95
    ?line {ok,_} = 'RANAPextract1':encode('InitiatingMessage', Val1).