~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

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

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
11
11
 
12
12
            ?line Msg = {initiatingMessage, testNBAPsystem:cell_setup_req_msg()},
13
13
            ?line ok = testNBAPsystem:compile(Config,per_bin,[optimize]),
14
 
 
15
 
            Parent = self(),
16
14
            
17
 
            ?line ok = asn1rt:load_driver(),
18
 
        
19
 
            smp2(Parent,NumOfProcs,Msg,2),
 
15
            enc_dec(NumOfProcs,Msg,2),
20
16
 
21
17
            N = 10000,
22
18
 
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]))};
 
19
            ?line {Time1,ok} = timer:tc(?MODULE,enc_dec,[NumOfProcs,Msg, N]),
 
20
            ?line {Time1S,ok} = timer:tc(?MODULE,enc_dec,[1, Msg, NumOfProcs * N]),
 
21
 
 
22
            ?line ok = testNBAPsystem:compile(Config,ber_bin,[optimize,nif]),
 
23
            ?line {Time3,ok} = timer:tc(?MODULE,enc_dec,[NumOfProcs,Msg, N]),
 
24
 
 
25
            ?line {Time3S,ok} = timer:tc(?MODULE,enc_dec,[1, Msg, NumOfProcs * N]),
 
26
 
 
27
            {comment,lists:flatten(
 
28
                       io_lib:format(
 
29
                         "Encode/decode time parallell with ~p cores: ~p [microsecs]~n"
 
30
                         "Encode/decode time sequential: ~p [microsecs]",
 
31
                         [NumOfProcs,Time1+Time3,Time1S+Time3S]))};
32
32
        false ->
33
33
            {skipped,"No smp support"}
34
34
    end.
35
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().
 
36
per_performance(Config) ->
 
37
    PrivDir = proplists:get_value(priv_dir, Config),
 
38
    NifDir = filename:join(PrivDir,"nif"),
 
39
    ErlDir = filename:join(PrivDir,"erl"),
 
40
    file:make_dir(NifDir),file:make_dir(ErlDir),
 
41
 
 
42
    ?line Msg = {initiatingMessage, testNBAPsystem:cell_setup_req_msg()},
 
43
    ?line ok = testNBAPsystem:compile([{priv_dir,NifDir}|Config],per_bin,
 
44
                                      [optimize]),
 
45
    ?line ok = testNBAPsystem:compile([{priv_dir,ErlDir}|Config],per_bin,
 
46
                                      []),
 
47
 
 
48
    Modules = ['NBAP-CommonDataTypes',
 
49
               'NBAP-Constants',
 
50
               'NBAP-Containers',
 
51
               'NBAP-IEs',
 
52
               'NBAP-PDU-Contents',
 
53
               'NBAP-PDU-Discriptions'],
 
54
 
 
55
 
 
56
    PreNif = fun() ->
 
57
                     code:add_patha(NifDir),
 
58
                     lists:foreach(fun(M) ->
 
59
                                           code:purge(M),
 
60
                                           code:load_file(M)
 
61
                                   end,Modules)
 
62
             end,
 
63
    
 
64
    PreErl = fun() ->
 
65
                     code:add_patha(ErlDir),
 
66
                     lists:foreach(fun(M) ->
 
67
                                           code:purge(M),
 
68
                                           code:load_file(M)
 
69
                                   end,Modules)
 
70
             end,
 
71
 
 
72
    Func = fun() ->
 
73
                   element(1,timer:tc(
 
74
                               asn1_wrapper,encode,['NBAP-PDU-Discriptions',
 
75
                                                    'NBAP-PDU',
 
76
                                                    Msg]))
 
77
           end,
 
78
 
 
79
    nif_vs_erlang_performance({{{PreNif,Func},{PreErl,Func}},100000,32}).
 
80
 
 
81
ber_performance(Config) ->
 
