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

« back to all changes in this revision

Viewing changes to lib/asn1/test/test_special_decode_performance.erl

  • 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
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2003-2010. 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
-module(test_special_decode_performance).
 
21
 
 
22
-export([compile/2,go/1,loop2/4,loop1/5]).
 
23
 
 
24
-include_lib("test_server/include/test_server.hrl").
 
25
 
 
26
 
 
27
compile(Config,Rule) when Rule==ber_bin_v2 ->
 
28
    ?line DataDir = ?config(data_dir,Config),
 
29
    ?line OutDir = ?config(priv_dir,Config),
 
30
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
31
    
 
32
    ?line asn1ct:compile(DataDir++"MEDIA-GATEWAY-CONTROL",
 
33
                         [ber_bin,optimize,asn1config,{outdir,OutDir},
 
34
                          {i,DataDir}]),
 
35
    ?line asn1ct:compile(DataDir++"PartialDecSeq",
 
36
                         [ber_bin,optimize,asn1config,{outdir,OutDir},
 
37
                          {i,DataDir}]);
 
38
compile(_,Rule) ->
 
39
    {skip,lists:concat(["not implemented yet for version: ",Rule])}.
 
40
 
 
41
go(all) ->
 
42
    {Time_S_s,Time_S_e,Time_S_c}=go(10000,'PartialDecSeq'),
 
43
    {Time_MGC_s,Time_MGC_e,Time_MGC_c}=go(10000,'MEDIA-GATEWAY-CONTROL'),
 
44
    ?line do_comment({Time_S_s,Time_MGC_s},
 
45
                     {Time_S_e,Time_MGC_e},
 
46
                     {Time_S_c,Time_MGC_c}).
 
47
 
 
48
go(N,Mod) ->
 
49
    ?line Val = val(Mod),
 
50
    ?line {ok,B} = Mod:encode(element(1,Val),Val),
 
51
    ?line go(Mod,list_to_binary(B),N).
 
52
 
 
53
go(Mod,Bin,N) ->
 
54
    ?line FsS = get_selective_funcs(Mod),
 
55
    ?line FsE = get_exclusive_funcs(Mod),
 
56
    ?line io:format("~nSize of value for module ~p: ~p bytes.~n~n",[Mod,size(Bin)]),
 
57
    ?line Time_s=go1(selective,Mod,FsS,Bin,N,0),
 
58
    ?line Time_e=go1(exclusive,Mod,FsE,Bin,N,0),
 
59
    ?line Time_c=go1(common,Mod,[decode],Bin,N,0),
 
60
    ?line {Time_s/length(FsS),Time_e/length(FsE),Time_c}.
 
61
 
 
62
go1(_,_,[],_,_,AccTime) ->
 
63
    ?line AccTime;
 
64
%% go1 for common decode
 
65
go1(common,Mod,_,Bin,N,_) ->
 
66
    ?line TT=get_top_type(Mod),
 
67
    ?line {Time,Result}=timer:tc(?MODULE,loop1,[Mod,decode,TT,Bin,N]),
 
68
    case Result of
 
69
        {ok,_R1} ->
 
70
            io:format("common Decode ~p:decode, ~p times on time ~p~n",
 
71
                      [Mod,N,Time]);
 
72
        Err ->
 
73
            io:format("common Decode ~p:decode failed: ~w~n~n",[Mod,Err])
 
74
    end,
 
75
    Time;
 
76
go1(Dec,Mod,[F|Fs],Bin,N,AccTime) ->
 
77
    ?line {Time,Result}=timer:tc(?MODULE,loop2,[Mod,F,Bin,N]),
 
78
    case Result of
 
79
        {ok,_R1} ->
 
80
            io:format("~p Decode ~p:~p, ~p times on time ~p~n",[Dec,Mod,F,N,Time]);
 
81
        Err ->
 
82
            io:format("~p Decode ~p:~p failed: ~w~n~n",[Dec,Mod,F,Err])
 
83
    end,
 
84
    go1(Dec,Mod,Fs,Bin,N,AccTime+Time).
 
85
 
 
86
do_comment({Time_S_s,Time_MGC_s},
 
87
           {Time_S_e,Time_MGC_e},
 
88
           {Time_S_c,Time_MGC_c}) ->
 
89
%    io:format("Time_s: ~w, Time_e: ~w, Time_c: ~w~n",[Time_s,Time_e,Time_c]),
 
90
    Time_sofc1 = Time_S_s/Time_S_c,
 
91
    Time_sofc2 = Time_MGC_s/Time_MGC_c,
 
