4242 start /1
4343 ]).
4444
45- -ifdef (namespaced_dicts ).
46- -type euf_dict () :: dict :dict ().
47- -else .
48- -type euf_dict () :: dict ().
49- -endif .
50-
5145-record (state , {
52- status = dict : new () :: euf_dict (),
46+ status = #{} :: map (),
5347 failures = [] :: [[pos_integer ()]],
5448 skips = [] :: [[pos_integer ()]],
5549 timings = binomial_heap :new () :: binomial_heap :binomial_heap (),
@@ -73,12 +67,12 @@ init(Options) ->
7367
7468handle_begin (group , Data , St ) ->
7569 GID = proplists :get_value (id , Data ),
76- Dict = St # state .status ,
77- St # state {status = dict : store ( GID , orddict :from_list ([{type , group }|Data ]), Dict ) };
70+ Status = St # state .status ,
71+ St # state {status = Status #{ GID => orddict :from_list ([{type , group }|Data ])} };
7872handle_begin (test , Data , St ) ->
7973 TID = proplists :get_value (id , Data ),
80- Dict = St # state .status ,
81- St # state {status = dict : store ( TID , orddict :from_list ([{type , test }|Data ]), Dict ) }.
74+ Status = St # state .status ,
75+ St # state {status = Status #{ TID => orddict :from_list ([{type , test }|Data ])} }.
8276
8377handle_end (group , Data , St ) ->
8478 St # state {status = merge_on_end (Data , St # state .status )};
@@ -151,12 +145,10 @@ print_progress_skipped(St) ->
151145print_progress_failed (_Exc , St ) ->
152146 print_colored (" F" , ? RED , St ).
153147
154- merge_on_end (Data , Dict ) ->
148+ merge_on_end (Data , Status ) ->
155149 ID = proplists :get_value (id , Data ),
156- dict :update (ID ,
157- fun (Old ) ->
158- orddict :merge (fun merge_data /3 , Old , orddict :from_list (Data ))
159- end , Dict ).
150+ #{ ID := Old } = Status ,
151+ Status #{ ID := orddict :merge (fun merge_data /3 , Old , orddict :from_list (Data )) }.
160152
161153merge_data (_K , undefined , X ) -> X ;
162154merge_data (_K , X , undefined ) -> X ;
@@ -175,7 +167,7 @@ print_failures(#state{failures=Fails}=State) ->
175167
176168print_failure_fun (# state {status = Status }= State ) ->
177169 fun (Key , Count ) ->
178- TestData = dict : fetch ( Key , Status ) ,
170+ #{ Key : = TestData } = Status ,
179171 TestId = format_test_identifier (TestData ),
180172 io :fwrite (" ~p ) ~ts~n " , [Count , TestId ]),
181173 print_failure_reason (proplists :get_value (status , TestData ),
@@ -197,13 +189,14 @@ print_failure_reason({error, Reason}, Output, State) ->
197189 print_failure_output (5 , Output , State ).
198190
199191print_failure_output (_ , <<>>, _ ) -> ok ;
192+ print_failure_output (_ , [<<>>], _ ) -> ok ;
200193print_failure_output (_ , undefined , _ ) -> ok ;
201194print_failure_output (Indent , Output , State ) ->
202195 print_colored (indent (Indent , " Output: ~ts " , [Output ]), ? CYAN , State ).
203196
204197print_assertion_failure ({Type , Props }, Stack , Output , State ) ->
205198 FailureDesc = format_assertion_failure (Type , Props , 5 ),
206- {M ,F ,A ,Loc } = lists :last (Stack ),
199+ {M ,F ,A ,Loc } = lists :last (prune_trace ( Stack ) ),
207200 LocationText = io_lib :format (" %% ~ts :~p :in `~ts `" , [proplists :get_value (file , Loc ),
208201 proplists :get_value (line , Loc ),
209202 format_function_name (M ,F ,A )]),
@@ -214,13 +207,19 @@ print_assertion_failure({Type, Props}, Stack, Output, State) ->
214207 print_failure_output (5 , Output , State ),
215208 io :nl ().
216209
210+ % % This is a simplified version of eunit_test:prune_trace/2
211+ prune_trace ([Entry | _ ]) when element (1 , Entry ) =:= eunit_test ->
212+ [Entry ];
213+ prune_trace (Stack ) ->
214+ lists :takewhile (fun (Entry ) -> element (1 , Entry ) =/= eunit_test end , Stack ).
215+
217216print_pending (# state {skips = []}) ->
218217 ok ;
219218print_pending (# state {status = Status , skips = Skips }= State ) ->
220219 io :nl (),
221220 io :fwrite (" Pending:~n " , []),
222221 lists :foreach (fun (ID ) ->
223- Info = dict : fetch ( ID , Status ) ,
222+ #{ ID : = Info } = Status ,
224223 case proplists :get_value (reason , Info ) of
225224 undefined ->
226225 ok ;
@@ -244,7 +243,7 @@ print_pending_reason(Reason0, Data, State) ->
244243print_profile (# state {timings = T , status = Status , profile = true }= State ) ->
245244 TopN = binomial_heap :take (10 , T ),
246245 TopNTime = abs (lists :sum ([ Time || {Time , _ } <- TopN ])),
247- TLG = dict : fetch ([], Status ) ,
246+ #{ [] : = TLG } = Status ,
248247 TotalTime = proplists :get_value (time , TLG ),
249248 if TotalTime =/= undefined andalso TotalTime > 0 andalso TopN =/= [] ->
250249 TopNPct = (TopNTime / TotalTime ) * 100 ,
@@ -258,7 +257,7 @@ print_profile(#state{profile=false}) ->
258257 ok .
259258
260259print_timing (# state {status = Status }) ->
261- TLG = dict : fetch ([], Status ) ,
260+ #{ [] : = TLG } = Status ,
262261 Time = proplists :get_value (time , TLG ),
263262 io :nl (),
264263 io :fwrite (" Finished in ~ts~n " , [format_time (Time )]),
@@ -288,7 +287,7 @@ print_results(Color, Total, Fail, Skip, Cancel, State) ->
288287
289288print_timing_fun (# state {status = Status }= State ) ->
290289 fun ({Time , Key }) ->
291- TestData = dict : fetch ( Key , Status ) ,
290+ #{ Key : = TestData } = Status ,
292291 TestId = format_test_identifier (TestData ),
293292 io :nl (),
294293 io :fwrite (" ~ts~n " , [TestId ]),
@@ -350,11 +349,16 @@ format_assertion_failure(Type, Props, I) when Type =:= assertion_failed
350349 HasHamcrestProps = ([expected , actual , matcher ] -- Keys ) =:= [],
351350 if
352351 HasEUnitProps ->
353- [indent (I , " Failure/Error: ?assert(~ts )~n " , [proplists :get_value (expression , Props )]),
354- indent (I , " expected: true~n " , []),
352+ Expected = proplists :get_value (expected , Props ),
353+ AssertMacro = case Expected of
354+ true -> assert ;
355+ false -> assertNot
356+ end ,
357+ [indent (I , " Failure/Error: ?~p (~ts )~n " , [AssertMacro , proplists :get_value (expression , Props )]),
358+ indent (I , " expected: ~p~n " , [Expected ]),
355359 case proplists :get_value (value , Props ) of
356- false ->
357- indent (I , " got: false " , []);
360+ Bool when is_boolean ( Bool ) ->
361+ indent (I , " got: ~p " , [Bool ]);
358362 {not_a_boolean , V } ->
359363 indent (I , " got: ~p " , [V ])
360364 end ];
0 commit comments