@@ -64,6 +64,10 @@ application.
6464
6565-include_lib (" kernel/include/file.hrl" ).
6666
67+ % % We are not mstone but the (mstone) lib module has general
68+ % % functions that we can use.
69+ -define (LIB , megaco_codec_mstone_lib ).
70+
6771-define (V3 , v3 ).
6872
6973-define (MEASURE_TIMEOUT , 100000 ). % 100 sec
@@ -179,49 +183,7 @@ display_system_info() ->
179183
180184
181185display_app_info () ->
182- display_megaco_info (),
183- display_asn1_info ().
184-
185- % % The instruction, nowarn_function, is because I can't figure out
186- % % how to suppress the warnings about
187- % % megaco_flex_scanner:is_enabled/0 and
188- % % megaco_flex_scanner:is_reentrant_enabled/0:
189- % %
190- % % "The pattern 'false' can never match the type 'true'"
191- % %
192- % % This is because the result of calling these function(s) is
193- % % basically decided at compile time (true or false).
194- -dialyzer ({nowarn_function , display_megaco_info / 0 }).
195- display_megaco_info () ->
196- MI = megaco :module_info (),
197- {value , {attributes , Attr }} = lists :keysearch (attributes , 1 , MI ),
198- {value , {app_vsn , Ver }} = lists :keysearch (app_vsn , 1 , Attr ),
199- FlexStr =
200- case megaco_flex_scanner :is_enabled () of
201- true ->
202- case megaco_flex_scanner :is_reentrant_enabled () of
203- true ->
204- " reentrant flex" ;
205- false ->
206- " non-reentrant flex"
207- end ;
208- false ->
209- " no flex"
210- end ,
211- io :format (" Megaco version: ~s (~s )~n " , [Ver , FlexStr ]).
212-
213- display_asn1_info () ->
214- AI = megaco_ber_media_gateway_control_v1 :info (),
215- Vsn =
216- case lists :keysearch (vsn , 1 , AI ) of
217- {value , {vsn , V }} when is_atom (V ) ->
218- atom_to_list (V );
219- {value , {vsn , V }} when is_list (V ) ->
220- V ;
221- _ ->
222- " unknown"
223- end ,
224- io :format (" ASN.1 version: ~s~n " , [Vsn ]).
186+ ? LIB :display_app_info ().
225187
226188
227189% % {MegaSec, Sec, MicroSec}
@@ -361,8 +323,8 @@ measure(_Factor, _Opts, _Dir, _Codec, _Conf, [], Res, _MCount) ->
361323 io :format (" ~n [~s ] Measurment on ~p messages:"
362324 " ~n Average:"
363325 " ~n Size: ~w bytes, "
364- " ~n Encode: ~w microsec , "
365- " ~n Decode: ~w microsec ~n~n " ,
326+ " ~n Encode: ~w nanosec , "
327+ " ~n Decode: ~w nanosec ~n~n " ,
366328 [? FTS (), length (Res ), Savg , Eavg , Davg ]),
367329
368330 {ok , lists :reverse (Res )};
@@ -485,7 +447,8 @@ do_measure_codec(Factor, Codec, Func, Conf, Version, Bin, MCount) ->
485447 {ok , Count } = measure_warmup (Codec , Func , Conf , Version , Bin , MCount ),
486448 Count2 = Count div Factor ,
487449 Res = timer :tc (? MODULE , do_measure_codec_loop ,
488- [Codec , Func , Conf , Version , Bin , Count2 , dummy ]),
450+ [Codec , Func , Conf , Version , Bin , Count2 , dummy ],
451+ nanosecond ),
489452 case Res of
490453 {Time , {ok , M }} ->
491454 exit ({measure_result , {M , Count2 , Time }});
0 commit comments