92
    Time_eofc1 = Time_S_e/Time_S_c,
 
93
    Time_eofc2 = Time_MGC_e/Time_MGC_c,
 
94
    Av_proc_sofc = 
 
95
        integer_to_list(round(((100*Time_sofc1) + (100*Time_sofc2))/2)),
 
96
    Av_proc_eofc =
 
97
        integer_to_list(round(((100*Time_eofc1) + (100*Time_eofc2))/2)),
 
98
    io:format("Av_proc_sofc = ~w, Av_proc_eofc = ~w~n",
 
99
              [Av_proc_sofc,Av_proc_eofc]),
 
100
    Comment = ["selective decode takes "++
 
101
               Av_proc_sofc ++" % of common decode time",
 
102
               "exclusive decode takes "++ Av_proc_eofc++
 
103
               " % of common decode time"],
 
104
    {comment,Comment}.
 
105
    
 
106
val('PartialDecSeq') ->
 
107
    {'F',{fb,{'E',12,[{'D',13,true},{'D',14,false},{'D',15,true},{'D',16,false},{'D',13,true},{'D',14,false},{'D',15,true},{'D',16,false},{'D',13,true},{'D',14,false},{'D',15,true},{'D',16,false}],true,{da,[{'A',17,{'D',18,false}},{'A',19,{'D',20,true}},{'A',21,{'D',22,false}},{'A',17,{'D',18,false}},{'A',19,{'D',20,true}},{'A',21,{'D',22,false}},{'A',17,{'D',18,false}},{'A',19,{'D',20,true}},{'A',21,{'D',22,false}},{'A',17,{'D',18,false}},{'A',19,{'D',20,true}},{'A',21,{'D',22,false}},{'A',17,{'D',18,false}},{'A',19,{'D',20,true}},{'A',21,{'D',22,false}},{'A',17,{'D',18,false}},{'A',19,{'D',20,true}},{'A',21,{'D',22,false}}]}}}};
 
108
 
 
109
val('MEDIA-GATEWAY-CONTROL') ->
 
110
    {'MegacoMessage',asn1_NOVALUE,{'Message',1,{ip4Address,{'IP4Address',[125,125,125,111],55555}},{transactions,[{transactionReply,{'TransactionReply',50007,asn1_NOVALUE,{actionReplies,[{'ActionReply',0,asn1_NOVALUE,asn1_NOVALUE,[{auditValueReply,{auditResult,{'AuditResult',{'TerminationID',[],[255,255,255]},[{mediaDescriptor,{'MediaDescriptor',asn1_NOVALUE,{multiStream,[{'StreamDescriptor',1,{'StreamParms',{'LocalControlDescriptor',sendRecv,asn1_NOVALUE,asn1_NOVALUE,[{'PropertyParm',[0,11,0,7],[[52,48]],asn1_NOVALUE}]},{'LocalRemoteDescriptor',[[{'PropertyParm',[0,0,176,1],[[48]],asn1_NOVALUE},{'PropertyParm',[0,0,176,8],[[73,78,32,73,80,52,32,49,50,53,46,49,50,53,46,49,50,53,46,49,49,49]],asn1_NOVALUE},{'PropertyParm',[0,0,176,15],[[97,117,100,105,111,32,49,49,49,49,32,82,84,80,47,65,86,80,32,32,52]],asn1_NOVALUE},{'PropertyParm',[0,0,176,12],[[112,116,105,109,101,58,51,48]],asn1_NOVALUE}]]},{'LocalRemoteDescriptor',[[{'PropertyParm',[0,0,176,1],[[48]],asn1_NOVALUE},{'PropertyParm',[0,0,176,8],[[73,78,32,73,80,52,32,49,50,52,46,49,50,52,46,49,50,52,46,50,50,50]],asn1_NOVALUE},{'PropertyParm',[0,0,176,15],[[97,117,100,105,111,32,50,50,50,50,32,82,84,80,47,65,86,80,32,32,52]],asn1_NOVALUE},{'PropertyParm',[0,0,176,12],[[112,116,105,109,101,58,51,48]],asn1_NOVALUE}]]}}}]}}},{packagesDescriptor,[{'PackagesItem',[0,11],1},{'PackagesItem',[0,11],1}]},{statisticsDescriptor,[{'StatisticsParameter',[0,12,0,4],[[49,50,48,48]]},{'StatisticsParameter',[0,11,0,2],[[54,50,51,48,48]]},{'StatisticsParameter',[0,12,0,5],[[55,48,48]]},{'StatisticsParameter',[0,11,0,3],[[52,53,49,48,48]]},{'StatisticsParameter',[0,12,0,6],[[48,46,50]]},{'StatisticsParameter',[0,12,0,7],[[50,48]]},{'StatisticsParameter',[0,12,0,8],[[52,48]]}]}]}}}]}]}}}]}}}.
 
