Prolog "plot"

Admin User, created Apr 23. 2025
         
/**
* Modern Albufeira Prolog Interpreter
*
* Warranty & Liability
* To the extent permitted by applicable law and unless explicitly
* otherwise agreed upon, XLOG Technologies AG makes no warranties
* regarding the provided information. XLOG Technologies AG assumes
* no liability that any problems might be solved with the information
* provided by XLOG Technologies AG.
*
* Rights & License
* All industrial property rights regarding the information - copyright
* and patent rights in particular - are the sole property of XLOG
* Technologies AG. If the company was not the originator of some
* excerpts, XLOG Technologies AG has at least obtained the right to
* reproduce, change and translate the information.
*
* Reproduction is restricted to the whole unaltered document. Reproduction
* of the information is only allowed for non-commercial uses. Selling,
* giving away or letting of the execution of the library is prohibited.
* The library can be distributed as part of your applications and libraries
* for execution provided this comment remains unchanged.
*
* Restrictions
* Only to be distributed with programs that add significant and primary
* functionality to the library. Not to be distributed with additional
* software intended to replace any components of the library.
*
* Trademarks
* Jekejeke is a registered trademark of XLOG Technologies AG.
*/
:- ensure_loaded(library(aggregate)).
:- ensure_loaded(library(util/format)).
:- ensure_loaded(library(misc/vector)).
/*******************************************************************/
/* Non-Progressive Plotting */
/*******************************************************************/
/**
* plot(D, L):
* plot(S, D, L):
* The predicate succeeds. As a side effect a line plot for the data D
* and plotting options L is created as a SVG graphics element. The
* ternary predicate allows specifying a markup writer S.
*/
% plot(+List, +List)
plot(D, Opts) :-
current_output(S),
plot(S, D, Opts).
% plot(+Stream, List, +List)
plot(S, D, Opts) :-
aggregate_all((min(X), max(X), min(A), max(B)),
(member([X|Ys], D), sys_plot_bound(Ys, A, B)),
(MinX2, MaxX2, MinY2, MaxY2)),
sys_plot_opts(Opts, v(100-100, ['line mark'|'line2 mark2']-
['line'|'line2'], w(MinX2-MaxX2,MinY2-MaxY2), ''-L),
v(Width-Height,Mark-Line,w(MinMaxX,MinMaxY), Css-[])),
svg_begin(S, [height(Height),width(Width),css(Css)|L]),
sys_plot_x_axis(MinMaxX, MinMaxY, Width, Height, S),
sys_plot_y_axis(MinMaxX, MinMaxY, Width, Height, S),
sys_plot_data(MinMaxX, MinMaxY, D, Width, Height, Mark, Line, S),
svg_end(S).
% sys_plot_bound(+List, -Number, -Number)
sys_plot_bound(Ys, MinY, MaxY) :-
aggregate_all((min(Y), max(Y)), member(Y, Ys), (MinY, MaxY)).
/*******************************************************************/
/* Progressive Plotting */
/*******************************************************************/
/**
* plot_begin(L):
* plot_begin(S, L):
* The predicate succeeds. As a side effect the axes for the plotting
* options L are created as a SVG graphics element. The binary predicate
* allows specifying a markup writer S.
*/
% plot_begin(+List)
plot_begin(Opts) :-
current_output(S),
plot_begin(S, Opts).
% plot_begin(+Stream, +List)
plot_begin(S, Opts) :-
sys_plot_opts(Opts, v(100-100, ['line mark'|'line2 mark2']-
['line'|'line2'], w((-1.0)-1.0,(-1.0)-1.0), ''-L),
v(Width-Height,_,w(MinMaxX,MinMaxY), Css-[])),
svg_begin(S, [height(Height),width(Width),css(Css)|L]),
sys_plot_x_axis(MinMaxX, MinMaxY, Width, Height, S),
sys_plot_y_axis(MinMaxX, MinMaxY, Width, Height, S),
svg_group_begin(S, 0.0, 0.0, 0.0).
/**
* plot_add(D, L):
* plot_add(S, D, L):
* The predicate succeeds. As a side effect a line plot for the data
* D and plotting options L is added to the SVG graphics element. The
* ternary predicate allows specifying a markup writer S.
*/
% plot_add(+List, +List)
plot_add(D, Opts) :-
current_output(S),
plot_add(S, D, Opts).
% plot_add(+Stream, +List, +List)
plot_add(S, D, Opts) :-
sys_plot_opts(Opts, v(100-100, ['line mark'|'line2 mark2']-
['line'|'line2'], w((-1.0)-1.0,(-1.0)-1.0), ''-_),
v(Width-Height,Mark-Line,w(MinMaxX,MinMaxY), _-[])),
sys_plot_data(MinMaxX, MinMaxY, D, Width, Height, Mark, Line, S).
/**
* plot_end:
* plot_end(S):
* The predicate succeeds as a side effect the SVG graphics element is
* closed. The unary predicate allows specifying a markup writer S.
*/
% plot_end
plot_end :-
current_output(S),
plot_end(S).
% plot_end(+Stream)
plot_end(S) :-
svg_group_end(S),
svg_end(S).
/*******************************************************************/
/* Axis Plotting */
/*******************************************************************/
/**
* sys_plot_x_axis(MinMaxX, MinMaxY, Width, Height, S):
* The predicate succeeds. As a side effect an x-axis is rendered.
*/
% sys_plot_x_axis(+Pair, +Pair, +Number, +Number, +Stream)
sys_plot_x_axis(MinX-MaxX, MinMaxY, Width, Height, S) :-
sys_coord_y_svg(MinMaxY, 0, SY, Height),
svg_line(S, 25, SY, (5*Width-25), SY, [class(pen)]),
SY2 is SY+5,
sys_plot_axis_prec(MinX-MaxX, Format),
between(0, 24, I),
X is MinX+I*(MaxX-MinX)/24,
sys_coord_x_svg(MinX-MaxX, X, SX, Width),
svg_line(S, SX, SY, SX, SY2, [class(pen)]),
(I mod 3 =:= 0 ->
format_atom(Format, [X], A),
SY3 is SY+17,
svg_text(S, SX, SY3, A, [class('label x-axis')]);
true),
fail.
sys_plot_x_axis(_, _, _, _, _).
/**
* sys_plot_y_axis(MinMaxX, MinMaxY, Width, Height, S):
* The predicate succeeds. As a side effect an y-axis is rendered.
*/
% sys_plot_y_axis(+Pair, +Pair, +Number, +Number, +Stream)
sys_plot_y_axis(MinMaxX, MinY-MaxY, Width, Height, S) :-
sys_coord_x_svg(MinMaxX, 0, SX, Width),
svg_line(S, SX, 25, SX, (4*Height-25), [class(pen)]),
SX2 is SX-5,
sys_plot_axis_prec(MinY-MaxY, Format),
between(0, 20, I),
Y is MinY+I*(MaxY-MinY)/20,
sys_coord_y_svg(MinY-MaxY, Y, SY, Height),
svg_line(S, SX2, SY, SX, SY, [class(pen)]),
(I mod 5 =:= 0 ->
format_atom(Format, [Y], A),
SY2 is SY+5, SX3 is SX-7,
svg_text(S, SX3, SY2, A, [class('label y-axis')]);
true),
fail.
sys_plot_y_axis(_, _, _, _, _).
% sys_plot_axis_prec(+Pair, -Atom)
sys_plot_axis_prec(Min-Max, '~2f') :- abs(Min) < 1, abs(Max) < 1, !.
sys_plot_axis_prec(Min-Max, '~1f') :- abs(Min) < 10, abs(Max) < 10, !.
sys_plot_axis_prec(_, '~0f').
/*******************************************************************/
/* Data Plotting */
/*******************************************************************/
/**
* sys_plot_data(MinMaxX, MinMaxY, D, Width, Height, Mark, Line, S):
* The predicate succeeds. As a side effect an data lines and marks
* for the data D are rendered.
*/
% sys_plot_data(+Pair, +Pair, +List, +Number, +Number, +Atom, +Atom, +Stream)
sys_plot_data(MinMaxX, MinMaxY, D, Width, Height, _, Line, S) :-
append(_, [[X2|Y2s],[X|Ys]|_], D),
sys_coord_x_svg(MinMaxX, X2, SX2, Width),
sys_coord_y_svg_list(MinMaxY, Y2s, SY2s, Height),
sys_coord_x_svg(MinMaxX, X, SX, Width),
sys_coord_y_svg_list(MinMaxY, Ys, SYs, Height),
sys_plot_data_lines(SY2s, SX2, SYs, SX, Line, S),
fail.
sys_plot_data(MinMaxX, MinMaxY, D, Width, Height, Mark, _, S) :-
member([X|Ys], D),
sys_coord_x_svg(MinMaxX, X, SX, Width),
sys_coord_y_svg_list(MinMaxY, Ys, SYs, Height),
sys_plot_data_marks(SYs, SX, Mark, S),
fail.
sys_plot_data(_, _, _, _, _, _, _, _).
% sys_plot_data_lines(+List, +Number, +List, +Number, +Atom, +Stream)
sys_plot_data_lines([], _, [], _, _, _).
sys_plot_data_lines([SY2|SY2s], SX2, [SY|SYs], SX, [Line|Lines], S) :- !,
sys_plot_data_line(SX2, SY2, SX, SY, Line, S),
sys_plot_data_lines(SY2s, SX2, SYs, SX, Lines, S).
sys_plot_data_lines([SY2|SY2s], SX2, [SY|SYs], SX, Line, S) :-
sys_plot_data_line(SX2, SY2, SX, SY, Line, S),
sys_plot_data_lines(SY2s, SX2, SYs, SX, Line, S).
% sys_plot_data_line(+Number, +Number, +Number, +Number, +Atom, +Stream)
sys_plot_data_line(_, _, _, _, '', _) :- !.
sys_plot_data_line(SX2, SY2, SX, SY, Line, S) :-
svg_line(S, SX2, SY2, SX, SY, [class(Line)]).
% sys_plot_data_marks(+List, +Number, +Term, +Stream)
sys_plot_data_marks([], _, _, _).
sys_plot_data_marks([SY|SYs], SX, [Mark|Marks], S) :- !,
sys_plot_data_mark(SX, SY, Mark, S),
sys_plot_data_marks(SYs, SX, Marks, S).
sys_plot_data_marks([SY|SYs], SX, Mark, S) :-
sys_plot_data_mark(SX, SY, Mark, S),
sys_plot_data_marks(SYs, SX, Mark, S).
% sys_plot_data_mark(+Number, +Number, +Atom, +Stream)
sys_plot_data_mark(_, _, '', _) :- !.
sys_plot_data_mark(SX, SY, Mark, S) :-
svg_circle(S, SX, SY, 3, [class(Mark)]).
/*******************************************************************/
/* Calculations */
/*******************************************************************/
% sys_coord_x_svg(+Pair, +Number, -Number, +Number)
sys_coord_x_svg(MinX-MaxX, X, SX, Width) :-
SX is 25+(5*Width-50)*(X-MinX)/(MaxX-MinX).
% sys_coord_y_svg(+Pair, +Number, -Number, +Number)
sys_coord_y_svg(MinY-MaxY, Y, SY, Height) :-
SY is (4*Height-25)-(4*Height-50)*(Y-MinY)/(MaxY-MinY).
% sys_coord_y_svg_list(+Pair, +List, -List, +Number)
sys_coord_y_svg_list(_, [], [], _).
sys_coord_y_svg_list(MinMaxY, [Y|Ys], [SY|SYs], Height) :-
sys_coord_y_svg(MinMaxY, Y, SY, Height),
sys_coord_y_svg_list(MinMaxY, Ys, SYs, Height).
/*******************************************************************/
/* Plot Options */
/*******************************************************************/
/**
* sys_plot_opts(L, F, G):
* The predicate succeeds in G with the options L starting with defaults F.
*/
% sys_plot_opts(+List, +Quad, -Quad)
sys_plot_opts(V, _, _) :- var(V),
throw(error(instantiation_error,_)).
sys_plot_opts([X|L], I, O) :- !,
sys_plot_opt(X, I, H),
sys_plot_opts(L, H, O).
sys_plot_opts([], H, H) :- !.
sys_plot_opts(L, _, _) :-
throw(error(type_error(list,L),_)).
% sys_plot_opt(+Option, +Quad, -Quad)
sys_plot_opt(V, _, _) :- var(V),
throw(error(instantiation_error,_)).
sys_plot_opt(width(W), v(_-H,E,F,G), v(W-H,E,F,G)) :- !.
sys_plot_opt(height(H), v(W-_,E,F,G), v(W-H,E,F,G)) :- !.
sys_plot_opt(mark(A), v(D,_-B,F,G), v(D,A-B,F,G)) :- !.
sys_plot_opt(line(B), v(D,A-_,F,G), v(D,A-B,F,G)) :- !.
sys_plot_opt(minx(M), v(D,E,w(_-Q,Y),G), v(D,E,w(M-Q,Y),G)) :- !.
sys_plot_opt(maxx(M), v(D,E,w(P-_,Y),G), v(D,E,w(P-M,Y),G)) :- !.
sys_plot_opt(miny(M), v(D,E,w(X,_-Q),G), v(D,E,w(X,M-Q),G)) :- !.
sys_plot_opt(maxy(M), v(D,E,w(X,P-_),G), v(D,E,w(X,P-M),G)) :- !.
sys_plot_opt(css(R), v(D,E,F,_-L), v(D,E,F,R-L)) :- !.
sys_plot_opt(class(C), v(D,E,F,R-[class(C)|L]), v(D,E,F,R-L)) :- !.
sys_plot_opt(style(S), v(D,E,F,R-[style(S)|L]), v(D,E,F,R-L)) :- !.
sys_plot_opt(O, _, _) :-
throw(error(type_error(plot_option,O),_)).