82
 
 
83
    ?line Msg = {initiatingMessage, testNBAPsystem:cell_setup_req_msg()},
 
84
    ?line ok = testNBAPsystem:compile(Config,ber_bin,[optimize,nif]),
 
85
 
 
86
 
 
87
    BerFun = fun() ->
 
88
                     {ok,B} = asn1_wrapper:encode('NBAP-PDU-Discriptions',
 
89
                                                  'NBAP-PDU', Msg),
 
90
                     asn1_wrapper:decode(
 
91
                        'NBAP-PDU-Discriptions',
 
92
                        'NBAP-PDU',
 
93
                        B)
 
94
             end,
 
95
    nif_vs_erlang_performance({BerFun,100000,32}).
 
96
 
 
97
cert_pem_performance(Config) when is_list(Config) ->
 
98
    cert_pem_performance({100000, 32});
 
99
cert_pem_performance({N,S}) ->
 
100
    nif_vs_erlang_performance({fun cert_pem/0,N,S}).
 
101
 
 
102
dsa_pem_performance(Config) when is_list(Config) ->
 
103
    cert_pem_performance({100000, 32});
 
104
dsa_pem_performance({N,S}) ->
 
105
    nif_vs_erlang_performance({fun dsa_pem/0,N,S}).
 
106
 
 
107
 
 
108
nif_vs_erlang_performance({{TC1,TC2},N,Sched}) ->
 
109
    random:seed({123,456,789}),
 
110
    io:format("Running a ~p sample with ~p max procs...~n~n",[N,Sched]),
 
111
    
 
112
    {True,False} = exec(TC1,TC2,Sched,N+1),
 
113
        
 
114
    io:format("~ndone!~n"),
 
115
 
 
116
    io:format("~n"),TStats = print_stats(strip(True,N div 20)),
 
117
    io:format("~n"),FStats = print_stats(strip(False,N div 20)),
 
118
    Str = io_lib:format("~nNifs are ~.3f% faster than erlang!~n",
 
119
                        [(element(2,FStats) - element(2,TStats)) / 
 
120
                             element(2,FStats) * 100]),
 
121
    io:format(Str),
 
122
    {comment, lists:flatten(Str)};
 
123
nif_vs_erlang_performance({T,N,Sched}) ->
 
124
    PTC1 = fun() ->
 
125
                  application:set_env(asn1, nif_loadable, true)
 
126
           end,
 
127
    PTC2 = fun() ->
 
128
                  application:set_env(asn1, nif_loadable, false)
 
129
           end,
 
130
    TC = fun() ->
 
131
                 element(1,timer:tc(T))
 
132
         end,
 
133
    nif_vs_erlang_performance({{{PTC1,TC},{PTC2,TC}},N,Sched}).
 
134
    
 
135
 
 
136
print_stats(Data) ->
 
137
    Length = length(Data),
 
138
    Mean = lists:sum(Data) / Length,
 
139
    Variance = lists:foldl(fun(N,Acc) -> math:pow(N - Mean, 2)+Acc end, 0, Data),
 
140
    StdDev = math:sqrt(Variance / Length),
 
141
    Median = lists:nth(round(Length/2),Data),
 
142
    Min = lists:min(Data),
 
143
    Max = lists:max(Data),
 
144
    if Length < 20 ->
 
145
            io:format("Data: ~w~n",[Data]);
 
146
       true ->
 
147
            ok
 
148
    end,
 
149
    io:format("Length: ~p~nMean: ~p~nStdDev: ~p~nMedian: ~p~nMin: ~p~nMax: ~p~n",
 
150
              [Length,Mean,StdDev,Median,Min,Max]),
 
151
    {Length,Mean,StdDev,Median,Min,Max}.
 
152
    
 
153
collect(Acc) ->
 
154
    receive
 
155
        {Tag,Val} ->
 
156
            Prev = proplists:get_value(Tag,Acc,[]),
 
