1:- module(progress_bar, [
    2	simple_spinner//1,			% simple_spinner(+Progress:int) is det.
    3	default_spinner//2,			% default_spinner(+Progress:int,TextLeft:text) is det.
    4	fancy_spinner//3,			% fancy_spinner(+Progress:int, +TextLeft:text, +TextRight:text) is det.			
    5	spinner//10,				% spinner(+Progress:int,
    6								%	+SpinLeftLeft:atom,+TextLeft:text,SpinLeftRight:atom,
    7								%	+SpinCenterLeft:atom,+TextCenter:text,+SpinCenterRight:atom,
    8								%	+SpinRightLeft:atom,+TextRight:text,+SpinRightRight:atom)
    9	spinner_end//0,
   10	simple_progress_bar//2,		% simple_progress_bar(+Index:int, +Total:int) is det.
   11	default_progress_bar//4,	% default_progress_bar(+Index:int, +Total:int, IntroText:text,OutroText:text)
   12	fancy_progress_bar//7,		% fancy_progress_bar(+Index:int, +Total:int, IntroText:text,OutroText:text,StartText,TodoText:text) is det.
   13	progress_bar//12			% progress_bar(+Index:int,+Total:int,+IntroText:text,+OutroText:text,
   14								%	+StartMarker:char,+StartText:text,+DoneChar:char,+DoneText:text,
   15								%	+TodoText:text,+TodoChar:char,+EndText:text,+EndMarker:char) is det. 
   16	]).

DCG rules that renders a text-based progress bar, or spinner

