@@ -271,7 +271,7 @@ expand_rescue(Meta, [Arg], S, E) ->
271
271
{EArg , SA , EA } ->
272
272
{[EArg ], SA , EA };
273
273
false ->
274
- form_error (Meta , E , ? MODULE , invalid_rescue_clause )
274
+ form_error (Meta , E , ? MODULE , { invalid_rescue_clause , Arg } )
275
275
end ;
276
276
expand_rescue (Meta , _ , _ , E ) ->
277
277
Error = {wrong_number_of_args_for_clause , " one argument" , origin (Meta , 'try' ), 'rescue' },
@@ -281,12 +281,16 @@ expand_rescue(Meta, _, _, E) ->
281
281
expand_rescue ({Name , _ , Atom } = Var , S , E ) when is_atom (Name ), is_atom (Atom ) ->
282
282
match (fun elixir_expand :expand /3 , Var , S , S , E );
283
283
284
- % % rescue var in _ => rescue var
284
+ % % rescue Alias => _ in [Alias]
285
+ expand_rescue ({'__aliases__' , _ , [_ | _ ]} = Alias , S , E ) ->
286
+ expand_rescue ({in , [], [{'_' , [], ? key (E , module )}, Alias ]}, S , E );
287
+
288
+ % % rescue var in _
285
289
expand_rescue ({in , _ , [{Name , _ , VarContext } = Var , {'_' , _ , UnderscoreContext }]}, S , E )
286
290
when is_atom (Name ), is_atom (VarContext ), is_atom (UnderscoreContext ) ->
287
- expand_rescue ( Var , S , E );
291
+ match ( fun elixir_expand : expand / 3 , Var , S , S , E );
288
292
289
- % % rescue var in [Exprs]
293
+ % % rescue var in (list() or atom())
290
294
expand_rescue ({in , Meta , [Left , Right ]}, S , E ) ->
291
295
{ELeft , SL , EL } = match (fun elixir_expand :expand /3 , Left , S , S , E ),
292
296
{ERight , SR , ER } = elixir_expand :expand (Right , SL , EL ),
@@ -301,12 +305,19 @@ expand_rescue({in, Meta, [Left, Right]}, S, E) ->
301
305
false
302
306
end ;
303
307
304
- % % rescue Error => _ in [Error]
308
+ % % rescue expr() => rescue expanded_expr()
309
+ expand_rescue ({_ , Meta , _ } = Arg , S , E ) ->
310
+ case 'Elixir.Macro' :expand_once (Arg , E #{line := ? line (Meta )}) of
311
+ Arg -> false ;
312
+ NewArg -> expand_rescue (NewArg , S , E )
313
+ end ;
314
+
315
+ % % rescue list() or atom() => _ in (list() or atom())
305
316
expand_rescue (Arg , S , E ) ->
306
317
expand_rescue ({in , [], [{'_' , [], ? key (E , module )}, Arg ]}, S , E ).
307
318
308
- normalize_rescue ({ '_' , _ , Atom } = N ) when is_atom (Atom ) -> N ;
309
- normalize_rescue ( Atom ) when is_atom ( Atom ) -> [Atom ];
319
+ normalize_rescue (Atom ) when is_atom (Atom ) ->
320
+ [Atom ];
310
321
normalize_rescue (Other ) ->
311
322
is_list (Other ) andalso lists :all (fun is_atom /1 , Other ) andalso Other .
312
323
@@ -389,9 +400,12 @@ format_error({wrong_number_of_args_for_clause, Expected, Kind, Key}) ->
389
400
format_error (multiple_after_clauses_in_receive ) ->
390
401
" expected a single -> clause for :after in \" receive\" " ;
391
402
392
- format_error (invalid_rescue_clause ) ->
393
- " invalid \" rescue\" clause. The clause should match on an alias, a variable "
394
- " or be in the \" var in [alias]\" format" ;
403
+ format_error ({invalid_rescue_clause , Arg }) ->
404
+ io_lib :format (
405
+ " invalid \" rescue\" clause. The clause should match on an alias, a variable "
406
+ " or be in the \" var in [alias]\" format. Got: ~ts " ,
407
+ ['Elixir.Macro' :to_string (Arg )]
408
+ );
395
409
396
410
format_error ({catch_before_rescue , Origin }) ->
397
411
io_lib :format (" \" catch\" should always come after \" rescue\" in ~ts " , [Origin ]);
0 commit comments