@@ -2023,8 +2023,7 @@ bsm_skip([], _) -> [].
20232023
20242024bsm_skip_is ([I0 |Is ], Extracted ) ->
20252025 case I0 of
2026- # b_set {anno = Anno0 ,
2027- op = bs_match ,
2026+ # b_set {op = bs_match ,
20282027 dst = Ctx ,
20292028 args = [# b_literal {val = T }= Type ,PrevCtx |Args0 ]}
20302029 when T =/= float , T =/= string , T =/= skip ->
@@ -2035,9 +2034,7 @@ bsm_skip_is([I0|Is], Extracted) ->
20352034 I0 ;
20362035 false ->
20372036 % % The value is never extracted.
2038- Args = [# b_literal {val = skip },PrevCtx ,Type |Args0 ],
2039- Anno = maps :remove (arg_types , Anno0 ),
2040- I0 # b_set {anno = Anno ,args = Args }
2037+ I0 # b_set {args = [# b_literal {val = skip },PrevCtx ,Type |Args0 ]}
20412038 end ,
20422039 [I |Is ];
20432040 # b_set {} ->
@@ -2138,7 +2135,7 @@ ssa_opt_bsm_shortcut({#opt_st{ssa=Linear0}=St, FuncDb}) ->
21382135 {St , FuncDb };
21392136 _ ->
21402137 Linear1 = bsm_shortcut (Linear0 , Positions ),
2141- Linear = bsm_tail (Linear1 , #{}),
2138+ Linear = bsm_tail (Linear1 , #{ 0 => any }),
21422139 ssa_opt_live ({St # opt_st {ssa = Linear }, FuncDb })
21432140 end .
21442141
@@ -2221,86 +2218,106 @@ bsm_shortcut([], _PosMap) -> [].
22212218% % m1(<<_, Rest/binary>>) -> m1(Rest);
22222219% % m1(<<>>) -> ok.
22232220% %
2224- % % The second clause of `m1/1` does not need to check for an empty
2225- % % binary.
2226-
2227- bsm_tail ([{L ,# b_blk {is = Is0 ,last = Last0 }= Blk0 }|Bs ], Map0 ) ->
2228- {Is ,Last ,Map } = bsm_tail_is (Is0 , Last0 , L , Map0 , []),
2229- Blk = Blk0 # b_blk {is = Is ,last = Last },
2230- [{L ,Blk }|bsm_tail (Bs , Map )];
2231- bsm_tail ([], _Map ) ->
2221+ % % The second clause of `m1/1` does not need to check for an empty bitstring.
2222+ % %
2223+ % % This is done by keeping track of which blocks are reachable solely because
2224+ % % of `bs_match` instructions that can only fail because the end has been
2225+ % % reached, and then eliminating the related `bs_match` and `bs_test_tail`
2226+ % % instructions in those blocks.
2227+
2228+ bsm_tail ([{L , # b_blk {is = Is0 }= Blk0 } | Bs ], Tags0 ) when is_map_key (L , Tags0 ) ->
2229+ {Blk , Tags } = bsm_tail_is_1 (Is0 , Blk0 , L , Tags0 ),
2230+ [{L , Blk } | bsm_tail (Bs , Tags )];
2231+ bsm_tail ([_ | Bs ], Tags ) ->
2232+ bsm_tail (Bs , Tags );
2233+ bsm_tail ([], _Tags ) ->
22322234 [].
22332235
2234- bsm_tail_is ([# b_set {op = bs_start_match ,anno = Anno ,dst = Dst }= I |Is ], Last , L , Map0 , Acc ) ->
2235- case Anno of
2236- #{arg_types := #{1 := Type }} ->
2237- case beam_types :get_bs_matchable_unit (Type ) of
2238- error ->
2239- bsm_tail_is (Is , Last , L , Map0 , [I |Acc ]);
2240- Unit when is_integer (Unit ) ->
2241- Map = Map0 #{Dst => Unit },
2242- bsm_tail_is (Is , Last , L , Map , [I |Acc ])
2243- end ;
2244- #{} ->
2245- bsm_tail_is (Is , Last , L , Map0 , [I |Acc ])
2246- end ;
2247- bsm_tail_is ([# b_set {op = bs_match ,dst = Dst ,args = Args },
2248- # b_set {op = {succeeded ,guard },dst = SuccDst ,args = [Dst ]}|_ ]= Is ,
2249- # b_br {bool = SuccDst ,fail = Fail }= Last ,
2250- _L , Map0 , Acc ) ->
2251- case bsm_tail_num_matched (Args , Map0 ) of
2252- unknown ->
2253- % % Unknown number of bits or the match operation will fail
2254- % % to match certain values.
2255- Map = Map0 #{Fail => unknown },
2256- {reverse (Acc , Is ),Last ,Map };
2257- Bits when is_integer (Bits ) ->
2258- case Map0 of
2259- #{Fail := Bits } ->
2260- {reverse (Acc , Is ),Last ,Map0 };
2261- #{Fail := _ } ->
2262- Map = Map0 #{Fail => unknown },
2263- {reverse (Acc , Is ),Last ,Map };
2264- #{} ->
2265- Map = Map0 #{Fail => Bits },
2266- {reverse (Acc , Is ),Last ,Map }
2267- end
2268- end ;
2269- bsm_tail_is ([# b_set {op = bs_test_tail ,args = [_ ,# b_literal {val = 0 }],dst = Dst }]= Is ,
2270- # b_br {bool = Dst ,succ = Succ }= Last0 , L , Map0 , Acc ) ->
2271- case Map0 of
2272- #{L := Bits } when is_integer (Bits ) ->
2273- % % The `bs_match` instruction targeting this block on failure
2274- % % will only fail when the end of the binary has been reached.
2275- % % There is no need for the test.
2276- Last = beam_ssa :normalize (Last0 # b_br {fail = Succ }),
2277- {reverse (Acc , Is ),Last ,Map0 };
2278- #{} ->
2279- {reverse (Acc , Is ),Last0 ,Map0 }
2280- end ;
2281- bsm_tail_is ([# b_set {}= I |Is ], Last , L , Map , Acc ) ->
2282- bsm_tail_is (Is , Last , L , Map , [I |Acc ]);
2283- bsm_tail_is ([], Last , _L , Map0 , Acc ) ->
2284- Map = foldl (fun (F , A ) ->
2285- A #{F => unknown }
2286- end , Map0 , beam_ssa :successors (# b_blk {is = [],last = Last })),
2287- {reverse (Acc ),Last ,Map }.
2288-
2289- bsm_tail_num_matched ([# b_literal {val = skip },Ctx ,Type ,Flags ,Size ,Unit ], Map ) ->
2290- bsm_tail_num_matched ([Type ,Ctx ,Flags ,Size ,Unit ], Map );
2291- bsm_tail_num_matched ([# b_literal {val = Type },Ctx ,# b_literal {},
2292- # b_literal {val = Size },# b_literal {val = Unit }], Map )
2236+ bsm_tail_is_1 ([# b_set {op = bs_match ,anno = Anno ,dst = Dst ,args = [_ , Ctx | _ ]= Args },
2237+ # b_set {op = {succeeded ,guard },dst = SuccDst ,args = [Dst ]}],
2238+ # b_blk {last = # b_br {bool = SuccDst ,succ = Succ ,fail = Fail }= Last }= Blk0 ,
2239+ L , Tags ) ->
2240+ case {Tags , bsm_tail_match_tag (Args , Anno )} of
2241+ {#{ L := Ctx }, Ctx } ->
2242+ % % This block can only be reached through matches that fail because
2243+ % % the context is empty, and the current match will likewise only
2244+ % % fail because the context is empty, so we KNOW that this cannot
2245+ % % succeed.
2246+ % %
2247+ % % Kill the instruction and propagate the condition.
2248+ Blk = Blk0 # b_blk {last = beam_ssa :normalize (Last # b_br {succ = Fail })},
2249+ {Blk , bsm_tail_update_target (Fail , Fail , Ctx , Tags )};
2250+ {#{ L := _ }, Tag } ->
2251+ % % `any` or different context. Mark the fail block with whether
2252+ % % it's reachable solely because the context is empty.
2253+ {Blk0 , bsm_tail_update_target (Succ , Fail , Tag , Tags )}
2254+ end ;
2255+ bsm_tail_is_1 ([# b_set {op = bs_test_tail ,args = [Ctx ,# b_literal {val = Size }],dst = Dst }],
2256+ # b_blk {last = # b_br {bool = Dst ,succ = Succ ,fail = Fail }= Last0 }= Blk0 ,
2257+ L , Tags ) ->
2258+ true = is_integer (Size ) andalso Size >= 0 , % Assertion.
2259+ case Tags of
2260+ #{ L := Ctx } ->
2261+ % % This block can only be reached through matches that fail because
2262+ % % the end of the context has been reached.
2263+ % %
2264+ % % Kill the instruction and propagate the condition.
2265+ Next = case Size of
2266+ 0 -> Succ ;
2267+ _ -> Fail
2268+ end ,
2269+ Last = beam_ssa :normalize (Last0 # b_br {succ = Next ,fail = Next }),
2270+ Blk = Blk0 # b_blk {last = Last },
2271+ {Blk , bsm_tail_update_target (Next , Next , Ctx , Tags )};
2272+ #{ L := _ } ->
2273+ % % `any` or different context. We cannot optimize this, but it's
2274+ % % safe to mark the success block as only being reachable when the
2275+ % % context is empty.
2276+ Tag = case Size of
2277+ 0 -> Ctx ;
2278+ _ -> any
2279+ end ,
2280+ {Blk0 , bsm_tail_update_target (Fail , Succ , Tag , Tags )}
2281+ end ;
2282+ bsm_tail_is_1 ([# b_set {} | Is ], Blk , L , Tags ) ->
2283+ bsm_tail_is_1 (Is , Blk , L , Tags );
2284+ bsm_tail_is_1 ([], Blk , _L , Tags0 ) ->
2285+ Tags = foldl (fun (Lbl , Acc ) ->
2286+ Acc #{ Lbl => any }
2287+ end , Tags0 , beam_ssa :successors (Blk )),
2288+ {Blk , Tags }.
2289+
2290+ bsm_tail_match_tag ([# b_literal {val = skip }, Ctx , Type | Rest ], Anno ) ->
2291+ bsm_tail_match_tag ([Type , Ctx | Rest ], Anno );
2292+ bsm_tail_match_tag ([# b_literal {val = Type },
2293+ # b_var {}= Ctx ,
2294+ # b_literal {},
2295+ # b_literal {val = Size },
2296+ # b_literal {val = Unit }],
2297+ Anno )
22932298 when (Type =:= integer orelse Type =:= binary ),
22942299 is_integer (Size ), is_integer (Unit ) ->
22952300 Bits = Size * Unit ,
2296- case Map of
2297- #{Ctx := Bits } when is_integer (Bits ) ->
2298- Bits ;
2301+ case Anno of
2302+ #{ arg_types := #{ 1 := CtxType } } ->
2303+ case beam_types :get_bs_matchable_unit (CtxType ) of
2304+ Bits -> Ctx ;
2305+ _ -> any
2306+ end ;
22992307 #{} ->
2300- unknown
2301- end ;
2302- bsm_tail_num_matched (_Args , _Map ) ->
2303- unknown .
2308+ any
2309+ end ;
2310+ bsm_tail_match_tag (_Args , _Anno ) ->
2311+ any .
2312+
2313+ bsm_tail_update_target (Succ , Fail , Tag , Tags ) when Succ =/= Fail ->
2314+ bsm_tail_update_target (Fail , Fail , Tag , Tags #{ Succ => any });
2315+ bsm_tail_update_target (Same , Same , Tag , Tags ) ->
2316+ case Tags of
2317+ #{ Same := Tag } -> Tags ;
2318+ #{ Same := _ } -> Tags #{ Same => any };
2319+ #{} -> Tags #{ Same => Tag }
2320+ end .
23042321
23052322% %%
23062323% %% Optimize binary construction.
0 commit comments