progress_bar makes available a DCG rule (e.g. simple_progress_bar, simple_spinner) that is to be used as part of the prolog messaging system to print the progress of a used defined process (see https://www.swi-prolog.org/pldoc/man?section=printmsg). Note that the term 'process' denotes an abstract task a user wishes to complete (i.e. it doens't refer to a separate thread)

The message is meant to be called repeatedly while the user- process progresses (i.e. it is part of the user processing loop). To this end the DCG rule (e.g. simple_progress_bar) should be provided: the current state (=Index), with respect to the total denoting completion (=Total). Additional information may be provided to allow informing the user about the processing (see example below). Note the spinner//10 doesn't define a Total (it does define Index) and therefore it's progress with respect to completion is unknown. When the user-process finishes, the user should call spinner_end//0 to end the spinner.

Under the hood, the DCG rules formats the message according to a specific layout (see progress_bar//12, and spinner//10 for details). simple_progress_bar//2, default_progress_bar//4, fancy_progress_bar//7 are specialisations of progress_bar//12 defaulting some of its values (similarily for spinner). While the user-process progresses, the DCG rule is called repeatedly (i.e. as part of the user defined loop). Every message is prefixed with a 'carriage-return only' character ('\r'), which effectively resets the last printed message, and creates the animation effect.

## Example

The example below illustrates the use of simple_progress_bar//2 within user_defined_predicate to visually portray advancement whilte iterating elements within the forall/2 loop. Within the forall-loop print_message/2 calls the DGC rule my_application_does_stuff//2 to format to pre-process the message passed to default_progress_bar//4.

user_defined_predicate(...) :-
        ...
        length(Items,Total),
        forall(nth1(Index,Items,Item), (
                print_message(informational,my_application_does_stuff(Index,Total)
                %  do something with Item
                ),
        ...

my_application_does_stuff(Index,Total) -->
        Percentage is (Index/Total) * 100,
        format(string(OutroText),"[~0f%]",[Percentage]),
        default_progress_bar(Index,Total,"Processing",OutroText).
author
- Joost Geurts
license
- MIT License

*/

   65:- use_module(library(dcg/basics)).   66:- use_module(library(error)).   67
   68:- use_module(library(debug)).   69:- debug(progress_bar).   70:- debug(progress_bar,"progress_bar pack loaded",[]).   71
   72:- multifile prolog:message//1.   73prolog:message(pb(Msg)) --> Msg.
 spinner(?Id:atom, ?Frames:list(atom)) is nondet
defines the spinners
   78spinner(none,['']).
   79spinner(classic,['|','/','—','\\']).
   80spinner(mini,['x','+']).
   81spinner(dots1,['.  ','.. ','...',' ..','  .']).
   82spinner(dots2,['.  ','.. ','...']).
   83spinner(bar,['▁','▃','▄','▅','▆','▇','█','▇','▆','▅','▄','▃']).
   84spinner(dqpb,['d', 'q', 'p', 'b']).
 simple_spinner(+Progress:int)// is det
renders a spinner message on the center of the screen-line
   89simple_spinner(Progress) --> 
   90	{
   91		SpinLeftLeft = none,
   92		TextLeft = "",
   93		SpinLeftRight = none,
   94		SpinCenterLeft = dots1,
   95		TextCenter = " Processing ",
   96		SpinCenterRight = dots1,
   97		SpinRightLeft = none,
   98		TextRight = "",
   99		SpinRightRight = none
  100	},
  101	spinner(Progress,SpinLeftLeft,TextLeft,SpinLeftRight,SpinCenterLeft,TextCenter,SpinCenterRight,SpinRightLeft,TextRight,SpinRightRight).
 default_spinner(+Progress:int, TextLeft:text)// is det
renders a text message followed by a spinner
  105default_spinner(Progress,TextLeft) --> 
  106	{
  107		SpinLeftLeft = none,
  108		SpinLeftRight = classic,
  109		SpinCenterLeft = none,
  110		TextCenter = "",
  111		SpinCenterRight = none,
  112		SpinRightLeft = none,
  113		TextRight = "",
  114		SpinRightRight = none
  115	},
  116	spinner(Progress,SpinLeftLeft,TextLeft,SpinLeftRight,SpinCenterLeft,TextCenter,SpinCenterRight,SpinRightLeft,TextRight,SpinRightRight).
 fancy_spinner(+Progress:int, +TextLeft:text, +TextRight:text)// is det
fancy_spinner renders a (dynamic) message on the left of the screen (including a spinner) and rights-aligned message
  120fancy_spinner(Progress,TextLeft,TextRight) --> 
  121	{
  122		SpinLeftLeft = bar,
  123		SpinLeftRight = none,
  124		SpinCenterLeft = none,
  125		TextCenter = "",
  126		SpinCenterRight = none,
  127		SpinRightLeft = none,
  128		SpinRightRight = none
  129	},
  130	spinner(Progress,SpinLeftLeft,TextLeft,SpinLeftRight,SpinCenterLeft,TextCenter,SpinCenterRight,SpinRightLeft,TextRight,SpinRightRight).
 spinner(+Progress:int, +SpinLeftLeft:atom, +TextLeft:text, SpinLeftRight:atom, +SpinCenterLeft:atom, +TextCenter:text, +SpinCenterRight:atom, +SpinRightLeft:atom, +TextRight:text, +SpinRightRight:atom)// is det
Generates a spinner message that is meant to be called repeatedly by a task to indicate its progress (while its completion cannot be determined ahead of timer, otherwise a progess bar would be more appropriate)

The layout of the spinner message is setup according to the following schema:

SLL TL SLR 			SCL TC SCR 			SRL TR SRR

SLL stands for Spinner-Left-Left, TL stands for Text-Left, SLR stands for Spinner-Left-Right The other abreviation follow the same schema

  160spinner(Progress,SpinLeftLeft,TextLeft,SpinLeftRight,SpinCenterLeft,TextCenter,SpinCenterRight,SpinRightLeft,TextRight,SpinRightRight) --> 
  161	{
  162		findall(Id,spinner(Id,_),Ids),
  163		must_be(nonneg, Progress),
  164		must_be(oneof(Ids),SpinLeftLeft),
  165		must_be(any,TextLeft), (atomic(TextLeft) -> TextLeftStr = TextLeft ; message_to_string(TextLeft,TextLeftStr)),
  166		must_be(oneof(Ids),SpinLeftRight),
  167		must_be(oneof(Ids),SpinCenterLeft),
  168		must_be(any,TextCenter), (atomic(TextCenter) -> TextCenterStr = TextCenter ; message_to_string(TextCenter,TextCenterStr)),
  169		must_be(oneof(Ids),SpinCenterRight),
  170		must_be(oneof(Ids),SpinRightLeft),
  171		must_be(any,TextRight), (atomic(TextRight) -> TextRightStr = TextRight ; message_to_string(TextRight,TextRightStr)),
  172		must_be(oneof(Ids),SpinRightRight)
  173	},
  174	remove_line_content, 
  175	prefix_line, 
  176	full_width_spinner(Progress,SpinLeftLeft,TextLeftStr,SpinLeftRight,SpinCenterLeft,TextCenterStr,SpinCenterRight,SpinRightLeft,TextRightStr,SpinRightRight),
  177	[flush].
 spinner_end// is det
spinner_end ends the the spinner
  181spinner_end --> [nl].
  182
  183full_width_spinner(Progress,SLL,TL,SLR,SCL,TC,SCR,SRL,TR,SRR) -->
  184   {
  185    	tty_size(_,W0),
  186    	Position = 0,
  187        Width is W0 - 3 % '% ' prefix + cursor
  188   },
  189   render_spinner(Progress,Position,Width,SLL,TL,SLR,SCL,TC,SCR,SRL,TR,SRR).
  190
  191% PosL				   PosC 			PosR
  192% SLL TL SLR 		SCL TC SCR 	  SRL TR SRR
  193render_spinner(Progress,Position,Width,SLL,TL,SLR,SCL,TC,SCR,SRL,TR,SRR) -->
  194	{
  195		must_be(nonneg,Position),
  196		must_be(nonneg,Width),
  197		PosL = Position,	
  198		spinner(SCL,[Frame_SCL|_]),atom_length(Frame_SCL,Len_SCL),
  199		string_length(TC,Len_TC),
  200		spinner(SCR,[Frame_SCR|_]),
  201		spinner(SCR,[Frame_SCR|_]),atom_length(Frame_SCR,Len_SCR),
  202		PosC is PosL + round(Width/2) - round((Len_SCL + Len_TC + Len_SCR) / 2) - 1,
  203		spinner(SRL,[Frame_SRL|_]),atom_length(Frame_SRL,Len_SRL),
  204		string_length(TR,Len_TR),
  205		spinner(SRR,[Frame_SRR|_]),atom_length(Frame_SRR,Len_SRR),
  206		PosR is Position + Width - Len_SRL - Len_TR - Len_SRR
  207	},  
  208	do_render_spinner(Progress,PosL,SLL,TL,SLR,PosC,SCL,TC,SCR,PosR,SRL,TR,SRR).
  209
  210do_render_spinner(Progress,PosL,SLL,TL,SLR,PosC,SCL,TC,SCR,PosR,SRL,TR,SRR) --> 
  211	{
  212		spinner(SLL,Frames_SLL),length(Frames_SLL,N_SLL), I_SLL is Progress mod N_SLL, nth0(I_SLL,Frames_SLL,Frame_SLL),
  213		spinner(SLR,Frames_SLR),length(Frames_SLR,N_SLR), I_SLR is Progress mod N_SLR, nth0(I_SLR,Frames_SLR,Frame_SLR),
  214		spinner(SCL,Frames_SCL),length(Frames_SCL,N_SCL), I_SCL is Progress mod N_SCL, nth0(I_SCL,Frames_SCL,Frame_SCL),
  215		spinner(SCR,Frames_SCR),length(Frames_SCR,N_SCR), I_SCR is Progress mod N_SCR, nth0(I_SCR,Frames_SCR,Frame_SCR),
  216		spinner(SRL,Frames_SRL),length(Frames_SRL,N_SRL), I_SRL is Progress mod N_SRL, nth0(I_SRL,Frames_SRL,Frame_SRL),
  217		spinner(SRR,Frames_SRR),length(Frames_SRR,N_SRR), I_SRR is Progress mod N_SRR, nth0(I_SRR,Frames_SRR,Frame_SRR),
  218
  219		MetaTabSpec = "~~~w|~~w~~w~~w~~~w|~~w~~w~~w~~~w|~~w~~w~~w",
  220		format(atom(TabSpec),MetaTabSpec,[PosL,PosC,PosR])
  221	},
  222	[TabSpec-[Frame_SLL,TL,Frame_SLR,Frame_SCL,TC,Frame_SCR,Frame_SRL,TR,Frame_SRR]].
 simple_progress_bar(+Index:int, +Total:int)// is det
simple_progress_bar renders a progress bar, and the percentage completed
  227simple_progress_bar(Index,Total) --> 
  228	{
  229		IntroText = '',
  230		Percentage is (Index/Total) * 100, format(string(OutroText),"[~0f%]",[Percentage]),
  231		StartMarker = '[',
  232		StartText = '',
  233		DoneChar = '*',
  234		DoneText = '',
  235		TodoText = '',
  236		TodoChar = ' ',
  237		EndText = '',
  238		EndMarker = ']'
  239	},
  240	progress_bar(Index,Total,IntroText,OutroText,StartMarker,StartText,DoneChar,DoneText,TodoText,TodoChar,EndText,EndMarker).
 default_progress_bar(+Index:int, +Total:int, IntroText:text, OutroText:text)// is det
default_progress_bar renders a progress bar, including an IntroText, OutroText (that may be dynamically updated)
  244default_progress_bar(Index,Total,IntroText,OutroText) --> 
  245	{
  246		StartMarker = '[',
  247		StartText = '',
  248		DoneChar = '=',
  249		DoneText = '>',
  250		TodoText = '',
  251		TodoChar = ' ',
  252		EndText = '',
  253		EndMarker = ']'
  254	},
  255	progress_bar(Index,Total,IntroText,OutroText,StartMarker,StartText,DoneChar,DoneText,TodoText,TodoChar,EndText,EndMarker).
 fancy_progress_bar(+Index:int, +Total:int, IntroText:text, OutroText:text, StartText, TodoText:text, EndText:text)// is det
fancy_progress_bar renders a progress bar, including an IntroText, OutroText, StartText, TodoText and EndText (that may be dynamically updated)
  259fancy_progress_bar(Index,Total,IntroText,OutroText,StartText,TodoText,EndText) -->
  260	{
  261		StartMarker = '\u2503',		% ┃
  262		DoneChar = '\u25A0',		% ■
  263		DoneText = '\u25BA',		% ►
  264		TodoChar = '\u25A1',		% □
  265		EndMarker = '\u2503'		% ┃
  266	},
  267	progress_bar(Index,Total,IntroText,OutroText,StartMarker,StartText,DoneChar,DoneText,TodoText,TodoChar,EndText,EndMarker).
 progress_bar(+Index:int, +Total:int, +IntroText:text, +OutroText:text, +StartMarker:char, +StartText:text, +DoneChar:char, +DoneText:text, +TodoText:text, +TodoChar:char, +EndText:text, +EndMarker:char)// is det
progress_bar renders the progress of a process using the full width of the terminal where Index represent the current advancement, and Total represent completion. (i.e. Index =< Total)

The layout of the bar is setup according to the following schema:

Intro [Start+++++++++++++++><---------End] Outro
  301% @fixme: IntroText, OutroText,StartText etc should be messages (or strings)	
  302progress_bar(Index,Total,IntroText,OutroText,StartMarker,StartText,DoneChar,DoneText,TodoText,TodoChar,EndText,EndMarker) --> 
  303	{
  304		must_be(nonneg,Index),
  305		must_be(nonneg,Total),
  306        must_be(any,IntroText), (atomic(IntroText) -> IntroTextStr = IntroText ; message_to_string(IntroText,IntroTextStr)),
  307        must_be(any,OutroText), (atomic(OutroText) -> OutroTextStr = OutroText ; message_to_string(OutroText,OutroTextStr)),
  308		must_be(char,StartMarker),
  309        must_be(any,StartText), (atomic(StartText) -> StartTextStr = StartText ; message_to_string(StartText,StartTextStr)),
  310        must_be(char,DoneChar),
  311        must_be(any,DoneText), (atomic(DoneText) -> DoneTextStr = DoneText ; message_to_string(DoneText,DoneTextStr)),
  312        must_be(any,TodoText), (atomic(TodoText) -> TodoTextStr = TodoText ; message_to_string(TodoText,TodoTextStr)),
  313        must_be(char,TodoChar),
  314        must_be(any,EndText), (atomic(EndText) -> EndTextStr = EndText ; message_to_string(EndText,EndTextStr)),
  315        must_be(char,EndMarker)
  316	},
  317	remove_line_content,
  318	prefix_line,
  319	full_width_bar(Index,Total,IntroTextStr,OutroTextStr,StartMarker,StartTextStr,DoneChar,DoneTextStr,TodoTextStr,TodoChar,EndTextStr,EndMarker),
  320	finished(Index,Total).
  321
  322remove_line_content --> [at_same_line,'\r'].
  323prefix_line --> ['% '].
  324finished(Total,Total) --> !,[nl].
  325finished(_,_) --> [flush].
  326
  327
  328% Renders an instance of the progress_bar using the full width of the terminal
  329full_width_bar(Index,Total,IntroText,OutroText,StartMarker,StartText,DoneChar,DoneText,TodoText,TodoChar,EndText,EndMarker) --> 
  330    {
  331    	tty_size(_,W0),
  332        Width is W0 - 2, % '% ' prefix
  333        StartPosition = 0 
  334    },
  335    render_bar(StartPosition,Width,Index,Total,IntroText,StartMarker,StartText,DoneChar,DoneText,TodoText,TodoChar,EndText,EndMarker,OutroText).
  336
  337% Renders a profress_bar of Width starting at StartPosition
  338render_bar(StartPosition,Width,Index,Total,IntroText,StartMarker,StartText,DoneChar,DoneText,TodoText,TodoChar,EndText,EndMarker,OutroText) -->
  339    {
  340    	must_be(nonneg,StartPosition),
  341        must_be(nonneg,Width),
  342        string_length(IntroText,LIntroText),
  343        string_length(StartMarker,LStartMarker),
  344        string_length(EndMarker,LEndMarker),
  345        string_length(OutroText,LOutroText),
  346
  347        BarWidth is Width - LIntroText - LStartMarker - LEndMarker - LOutroText, 
  348        (Index == Total -> % for rounding errors
  349        	(DoneWidth = BarWidth, TodoWidth = 0) 
  350        	;
  351        	(
  352        		DoneWidth is floor(Index * (BarWidth / Total)),
  353        		TodoWidth is BarWidth - DoneWidth
  354        	)
  355        )
  356        %debug(progress_bar,"progress:~w, Width:~w, BarWidth:~w, DoneWidth:~w, TodoWidth:~w",[Index/Total,Width,BarWidth,DoneWidth,TodoWidth])
  357    },
  358    do_render_bar(StartPosition,DoneWidth,TodoWidth,IntroText,StartMarker,StartText,DoneChar,DoneText,TodoText,TodoChar,EndText,EndMarker,OutroText).
 do_render_bar(+StartPosition:int, +DoneWidth:int, +ToDoWidth:int, +StartMarker, +StartText:text, +DoneChar:char, +DoneText:text, +TodoText:text, +TodoChar:char, +EndText:text, +EndMarker:char)// is det
render_bar does the actual rendering: It generates Template for format/3, and processes the arguments StartPosition represents the position to start the rendering DoneWidth represents the length (in characters) of the Done area TodoWidth represents the length (in characters) of the Todo area
  370do_render_bar(StartPosition,DoneWidth,TodoWidth,IntroText,StartMarker,StartText,DoneChar,DoneText,TodoText,TodoChar,EndText,EndMarker,OutroText) -->
  371    {
  372        must_be(nonneg,DoneWidth),
  373        must_be(nonneg,TodoWidth),
  374        progress_text(StartText,DoneWidth,DoneChar,DoneText,TodoText,TodoChar,TodoWidth,EndText,ProgressText),
  375        MetaTabSpec = '~~~w|~w~w~w~w~w',
  376        format(atom(TabSpec),MetaTabSpec,[StartPosition,IntroText,StartMarker,ProgressText,EndMarker,OutroText]) 
  377   },
  378    [TabSpec].
  379
  380repeat_string(_,0,"") :- !.
  381repeat_string(Str,1,Str) :- !.
  382repeat_string(Str,N,Result) :-
  383	NN is N - 1,
  384	repeat_string(Str,NN,Result0),
  385	string_concat(Str,Result0,Result).
  386
  387reverse_string(Str,StrR) :-	
  388	string_codes(Str,Cs),
  389	reverse(Cs,CsR),
  390	string_codes(StrR,CsR).
  391
  392super_impose_left(Base,Super,Result) :-
  393	super_impose(Base,Super,Result).
  394
  395super_impose_right(Base,Super,Result) :-
  396	reverse_string(Base,BaseR),
  397	reverse_string(Super,SuperR),
  398	super_impose(BaseR,SuperR,ResultR),
  399	reverse_string(ResultR,Result).
  400
  401super_impose(Base,Super,Result) :-
  402	normalise_text(Base,BaseN),
  403	normalise_text(Super,SuperN),
  404	string_codes(BaseN,BaseCs),
  405	string_codes(SuperN,SuperCs),
  406	super_impose_codes(BaseCs,SuperCs,ResultCs),
  407	string_codes(Result,ResultCs).
  408
  409super_impose_codes([],[],[]) :- !.
  410super_impose_codes(BaseCs,[],BaseCs) :- !.
  411super_impose_codes([],SuperCs,SuperCs) :- !.
  412
  413super_impose_codes([BaseC|BaseCs],[SuperC|SuperCs],[BaseC|ResultCs]) :-
  414	code_type(SuperC,white),!,	% @FIXME 
  415	super_impose_codes(BaseCs,SuperCs,ResultCs).
  416
  417super_impose_codes([_|BaseCs],[SuperC|SuperCs],[SuperC|ResultCs]) :-
  418	super_impose_codes(BaseCs,SuperCs,ResultCs).
  419
  420normalise_text(Str,StrN) :-
  421	atom_codes(Str, Cs),
  422   	phrase(normalise_text(StrN), Cs, []).
  425normalise_text(Text) --> normalise_chars(Cs),{atom_codes(Text,Cs)}.
  426normalise_chars(NCs) --> normalise_char(C), normalise_chars(Cs),!,{append(C,Cs,NCs)}.
  427normalise_chars([]) --> !.
  428
  429normalise_char(Cs) --> "\t",{atom_codes("   ",Cs)},!.
  430normalise_char(Cs) --> "\r",{atom_codes("",Cs)},!.
  431normalise_char(Cs) --> "\f",{atom_codes("",Cs)},!.
  432normalise_char(Cs) --> "\240",{atom_codes(" ",Cs)},!. % non-breaking space
  433
  434normalise_char([C]) --> [C],!.
  435
  436progress_text(StartText,DoneWidth,DoneChar,DoneText,TodoText,TodoChar,TodoWidth,EndText,ProgressText) :-
  437	done_bar(DoneWidth,DoneChar,DoneText,DoneBar),
  438	todo_bar(TodoWidth,TodoChar,TodoText,TodoBar),
  439	string_concat(DoneBar,TodoBar,Bar0),
  440	super_impose(Bar0,StartText,Bar1),
  441	super_impose_right(Bar1,EndText,ProgressText).
  442
  443todo_bar(TodoWidth,TodoChar,TodoText,TodoBar) :-
  444	reverse_string(TodoText,RTodoText),
  445	done_bar(TodoWidth,TodoChar,RTodoText,RTodoBar),
  446	reverse_string(RTodoBar,TodoBar).
  447
  448done_bar(DoneWidth,_DoneChar,DoneText,DoneBar) :-
  449	string_length(DoneText,N),
  450	DoneWidth =< N,!,
  451	sub_string(DoneText, _, DoneWidth, 0, DoneBar).
  452
  453done_bar(DoneWidth,DoneChar,DoneText,DoneBar) :-
  454	string_length(DoneText,N),
  455	DoneN is DoneWidth - N,
  456	repeat_string(DoneChar,DoneN,DoneChars),
  457	string_concat(DoneChars,DoneText,DoneBar)