157
            collect(lists:keystore(Tag,1,Acc,{Tag,[Val|Prev]}))
 
158
    after 100 ->
 
159
            Acc
 
160
    end.
 
161
 
 
162
exec(One,Two,Max,N) ->
 
163
    exec(One,Two,Max,N,{[],[]}).
 
164
exec(_,_,_,1,{D1,D2}) ->
 
165
    {lists:flatten(D1),lists:flatten(D2)};
 
166
exec({PreOne,One} = O,{PreTwo,Two} = T,MaxProcs, N, {D1,D2}) ->
 
167
    Num = random:uniform(round(N/2)),
 
168
    if Num rem 3 == 0 ->
 
169
            timer:sleep(Num rem 1000);
 
170
       true ->
 
171
            ok
 
172
    end,
 
173
    Procs = random:uniform(MaxProcs),
 
174
    io:format("\tBatch: ~p items in ~p processes, ~p left~n",[Num,Procs,N-Num]),
 
175
    if Num rem 2 == 1 ->
 
176
            erlang:garbage_collect(),
 
177
            PreOne(),
 
178
            MoreOne = pexec(One, Num, Procs, []),
 
179
            erlang:garbage_collect(),
 
180
            PreTwo(),
 
181
            MoreTwo = pexec(Two, Num, Procs, []);
 
182
       true ->
 
183
            erlang:garbage_collect(),
 
184
            PreTwo(),
 
185
            MoreTwo = pexec(Two, Num, Procs, []),
 
186
            erlang:garbage_collect(),
 
187
            PreOne(),
 
188
            MoreOne = pexec(One, Num, Procs, [])
 
189
    end,
 
190
    exec(O,T,MaxProcs,N-Num,{[MoreOne|D1],
 
191
                             [MoreTwo|D2]}).
 
192
 
 
193
pexec(_Fun, _, 0, []) ->
 
194
    [];
 
195
pexec(Fun, _, 0, [{Ref,Pid}|Rest]) ->
 
196
    receive
 
197
        {data,D} ->
 
198
            [D|pexec(Fun,0,0,[{Ref,Pid}|Rest])];
 
199
        {'DOWN', Ref, process, Pid, normal} ->
 
200
            pexec(Fun, 0,0,Rest)
 
201
    end;
 
202
pexec(Fun, 0, 1, AccProcs) ->
 
203
    pexec(Fun, 0, 0, AccProcs);
 
204
pexec(Fun, N, 1, AccProcs) ->
 
205
    [Fun()|pexec(Fun, N - 1, 1, AccProcs)];
 
206
pexec(Fun, N, Procs, AccProcs) ->
 
207
    S = self(),
 
208
    Pid = spawn(fun() ->
 
209
                        S ! {data,pexec(Fun,N,1,[])}
 
210
                end),
 
211
    Ref = erlang:monitor(process, Pid),
 
212
    pexec(Fun, N, Procs - 1, [{Ref,Pid}|AccProcs]).
 
213
 
 
214
strip(Data,Num) ->
 
215
    {_,R} = lists:split(Num,lists:sort(Data)),
 
216
    element(2,lists:split(Num,lists:reverse(R))).
 
217
 
 
218
faster(A,B) ->
 
219
    (B - A)/B * 100.
 
220
 
 
221
enc_dec(1, Msg, N) ->
 
222
    worker_loop(N, Msg);
 
223
enc_dec(NumOfProcs,Msg, N) ->
 
224
    pforeach(fun(_) ->
 
225
                     worker_loop(N, Msg)
 
226
             end, [I || I <- lists:seq(1,NumOfProcs)]).
45
227
 
46
228
worker_loop(0, _Msg) ->
47
229
    ok;
50
232
                                     'NBAP-PDU',
51
233
                                     Msg),
52
234
    ?line {ok,_Msg}=asn1_wrapper:decode('NBAP-PDU-Discriptions',
53
 
                                     'NBAP-PDU',
54
 
                                     B),
 
