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