Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
0425-megaco-Fixed-various-dialyzer-related-issu...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 0425-megaco-Fixed-various-dialyzer-related-issues.patch of Package erlang
From 53c7de3ad0c8e2143ec2a6abdd4daa45e77ff61b Mon Sep 17 00:00:00 2001 From: Micael Karlberg <bmk@erlang.org> Date: Wed, 13 Jul 2022 16:36:32 +0200 Subject: [PATCH 5/7] [megaco] Fixed various dialyzer related issues OTP-18179 --- lib/megaco/src/app/megaco.erl | 8 +- lib/megaco/src/engine/megaco_config.erl | 28 ++-- lib/megaco/src/engine/megaco_digit_map.erl | 4 +- lib/megaco/src/engine/megaco_messenger.erl | 137 +++++++++--------- lib/megaco/src/engine/megaco_monitor.erl | 6 +- lib/megaco/src/engine/megaco_stats.erl | 4 +- lib/megaco/src/engine/megaco_trans_sender.erl | 8 +- lib/megaco/src/flex/megaco_flex_scanner.erl | 12 +- lib/megaco/src/tcp/megaco_tcp.erl | 18 +-- lib/megaco/src/tcp/megaco_tcp_connection.erl | 12 +- lib/megaco/src/udp/megaco_udp.erl | 18 +-- lib/megaco/src/udp/megaco_udp_server.erl | 6 +- 12 files changed, 132 insertions(+), 129 deletions(-) diff --git a/lib/megaco/src/app/megaco.erl b/lib/megaco/src/app/megaco.erl index de6caaae3b..d0816b1dd0 100644 --- a/lib/megaco/src/app/megaco.erl +++ b/lib/megaco/src/app/megaco.erl @@ -721,10 +721,10 @@ nc() -> nc(Mods). nc(all) -> - application:load(?APPLICATION), + _ = application:load(?APPLICATION), case application:get_key(?APPLICATION, modules) of {ok, Mods} -> - application:unload(?APPLICATION), + _ = application:unload(?APPLICATION), nc(Mods); _ -> {error, not_found} @@ -741,10 +741,10 @@ ni() -> end. ni(all) -> - application:load(?APPLICATION), + _ = application:load(?APPLICATION), case application:get_key(?APPLICATION, modules) of {ok, Mods} -> - application:unload(?APPLICATION), + _ = application:unload(?APPLICATION), ni(Mods); _ -> {error, not_found} diff --git a/lib/megaco/src/engine/megaco_config.erl b/lib/megaco/src/engine/megaco_config.erl index 0805acab9b..1b019fd535 100644 --- a/lib/megaco/src/engine/megaco_config.erl +++ b/lib/megaco/src/engine/megaco_config.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2000-2021. All Rights Reserved. +%% Copyright Ericsson AB 2000-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -899,9 +899,9 @@ init([Parent]) -> do_init() -> ?megaco_test_init(), - ets:new(megaco_config, [public, named_table, {keypos, 1}]), - ets:new(megaco_local_conn, [public, named_table, {keypos, 2}]), - ets:new(megaco_remote_conn, [public, named_table, {keypos, 2}, bag]), + _ = ets:new(megaco_config, [public, named_table, {keypos, 1}]), + _ = ets:new(megaco_local_conn, [public, named_table, {keypos, 2}]), + _ = ets:new(megaco_remote_conn, [public, named_table, {keypos, 2}, bag]), megaco_stats:init(megaco_stats, global_snmp_counters()), init_scanner(), init_user_defaults(), @@ -1467,7 +1467,7 @@ handle_start_user(Mid, Config) -> case catch user_info(Mid, mid) of {'EXIT', _} -> DefaultConfig = user_info(default, all), - do_handle_start_user(Mid, DefaultConfig), + _ = do_handle_start_user(Mid, DefaultConfig), do_handle_start_user(Mid, Config); _LocalMid -> {error, {user_already_exists, Mid}} @@ -1482,7 +1482,7 @@ do_handle_start_user(UserMid, [{Item, Val} | Rest]) -> {error, Reason} end; do_handle_start_user(UserMid, []) -> - do_update_user(UserMid, mid, UserMid), + _ = do_update_user(UserMid, mid, UserMid), ok; do_handle_start_user(UserMid, BadConfig) -> ets:match_delete(megaco_config, {{UserMid, '_'}, '_'}), @@ -1715,7 +1715,7 @@ update_auto_ack(#conn_data{trans_timer = To, %% sender goes down. %% Do we need to store the ref? Will we ever need to %% cancel this (apply_at_exit)? - megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), + _ = megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), CD#conn_data{auto_ack = true, trans_sender = Pid}; @@ -1746,7 +1746,7 @@ update_trans_ack(#conn_data{trans_timer = To, %% sender goes down. %% Do we need to store the ref? Will we ever need to %% cancel this (apply_at_exit)? - megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), + _ = megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), CD#conn_data{trans_ack = true, trans_sender = Pid}; @@ -1775,7 +1775,7 @@ update_trans_req(#conn_data{trans_timer = To, %% sender goes down. %% Do we need to store the ref? Will we ever need to %% cancel this (apply_at_exit)? - megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), + _ = megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), CD#conn_data{trans_req = true, trans_sender = Pid}; @@ -1799,7 +1799,7 @@ update_trans_timer(#conn_data{auto_ack = true, %% sender goes down. %% Do we need to store the ref? Will we ever need to %% cancel this (apply_at_exit)? - megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), + _ = megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), CD#conn_data{trans_timer = To, trans_sender = Pid}; @@ -1817,7 +1817,7 @@ update_trans_timer(#conn_data{trans_req = true, %% sender goes down. %% Do we need to store the ref? Will we ever need to %% cancel this (apply_at_exit)? - megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), + _ = megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), CD#conn_data{trans_timer = To, trans_sender = Pid}; @@ -1968,7 +1968,7 @@ trans_sender_start(#conn_data{conn_handle = CH, %% sender goes down. %% Do we need to store the ref? Will we ever need to %% cancel this (apply_at_exit)? - megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), + _ = megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), CD#conn_data{trans_sender = Pid}; @@ -1997,7 +1997,7 @@ trans_sender_start(#conn_data{conn_handle = CH, %% sender goes down. %% Do we need to store the ref? Will we ever need to %% cancel this (apply_at_exit)? - megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), + _ = megaco_monitor:apply_at_exit(?MODULE, trans_sender_exit, [CH], Pid), CD#conn_data{trans_sender = Pid}; @@ -2150,7 +2150,7 @@ update_snmp_counters(CH, PrelCH, [Counter|Counters]) -> PrelKey = {PrelCH, Counter}, Key = {CH, Counter}, [{PrelKey,PrelVal}] = ets:lookup(megaco_stats, PrelKey), - ets:update_counter(megaco_stats, Key, PrelVal), + _ = ets:update_counter(megaco_stats, Key, PrelVal), ets:delete(megaco_stats, PrelKey), update_snmp_counters(CH, PrelCH, Counters). diff --git a/lib/megaco/src/engine/megaco_digit_map.erl b/lib/megaco/src/engine/megaco_digit_map.erl index 5b8b1f3b8f..820cb2179e 100644 --- a/lib/megaco/src/engine/megaco_digit_map.erl +++ b/lib/megaco/src/engine/megaco_digit_map.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2000-2016. All Rights Reserved. +%% Copyright Ericsson AB 2000-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -842,7 +842,7 @@ cast(Pid, Event) -> test(DigitMap, Events) -> Self = self(), Pid = spawn_link(?MODULE, test_eval, [DigitMap, Self]), - report(Pid, Events), + _ = report(Pid, Events), receive {Self, Pid, Res} -> Res; diff --git a/lib/megaco/src/engine/megaco_messenger.erl b/lib/megaco/src/engine/megaco_messenger.erl index 2a9ecee2a7..dfb10dc869 100644 --- a/lib/megaco/src/engine/megaco_messenger.erl +++ b/lib/megaco/src/engine/megaco_messenger.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1999-2019. All Rights Reserved. +%% Copyright Ericsson AB 1999-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -545,7 +545,7 @@ disconnect(ConnHandle, DiscoReason) case megaco_config:disconnect(ConnHandle) of {ok, ConnData, RemoteConnData} -> ControlRef = ConnData#conn_data.monitor_ref, - cancel_apply_at_exit(ControlRef), + _ = cancel_apply_at_exit(ControlRef), handle_disconnect_callback(ConnData, DiscoReason), ControlNode = node_of_control_pid(ConnData#conn_data.control_pid), case ControlNode =:= node() of @@ -554,7 +554,7 @@ disconnect(ConnHandle, DiscoReason) CancelFun = fun(RCD) -> UserRef = RCD#remote_conn_data.monitor_ref, - cancel_apply_at_exit(UserRef), + _ = cancel_apply_at_exit(UserRef), RCD#remote_conn_data.user_node end, Nodes = lists:map(CancelFun, RemoteConnData), @@ -602,7 +602,7 @@ disconnect_remote(_Reason, ConnHandle, UserNode) -> case megaco_config:disconnect_remote(ConnHandle, UserNode) of [RCD] -> Ref = RCD#remote_conn_data.monitor_ref, - cancel_apply_at_exit(Ref), + _ = cancel_apply_at_exit(Ref), ok; [] -> {error, {no_connection, ConnHandle}} @@ -619,9 +619,10 @@ receive_message(ReceiveHandle, ControlPid, SendHandle, Bin) -> receive_message(ReceiveHandle, ControlPid, SendHandle, Bin, Extra) -> Opts = [link , {min_heap_size, 5000}], - spawn_opt(?MODULE, - process_received_message, - [ReceiveHandle, ControlPid, SendHandle, Bin, self(), Extra], Opts), + _ = spawn_opt(?MODULE, + process_received_message, + [ReceiveHandle, + ControlPid, SendHandle, Bin, self(), Extra], Opts), ok. %% This function is called via the spawn_opt function with the link @@ -1131,20 +1132,20 @@ prepare_autoconnecting_trans(ConnData, [Trans | Rest], AckList, ReqList, Extra) Limit = ConnData#conn_data.sent_pending_limit, TransId = to_remote_trans_id(ConnData2), - case check_and_maybe_incr_pending_limit(Limit, sent, TransId) of - ok -> - send_pending(ConnData2); - error -> - %% Pending limit: - %% In this (granted, highly hypothetical case) - %% we would make the user very confused if we - %% called the abort callback function, since - %% the request callback function has not yet - %% been called. Alas, we skip this call here. - send_pending_limit_error(ConnData); - aborted -> - ignore - end, + _ = case check_and_maybe_incr_pending_limit(Limit, sent, TransId) of + ok -> + send_pending(ConnData2); + error -> + %% Pending limit: + %% In this (granted, highly hypothetical case) + %% we would make the user very confused if we + %% called the abort callback function, since + %% the request callback function has not yet + %% been called. Alas, we skip this call here. + send_pending_limit_error(ConnData); + aborted -> + ignore + end, prepare_autoconnecting_trans(ConnData2, Rest, AckList, ReqList, Extra); _ -> @@ -1251,8 +1252,8 @@ prepare_request(ConnData, T, Rest, AckList, ReqList, Extra) -> ?report_debug(ConnData, "prepare request: conflicting requests", [TransId]), - send_pending(ConnData), - megaco_monitor:cancel_apply_after(PendingRef), + _ = send_pending(ConnData), + _ = megaco_monitor:cancel_apply_after(PendingRef), prepare_normal_trans(ConnData, Rest, AckList, ReqList, Extra) end; @@ -1294,7 +1295,7 @@ prepare_request(ConnData, T, Rest, AckList, ReqList, Extra) -> %% %% ------------------------------------------ - send_pending(ConnData), + _ = send_pending(ConnData), prepare_normal_trans(ConnData, Rest, AckList, ReqList, Extra); @@ -1330,8 +1331,8 @@ prepare_request(ConnData, T, Rest, AckList, ReqList, Extra) -> %% State == prepare: %% The user does not know about this request %% so we can safely perform cleanup. - %% - megaco_monitor:cancel_apply_after(Ref), + %% + _ = megaco_monitor:cancel_apply_after(Ref), send_pending_limit_error(ConnData), if State == eval_request -> @@ -1682,7 +1683,7 @@ do_handle_request(AckAction, {ok, Bin}, ConnData, TransId) %% - Delete the pending counter %% - megaco_monitor:cancel_apply_after(PendingRef), + _ = megaco_monitor:cancel_apply_after(PendingRef), megaco_config:del_pending_counter(sent, TransId), Method = timer_method(AckAction), @@ -1725,7 +1726,7 @@ do_handle_request(AckAction, {ok, {Sent, NotSent}}, ConnData, TransId) %% - Delete the pending counter %% - megaco_monitor:cancel_apply_after(PendingRef), + _ = megaco_monitor:cancel_apply_after(PendingRef), megaco_config:del_pending_counter(sent, TransId), Method = timer_method(AckAction), @@ -2178,7 +2179,7 @@ handle_recv_pending(#conn_data{long_request_resend = LRR, %% We can now drop the "bytes", since we will %% not resend from now on. - megaco_monitor:cancel_apply_after(Ref), + _ = megaco_monitor:cancel_apply_after(Ref), {WaitFor, CurrTimer} = megaco_timer:init(InitTimer), ConnHandle = ConnData#conn_data.conn_handle, M = ?MODULE, @@ -2234,7 +2235,7 @@ handle_recv_pending(#conn_data{conn_handle = ConnHandle} = ConnData, TransId, %% We just need to recalculate the timer, i.e. %% increment the timer (one "slot" has been consumed). - megaco_monitor:cancel_apply_after(Ref), + _ = megaco_monitor:cancel_apply_after(Ref), {WaitFor, Timer2} = megaco_timer:restart(CurrTimer), ConnHandle = ConnData#conn_data.conn_handle, M = ?MODULE, @@ -2256,12 +2257,12 @@ handle_recv_pending_error(ConnData, TransId, Req, T, Extra) -> megaco_monitor:delete_request(TransId), %% 2) Possibly cancel the timer - case Req#request.timer_ref of - {_, Ref} -> - megaco_monitor:cancel_apply_after(Ref); - _ -> - ok - end, + _ = case Req#request.timer_ref of + {_, Ref} -> + megaco_monitor:cancel_apply_after(Ref); + _ -> + ok + end, %% 3) Delete the (receive) pending counter megaco_config:del_pending_counter(recv, TransId), @@ -2310,10 +2311,10 @@ handle_reply( [T]), %% Stop the request timer - megaco_monitor:cancel_apply_after(Ref), %% OTP-4843 + _ = megaco_monitor:cancel_apply_after(Ref), %% OTP-4843 %% Acknowledge the segment - send_segment_reply(ConnData, SN), + _ = send_segment_reply(ConnData, SN), %% First segment for this reply NewFields = @@ -2353,7 +2354,7 @@ handle_reply( [T]), %% Acknowledge the segment - send_segment_reply(ConnData, SN), + _ = send_segment_reply(ConnData, SN), %% Updated/handle received segment case lists:member(SN, Segs) of @@ -2400,7 +2401,7 @@ handle_reply( [T]), %% Acknowledge the segment - send_segment_reply(ConnData, SN), + _ = send_segment_reply(ConnData, SN), %% Updated received segments case lists:member(SN, Segs) of @@ -2413,9 +2414,9 @@ handle_reply( Last = case is_all_segments([SN | Segs]) of {true, _Sorted} -> - megaco_monitor:cancel_apply_after(SegRef), + _ = megaco_monitor:cancel_apply_after(SegRef), megaco_monitor:delete_request(TransId), - send_ack(ConnData), + _ = send_ack(ConnData), true; {false, Sorted} -> megaco_monitor:update_request_field(TransId, @@ -2477,10 +2478,10 @@ handle_reply( "first/complete seg", [T]), %% Stop the request timer - megaco_monitor:cancel_apply_after(Ref), %% OTP-4843 + _ = megaco_monitor:cancel_apply_after(Ref), %% OTP-4843 %% Acknowledge the ("last") segment - send_segment_reply_complete(ConnData, SN), + _ = send_segment_reply_complete(ConnData, SN), %% It is ofcourse pointless to split %% a transaction into just one segment, @@ -2508,7 +2509,7 @@ handle_reply( true -> %% Just one segment! megaco_monitor:delete_request(TransId), - send_ack(ConnData), + _ = send_ack(ConnData), true end, @@ -2537,7 +2538,7 @@ handle_reply( [T]), %% Acknowledge the ("last") segment - send_segment_reply_complete(ConnData, SN), + _ = send_segment_reply_complete(ConnData, SN), %% Updated received segments %% This is _probably_ the last segment, but some of @@ -2555,7 +2556,7 @@ handle_reply( "[segmented] trans reply - " "complete set", [T]), megaco_monitor:delete_request(TransId), - send_ack(ConnData), + _ = send_ack(ConnData), true; {false, Sorted} -> ConnHandle = ConnData#conn_data.conn_handle, @@ -2736,11 +2737,11 @@ do_handle_reply(CD, %% This is the first reply (maybe of many) megaco_monitor:delete_request(TransId), megaco_monitor:request_lockcnt_del(TransId), - megaco_monitor:cancel_apply_after(Ref), % OTP-4843 + _ = megaco_monitor:cancel_apply_after(Ref), % OTP-4843 megaco_config:del_pending_counter(recv, TransId), % OTP-7189 %% Send acknowledgement - maybe_send_ack(T#megaco_transaction_reply.immAckRequired, CD), + _ = maybe_send_ack(T#megaco_transaction_reply.immAckRequired, CD), UserReply = case T#megaco_transaction_reply.transactionResult of @@ -2778,7 +2779,7 @@ do_handle_reply(CD, %% This *is* the first reply!! %% 1) Stop resend timer {_Type, Ref} = Req#request.timer_ref, % OTP-4843 - megaco_monitor:cancel_apply_after(Ref), % OTP-4843 + _ = megaco_monitor:cancel_apply_after(Ref), % OTP-4843 %% 2) Delete pending counter megaco_config:del_pending_counter(recv, TransId), % OTP-7189 @@ -2793,7 +2794,7 @@ do_handle_reply(CD, RKAWaitFor), %% 4) Maybe send acknowledgement (three-way-handshake) - maybe_send_ack(T#megaco_transaction_reply.immAckRequired, CD), + _ = maybe_send_ack(T#megaco_transaction_reply.immAckRequired, CD), %% 5) And finally store the updated request record Req2 = Req#request{keep_alive_ref = RKARef}, @@ -2869,11 +2870,11 @@ handle_segment_reply(CD, handle_segment_reply_callback(CD, TransId, SN, SC, Extra), case lists:keysearch(SN, 1, Sent) of {value, {SN, _Bin, SegTmr}} -> - megaco_monitor:cancel_apply_after(SegTmr), %% BMK BMK + _ = megaco_monitor:cancel_apply_after(SegTmr), %% BMK BMK case lists:keydelete(SN, 1, Sent) of [] -> %% We are done Ref = Rep#reply.timer_ref, - megaco_monitor:cancel_apply_after(Ref), + _ = megaco_monitor:cancel_apply_after(Ref), megaco_monitor:update_reply_field(TransId2, #reply.bytes, []), @@ -2896,7 +2897,7 @@ handle_segment_reply(CD, handle_segment_reply_callback(CD, TransId, SN, SC, Extra), case lists:keysearch(SN, 1, Sent) of {value, {SN, _Bin, SegTmr}} -> - megaco_monitor:cancel_apply_after(SegTmr), %% BMK BMK + _ = megaco_monitor:cancel_apply_after(SegTmr), %% BMK BMK NewSent = lists:keydelete(SN, 1, Sent), [{SN2, Bin2}|NewNotSent] = NotSent, case send_reply_segment(CD, "send trans reply segment", @@ -3026,14 +3027,14 @@ handle_ack(ConnData, OrigAckStatus, handle_ack_callback(ConnData, AckStatus, AckAction, T, Extra). handle_ack_cleanup(TransId, ReplyRef, PendingRef) -> - megaco_monitor:cancel_apply_after(ReplyRef), - megaco_monitor:cancel_apply_after(PendingRef), + _ = megaco_monitor:cancel_apply_after(ReplyRef), + _ = megaco_monitor:cancel_apply_after(PendingRef), megaco_monitor:delete_reply(TransId), megaco_config:del_pending_counter(sent, TransId). %% BMK: Still existing? cancel_segment_timers(SegSent) when is_list(SegSent) -> Cancel = fun({_, _, Ref}) -> - megaco_monitor:cancel_apply_after(Ref) + megaco_monitor:cancel_apply_after(Ref) end, lists:foreach(Cancel, SegSent); cancel_segment_timers(_) -> @@ -4033,7 +4034,7 @@ send_reply(#conn_data{serial = Serial, {ok, Bin} when is_binary(Bin) andalso (TransReq =:= true) -> ?rt2("send_reply - pass it on to the transaction sender", [size(Bin)]), - megaco_trans_sender:send_reply(TransSnd, Bin), + _ = megaco_trans_sender:send_reply(TransSnd, Bin), {ok, Bin}; {ok, Bin} when is_binary(Bin) -> @@ -4070,7 +4071,7 @@ send_reply(#conn_data{serial = Serial, error_msg("failed encoding transaction reply body: ~s", [format_encode_error_reason(Reason)]), Body = {transactions, [{transactionReply, TR3}]}, - megaco_messenger_misc:send_body(CD, TraceLabel, Body), + _ = megaco_messenger_misc:send_body(CD, TraceLabel, Body), Error end. @@ -4457,7 +4458,7 @@ do_receive_reply_remote(ConnData, TransId, UserReply, Extra) -> megaco_monitor:delete_request(TransId), megaco_monitor:request_lockcnt_del(TransId), - megaco_monitor:cancel_apply_after(Ref), % OTP-4843 + _ = megaco_monitor:cancel_apply_after(Ref), % OTP-4843 megaco_config:del_pending_counter(recv, TransId), % OTP-7189 ConnData2 = ConnData#conn_data{user_mod = UserMod, @@ -4471,7 +4472,7 @@ cancel_reply(ConnData, #reply{state = waiting_for_ack, user_mod = UserMod, user_args = UserArgs} = Rep, Reason) -> ?report_trace(ignore, "cancel reply [waiting_for_ack]", [Rep]), - megaco_monitor:cancel_apply_after(Rep#reply.pending_timer_ref), + _ = megaco_monitor:cancel_apply_after(Rep#reply.pending_timer_ref), Serial = (Rep#reply.trans_id)#trans_id.serial, ConnData2 = ConnData#conn_data{serial = Serial, user_mod = UserMod, @@ -4486,8 +4487,8 @@ cancel_reply(_ConnData, #reply{state = aborted} = Rep, _Reason) -> timer_ref = ReplyRef, pending_timer_ref = PendingRef} = Rep, megaco_monitor:delete_reply(TransId), - megaco_monitor:cancel_apply_after(ReplyRef), - megaco_monitor:cancel_apply_after(PendingRef), % Still running? + _ = megaco_monitor:cancel_apply_after(ReplyRef), + _ = megaco_monitor:cancel_apply_after(PendingRef), % Still running? megaco_config:del_pending_counter(sent, TransId), % Still existing? ok; @@ -4497,8 +4498,8 @@ cancel_reply(_ConnData, Rep, ignore) -> timer_ref = ReplyRef, pending_timer_ref = PendingRef} = Rep, megaco_monitor:delete_reply(TransId), - megaco_monitor:cancel_apply_after(ReplyRef), - megaco_monitor:cancel_apply_after(PendingRef), % Still running? + _ = megaco_monitor:cancel_apply_after(ReplyRef), + _ = megaco_monitor:cancel_apply_after(PendingRef), % Still running? megaco_config:del_pending_counter(sent, TransId), % Still existing? ok; @@ -4508,7 +4509,7 @@ cancel_reply(_CD, _Rep, _Reason) -> request_keep_alive_timeout(ConnHandle, TransId) -> megaco_config:del_pending_counter(ConnHandle, TransId), - megaco_monitor:lookup_request(TransId), + _ = megaco_monitor:lookup_request(TransId), ok. @@ -4853,7 +4854,7 @@ handle_reply_timer_timeout(ConnHandle, TransId) -> {_Converted, #reply{pending_timer_ref = Ref, % aborted? bytes = SegSent}} -> % may be a binary - megaco_monitor:cancel_apply_after(Ref), + _ = megaco_monitor:cancel_apply_after(Ref), cancel_segment_timers(SegSent), megaco_monitor:delete_reply(TransId), megaco_config:del_pending_counter(sent, TransId); @@ -4979,7 +4980,7 @@ handle_pending_timeout(CD, TransId, Timer) -> %% %% --------------------------------------------- - send_pending(CD), + _ = send_pending(CD), case Timer of timeout -> %% We are done diff --git a/lib/megaco/src/engine/megaco_monitor.erl b/lib/megaco/src/engine/megaco_monitor.erl index efda4d3716..34bd3a6706 100644 --- a/lib/megaco/src/engine/megaco_monitor.erl +++ b/lib/megaco/src/engine/megaco_monitor.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2000-2020. All Rights Reserved. +%% Copyright Ericsson AB 2000-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -232,8 +232,8 @@ cast(Msg) -> init([Parent]) -> ?d("init -> entry", []), process_flag(trap_exit, true), - ets:new(megaco_requests, [public, named_table, {keypos, 2}]), - ets:new(megaco_replies, [public, named_table, {keypos, 2}]), + _ = ets:new(megaco_requests, [public, named_table, {keypos, 2}]), + _ = ets:new(megaco_replies, [public, named_table, {keypos, 2}]), ?d("init -> done", []), {ok, #state{parent_pid = Parent}}. diff --git a/lib/megaco/src/engine/megaco_stats.erl b/lib/megaco/src/engine/megaco_stats.erl index 1ca9faedb4..bf9d790074 100644 --- a/lib/megaco/src/engine/megaco_stats.erl +++ b/lib/megaco/src/engine/megaco_stats.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2002-2016. All Rights Reserved. +%% Copyright Ericsson AB 2002-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -48,7 +48,7 @@ init(Name) -> init(Name, []). init(Name, GlobalCounters) -> - ets:new(Name, [public, named_table, {keypos, 1}]), + _ = ets:new(Name, [public, named_table, {keypos, 1}]), ets:insert(Name, {global_counters, GlobalCounters}), create_global_snmp_counters(Name, GlobalCounters). diff --git a/lib/megaco/src/engine/megaco_trans_sender.erl b/lib/megaco/src/engine/megaco_trans_sender.erl index 871a074171..4bb96e1cf4 100644 --- a/lib/megaco/src/engine/megaco_trans_sender.erl +++ b/lib/megaco/src/engine/megaco_trans_sender.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2003-2016. All Rights Reserved. +%% Copyright Ericsson AB 2003-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -162,12 +162,12 @@ loop(#state{reqs = [], acks = [], timeout = Timeout} = S, _) -> {send_ack_now, Serial} -> ?d("loop(empty) -> received send_ack_now [~w] request", [Serial]), - send_msg(S#state.conn_handle, [], [Serial]), + _ = send_msg(S#state.conn_handle, [], [Serial]), loop(S, Timeout); {send_req, Tid, Req} when size(Req) >= S#state.req_maxsize -> ?d("loop(empty) -> received (big) send_req request ~w", [Tid]), - send_msg(S#state.conn_handle, [{Tid, Req}], []), + _ = send_msg(S#state.conn_handle, [{Tid, Req}], []), loop(S, Timeout); {send_req, Tid, Req} -> @@ -691,7 +691,7 @@ system_continue(_Parent, _Dbg, {S,To}) -> system_terminate(Reason, _Parent, _Dbg, {S, _}) -> #state{conn_handle = CH, reqs = Reqs, acks = Acks} = S, - send_msg(CH, Reqs, Acks), + _ = send_msg(CH, Reqs, Acks), exit(Reason). system_code_change(S, _Module, _OLdVsn, _Extra) -> diff --git a/lib/megaco/src/flex/megaco_flex_scanner.erl b/lib/megaco/src/flex/megaco_flex_scanner.erl index 174d430fb2..74f63b6ee3 100644 --- a/lib/megaco/src/flex/megaco_flex_scanner.erl +++ b/lib/megaco/src/flex/megaco_flex_scanner.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2001-2020. All Rights Reserved. +%% Copyright Ericsson AB 2001-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -32,10 +32,12 @@ -define(SMP_SUPPORT_DEFAULT(), erlang:system_info(smp_support)). -dialyzer({nowarn_function, is_enabled/0}). +-spec is_enabled() -> boolean(). is_enabled() -> (true =:= ?ENABLE_MEGACO_FLEX_SCANNER). -dialyzer({nowarn_function, is_reentrant_enabled/0}). +-spec is_reentrant_enabled() -> boolean(). is_reentrant_enabled() -> (true =:= ?MEGACO_REENTRANT_FLEX_SCANNER). @@ -72,7 +74,7 @@ start(SMP) when ((SMP =:= true) orelse (SMP =:= false)) -> do_start(SMP) -> Path = lib_dir(), - erl_ddll:start(), + _ = erl_ddll:start(), load_driver(Path), PortOrPorts = open_drv_port(SMP), {ok, PortOrPorts}. @@ -117,7 +119,7 @@ open_drv_port() -> Port when is_port(Port) -> Port; {'EXIT', Reason} -> - erl_ddll:unload_driver(drv_name()), + _ = erl_ddll:unload_driver(drv_name()), throw({error, {open_port, Reason}}) end. @@ -136,13 +138,13 @@ drv_name() -> stop(Port) when is_port(Port) -> erlang:port_close(Port), - erl_ddll:unload_driver(drv_name()), + _ = erl_ddll:unload_driver(drv_name()), stopped; stop(Ports) when is_tuple(Ports) -> stop(tuple_to_list(Ports)); stop(Ports) when is_list(Ports) -> lists:foreach(fun(Port) -> erlang:port_close(Port) end, Ports), - erl_ddll:unload_driver(drv_name()), + _ = erl_ddll:unload_driver(drv_name()), stopped. diff --git a/lib/megaco/src/tcp/megaco_tcp.erl b/lib/megaco/src/tcp/megaco_tcp.erl index 6ff8e5793f..7fa7c24375 100644 --- a/lib/megaco/src/tcp/megaco_tcp.erl +++ b/lib/megaco/src/tcp/megaco_tcp.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1999-2021. All Rights Reserved. +%% Copyright Ericsson AB 1999-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -205,7 +205,7 @@ connect(SupPid, Parameters) -> {ok, Pid} -> ?d1("connect -> connection started: " "~n Pid: ~p", [Pid]), - gen_tcp:controlling_process(Socket, Pid), + _ = gen_tcp:controlling_process(Socket, Pid), ?d2("connect -> control transferred"), {ok, Socket, Pid}; {error, Reason} -> @@ -249,13 +249,13 @@ send_message(Socket, Data) -> "~n size(Data): ~p", [Socket, sz(Data)]), {Size, NewData} = add_tpkt_header(Data), Res = gen_tcp:send(Socket, NewData), - case Res of - ok -> - incNumOutMessages(Socket), - incNumOutOctets(Socket, Size); - _ -> - ok - end, + _ = case Res of + ok -> + incNumOutMessages(Socket), + incNumOutOctets(Socket, Size); + _ -> + ok + end, Res. -ifdef(megaco_debug). diff --git a/lib/megaco/src/tcp/megaco_tcp_connection.erl b/lib/megaco/src/tcp/megaco_tcp_connection.erl index 136bfda2e5..0e5ea69066 100644 --- a/lib/megaco/src/tcp/megaco_tcp_connection.erl +++ b/lib/megaco/src/tcp/megaco_tcp_connection.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1999-2016. All Rights Reserved. +%% Copyright Ericsson AB 1999-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -146,7 +146,7 @@ handle_info({tcp, Socket, <<3:8, _X:8, Length:16, Msg/binary>>}, incNumInMessages(Socket), incNumInOctets(Socket, 4+size(Msg)), apply(Mod, receive_message, [RH, self(), Socket, Msg]), - inet:setopts(Socket, [{active, once}]), + _ = inet:setopts(Socket, [{active, once}]), {noreply, TcpRec}; handle_info({tcp, Socket, <<3:8, _X:8, Length:16, Msg/binary>>}, #megaco_tcp{socket = Socket, serialize = false} = TcpRec) -> @@ -154,7 +154,7 @@ handle_info({tcp, Socket, <<3:8, _X:8, Length:16, Msg/binary>>}, incNumInMessages(Socket), incNumInOctets(Socket, 4+size(Msg)), receive_message(Mod, RH, Socket, Length, Msg), - inet:setopts(Socket, [{active, once}]), + _ = inet:setopts(Socket, [{active, once}]), {noreply, TcpRec}; handle_info({tcp, Socket, <<3:8, _X:8, _Length:16, Msg/binary>>}, #megaco_tcp{socket = Socket, serialize = true} = TcpRec) -> @@ -162,7 +162,7 @@ handle_info({tcp, Socket, <<3:8, _X:8, _Length:16, Msg/binary>>}, incNumInMessages(Socket), incNumInOctets(Socket, 4+size(Msg)), process_received_message(Mod, RH, Socket, Msg), - inet:setopts(Socket, [{active, once}]), + _ = inet:setopts(Socket, [{active, once}]), {noreply, TcpRec}; handle_info({tcp, Socket, Msg}, TcpRec) -> incNumErrors(Socket), @@ -188,8 +188,8 @@ process_received_message(Mod, RH, SH, Msg) -> receive_message(Mod, RH, SendHandle, Length, Msg) -> Opts = [link , {min_heap_size, ?HEAP_SIZE(Length)}], - spawn_opt(?MODULE, handle_received_message, - [Mod, RH, self(), SendHandle, Msg], Opts), + _ = spawn_opt(?MODULE, handle_received_message, + [Mod, RH, self(), SendHandle, Msg], Opts), ok. diff --git a/lib/megaco/src/udp/megaco_udp.erl b/lib/megaco/src/udp/megaco_udp.erl index 099f4b7455..02ac6554a0 100644 --- a/lib/megaco/src/udp/megaco_udp.erl +++ b/lib/megaco/src/udp/megaco_udp.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1999-2021. All Rights Reserved. +%% Copyright Ericsson AB 1999-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -129,7 +129,7 @@ open(SupPid, Options) -> NewUdpRec = UdpRec#megaco_udp{socket = Socket}, case start_udp_server(SupPid, NewUdpRec) of {ok, ControlPid} -> - gen_udp:controlling_process(Socket, ControlPid), + _ = gen_udp:controlling_process(Socket, ControlPid), {ok, Socket, ControlPid}; {error, Reason} -> Error = {error, {could_not_start_udp_server, Reason}}, @@ -220,13 +220,13 @@ create_snmp_counters(SH, [Counter|Counters]) -> send_message(SH, Data) when is_record(SH, send_handle) -> #send_handle{socket = Socket, addr = Addr, port = Port} = SH, Res = gen_udp:send(Socket, Addr, Port, Data), - case Res of - ok -> - incNumOutMessages(SH), - incNumOutOctets(SH, size(Data)); - _ -> - ok - end, + _ = case Res of + ok -> + incNumOutMessages(SH), + incNumOutOctets(SH, size(Data)); + _ -> + ok + end, Res; send_message(SH, _Data) -> {error, {bad_send_handle, SH}}. diff --git a/lib/megaco/src/udp/megaco_udp_server.erl b/lib/megaco/src/udp/megaco_udp_server.erl index 5abb4165ae..60914083a0 100644 --- a/lib/megaco/src/udp/megaco_udp_server.erl +++ b/lib/megaco/src/udp/megaco_udp_server.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1999-2021. All Rights Reserved. +%% Copyright Ericsson AB 1999-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -162,7 +162,7 @@ handle_info({udp, _Socket, Ip, Port, Msg}, Sz -> receive_message(Mod, RH, SH, Sz, Msg) end, - activate(Socket), + _ = activate(Socket), {noreply, UdpRec}; handle_info({udp, _Socket, Ip, Port, Msg}, #megaco_udp{serialize = true} = UdpRec) -> @@ -172,7 +172,7 @@ handle_info({udp, _Socket, Ip, Port, Msg}, incNumInMessages(SH), incNumInOctets(SH, MsgSize), process_received_message(Mod, RH, SH, Msg), - activate(Socket), + _ = activate(Socket), {noreply, UdpRec}; handle_info(Info, UdpRec) -> warning_msg("received unexpected info: " -- 2.35.3
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor