Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
3521-Quote-all-occurrences-of-the-maybe-atom.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 3521-Quote-all-occurrences-of-the-maybe-atom.patch of Package erlang
From 8ba0863a1409d4e51209c6c4671702fe4ff23c30 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org> Date: Mon, 14 Feb 2022 11:46:28 +0100 Subject: [PATCH] Quote all occurrences of the `maybe` atom `maybe` will (most likely) become a keyword in a future release. --- lib/compiler/src/beam_call_types.erl | 16 +++++++------- lib/compiler/src/beam_ssa_dead.erl | 26 +++++++++++------------ lib/compiler/src/beam_ssa_pre_codegen.erl | 4 ++-- lib/compiler/src/beam_ssa_type.erl | 20 ++++++++--------- lib/compiler/src/beam_validator.erl | 12 +++++------ lib/compiler/src/sys_core_fold.erl | 8 +++---- 6 files changed, 43 insertions(+), 43 deletions(-) diff --git a/lib/compiler/src/beam_call_types.erl b/lib/compiler/src/beam_call_types.erl index 0926f60195..fbed43b43f 100644 --- a/lib/compiler/src/beam_call_types.erl +++ b/lib/compiler/src/beam_call_types.erl @@ -38,7 +38,7 @@ Mod :: atom(), Func :: atom(), ArgTypes :: [normal_type()], - Result :: yes | no | maybe. + Result :: 'yes' | 'no' | 'maybe'. will_succeed(erlang, Op, [LHS, RHS]) when Op =:= '+'; Op =:= '-'; Op =:= '*' -> @@ -62,7 +62,7 @@ will_succeed(erlang, '--', [LHS, RHS]) - {yes, yes} -> yes; {no, _} -> no; {_, no} -> no; - {_, _} -> maybe + {_, _} -> 'maybe' end; will_succeed(erlang, BoolOp, [LHS, RHS]) when BoolOp =:= 'and'; BoolOp =:= 'or' -> @@ -71,7 +71,7 @@ will_succeed(erlang, BoolOp, [LHS, RHS]) {yes, yes} -> yes; {no, _} -> no; {_, no} -> no; - {_, _} -> maybe + {_, _} -> 'maybe' end; will_succeed(erlang, bit_size, [Arg]) -> succeeds_if_type(Arg, #t_bitstring{}); @@ -139,26 +139,26 @@ fails_on_conflict([ArgType | Args], [Req _ -> fails_on_conflict(Args, Types) end; fails_on_conflict([], []) -> - maybe. + 'maybe'. succeeds_if_type(ArgType, Required) -> case beam_types:meet(ArgType, Required) of ArgType -> yes; none -> no; - _ -> maybe + _ -> 'maybe' end. succeeds_if_smallish(#t_integer{elements={Min,Max}}) when abs(Min) bsr 128 =:= 0, abs(Max) bsr 128 =:= 0 -> yes; succeeds_if_smallish(_) -> - maybe. + 'maybe'. succeeds_if_smallish(LHS, RHS) -> case {succeeds_if_smallish(LHS), succeeds_if_smallish(RHS)} of {yes, yes} -> yes; - {_, _} -> maybe + {_, _} -> 'maybe' end. %% diff --git a/lib/compiler/src/beam_ssa_dead.erl b/lib/compiler/src/beam_ssa_dead.erl index 1d53dfab81..1d12666ba1 100644 --- a/lib/compiler/src/beam_ssa_dead.erl +++ b/lib/compiler/src/beam_ssa_dead.erl @@ -543,7 +543,7 @@ eval_switch_1([{Lit,Lbl}|T], Arg, PrevOp, Fail) -> no -> %% This branch will never be taken. eval_switch_1(T, Arg, PrevOp, Fail); - maybe -> + 'maybe' -> %% This label could be reached. eval_switch_1(T, Arg, PrevOp, none) end; @@ -707,11 +707,11 @@ eval_test(Bif, Args, #st{test=Prev}) -> case will_succeed(Prev, Test) of yes -> #b_literal{val=true}; no -> #b_literal{val=false}; - maybe -> none + 'maybe' -> none end end. -%% will_succeed(PrevCondition, Condition) -> yes | no | maybe +%% will_succeed(PrevCondition, Condition) -> yes | no | 'maybe' %% PrevCondition is a condition known to be true. This function %% will tell whether Condition will succeed. @@ -733,29 +733,29 @@ will_succeed({{'not',is_boolean},Var}, {'=:=',Var,#b_literal{val=Lit}}) when is_boolean(Lit) -> no; will_succeed({_,_}, {_,_}) -> - maybe; + 'maybe'; will_succeed({_,_}, {_,_,_}) -> - maybe; + 'maybe'; will_succeed({_,_,_}, {_,_}) -> - maybe; + 'maybe'; will_succeed({_,_,_}, {_,_,_}) -> - maybe. + 'maybe'. will_succeed_test({'not',Test1}, Test2) -> case Test1 =:= Test2 of true -> no; - false -> maybe + false -> 'maybe' end; will_succeed_test(is_tuple, {is_tagged_tuple,_,_}) -> - maybe; + 'maybe'; will_succeed_test({is_tagged_tuple,_,_}, is_tuple) -> yes; will_succeed_test(is_list, is_nonempty_list) -> - maybe; + 'maybe'; will_succeed_test(is_nonempty_list, is_list) -> yes; will_succeed_test(_T1, _T2) -> - maybe. + 'maybe'. will_succeed_1('=:=', A, '<', B) -> if @@ -824,7 +824,7 @@ will_succeed_1('==', A, '/=', B) -> will_succeed_1('/=', A, '/=', B) when A == B -> yes; will_succeed_1('/=', A, '==', B) when A == B -> no; -will_succeed_1(_, _, _, _) -> maybe. +will_succeed_1(_, _, _, _) -> 'maybe'. will_succeed_vars('=/=', Var, '=:=', Var) -> no; will_succeed_vars('=:=', Var, '=/=', Var) -> no; @@ -834,7 +834,7 @@ will_succeed_vars('=:=', Val, '=<', Val) -> yes; will_succeed_vars('/=', Var, '==', Var) -> no; will_succeed_vars('==', Var, '/=', Var) -> no; -will_succeed_vars(_, _, _, _) -> maybe. +will_succeed_vars(_, _, _, _) -> 'maybe'. eval_type_test(Test, Arg) -> case eval_type_test_1(Test, Arg) of diff --git a/lib/compiler/src/beam_ssa_pre_codegen.erl b/lib/compiler/src/beam_ssa_pre_codegen.erl index cfd2d196fb..46ed12490f 100644 --- a/lib/compiler/src/beam_ssa_pre_codegen.erl +++ b/lib/compiler/src/beam_ssa_pre_codegen.erl @@ -2509,7 +2509,7 @@ reserve_zreg([#b_set{op=Op,dst=Dst}], #b_br{bool=Dst}, ShortLived, A) -> case use_zreg(Op) of yes -> [{Dst,z} | A]; no -> A; - maybe -> reserve_test_zreg(Dst, ShortLived, A) + 'maybe' -> reserve_test_zreg(Dst, ShortLived, A) end; reserve_zreg([#b_set{op=Op,dst=Dst} | Is], Last, ShortLived, A) -> case use_zreg(Op) of @@ -2541,7 +2541,7 @@ use_zreg(get_tl) -> no; use_zreg(get_tuple_element) -> no; %% Assume the instruction can use a z register, provided it's the last in its %% block and that the result is only used in the terminator. -use_zreg(_) -> maybe. +use_zreg(_) -> 'maybe'. %% If V is defined just before a branch, we may be able to combine it into a %% test instruction. Type = case will_succeed(I, Ts0, Ds0, Sub) of yes -> beam_types:make_atom(true); no -> beam_types:make_atom(false); - maybe -> beam_types:make_boolean() + 'maybe' -> beam_types:make_boolean() end, case Type of #t_atom{elements=[true]} -> @@ -1097,7 +1097,7 @@ will_succeed_1(#b_set{op=bs_start_match, %% Is it at all possible to match? case beam_types:meet(ArgType, #t_bs_matchable{}) of none -> no; - _ -> maybe + _ -> 'maybe' end end; @@ -1127,17 +1127,17 @@ will_succeed_1(#b_set{op=bs_create_bin}, %% fail. Construction is unlikely to fail, and if it fails, the %% instruction in the runtime system will generate an exception with %% better information of what went wrong. - maybe; + 'maybe'; will_succeed_1(#b_set{op=bs_match, args=[#b_literal{val=Type},_,_,#b_literal{val=Size},_]}, _Src, _Ts, _Sub) -> if is_integer(Size), Size >= 0 -> - maybe; + 'maybe'; Type =:= binary, Size =:= all -> %% `all` is a legal size for binary segments at the end of %% a binary pattern. - maybe; + 'maybe'; true -> %% Invalid size. Matching will fail. no @@ -1145,18 +1145,18 @@ will_succeed_1(#b_set{op=bs_match, %% These operations may fail even though we know their return value on success. will_succeed_1(#b_set{op=call}, _Src, _Ts, _Sub) -> - maybe; + 'maybe'; will_succeed_1(#b_set{op=get_map_element}, _Src, _Ts, _Sub) -> - maybe; + 'maybe'; will_succeed_1(#b_set{op=wait_timeout}, _Src, _Ts, _Sub) -> %% It is essential to keep the {succeeded,body} instruction to %% ensure that the failure edge, which potentially leads to a %% landingpad, is preserved. If the failure edge is removed, a Y %% register holding a `try` tag could be reused prematurely. - maybe; + 'maybe'; will_succeed_1(#b_set{}, _Src, _Ts, _Sub) -> - maybe. + 'maybe'. simplify_is_record(I, #t_tuple{exact=Exact, size=Size, @@ -1170,7 +1170,7 @@ simplify_is_record(I, #t_tuple{exact=Exa %% Is it at all possible for the tag to match? case beam_types:meet(raw_type(RecTag, Ts), TagType) of none -> no; - _ -> maybe + _ -> 'maybe' end end, if diff --git a/lib/compiler/src/beam_validator.erl b/lib/compiler/src/beam_validator.erl index 8a5fd5b416..7471da226d 100644 --- a/lib/compiler/src/beam_validator.erl +++ b/lib/compiler/src/beam_validator.erl @@ -1236,7 +1236,7 @@ validate_tail_call(Deallocate, Func, Live, #vst{current=#st{numy=NumY}}=Vst0) -> %% The call cannot fail; we don't need to handle exceptions Vst = deallocate(Vst0), verify_return(Vst); - maybe when Deallocate =:= NumY -> + 'maybe' when Deallocate =:= NumY -> %% The call may fail; make sure we update exception state Vst = deallocate(Vst0), branch(?EXCEPTION_LABEL, Vst, fun verify_return/1); @@ -1269,7 +1269,7 @@ validate_body_call(Func, Live, case will_call_succeed(Func, Vst) of yes -> SuccFun(Vst); - maybe -> + 'maybe' -> branch(?EXCEPTION_LABEL, Vst, SuccFun); no -> branch(?EXCEPTION_LABEL, Vst, fun kill_state/1) @@ -1482,7 +1482,7 @@ validate_bif(Kind, Op, Fail, Ss, Dst, OrigVst, Vst) -> %% This BIF always fails; jump directly to the fail block or %% exception handler. branch(Fail, Vst, fun kill_state/1); - maybe -> + 'maybe' -> validate_bif_1(Kind, Op, Fail, Ss, Dst, OrigVst, Vst) end. @@ -3102,7 +3102,7 @@ will_bif_succeed(raise, [_,_], _Vst) -> will_bif_succeed(Op, Ss, Vst) -> case is_float_arith_bif(Op, Ss) of true -> - maybe; + 'maybe'; false -> Args = [normalize(get_term_type(Arg, Vst)) || Arg <- Ss], beam_call_types:will_succeed(erlang, Op, Args) @@ -3119,10 +3119,10 @@ will_call_succeed({f,Lbl}, #vst{ft=Ft}) -> #{Lbl := #{always_fails := true}} -> no; #{} -> - maybe + 'maybe' end; will_call_succeed(_Call, _Vst) -> - maybe. + 'maybe'. get_call_args(Arity, Vst) -> get_call_args_1(0, Arity, Vst). diff --git a/lib/compiler/src/sys_core_fold.erl b/lib/compiler/src/sys_core_fold.erl index c8d1b00378..c25702f63a 100644 --- a/lib/compiler/src/sys_core_fold.erl +++ b/lib/compiler/src/sys_core_fold.erl @@ -1433,15 +1433,15 @@ shadow_warning([C|Cs], Line, Anno) -> shadow_warning(Cs, Line, Anno); shadow_warning([], _, _) -> ok. -%% will_succeed(Guard) -> yes | maybe | no. +%% will_succeed(Guard) -> yes | 'maybe' | no. %% Test if we know whether a guard will succeed/fail or just don't %% know. Be VERY conservative! will_succeed(#c_literal{val=true}) -> yes; will_succeed(#c_literal{val=false}) -> no; -will_succeed(_Guard) -> maybe. +will_succeed(_Guard) -> 'maybe'. -%% will_match(Expr, [Pattern]) -> yes | maybe. +%% will_match(Expr, [Pattern]) -> yes | 'maybe'. %% We KNOW that this function is only used after optimizations %% in case_opt/4. Therefore clauses that can definitely not match %% have already been pruned. @@ -1451,7 +1451,7 @@ will_match(#c_values{es=Es}, Ps) -> will_match(E, [P]) -> will_match_1(cerl_clauses:match(P, E)). -will_match_1({false,_}) -> maybe; +will_match_1({false,_}) -> 'maybe'; will_match_1({true,_}) -> yes. %% opt_bool_case(CoreExpr, Sub) - CoreExpr'. -- 2.34.1
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