235
                                        'NBAP-PDU',
 
236
                                        B),
55
237
    worker_loop(N - 1, Msg).
56
238
 
57
239
 
58
 
wait_pids([]) -> 
59
 
    ok;
60
 
wait_pids(Pids) ->
 
240
pforeach(Fun, List) ->
 
241
    pforeach(Fun, List, []).
 
242
pforeach(Fun, [], [{Pid,Ref}|Pids]) ->
61
243
    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).
 
244
        {'DOWN', Ref, process, Pid, normal} ->
 
245
            pforeach(Fun, [], Pids)
 
246
    end;
 
247
pforeach(Fun, [H|T], Pids) ->
 
248
    Pid = spawn(fun() -> Fun(H) end),
 
249
    Ref = erlang:monitor(process, Pid),
 
250
    pforeach(Fun, T, [{Pid, Ref}|Pids]);
 
251
pforeach(_Fun,[],[]) ->
 
252
    ok.
75
253
    
76
254
-record('InitiatingMessage',{procedureCode,criticality,value}).
77
255
-record('Iu-ReleaseCommand',{first,second}).
93
271
    ?line {ok,_} = 'RANAPextract1':encode('InitiatingMessage', Val1),
94
272
    asn1rt:unload_driver(),
95
273
    ?line {ok,_} = 'RANAPextract1':encode('InitiatingMessage', Val1).
 
274
 
 
275
cert_pem() ->
 
276
    'OTP-PUB-KEY':decode('Certificate',<<48,130,3,184,48,130,3,33,160,3,2,1,2,2,1,1,48,13,6,9,42,134,72,134,247,13,1,1,5,5,0,48,129,131,49,14,48,12,6,3,85,4,3,19,5,111,116,112,67,65,49,19,48,17,6,3,85,4,11,19,10,69,114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,19,11,69,114,105,99,115,115,111,110,32,65,66,49,11,48,9,6,3,85,4,6,19,2,83,69,49,18,48,16,6,3,85,4,7,19,9,83,116,111,99,107,104,111,108,109,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48,30,23,13,48,56,48,49,48,57,48,56,50,57,51,48,90,23,13,49,55,49,49,49,55,48,56,50,57,51,48,90,48,129,132,49,15,48,13,6,3,85,4,3,19,6,99,108,105,101,110,116,49,19,48,17,6,3,85,4,11,19,10,69,114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,19,11,69,114,105,99,115,115,111,110,32,65,66,49,11,48,9,6,3,85,4,6,19,2,83,69,49,18,48,16,6,3,85,4,7,19,9,83,116,111,99,107,104,111,108,109,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48,129,159,48,13,6,9,42,134,72,134,247,13,1,1,1,5,0,3,129,141,0,48,129,137,2,129,129,0,245,56,68,254,220,239,193,190,63,221,182,60,67,77,121,163,214,136,137,183,139,8,166,30,100,27,45,17,126,58,15,173,151,218,75,224,148,14,22,164,10,100,186,183,104,175,197,97,96,182,146,150,106,129,140,100,194,106,90,62,133,233,155,46,155,33,101,220,83,193,182,232,240,99,253,249,114,8,159,172,143,77,179,132,229,205,29,110,185,233,224,52,25,149,249,100,80,229,199,125,23,106,146,233,159,26,13,8,161,206,221,43,240,149,42,45,194,190,85,6,235,152,220,219,160,32,144,67,2,3,1,0,1,163,130,1,55,48,130,1,51,48,9,6,3,85,29,19,4,2,48,0,48,11,6,3,85,29,15,4,4,3,2,5,224,48,29,6,3,85,29,14,4,22,4,20,26,59,44,5,72,211,158,214,23,34,30,241,125,27,123,115,93,163,231,120,48,129,179,6,3,85,29,35,4,129,171,48,129,168,128,20,6,171,128,52,58,164,184,118,178,189,157,46,40,229,109,145,222,125,1,155,161,129,140,164,129,137,48,129,134,49,17,48,15,6,3,85,4,3,19,8,101,114,108,97,110,103,67,65,49,19,48,17,6,3,85,4,11,19,10,69,114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,19,11,69,114,105,99,115,115,111,110,32,65,66,49,18,48,16,6,3,85,4,7,19,9,83,116,111,99,107,104,111,108,109,49,11,48,9,6,3,85,4,6,19,2,83,69,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,130,1,1,48,33,6,3,85,29,17,4,26,48,24,129,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48,33,6,3,85,29,18,4,26,48,24,129,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48,13,6,9,42,134,72,134,247,13,1,1,5,5,0,3,129,129,0,93,11,112,227,121,15,121,179,247,135,110,216,17,197,84,18,149,166,147,142,190,178,0,209,190,0,142,233,144,100,194,205,220,182,73,204,108,42,95,23,48,63,4,120,239,42,194,25,184,35,117,107,96,229,18,45,76,122,125,40,171,210,132,50,146,178,160,55,17,35,255,208,114,30,47,55,185,154,155,165,204,180,14,143,20,234,6,234,201,225,72,235,5,87,61,255,250,23,217,1,144,246,98,221,223,102,49,168,177,13,70,241,26,27,254,251,217,14,244,18,242,197,151,50,186,214,15,42>>).
 
