1/*
    2 * Part of plml: Prolog-Matlab interface
    3 * Copyright Samer Abdallah (Queen Mary University of London; UCL) 2004-2015
    4 *
    5 *	This program is free software; you can redistribute it and/or
    6 *	modify it under the terms of the GNU General Public License
    7 *	as published by the Free Software Foundation; either version 2
    8 *	of the License, or (at your option) any later version.
    9 *
   10 *	This program is distributed in the hope that it will be useful,
   11 *	but WITHOUT ANY WARRANTY; without even the implied warranty of
   12 *	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   13 *	GNU General Public License for more details.
   14 *
   15 *	You should have received a copy of the GNU General Public
   16 *	License along with this library; if not, write to the Free Software
   17 *	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
   18 */
   19
   20:- module(plml_utils, 
   21	[	compileoptions/2
   22	,	multiplot/2
   23	,  mhelp/1
   24	,	op(550,xfx,..)		% range of integers
   25	]).   26	
   27
   28:- multifile user:optionset/2.

Prolog-Matlab utilities

*/

   35:- use_module(library(plml_core)).   36:- use_module(library(plml_dcg)).   37
   38:- set_prolog_flag(back_quotes,symbol_char).   39:- set_prolog_flag(double_quotes,codes).   40
   41
   42% for dealing with option lists
 mhelp(+Name:atom) is det
Lookup Matlab help on the given name. Equivalent to executing help(`X).
   46mhelp(X) :- ml_exec(ml,help(q(X))).
 compileoptions(+Opts:list(ml_options), -Prefs:ml_expr(options)) is det
Convert list of option specifiers into a Matlab expression representing options (ie a struct). Each specifier can be a Name:Value pair, a name to be looked up in the optionset/2 predicate, a nested list of ml_options compileoptions :: list (optionset | atom:value | struct) -> struct. NB. option types are as follows:
X :: ml_options :- optionset(X,_).
X :: ml_options :- X :: ml_option(_).
X :: ml_options :- X :: list(ml_options).
X :: ml_options :- X :: ml_expr(struct(_)).

ml_option(A) ---> atom:ml_expr(A).
   65compileoptions(Opts,Prefs) :-
   66	rec_optslist(Opts,OptsList),
   67	Prefs=..[prefs|OptsList].
   68
   69rec_optslist([],[]).
   70rec_optslist([H|T],L) :-
   71	( % mutually exclusive types for H
   72		optionset(H,Opts1) -> rec_optslist(Opts1,Opts)
   73	;  H=Name:Value       -> Opts=[`Name,Value]
   74	;	is_list(H)         -> rec_optslist(H,Opts) 
   75	; /* assume struct */    Opts=[H]
   76	),
   77	rec_optslist(T,TT),
   78	append(Opts,TT,L).
   79
   80rtimes(X,Y,Z) :-
   81	( var(X) -> X is Z/Y
   82	; var(Y) -> Y is Z/X
   83	;           Z is X*Y).
   84
   85					
   86% Execute several plots as subplots. The layout can be
   87% vertical, horizontal, or explicity given as Rows*Columns.
   88
   89
   90% mplot is a private procedure used by multiplot
   91mplot(subplot(H,W),N,Plot,Ax) :- ?? (subplot(H,W,N); Plot), Ax===gca.
   92mplot(figure,N,Plot,Ax) :- ?? (figure(N); Plot), Ax===gca.
   93
   94%% multiplot(+Type:ml_plot, +Cmds:list(ml_expr(_))) is det.
   95%% multiplot(+Type:ml_plot, +Cmds:list(ml_expr(_)), -Axes:list(ml_val(handle))) is det.
   96%
   97%  Executes plotting commands in Cmds in multiple figures or axes as determined
   98%  by Type. Valid types are:
   99%    * figs(Range)
  100%      Executes each plot in a separate figure, Range must be P..Q where P 
  101%      and Q are figure numbers.
  102%    * vertical
  103%      Executes each plot in a subplot; 
  104%      subplots are arranged vertically top to bottom in the current figure.
  105%    * horizontal
  106%      Executes each plot in a subplot; 
  107%      subplots are arranged horizontally left to right in the current figure.
  108%    * [Type, link(Axis)]
  109%      As for multplot type Type, but link X or Y axis scales as determined by Axis,
  110%      which can be `x, `y, or `xy.
  111%
  112%  Three argument form returns a list containing the Matlab handles to axes objects,
  113%  one for each plot.
  114multiplot(Type,Plots) :- multiplot(Type,Plots,_).
  115
  116multiplot([Layout|Opts],Plots,Axes) :- !,
  117	multiplot(Layout,Plots,Axes),
  118	member(link(A),Opts) ->
  119		?? (linkaxes(Axes,`off); hide(linkaxes(Axes,`A)))
  120	;	true.
  121
  122multiplot(figs(P..Q),Plots,Axes) :- !,
  123	length(Plots,N),
  124	between(1,inf,P), Q is P+N-1,
  125	numlist(P,Q,PlotNums),
  126	maplist(mplot(figure),PlotNums,Plots,Axes).
  127	
  128multiplot(Layout,Plots,Axes) :-
  129	length(Plots,N),
  130	member(Layout:H*W,[vertical:N*1, horizontal:1*N, H*W:H*W]),
  131	rtimes(H,W,N), % bind any remaining variables
  132	numlist(1,N,PlotNums),
  133	maplist(mplot(subplot(H,W)),PlotNums,Plots,Axes).
 optionset(+Key:term, -Opts:list(ml_options)) is semidet
Extensible predicate for mapping arbitrary terms to a list of options to be processed by compileoptions/2.
  141%user:portray(A|B) :- print(A), write('|'), print(B).
  142%user:portray(Z) :- mlWSNAME(Z,N,ID), format('<~w:~w>',[ID,N]).