view cpack/dml/examples/visuals.pl @ 0:718306e29690 tip

commiting public release
author Daniel Wolff
date Tue, 09 Feb 2016 21:05:06 +0100
parents
children
line wrap: on
line source
:- use_module(library(mlserver)).
:- use_module(library(semweb/rdf_label)).
:- use_module(components(matlab)).
:- use_module(components(audio)).
:- use_module(components(score)).
:- use_rendering(matlab,[size(12,8),cache(true)]).
:- use_rendering(html).

%:- include(search).

/** <examples>
 ?- test_plot(X).
 ?- test_html(X).
 ?- X=html(\figure(??bar(rand(10,1)),5,3)), Y=fig(plot(1:10),5,3), hold.
 ?- ml_fig(??bar(1:10),5,3), ml_fig(??plot(sin(0:0.05:12)),5,3).
 ?- finder_player(title(brandenburg),Player).
 ?- finder_player(title('prelude and fugue')/\composer(bach),Player).
 ?- R::title(prelude)/\title(cello)/\humdrum, 
 	X=html(\score(R,150)),
    Y=html(\score_audio_player(R)).
          
*/

bar(Opts,X-Y,Fig) :- decorate(fig(bar(X,Y),15,5),Opts,Fig).
plot(Opts,X-Y,Fig) :- decorate(fig(plot(X,Y),15,5),Opts,Fig).
                                             
ml_fig(Cmd,W,H) :- write_html(\figure(Cmd,W,H)).

decorate(fig(Cmd,W,H),Opts,fig(Cmd2,W,H)) :-
    (   option(labels(XL,YL),Opts)
    ->	Cmd1 = (Cmd;xlabel(q(XL));ylabel(q(YL)))
    ;   Cmd1 = Cmd
    ),
    (   option(title(T),Opts)
    ->	Cmd2 = (Cmd1;title(q(T)))  
    ;   Cmd2 = Cmd1
    ).


/* Note that there is a subtle problem which affects
 * the use of the figure//3 HTML component: the first argument
 * is a module-qualified goal, and gets tagged with the name
 * of the module created to run the current pengine query.
 * The component results in an HTML IMAGE element whos
 * URL encodes the goal and its module. If the pengine query
 * has terminated by the time the image URL is dereferenced,
 * the call fails. Thus, to make this work with write_html/1
 * you need either a delay (eg sleep(3)) after the call, to allow
 * the image to render before the query terminates, or you need
 * to introduce some nondeterminism so that the query remains 
 * active. To make it work with html term rendering, only the 
 * non-determinism method will work. To do this, you can add the
 * following hold as a final goal - it succeeds but leaves a choice point.
 */
hold :- true; fail.

test_plot(fig(plot(X,X.^2))) :- X= -1:0.01:1.

test_html(html(span([b(hello),' ',i(world)]))).
test_html(html(\figure(??imagesc(magic(5)),3,3))).
test_html(_) :- fail.