277
 
 
278
dsa_pem() ->
 
279
    'OTP-PUB-KEY':decode('DSAPrivateKey',<<48,130,1,187,2,1,0,2,129,129,0,183,179,230,217,37,99,144,157,21,228,204,162,207,61,246,144,58,139,139,184,184,43,108,206,0,115,173,208,100,233,201,121,21,90,179,119,53,140,25,52,34,202,121,211,164,107,43,56,68,162,159,51,244,232,138,126,164,109,121,89,237,142,57,28,32,188,44,67,253,111,121,104,40,141,211,255,140,118,37,234,150,201,155,160,16,17,51,59,26,249,41,129,16,211,119,128,95,254,182,235,132,0,92,206,93,77,106,217,201,132,203,4,75,201,246,204,216,162,1,84,79,211,10,21,152,195,103,145,2,21,0,213,30,184,86,247,16,247,69,192,241,35,138,84,57,140,3,71,65,206,233,2,129,129,0,148,179,24,63,74,91,128,25,96,29,5,78,223,246,175,0,121,86,54,178,42,231,98,241,147,180,157,60,149,160,50,243,227,76,175,89,234,203,252,242,76,108,9,204,157,182,59,206,227,127,99,215,42,156,194,78,116,25,7,62,243,169,45,5,101,179,247,127,199,144,135,103,23,42,154,125,231,248,154,101,175,155,101,42,232,41,80,41,47,128,208,11,31,106,63,12,202,207,135,80,200,136,250,171,31,118,52,91,200,138,112,111,179,23,214,123,21,118,194,179,0,185,217,52,197,182,236,13,2,129,128,124,66,0,111,121,139,142,209,95,136,95,237,177,150,248,252,49,135,117,100,155,232,138,244,132,89,40,5,70,125,202,96,78,239,76,37,125,149,82,64,107,54,227,73,25,180,227,41,0,234,73,47,80,242,242,129,250,61,68,62,39,38,156,193,146,40,241,247,106,215,223,202,194,110,130,62,186,90,18,28,196,174,99,47,193,61,130,100,150,25,248,115,164,231,153,99,46,69,66,139,33,187,51,49,35,219,234,29,44,172,166,247,42,16,177,187,9,162,81,243,33,26,100,46,78,57,203,135,2,20,89,128,159,14,187,249,182,172,15,88,162,110,211,71,179,209,29,125,217,38>>),
 
