view cpack/dml/api/matlab.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
/* Part of DML (Digital Music Laboratory)
	Copyright 2014-2015 Samer Abdallah, University of London
	 
	This program is free software; you can redistribute it and/or
	modify it under the terms of the GNU General Public License
	as published by the Free Software Foundation; either version 2
	of the License, or (at your option) any later version.

	This program is distributed in the hope that it will be useful,
	but WITHOUT ANY WARRANTY; without even the implied warranty of
	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
	GNU General Public License for more details.

	You should have received a copy of the GNU General Public
	License along with this library; if not, write to the Free Software
	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
*/

:- module(api_matlab, []).

:- use_module(library(http/http_dispatch)).
:- use_module(library(http/http_parameters)).
:- use_module(library(sandbox)).
:- use_module(library(insist)).
:- use_module(library(fileutils)).
:- use_module(library(swipe)).
:- use_module(library(httpfiles)).
:- use_module(library(mlserver)).

:- set_prolog_flag(double_quotes,string).
:- set_prolog_flag(back_quotes,symbol_char).

:- http_handler(api(matlab/render), figure_render, []).

:- setting(matlab:pixels_per_inch,number,150,"Pixels per inch for in browser figures").
:- setting(matlab:default_figure_format,oneof([png,svg]),svg,"Default Matlab figure rendering method").

:- initialization catch(mutex_create(_,[alias(matlab_fig)]),Ex,print_message(warning,Ex)).

%% figure_render(+Request) is det.
%
%  HTTP handler for rendering Matlab figures.
figure_render(Request) :-
   setting(matlab:pixels_per_inch,DefPPI),
   http_parameters(Request,
      [ code(CodeA,[ atom, optional(false), description("Prolog rendering goal")])
      , format(F, [ oneof([eps,svg,pdf,png]), optional(false), description("Output format") ]) 
      , width(W,  [ number, optional(true), default(10), description("Width in cm")])
      , height(H, [ number, optional(true), default(6), description("Height in cm")])
      , color_map(CMA, [ atom, optional(true), default(hot) ])
      , font_name(FN,  [ atom, optional(true), default(helvetica) ])
      , font_size(FS,  [ number, optional(true), default(8) ])
      , line_width(LW, [ number, optional(true), default(0.75) ])
      , marker_size(MS,[ number, optional(true), default(4) ])
      , ppi(PPI,       [ number, optional(true), default(DefPPI), description("PNG resolution")])
      ]),
   debug(matlab,"Attempting to parse \"~s\".",[CodeA]),
   atom_to_term(CodeA,Code,[]),
   atom_to_term(CMA,CM,[]),
   (  user_db:logged_on(A)
   -> debug(matlab,"Logged on as ~w, no checking",[A])
   ;  debug(matlab,"Checking ~q for safety...",[Code]),
      sandbox:safe_goal(Code),
      debug(matlab,"Goal is safe.",[])
   ),
   insist(with_temp_dir(Dir, (
      render(F,Code,Dir, [  size(W,H), ppi(PPI),color_map(CM),line_width(LW)
                         ,  font_name(FN),font_size(FS),marker_size(MS) ]),
      atom_concat('tmp_.',F,Out),
      absolute_file_name(Dir/Out,File),
      reply_file(File,F)
   ))).


render(eps,Code,D,Opts) :- with_mutex(matlab_fig,print_fig(Code,D,Opts,'-depsc2')).
render(pdf,Code,D,Opts) :- render(eps,Code,D,Opts), run(in(D,sh(0>>0, "epstopdf tmp_.eps"))).
render(svg,Code,D,Opts) :- render(pdf,Code,D,Opts), run(in(D,sh(0>>0, "pdf2svg tmp_.pdf tmp_.svg"))).
render(png,Code,D,Opts) :- 
   render(eps,Code,D,Opts),
   option(ppi(PPI),Opts),
   run(in(D,sh(0>>0, "gs -dBATCH -dNumRenderingThreads=2 -dEPSCrop -dNOPAUSE -sDEVICE=pngalpha -sOutputFile=tmp_.png -r~d -q tmp_.eps",[\PPI]))).

render_fig(Code,Opts) :-
   option(color_map(ColorMap),Opts),
   option(font_name(FontName),Opts),
   option(font_size(FontSize),Opts),
   option(line_width(LineWidth),Opts),
   option(marker_size(MarkerSize),Opts),
   option(colour(Colour),Opts,1),
   option(axes_line_width_ratio(LWR),Opts,0.5),
   option(figure(Fig),Opts,99),
   ml_async(exec( dml_paperfig(Fig,`FontName,FontSize,LineWidth,Colour,MarkerSize,LWR);
                  colormap(ColorMap)),20),
   debug(matlab,'Calling: ~q',[Code]),
   with_output_to(string(_),call(Code)).

print_fig(Code,Dir,Opts,PrintOpt) :-
   render_fig(Code,Opts),
   debug(matlab,'Saving figure to ~w',[Dir]),
   absolute_file_name(Dir/'tmp_',Name),
   (  option(size(Width,Height),Opts)
   -> ml_async(exec(dml_fsetup(Width,Height,`centimeters)),20)
   ;  true),
   ml_async(exec(print(`PrintOpt,`Name)),120).