Skip to content

Commit

Permalink
Include test unit in generating the summary.
Browse files Browse the repository at this point in the history
  • Loading branch information
JanWielemaker committed Feb 1, 2023
1 parent 49b44fd commit 09c90d4
Showing 1 changed file with 18 additions and 14 deletions.
32 changes: 18 additions & 14 deletions plunit.pl
Expand Up @@ -1946,17 +1946,17 @@

message(plunit(begin(Unit:Test, _Location, Progress))) -->
{ tty_columns(SummaryWidth, _Margin),
test_name_summary(Test, SummaryWidth, NameS),
test_name_summary(Unit:Test, SummaryWidth, NameS),
progress_string(Progress, ProgressS)
},
( { tty_feedback,
tty_clear_to_eol(CE)
}
-> [ at_same_line, '\r[~w] ~w:~w ..~w'-[ProgressS, Unit, NameS,
-> [ at_same_line, '\r[~w] ~w ..~w'-[ProgressS, NameS,
CE], flush ]
; { jobs(_) }
-> [ '[~w] ~w:~w ..'-[ProgressS, Unit, NameS] ]
; [ '[~w] ~w:~w ..'-[ProgressS, Unit, NameS], flush ]
-> [ '[~w] ~w ..'-[ProgressS, NameS] ]
; [ '[~w] ~w ..'-[ProgressS, NameS], flush ]
).
message(plunit(end(_UnitTest, _Location, _Progress))) -->
[].
Expand All @@ -1969,12 +1969,12 @@
{ jobs(_),
!,
tty_columns(SummaryWidth, Margin),
test_name_summary(Test, SummaryWidth, NameS),
test_name_summary(Unit;Test, SummaryWidth, NameS),

This comment has been minimized.

Copy link
@borisvassilev

borisvassilev Feb 2, 2023

Shouldn't this be : instead of ;?

This comment has been minimized.

Copy link
@JanWielemaker

JanWielemaker Feb 2, 2023

Author Member

Oops. Thanks.

progress_string(Progress, ProgressS),
progress_tag(Status, Tag, _Keep, Style)
},
[ ansi(Style, '[~w] ~w:~w ~`.t ~w (~3f sec)~*|',
[ProgressS, Unit, NameS, Tag, Time.wall, Margin]) ].
[ ansi(Style, '[~w] ~~w ~`.t ~w (~3f sec)~*|',

This comment has been minimized.

Copy link
@borisvassilev

borisvassilev Feb 2, 2023

It seems there is one `~' too many left.

This comment has been minimized.

Copy link
@JanWielemaker

JanWielemaker Feb 2, 2023

Author Member

Thanks. Found that as well 😄

[ProgressS, NameS, Tag, Time.wall, Margin]) ].
message(plunit(progress(_UnitTest, Status, _Progress, Time))) -->
{ tty_columns(_SummaryWidth, Margin),
progress_tag(Status, Tag, _Keep, Style)
Expand Down Expand Up @@ -2230,12 +2230,16 @@
atom_length(Text, Len),
( Len =< MaxLen
-> Summary = Text
; Pre is MaxLen - 8,
; End is MaxLen//2,
Pre is MaxLen - End - 2,
sub_string(Text, 0, Pre, _, PreText),
sub_string(Text, _, 5, 0, PostText),
format(string(Summary), '~w...~w', [PreText,PostText])
sub_string(Text, _, End, 0, PostText),
format(string(Summary), '~w..~w', [PreText,PostText])
).

summary_string(Unit:Test, String) =>
summary_string(Test, String1),
atomics_to_string([Unit, String1], :, String).
summary_string(@(Name,Vars), String) =>
format(string(String), '~W (using ~W)',
[ Name, [numbervars(true), quoted(false)],
Expand Down Expand Up @@ -2335,11 +2339,11 @@

job_feedback(begin(Unit:Test, _Location, Progress)) =>
tty_columns(SummaryWidth, _Margin),
test_name_summary(Test, SummaryWidth, NameS),
test_name_summary(Unit:Test, SummaryWidth, NameS),
progress_string(Progress, ProgressS),
tty_clear_to_eol(CE),
job_format(comment, '\r[~w] ~w:~w ..~w',
[ProgressS, Unit, NameS, CE]),
job_format(comment, '\r[~w] ~w ..~w',
[ProgressS, NameS, CE]),
flush_output.
job_feedback(end(_UnitTest, _Location, _Progress)) =>
true.
Expand Down Expand Up @@ -2465,7 +2469,7 @@
tty_columns(SummaryWidth, Margin) :-
tty_width(W),
Margin is W-8,
SummaryWidth = max(20,Margin-50).
SummaryWidth is max(20,Margin-34).

tty_width(W) :-
current_predicate(tty_size/2),
Expand Down

1 comment on commit 09c90d4

@JanWielemaker
Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This commit has been mentioned on SWI-Prolog. There might be relevant details there:

https://swi-prolog.discourse.group/t/improving-unit-tests/6091/38

Please sign in to comment.