280
    'OTP-PUB-KEY':decode('SubjectPublicKeyInfo',<<48,130,1,183,48,130,1,44,6,7,42,134,72,206,56,4,1,48,130,1,31,2,129,129,0,183,179,230,217,37,99,144,157,21,228,204,162,207,61,246,144,58,139,139,184,184,43,108,206,0,115,173,208,100,233,201,121,21,90,179,119,53,140,25,52,34,202,121,211,164,107,43,56,68,162,159,51,244,232,138,126,164,109,121,89,237,142,57,28,32,188,44,67,253,111,121,104,40,141,211,255,140,118,37,234,150,201,155,160,16,17,51,59,26,249,41,129,16,211,119,128,95,254,182,235,132,0,92,206,93,77,106,217,201,132,203,4,75,201,246,204,216,162,1,84,79,211,10,21,152,195,103,145,2,21,0,213,30,184,86,247,16,247,69,192,241,35,138,84,57,140,3,71,65,206,233,2,129,129,0,148,179,24,63,74,91,128,25,96,29,5,78,223,246,175,0,121,86,54,178,42,231,98,241,147,180,157,60,149,160,50,243,227,76,175,89,234,203,252,242,76,108,9,204,157,182,59,206,227,127,99,215,42,156,194,78,116,25,7,62,243,169,45,5,101,179,247,127,199,144,135,103,23,42,154,125,231,248,154,101,175,155,101,42,232,41,80,41,47,128,208,11,31,106,63,12,202,207,135,80,200,136,250,171,31,118,52,91,200,138,112,111,179,23,214,123,21,118,194,179,0,185,217,52,197,182,236,13,3,129,132,0,2,129,128,124,66,0,111,121,139,142,209,95,136,95,237,177,150,248,252,49,135,117,100,155,232,138,244,132,89,40,5,70,125,202,96,78,239,76,37,125,149,82,64,107,54,227,73,25,180,227,41,0,234,73,47,80,242,242,129,250,61,68,62,39,38,156,193,146,40,241,247,106,215,223,202,194,110,130,62,186,90,18,28,196,174,99,47,193,61,130,100,150,25,248,115,164,231,153,99,46,69,66,139,33,187,51,49,35,219,234,29,44,172,166,247,42,16,177,187,9,162,81,243,33,26,100,46,78,57,203,135>>),
 
281
    'OTP-PUB-KEY':decode('DSAParams',<<48,130,1,31,2,129,129,0,183,179,230,217,37,99,144,157,21,228,204,162,207,61,246,144,58,139,139,184,184,43,108,206,0,115,173,208,100,233,201,121,21,90,179,119,53,140,25,52,34,202,121,211,164,107,43,56,68,162,159,51,244,232,138,126,164,109,121,89,237,142,57,28,32,188,44,67,253,111,121,104,40,141,211,255,140,118,37,234,150,201,155,160,16,17,51,59,26,249,41,129,16,211,119,128,95,254,182,235,132,0,92,206,93,77,106,217,201,132,203,4,75,201,246,204,216,162,1,84,79,211,10,21,152,195,103,145,2,21,0,213,30,184,86,247,16,247,69,192,241,35,138,84,57,140,3,71,65,206,233,2,129,129,0,148,179,24,63,74,91,128,25,96,29,5,78,223,246,175,0,121,86,54,178,42,231,98,241,147,180,157,60,149,160,50,243,227,76,175,89,234,203,252,242,76,108,9,204,157,182,59,206,227,127,99,215,42,156,194,78,116,25,7,62,243,169,45,5,101,179,247,127,199,144,135,103,23,42,154,125,231,248,154,101,175,155,101,42,232,41,80,41,47,128,208,11,31,106,63,12,202,207,135,80,200,136,250,171,31,118,52,91,200,138,112,111,179,23,214,123,21,118,194,179,0,185,217,52,197,182,236,13>>),
 