111
 
 
112
%% val('PartialDecSeq') ->
 
113
%%     {'F',{fb,{'E',35,[{'D',3,true},{'D',4,false},{'D',5,true},{'D',6,true},{'D',7,false},{'D',8,true},{'D',9,true},{'D',10,false},{'D',11,true},{'D',12,true},{'D',13,false},{'D',14,true}],false,{dc,{'E_d_dc',15,true,{'E_d_dc_dcc',17,4711}}}}}}.
 
114
 
 
115
loop1(Mod,decode,TT,Bin,1) ->
 
116
    {ok,_Msg}=Mod:decode(TT,Bin);
 
117
loop1(Mod,decode,TT,Bin,N) ->
 
118
    {ok,_Msg}=Mod:decode(TT,Bin),
 
119
    loop1(Mod,decode,TT,Bin,N-1).
 
120
 
 
121
loop2(Mod,FS,Bin,1) ->
 
122
    {ok,_Msg}=Mod:FS(Bin);
 
123
loop2(Mod,FS,Bin,N) ->
 
124
    {ok,_Msg}=Mod:FS(Bin),
 
125
    loop2(Mod,FS,Bin,N-1).
 
126
 
 
127
%% loop3(Mod,F,Bin,1) ->
 
128
%%     {ok,Msg}=Mod:F(Bin),
 
129
%%     decode_parts(Mod,F,Msg);
 
130
%% loop3(Mod,F,Bin,N) ->
 
131
%%     {ok,Msg}=Mod:F(Bin),
 
132
%%     decode_parts(Mod,F,Msg),
 
133
%%     loop3(Mod,F,Bin,N-1).
 
134
 
 
135
get_selective_funcs('PartialDecSeq') ->
 
136
%    [selected_decode_F1,selected_decode_F2,selected_decode_F3,selected_decode_F4];
 
137
    [selected_decode_F1,selected_decode_F3,selected_decode_F4];
 
138
get_selective_funcs('MEDIA-GATEWAY-CONTROL') ->
 
139
    [decode_MegacoMessage_selective].
 
140
 
 
141
get_exclusive_funcs('PartialDecSeq') ->
 
142
    [decode_F_fb_incomplete,decode_F_fb_exclusive2,decode_F_fb_exclusive3];
 
143
get_exclusive_funcs('MEDIA-GATEWAY-CONTROL') ->
 
144
    [decode_MegacoMessage_exclusive].
 
145
 
 
146
get_top_type('PartialDecSeq') ->
 
147
    'F';
 
148
get_top_type('MEDIA-GATEWAY-CONTROL') ->
 
149
    'MegacoMessage'.
 
150
 
 
151
%% decode_parts('PartialDecSeq',decode_F_fb_incomplete,Msg) ->
 
152
%%     {fb,{'E',12,{E_bKey,E_bMsg},true,{E_dKey,E_dMsg}}}=Msg,
 
153
%%     {ok,_}='Seq':decode_part(E_bKey,E_bMsg),
 
154
%%     {ok,_}='Seq':decode_part(E_dKey,E_dMsg);
 
155
%% decode_parts('PartialDecSeq',decode_F_fb_exclusive2,Msg) ->
 
156
%%     {fb,{'E',12,{E_bKey,E_bMsg},true,{d,{E_dKey,E_dMsg}}}} = Msg,
 
157
%%     {ok,_}='Seq':decode_part(E_bKey,E_bMsg),
 
158
%%     {ok,_}='Seq':decode_part(E_dKey,E_dMsg);
 
159
%% decode_parts('MEDIA-GATEWAY-CONTROL',decode_MegacoMessage_exclusive,Msg) ->
 
160
%%     {'MegacoMessage',asn1_NOVALUE,{'Message',1,{M_MidKey,M_MidMsg},
 
161
%%                                 {M_mBKey,M_mBMsg}}} = Msg,
 
162
%%     {ok,_}='MEDIA-GATEWAY-CONTROL':decode_part(M_MidKey,M_MidMsg),
 
163
%%     {ok,_}='MEDIA-GATEWAY-CONTROL':decode_part(M_mBKey,M_mBMsg).
 
164
    
 
165