Mercurial > hg > dml-open-cliopatria
comparison cpack/dml/lib/mlfigs.pl @ 0:718306e29690 tip
commiting public release
author | Daniel Wolff |
---|---|
date | Tue, 09 Feb 2016 21:05:06 +0100 |
parents | |
children |
comparison
equal
deleted
inserted
replaced
-1:000000000000 | 0:718306e29690 |
---|---|
1 :- module(mlfigs, [ml_fig/6, ml_fig/5,ml_post/3, ml_opts/3]). | |
2 | |
3 %:- use_module(library(dcg_core)). | |
4 :- use_module(library(dcg_pair)). | |
5 :- use_module(library(computations),[unzip/3, (*)/4]). | |
6 :- use_module(library(mlserver)). | |
7 :- use_module(library(optutils)). | |
8 | |
9 % ------- tools for building matlab charts ------- | |
10 ml_fig(Type,XL,YL,Datasets,F) :- ml_fig(Type,XL,YL,Datasets,[],F). | |
11 ml_fig(Type,XL,YL,Datasets,Opts,fig(Code;xlabel(q(XL));ylabel(q(YL)),Opts1)) :- | |
12 unzip(Datasets,Names,Data), | |
13 maplist(term_to_atom*atom_string,Names,Labels), | |
14 compile(Type,Labels,Data,Opts,Opts1,Cmds,[]), | |
15 sequence(Cmds,Code). | |
16 | |
17 ml_post(Code,fig(Code0),fig(Code0;Code)). | |
18 ml_post(Code,fig(Code0,O),fig(Code0;Code,O)). | |
19 ml_opts(Opts,fig(Code),fig(Code,Opts)). | |
20 ml_opts(Opts,fig(Code,Opts0), fig(Code,Opts1)) :- | |
21 merge_options(Opts,Opts0,Opts1). | |
22 | |
23 | |
24 compile(T,Names,Data,Opts,Opts1) --> | |
25 plot(T,Data), | |
26 {option_default_select(legend(Pos),best,Opts,Opts1)}, | |
27 [box("off"), set(gca,"TickDir","out")], | |
28 ( {Pos=off} -> [] | |
29 ; [legend(cell(Names),"Location",q(Pos), | |
30 "LineWidth",0.25*get(gcf,"DefaultAxesLineWidth"))] | |
31 ). | |
32 | |
33 sequence([C],C) :- !. | |
34 sequence([C1|Cs],C1;Ss) :- sequence(Cs,Ss). | |
35 | |
36 pairs_to_cell(Pairs,{X,Y}) :- unzip(Pairs,X,Y). | |
37 | |
38 plot(bars,Data) --> plot(bars(grouped),Data). | |
39 plot(bars(Arr),Data) --> plot(multi((x,y,varargin)\\bar(x,y,q(Arr),"EdgeColor","none",cref(varargin,[':']))),Data). | |
40 plot(areas,Data) --> plot(multi(@area),Data). | |
41 plot(multi(Fn),Data) --> | |
42 {length(Data,L)}, | |
43 {maplist(pairs_to_cell,Data,Cells)}, | |
44 [multibar(Fn,cell(Cells)),caxis([1,L+1])]. | |
45 plot(scat(T,Ms),Points) --> | |
46 hold(run_left(foldl(scat(T,Ms),Points),0,N)), | |
47 [caxis([1,N+1])]. | |
48 plot(lines,Points) --> | |
49 {length(Points,N)}, | |
50 hold(run_left(foldl(line(N),Points),0,_)). | |
51 | |
52 scat(o,Ms,Points) --> | |
53 \< (succ, dcg_core:get(N)), | |
54 {unzip(Points,X,Y), length(Points,L), nth1(N,Ms,M)}, | |
55 \> [scatter(X,Y,get(gcf,"DefaultLineMarkerSize").^2,repmat(N,L,1),M)]. | |
56 scat(f,Ms,Points) --> | |
57 \< (succ, dcg_core:get(N)), | |
58 {unzip(Points,X,Y), length(Points,L), nth1(N,Ms,M)}, | |
59 \> [scatter(X,Y,get(gcf,"DefaultLineMarkerSize").^2,repmat(N,L,1),M,"filled")]. | |
60 | |
61 scat(p,Ms,Points) --> | |
62 \< (succ, dcg_core:get(N)), {marker(N,M)}, | |
63 {unzip(Points,X,Y)}, | |
64 {nth1(N,Ms,M)}, | |
65 \> [scat(arr([X,Y]),"marker",M)]. | |
66 | |
67 line(N,Xs-Ys) --> | |
68 \< (succ, dcg_core:get(I)), | |
69 \> [plot(Xs,Ys,"-","Color",row(get(gcf,"Colormap"),floor(I/N)))]. | |
70 | |
71 marker(N,M) :- | |
72 I is N mod 5, | |
73 nth0(I,["r.","g.","c.","b.","m."],M). | |
74 | |
75 hold(G) --> [newplot,hold("on")], phrase(G), [hold("off")]. |