282
    'OTP-PUB-KEY':decode('DSAPublicKey',<<2,129,128,124,66,0,111,121,139,142,209,95,136,95,237,177,150,248,252,49,135,117,100,155,232,138,244,132,89,40,5,70,125,202,96,78,239,76,37,125,149,82,64,107,54,227,73,25,180,227,41,0,234,73,47,80,242,242,129,250,61,68,62,39,38,156,193,146,40,241,247,106,215,223,202,194,110,130,62,186,90,18,28,196,174,99,47,193,61,130,100,150,25,248,115,164,231,153,99,46,69,66,139,33,187,51,49,35,219,234,29,44,172,166,247,42,16,177,187,9,162,81,243,33,26,100,46,78,57,203,135>>),
 
283
    'OTP-PUB-KEY':encode('DSAParams',{params,{'Dss-Parms',129000451850199666185842362389296595317127259539517666765336291347244303954511451744518587442120964433734460998523119938005801396466878889993179871123036311260456172022864663021425348874648247531097042575063545128239655736096045972718934778583429973433661785691086624069991876932064334822608460064613803976593,1216700114794736143432235288305776850295620488937,104420402274523493329542694749036577763086597934731674202966304958550599470165597750883637440049774107540742087494301536297571301945349213110548764383811017178451900599240379681904765817950545426764751538502808499880604633364255316249231153053427235538288687666086821781456733226598288985591031656134573747213}}),
 
284
    'OTP-PUB-KEY':encode(
 
285
      'SubjectPublicKeyInfo',
 
286
      {'SubjectPublicKeyInfo',
 
287
       {'AlgorithmIdentifier',
 
288
        {1,2,840,10040,4,1},
 
289
        <<48,130,1,31,2,129,129,0,183,179,230,217,37,99,144,157,21,228,204,162,207,61,246,144,58,139,139,184,184,43,108,206,0,115,173,208,100,233,201,121,21,90,179,119,53,140,25,52,34,202,121,211,164,107,43,56,68,162,159,51,244,232,138,126,164,109,121,89,237,142,57,28,32,188,44,67,253,111,121,104,40,141,211,255,140,118,37,234,150,201,155,160,16,17,51,59,26,249,41,129,16,211,119,128,95,254,182,235,132,0,92,206,93,77,106,217,201,132,203,4,75,201,246,204,216,162,1,84,79,211,10,21,152,195,103,145,2,21,0,213,30,184,86,247,16,247,69,192,241,35,138,84,57,140,3,71,65,206,233,2,129,129,0,148,179,24,63,74,91,128,25,96,29,5,78,223,246,175,0,121,86,54,178,42,231,98,241,147,180,157,60,149,160,50,243,227,76,175,89,234,203,252,242,76,108,9,204,157,182,59,206,227,127,99,215,42,156,194,78,116,25,7,62,243,169,45,5,101,179,247,127,199,144,135,103,23,42,154,125,231,248,154,101,175,155,101,42,232,41,80,41,47,128,208,11,31,106,63,12,202,207,135,80,200,136,250,171,31,118,52,91,200,138,112,111,179,23,214,123,21,118,194,179,0,185,217,52,197,182,236,13>>},
 
290
       {0,
 
291
        <<2,129,128,124,66,0,111,121,139,142,209,95,136,95,237,177,150,248,252,49,135,117,100,155,232,138,244,132,89,40,5,70,125,202,96,78,239,76,37,125,149,82,64,107,54,227,73,25,180,227,41,0,234,73,47,80,242,242,129,250,61,68,62,39,38,156,193,146,40,241,247,106,215,223,202,194,110,130,62,186,90,18,28,196,174,99,47,193,61,130,100,150,25,248,115,164,231,153,99,46,69,66,139,33,187,51,49,35,219,234,29,44,172,166,247,42,16,177,187,9,162,81,243,33,26,100,46,78,57,203,135>>}}).