samer@0
|
1 /*
|
samer@0
|
2 * Prolog part of Prolog-Matlab interface
|
samer@1
|
3 * Version 1
|
samer@0
|
4 *
|
samer@0
|
5 * Samer Abdallah (2004-2012)
|
samer@0
|
6 * Centre for Digital Music, QMUl.
|
samer@0
|
7 */
|
samer@0
|
8
|
samer@0
|
9 :- module(plml,
|
samer@0
|
10 [ ml_open/1 % (+Id)
|
samer@0
|
11 , ml_open/2 % (+Id, +Host)
|
samer@0
|
12 , ml_open/3 % (+Id, +Host, +Options)
|
samer@0
|
13 , ml_close/1 % (+Id)
|
samer@0
|
14
|
samer@0
|
15 , ml_exec/2 % (+Id, +Expr)
|
samer@0
|
16 , ml_eval/4 % (+Id, +Expr, +Types, -Vals)
|
samer@0
|
17 , ml_test/2 % (+Id, +Expr)
|
samer@0
|
18
|
samer@0
|
19 , (??)/1 % (+Expr) ~execute Matlab expression
|
samer@0
|
20 , (???)/1 % (+Expr) ~test Matlab boolean expression
|
samer@0
|
21 , (===)/2 % (-Vals,+Expr) ~evaluate Matlab expression
|
samer@0
|
22
|
samer@0
|
23 , term_mlstring/3 % (+Id, +Expr, -String) ~Prolog term to Matlab string
|
samer@0
|
24 , term_texatom/2 % (+Expr, -Atom) ~Prolog term to TeX expression
|
samer@0
|
25 , wsvar/3 % (+WSBlob, -Name, -Id)
|
samer@0
|
26
|
samer@0
|
27 % MATBASE
|
samer@0
|
28 , persist_item/2 % (+Expr,-Expr) ~ convert volatile subterms to persistent form
|
samer@0
|
29 , matbase_mat/2 % (+Dir, -Loc) ~ Find matbase MAT files
|
samer@0
|
30 , dropmat/2 % (+Id, +Loc) ~ remove MAT file from matbase
|
samer@0
|
31 , exportmat/3 % (+Id, +Loc, +Dir) ~ export MAT file from matbase
|
samer@0
|
32
|
samer@0
|
33
|
samer@0
|
34 % Utilities
|
samer@0
|
35 , compileoptions/2
|
samer@0
|
36 , multiplot/2
|
samer@0
|
37 , mhelp/1
|
samer@0
|
38
|
samer@37
|
39 , op(650,fy,'`') % quoting things
|
samer@37
|
40 , op(160,xf,'``') % postfix transpose operator
|
samer@0
|
41 , op(100,fy,@) % function handles
|
samer@0
|
42
|
samer@0
|
43 % note slightly reduced precedence of array operators -
|
samer@0
|
44 % hope this doesn't break everything...
|
samer@0
|
45 , op(210,xfy,.^) % array exponentiation
|
samer@0
|
46 , op(410,yfx,.*) % array times
|
samer@0
|
47 , op(410,yfx,./) % array division
|
samer@0
|
48 , op(410,xfy,.\) % reverse array division
|
samer@0
|
49 , op(400,xfy,\) % reverse matrix division
|
samer@0
|
50 , op(700,xfx,===) % variable binding/assignment in matlab query
|
samer@0
|
51 , op(700,xfx,:==) % variable binding/assignment in matlab query
|
samer@0
|
52 , op(951,fx,??) % evaluate term as matlab
|
samer@0
|
53 , op(951,fx,???) % evaluate term as matlab boolean
|
samer@0
|
54 , op(100,yfx,#) % field indexing (note left-associativity)
|
samer@0
|
55 , op(750,fy,\\) % thunk abdstraction
|
samer@0
|
56 , op(750,xfy,\\) % lambda abdstraction
|
samer@0
|
57
|
samer@0
|
58 % exported after being imported from ops
|
samer@0
|
59 , op(1100,xfx,::) % type specification (esp for arrays)
|
samer@37
|
60 , op(550,xfx,..) % range of integers
|
samer@0
|
61 ]).
|
samer@0
|
62
|
samer@0
|
63
|
samer@0
|
64 :- multifile(user:optionset/2).
|
samer@0
|
65 :- multifile(user:matlab_path/2).
|
samer@0
|
66 :- multifile(user:matlab_init/2).
|
samer@0
|
67 :- multifile(user:pl2ml_hook/2).
|
samer@0
|
68
|
samer@0
|
69
|
samer@0
|
70 /** <module> Prolog-Matlab interface
|
samer@0
|
71
|
samer@0
|
72 ---++++ Types
|
samer@0
|
73
|
samer@0
|
74 *|ml_eng|* - Any atom identifying a Matlab engine.
|
samer@0
|
75
|
samer@0
|
76 *|ml_stmt|* - A Matlab statement
|
samer@0
|
77 ==
|
samer@0
|
78 X;Y :: ml_stmt :- X:ml_stmt, Y:ml_stmt.
|
samer@0
|
79 X,Y :: ml_stmt :- X:ml_stmt, Y:ml_stmt.
|
samer@0
|
80 X=Y :: ml_stmt :- X:ml_lval, Y:ml_expr.
|
samer@0
|
81 hide(X) :: ml_stmt :- X:ml_stmt.
|
samer@0
|
82 ==
|
samer@0
|
83
|
samer@0
|
84 ==
|
samer@0
|
85 ml_expr(A) % A Matlab expression, possibly with multiple return values
|
samer@0
|
86 ml_loc ---> mat(atom,atom). % Matbase locator
|
samer@0
|
87 ==
|
samer@0
|
88
|
samer@0
|
89 ---++++ Matlab expression syntax
|
samer@0
|
90
|
samer@0
|
91 The Matlab expression syntax adopted by this module allows Prolog terms to represent
|
samer@0
|
92 or denote Matlab expressions. Let T be the domain of recognised Prolog terms (corresponding to
|
samer@0
|
93 the type ml_expr), and M be the domain of Matlab expressions written in Matlab syntax.
|
samer@0
|
94 Then V : T->M is the valuation function which maps Prolog term X to Matlab expression V[X].
|
samer@0
|
95 These are some of the constructs it recognises:
|
samer@0
|
96
|
samer@0
|
97 Constructs valid only in top level statements, not subexpressions:
|
samer@0
|
98 ==
|
samer@0
|
99 X;Y % |--> V[X]; V[Y] (sequential evaluation hiding first result)
|
samer@0
|
100 X,Y % |--> V[X], V[Y] (sequential evaluation displaying first result)
|
samer@0
|
101 X=Y % |--> V[X]=V[Y] (assignment, X must denote a valid left-value)
|
samer@0
|
102 hide(X) % |--> V[X]; (execute X but hide return value)
|
samer@32
|
103 if(X,Y) % |--> if V[X], V[Y], end
|
samer@32
|
104 if(X,Y,Z) % |--> if V[X], V[Y], else V[Z], end
|
samer@0
|
105 ==
|
samer@0
|
106
|
samer@0
|
107 Things that look and work like Matlab syntax (more or less):
|
samer@0
|
108 ==
|
samer@0
|
109 +X % |--> uplus(V[X])
|
samer@0
|
110 -X % |--> uminus(V[X])
|
samer@0
|
111 X+Y % |--> plus(V[X],V[Y])
|
samer@0
|
112 X-Y % |--> minus(V[X],V[Y])
|
samer@0
|
113 X^Y % |--> mpower(V[X],V[Y])
|
samer@0
|
114 X*Y % |--> mtimes(V[X],V[Y])
|
samer@0
|
115 X/Y % |--> mrdivide(V[X],V[Y])
|
samer@0
|
116 X\Y % |--> mldivide(V[X],V[Y])
|
samer@0
|
117 X.^Y % |--> power(V[X],V[Y])
|
samer@0
|
118 X.*Y % |--> times(V[X],V[Y])
|
samer@0
|
119 X./Y % |--> rdivide(V[X],V[Y])
|
samer@0
|
120 X.\Y % |--> ldivide(V[X],V[Y])
|
samer@0
|
121 X:Y:Z % |--> colon(V[X],V[Y],V[Z])
|
samer@0
|
122 X:Z % |--> colon(V[X],V[Z])
|
samer@0
|
123 X>Z % |--> gt(V[X],V[Y])
|
samer@0
|
124 X>=Z % |--> ge(V[X],V[Y])
|
samer@0
|
125 X<Z % |--> lt(V[X],V[Y])
|
samer@0
|
126 X=<Z % |--> le(V[X],V[Y])
|
samer@0
|
127 X==Z % |--> eq(V[X],V[Y])
|
samer@0
|
128 [X1,X2,...] % |--> [ V[X1], V[X2], ... ]
|
samer@0
|
129 [X1;X2;...] % |--> [ V[X1]; V[X2]; ... ]
|
samer@0
|
130 {X1,X2,...} % |--> { V[X1], V[X2], ... }
|
samer@0
|
131 {X1;X2;...} % |--> { V[X1]; V[X2]; ... }
|
samer@0
|
132 @X % |--> @V[X] (function handle)
|
samer@0
|
133 ==
|
samer@0
|
134
|
samer@0
|
135 Things that do not look like Matlab syntax but provide standard Matlab features:
|
samer@0
|
136 ==
|
samer@0
|
137 'Infinity' % |--> inf (positive infinity)
|
samer@0
|
138 'Nan' % |--> nan (not a number)
|
samer@0
|
139 X`` % |--> ctranpose(V[X]) (conjugate transpose, V[X]')
|
samer@0
|
140 X#Y % |--> getfield(V[X],V[q(Y)])
|
samer@0
|
141 X\\Y % |--> @(V[X])V[Y] (same as lambda(X,Y))
|
samer@0
|
142 \\Y % |--> @()V[Y] (same as thunk(Y))
|
samer@0
|
143 lambda(X,Y) % |--> @(V[X])V[Y] (anonymous function with arguments X)
|
samer@0
|
144 thunk(Y) % |--> @()V[Y] (anonymous function with no arguments)
|
samer@0
|
145 vector(X) % |--> horzcat(V[X1],V[X2], ...)
|
samer@0
|
146 atvector(X) % as vector but assumes elements of X are assumed all atomic
|
samer@0
|
147 cell(X) % construct 1xN cell array from elements of X
|
samer@0
|
148 `X % same as q(X)
|
samer@0
|
149 q(X) % wrap V[X] in single quotes (escaping internal quotes)
|
samer@0
|
150 qq(X) % wrap V[X] in double quotes (escaping internal double quotes)
|
samer@0
|
151 tq(X) % wrap TeX expression in single quotes (escape internal quotes)
|
samer@0
|
152 ==
|
samer@0
|
153
|
samer@0
|
154 Referencing different value representations.
|
samer@0
|
155 ==
|
samer@0
|
156 mat(X,Y) % denotes a value in the Matbase using a dbload expression
|
samer@0
|
157 mx(X:mx_blob) % denotes an MX Matlab array in SWI memory
|
samer@0
|
158 ws(X:ws_blob) % denotes a variable in a Matlab workspace
|
samer@0
|
159 wsseq(X:ws_blob) % workspace variable containing list as cell array.
|
samer@0
|
160 ==
|
samer@0
|
161
|
samer@0
|
162 Tricky bits.
|
samer@0
|
163 ==
|
samer@0
|
164 apply(X,AX) % X must denote a function or array, applied to list of arguments AX.
|
samer@0
|
165 cref(X,Y) % cell dereference, |--> V[X]{ V[Y1], V[Y2], ... }
|
samer@0
|
166 arr(Lists) % multidimensional array from nested lists.
|
samer@0
|
167 arr(Lists,Dims) % multidimensional array from nested lists.
|
samer@0
|
168 ==
|
samer@0
|
169
|
samer@0
|
170 Things to bypass default formatting
|
samer@0
|
171 ==
|
samer@0
|
172 noeval(_) % triggers a failure when processed
|
samer@0
|
173 atom(X) % write atom X as write/1
|
samer@0
|
174 term(X) % write term X as write/1
|
samer@0
|
175 \(P) % escape and call phrase P directly to generate Matlab string
|
samer@0
|
176 $(X) % calls pl2ml_hook/2, denotes V[Y] where plml_hook(X,Y).
|
samer@0
|
177 '$VAR'(N) % gets formatted as p_N where N is assumed to be atomic.
|
samer@0
|
178 ==
|
samer@0
|
179
|
samer@0
|
180 All other Prolog atoms are written using write/1, while other Prolog terms
|
samer@0
|
181 are assumed to be calls to Matlab functions named according to the head functor.
|
samer@0
|
182 Thus V[ <head>( <arg1>, <arg2>, ...) ] = <head>(V[<arg1>, V[<arg2>], ...).
|
samer@0
|
183
|
samer@0
|
184 There are some incompatibilities between Matlab syntax and Prolog syntax,
|
samer@0
|
185 that is, syntactic structures that Prolog cannot parse correctly:
|
samer@0
|
186
|
samer@0
|
187 * 'Command line' syntax, ie where a function of string arguments:
|
samer@0
|
188 "save('x','Y')" can be written as "save x Y" in Matlab,
|
samer@0
|
189 but in Prolog, you must use function call syntax with quoted arguments:
|
samer@0
|
190 save(`x,`'Y').
|
samer@0
|
191
|
samer@0
|
192 * Matlab's postfix transpose operator "x'" must be written using a different
|
samer@0
|
193 posfix operator "x``" or function call syntax "ctranspose(x)".
|
samer@0
|
194
|
samer@0
|
195 * Matlab cell referencing using braces, as in x{1,2} must be written
|
samer@0
|
196 as "cref(x,1,2)".
|
samer@0
|
197
|
samer@0
|
198 * Field referencing using dot (.), eg x.thing - currently resolved
|
samer@0
|
199 by using hash (#) operator, eg x#thing.
|
samer@0
|
200
|
samer@0
|
201 * Using variables as arrays and indexing them. The problem is that
|
samer@0
|
202 Prolog doesn't let you write a term with a variable as the head
|
samer@0
|
203 functor.
|
samer@0
|
204
|
samer@0
|
205
|
samer@0
|
206 @tbd
|
samer@0
|
207
|
samer@0
|
208 Use mat(I) and tmp(I) as types to include engine Id.
|
samer@0
|
209
|
samer@0
|
210 Clarify relationship between return values and valid Matlab denotation.
|
samer@0
|
211
|
samer@0
|
212 Reshape/2 array representation: reshape([ ... ],Size)
|
samer@0
|
213 Expression language: arr(Vals,Shape,InnerFunctor) - allows efficient
|
samer@0
|
214 representation of arrays of arbitrary things. Will require more strict
|
samer@0
|
215 nested list form.
|
samer@0
|
216
|
samer@0
|
217 Deprecate old array(Vals::Type) and cell(Vals::Type) left-value syntax.
|
samer@0
|
218
|
samer@0
|
219 Remove I from ml_expr//2 and add to mx type?
|
samer@0
|
220 */
|
samer@0
|
221
|
samer@0
|
222 :- use_module(library(apply_macros)).
|
samer@37
|
223 :- use_module(library(dcg_core)).
|
samer@37
|
224 :- use_module(library(dcg_codes)).
|
samer@37
|
225
|
samer@37
|
226 :- set_prolog_flag(back_quotes,symbol_char).
|
samer@37
|
227 :- set_prolog_flag(double_quotes,codes).
|
samer@0
|
228
|
samer@0
|
229 :- op(700,xfx,===). % variable binding/assignment in matlab query
|
samer@0
|
230 :- op(951,fx,??). % evaluate term as matlab
|
samer@0
|
231 :- op(951,fx,???). % evaluate term as matlab boolean
|
samer@0
|
232 :- op(650,fy,`). % quoting things
|
samer@0
|
233 :- op(160,xf,``). % postfix transpose operator
|
samer@0
|
234 :- op(100,fy,@). % function handles
|
samer@0
|
235 :- op(200,xfy,.^). % array exponentiation
|
samer@0
|
236 :- op(410,yfx,.*). % array times
|
samer@0
|
237 :- op(410,yfx,./). % array division
|
samer@0
|
238 :- op(410,xfy,.\). % array reverse division
|
samer@0
|
239 :- op(400,xfy,\). % matrix reverse division
|
samer@0
|
240 :- op(100,yfx,#). % field indexing (note left-associativity)
|
samer@0
|
241
|
samer@27
|
242 :- dynamic current_engine/1.
|
samer@0
|
243
|
samer@27
|
244 :- use_foreign_library(foreign(plml)).
|
samer@27
|
245 :- initialization(at_halt(ml_closeall)).
|
samer@19
|
246
|
samer@19
|
247 ml_closeall :-
|
samer@27
|
248 forall(current_engine(Id), ml_close(Id)).
|
samer@0
|
249
|
samer@0
|
250
|
samer@37
|
251 % from utils.pl
|
samer@37
|
252 bt_call(Do,Undo) :- Do, (true ; once(Undo), fail).
|
samer@37
|
253 user:goal_expansion( bt_call(Do,Undo), (Do, (true; once(Undo), fail))).
|
samer@37
|
254
|
samer@0
|
255 %% matlab_init( -Key, -Cmd:ml_expr) is nondet.
|
samer@0
|
256 % Each user-defined clause of matlab_init/2 causes Cmd to be executed
|
samer@0
|
257 % whenever a new Matlab session is started.
|
samer@0
|
258
|
samer@0
|
259 %% matlab_path( -Key, -Path:list(atom)) is nondet.
|
samer@0
|
260 % Each user-defined clause of matlab_path/2 causes the directories in Path
|
samer@0
|
261 % to be added to the Matlab path of every new Matlab session. Directories
|
samer@24
|
262 % are relative to the root directory where padd.m is found.
|
samer@0
|
263
|
samer@0
|
264 %% pl2ml_hook(+X:term,-Y:ml_expr) is nondet.
|
samer@0
|
265 % Clauses of pl2ml_hook/2 allow for extensions to the Matlab expression
|
samer@0
|
266 % language such that =|V[$X] = V[Y]|= if =|pl2ml_hook(X,Y)|=.
|
samer@0
|
267
|
samer@0
|
268
|
samer@0
|
269
|
samer@0
|
270 %% ml_open(+Id:ml_eng,+Host:atom,+Options:list(_)) is det.
|
samer@0
|
271 %% ml_open(+Id:ml_eng, +Host:atom) is det.
|
samer@0
|
272 %% ml_open(+Id:ml_eng) is det.
|
samer@0
|
273 %
|
samer@0
|
274 % Start a Matlab session on the given host. If Host=localhost
|
samer@0
|
275 % or the name of the current current host as returned by hostname/1,
|
samer@0
|
276 % then a Matlab process is started directly. Otherwise, it is
|
samer@0
|
277 % started remotely via SSH. Options defaults to []. Host defaults to
|
samer@0
|
278 % localhost.
|
samer@0
|
279 %
|
samer@0
|
280 % Start a Matlab session on the specified host using default options.
|
samer@0
|
281 % If Host is not given, it defaults to localhost. Session will be
|
samer@0
|
282 % associated with the given Id, which should be an atom. See ml_open/3.
|
samer@0
|
283 %
|
samer@31
|
284 % Valid options are below. Note that matlab is always called with
|
samer@31
|
285 % the -nodesktop and -nosplash options.
|
samer@31
|
286 % * noinit
|
samer@31
|
287 % If present, do not run initialisation commands specified by
|
samer@31
|
288 % matlab_path/2 and matlab_init/2 clauses. Otherwise, do run them.
|
samer@0
|
289 % * debug(In,Out)
|
samer@0
|
290 % if present, Matlab is started in a script which captures standard
|
samer@15
|
291 % input and output to files In and Out respectively. (tbd)
|
samer@31
|
292 % * cmd(Cmd:atom)
|
samer@31
|
293 % Call Cmd as the matlab executable. Default is 'matlab' (i.e. search
|
samer@37
|
294 % for matlab on the PATH). Can be used to select a different executable
|
samer@31
|
295 % or to add command line options.
|
samer@31
|
296 % * awt(Flag:bool)
|
samer@31
|
297 % If false (default), call Matlab with -noawt option. Otherwise, Java graphics
|
samer@31
|
298 % will be available.
|
samer@0
|
299
|
samer@0
|
300 ml_open(Id) :- ml_open(Id,localhost,[]).
|
samer@0
|
301 ml_open(Id,Host) :- ml_open(Id,Host,[]).
|
samer@0
|
302 ml_open(Id,Host,Options) :-
|
samer@27
|
303 ground(Id),
|
samer@0
|
304 options_flags(Options,Flags),
|
samer@30
|
305 option(cmd(Bin),Options,matlab),
|
samer@35
|
306 ( (Host=localhost;hostname(Host))
|
samer@30
|
307 -> format(atom(Exec),'exec ~w',[Bin]) % using exec fixes Ctrl-C bug
|
samer@35
|
308 ; format(atom(Exec),'ssh ~w ~w',[Host,Bin])
|
samer@0
|
309 ),
|
samer@0
|
310 ( member(debug(In,Out),Options)
|
samer@19
|
311 -> debug(plml,'Running Matlab with protocol logging.',[]),
|
samer@19
|
312 debug(plml,'| Prolog > Matlab logged to "~w"',[In]),
|
samer@19
|
313 debug(plml,'| Prolog < Matlab logged to "~w"',[Out]),
|
samer@19
|
314 absolute_file_name(foreign(logio),Spy,[access(read)]),
|
samer@19
|
315 format(atom(Exec1),'~w ~w ~w ~w',[Spy,In,Out,Exec])
|
samer@0
|
316 ; Exec1=Exec
|
samer@0
|
317 ),
|
samer@18
|
318 format(atom(Cmd),'~w ~w',[Exec1,Flags]),
|
samer@20
|
319 debug(plml,'About to start Matlab with: ~w',[Cmd]),
|
samer@0
|
320 mlOPEN(Cmd,Id),
|
samer@24
|
321 addpath(db),
|
samer@27
|
322 assert(current_engine(Id)),
|
samer@0
|
323 ( member(noinit,Options) -> true
|
samer@0
|
324 ; forall( matlab_path(_,Dir), maplist(nofail(addpath),Dir)),
|
samer@0
|
325 forall( matlab_init(_,Cmd), nofail(Cmd))
|
samer@0
|
326 ).
|
samer@0
|
327
|
samer@0
|
328 addpath(local(D)) :- !, ml_exec(ml,padl(q(D))).
|
samer@0
|
329 addpath(D) :- !, ml_exec(ml,padd(q(D))).
|
samer@0
|
330
|
samer@0
|
331 %% ml_close(+Id:ml_eng) is det.
|
samer@0
|
332 % Close Matlab session associated with Id.
|
samer@27
|
333 ml_close(Id) :- ground(Id), mlCLOSE(Id), retract(current_engine(Id)).
|
samer@0
|
334
|
samer@0
|
335 nofail(P) :- catch(ignore(call(P)), E, print_message(warning,E)).
|
samer@0
|
336 nofail(P,X) :- catch(ignore(call(P,X)), E, print_message(warning,E)).
|
samer@0
|
337
|
samer@31
|
338 options_flags(Opts,Flags) :-
|
samer@31
|
339 option(awt(AWT),Opts,false),
|
samer@31
|
340 ( AWT=true
|
samer@31
|
341 -> Flags='-nodesktop -nosplash'
|
samer@31
|
342 ; Flags='-nodesktop -nosplash -noawt'
|
samer@31
|
343 ).
|
samer@0
|
344
|
samer@0
|
345
|
samer@0
|
346 %% ml_exec(+Id:ml_eng, +Expr:ml_expr) is det.
|
samer@0
|
347 %
|
samer@0
|
348 % Execute Matlab expression without returning any values.
|
samer@0
|
349 ml_exec(Id,X) :-
|
samer@0
|
350 term_mlstring(Id,X,C), !,
|
samer@20
|
351 debug(plml,'plml:ml_exec>> ~s',[C]),
|
samer@0
|
352 mlEXEC(Id,C).
|
samer@0
|
353
|
samer@0
|
354 %% ml_eval(+Id:ml_eng, +Expr:ml_expr, +Types:list(type), -Res:list(ml_val)) is det.
|
samer@0
|
355 %
|
samer@0
|
356 % Evaluate Matlab expression binding return values to results list Res. This new
|
samer@0
|
357 % form uses an explicit output types list, so Res can be completely unbound on entry
|
samer@0
|
358 % even when multiple values are required.
|
samer@0
|
359 ml_eval(Id,X,Types,Vals) :-
|
samer@0
|
360 maplist(alloc_ws(Id),Types,Vars),
|
samer@13
|
361 ml_exec(Id,hide(wsx(Vars)=X)),
|
samer@0
|
362 maplist(convert_ws,Types,Vars,Vals).
|
samer@0
|
363
|
samer@0
|
364 alloc_ws(I,_,Z) :- mlWSALLOC(I,Z).
|
samer@0
|
365
|
samer@0
|
366 %% ml_test(+Id:ml_eng, +X:ml_expr(bool)) is semidet.
|
samer@0
|
367 % Succeeds if X evaluates to true in Matlab session Id.
|
samer@0
|
368 ml_test(Id,X) :- ml_eval(Id,X,[bool],[1]).
|
samer@0
|
369
|
samer@0
|
370
|
samer@0
|
371
|
samer@0
|
372 %% ===(Y:ml_vals(A), X:ml_expr(A)) is det.
|
samer@0
|
373 % Evaluate Matlab expression X as in ml_eval/4, binding one or more return values
|
samer@0
|
374 % to Y. If Y is unbound or a single ml_val(_), only the first return value is bound.
|
samer@0
|
375 % If Y is a list, multiple return values are processed.
|
samer@0
|
376 Y === X :-
|
samer@0
|
377 ( is_list(Y)
|
samer@0
|
378 -> maplist(leftval,Y,TX,VX), ml_eval(ml,X,TX,VX)
|
samer@0
|
379 ; leftval(Y,T,V), ml_eval(ml,X,[T],[V])
|
samer@0
|
380 ).
|
samer@0
|
381
|
samer@0
|
382 %% leftval( +TVal:tagged(T), -T:type, -Val:T) is det.
|
samer@0
|
383 % True if TVal is a tagged value whos type is T and value is Val.
|
samer@0
|
384 leftval( ws(X), ws, ws(X)).
|
samer@0
|
385 leftval( mx(X), mx, mx(X)).
|
samer@0
|
386 leftval( float(X), float, X).
|
samer@0
|
387 leftval( int(X), int, X).
|
samer@0
|
388 leftval( bool(X), bool, X).
|
samer@0
|
389 leftval( atom(X), atom, X).
|
samer@0
|
390 leftval( term(X), term, X).
|
samer@0
|
391 leftval( string(X), string,X).
|
samer@0
|
392 leftval( mat(X), mat, X).
|
samer@0
|
393 leftval( tmp(X), tmp, X).
|
samer@0
|
394 leftval( loc(X), loc, X).
|
samer@0
|
395 leftval( wsseq(X), wsseq, wsseq(X)).
|
samer@0
|
396 leftval( list(T,X), list(T), X).
|
samer@0
|
397 leftval( array(X::[Size->Type]), array(Type,Size), X) :- !.
|
samer@0
|
398 leftval( array(X::[Size]), array(float,Size), X) :- !.
|
samer@0
|
399 leftval( cell(X::[Size->Type]), cell(Type,Size), X) :- !.
|
samer@0
|
400 leftval( cell(X::[Size]), cell(mx,Size), X) :- !.
|
samer@0
|
401 leftval( Val:Type, Type, Val).
|
samer@0
|
402
|
samer@0
|
403
|
samer@0
|
404 %% ??(X:ml_expr(_)) is det.
|
samer@0
|
405 % Execute Matlab expression X as with ml_exec/2, without returning any values.
|
samer@0
|
406 ?? X :- ml_exec(ml,X).
|
samer@0
|
407
|
samer@0
|
408 %% ???(X:ml_expr(bool)) is semidet.
|
samer@0
|
409 % Evaluate Matlab boolean expression X as with ml_test/2.
|
samer@0
|
410 ??? Q :- ml_test(ml,Q).
|
samer@0
|
411
|
samer@0
|
412
|
samer@0
|
413 /*
|
samer@0
|
414 * DCG for term to matlab conversion
|
samer@0
|
415 * the big problem with Matlab syntax is that you cannot always replace
|
samer@0
|
416 * a name representing a value with an expression that reduces to that
|
samer@0
|
417 * value. Eg
|
samer@0
|
418 * X=magic(5), X(3,4)
|
samer@0
|
419 * is ok, but
|
samer@0
|
420 * (magic(5))(3,4)
|
samer@0
|
421 * is not. Similarly x=@sin, x(0.5) but not (@sin)(0.5)
|
samer@0
|
422 * This is really infuriating.
|
samer@0
|
423 */
|
samer@0
|
424
|
samer@0
|
425
|
samer@0
|
426 % top level statement rules
|
samer@0
|
427 stmt(I,hide(A)) --> !, stmt(I,A), ";".
|
samer@0
|
428 stmt(I,(A;B)) --> !, stmt(I,A), ";", stmt(I,B).
|
samer@0
|
429 stmt(I,(A,B)) --> !, stmt(I,A), ",", stmt(I,B).
|
samer@0
|
430 stmt(I,A=B) --> !, ml_expr(I,A), "=", ml_expr(I,B).
|
samer@32
|
431 stmt(I,if(A,B)) --> !, "if ",ml_expr(I,A), ", ", stmt(I,B), ", end".
|
samer@32
|
432 stmt(I,if(A,B,C)) --> !, "if ",ml_expr(I,A), ", ", stmt(I,B), ", else ", stmt(I,C), ", end".
|
samer@0
|
433 stmt(I,Expr) --> !, ml_expr(I,Expr).
|
samer@0
|
434
|
samer@0
|
435
|
samer@0
|
436 %% ml_expr(+Id:ml_eng,+X:ml_expr(A))// is nondet.
|
samer@0
|
437 % Convert Matlab expression as a Prolog term to string representation.
|
samer@37
|
438 ml_expr(_,\X) --> !, phrase(X).
|
samer@0
|
439 ml_expr(I,$X) --> !, {pl2ml_hook(X,Y)}, ml_expr(I,Y).
|
samer@0
|
440 ml_expr(I,q(X)) --> !, q(stmt(I,X)).
|
samer@0
|
441 ml_expr(I,qq(X)) --> !, qq(stmt(I,X)).
|
samer@0
|
442 ml_expr(_,tq(X)) --> !, q(pl2tex(X)).
|
samer@0
|
443 ml_expr(_,atom(X)) --> !, atm(X).
|
samer@0
|
444 ml_expr(_,term(X)) --> !, wr(X). % this could be dangerous
|
samer@0
|
445 ml_expr(_,mat(X,Y)) --> !, "dbload(", loc(X,Y), ")".
|
samer@0
|
446 ml_expr(_,loc(L)) --> !, { L=mat(X,Y) }, loc(X,Y).
|
samer@0
|
447 ml_expr(I,mx(X)) --> !, { mlWSALLOC(I,Z), mlWSPUT(Z,X) }, ml_expr(I,ws(Z)).
|
samer@0
|
448 ml_expr(I,ws(A)) --> !, { mlWSNAME(A,N,I) }, atm(N).
|
samer@0
|
449 ml_expr(I,wsx([A|B])) --> !, { mlWSNAME(A,N,I) }, "[", atm(N), wsx(B), "]".
|
samer@0
|
450 ml_expr(I,wsseq(A)) --> !, { mlWSNAME(A,N,I) }, atm(N).
|
samer@0
|
451 ml_expr(_,noeval(_)) --> !, {fail}. % causes evaluation to fail.
|
samer@0
|
452
|
samer@0
|
453 ml_expr(_,'Infinity') --> !, "inf".
|
samer@0
|
454 ml_expr(_,'Nan') --> !, "nan".
|
samer@0
|
455
|
samer@0
|
456 ml_expr(I,A+B) --> !, "plus", args(I,A,B).
|
samer@0
|
457 ml_expr(I,A-B) --> !, "minus", args(I,A,B).
|
samer@0
|
458 ml_expr(I, -B) --> !, "uminus", args(I,B).
|
samer@0
|
459 ml_expr(I, +B) --> !, "uplus", args(I,B).
|
samer@0
|
460 ml_expr(I,A^B) --> !, "mpower", args(I,A,B).
|
samer@0
|
461 ml_expr(I,A*B) --> !, "mtimes", args(I,A,B).
|
samer@0
|
462 ml_expr(I,A/B) --> !, "mrdivide", args(I,A,B).
|
samer@0
|
463 ml_expr(I,A\B) --> !, "mldivide", args(I,A,B).
|
samer@0
|
464 ml_expr(I,A.^B)--> !, "power", args(I,A,B).
|
samer@0
|
465 ml_expr(I,A.*B)--> !, "times", args(I,A,B).
|
samer@0
|
466 ml_expr(I,A./B)--> !, "rdivide", args(I,A,B).
|
samer@0
|
467 ml_expr(I,A.\B)--> !, "ldivide", args(I,A,B).
|
samer@0
|
468 ml_expr(I,A>B) --> !, "gt",args(I,A,B).
|
samer@0
|
469 ml_expr(I,A<B) --> !, "lt",args(I,A,B).
|
samer@0
|
470 ml_expr(I,A>=B)--> !, "ge",args(I,A,B).
|
samer@0
|
471 ml_expr(I,A=<B)--> !, "le",args(I,A,B).
|
samer@0
|
472 ml_expr(I,A==B)--> !, "eq",args(I,A,B).
|
samer@0
|
473 ml_expr(I,A:B) --> !, range(I,A,B).
|
samer@0
|
474
|
samer@0
|
475 ml_expr(_,[]) --> !, "[]".
|
samer@0
|
476 ml_expr(_,{}) --> !, "{}".
|
samer@0
|
477 ml_expr(I,[X]) --> !, "[", matrix(v,I,X), "]".
|
samer@0
|
478 ml_expr(I,[X|XX]) --> !, "[", ml_expr(I,X), seqmap(do_then_call(",",ml_expr(I)),XX), "]".
|
samer@0
|
479 ml_expr(I,{X}) --> !, "{", matrix(_,I,X), "}".
|
samer@0
|
480
|
samer@0
|
481 ml_expr(I, `B) --> !, q(stmt(I,B)).
|
samer@0
|
482 ml_expr(I,A#B) --> !, "getfield", args(I,A,q(B)).
|
samer@0
|
483 ml_expr(I,B``) --> !, "ctranspose", args(I,B).
|
samer@0
|
484 ml_expr(_,@B) --> !, "@", atm(B).
|
samer@0
|
485 ml_expr(I, \\B) --> !, "@()", ml_expr(I,B).
|
samer@0
|
486 ml_expr(I, A\\B) --> !, { term_variables(A,V), varnames(V) },
|
samer@33
|
487 "@(", varlist(A), ")", ml_expr(I,B).
|
samer@0
|
488 ml_expr(I,lambda(A,B)) --> !, ml_expr(I,A\\B).
|
samer@0
|
489 ml_expr(I,thunk(B)) --> !, ml_expr(I, \\B).
|
samer@0
|
490
|
samer@0
|
491
|
samer@0
|
492 % !! This is problematic: we are using apply to represent both
|
samer@0
|
493 % function application and array dereferencing. For function
|
samer@0
|
494 % calls, A must be a function name atom or a function handle
|
samer@0
|
495 % If A is an array, it cannot be an expression, unless we
|
samer@0
|
496 % switch to using the paren Matlab function, which will be slower.
|
samer@0
|
497 ml_expr(I,apply(A,B)) --> !, ml_expr(I,A), arglist(I,B).
|
samer@0
|
498 ml_expr(I,cref(A,B)) --> !, ml_expr(I,A), "{", clist(I,B), "}".
|
samer@0
|
499
|
samer@0
|
500 % array syntax
|
samer@0
|
501 ml_expr(I,arr($X)) --> !, { pl2ml_hook(X,L) }, ml_expr(I,arr(L)).
|
samer@0
|
502 ml_expr(I,arr(L)) --> !, { array_dims(L,D) }, array(D,I,L).
|
samer@0
|
503 ml_expr(I,arr(D,L)) --> !, array(D,I,L).
|
samer@0
|
504 ml_expr(I,arr(D,L,P)) --> !, array(D,I,P,L).
|
samer@0
|
505 ml_expr(I,atvector(L))--> !, "[", clist_at(I,L), "]".
|
samer@0
|
506 ml_expr(I,vector(L)) --> !, "[", clist(I,L), "]".
|
samer@0
|
507 ml_expr(I,cell(L)) --> !, "{", clist(I,L), "}".
|
samer@0
|
508 ml_expr(_,'$VAR'(N)) --> !, "p_", atm(N).
|
samer@0
|
509
|
samer@0
|
510 % catch these and throw exception
|
samer@0
|
511 ml_expr(_,hide(A)) --> {throw(ml_illegal_expression(hide(A)))}.
|
samer@0
|
512 ml_expr(_,(A;B)) --> {throw(ml_illegal_expression((A;B)))}.
|
samer@0
|
513 ml_expr(_,(A,B)) --> {throw(ml_illegal_expression((A,B)))}.
|
samer@0
|
514 ml_expr(_,A=B) --> {throw(ml_illegal_expression(A=B))}.
|
samer@0
|
515
|
samer@0
|
516 % these are the catch-all clauses which will deal with matlab names, and literals
|
samer@0
|
517 % should we filter on the head functor?
|
samer@37
|
518 ml_expr(_,A) --> {string(A)}, !, q(str(A)).
|
samer@0
|
519 ml_expr(_,A) --> {atomic(A)}, !, atm(A).
|
samer@0
|
520 ml_expr(I,F) --> {F=..[H|AX]}, atm(H), arglist(I,AX).
|
samer@0
|
521
|
samer@0
|
522 ml_expr_with(I,Lambda,Y) --> {copy_term(Lambda,Y\\PY)}, ml_expr(I,PY).
|
samer@0
|
523
|
samer@0
|
524
|
samer@0
|
525 % dimensions implicit in nested list representation
|
samer@0
|
526 array_dims([X|_],M) :- !, array_dims(X,N), succ(N,M).
|
samer@0
|
527 array_dims(_,0).
|
samer@0
|
528
|
samer@0
|
529 % efficiently output row vector of workspace variable names
|
samer@0
|
530 wsx([]) --> [].
|
samer@0
|
531 wsx([A|AX]) --> { mlWSNAME(A,N,_) }, ",", atm(N), wsx(AX).
|
samer@0
|
532
|
samer@0
|
533 %% array(+Dims:natural, +Id:ml_eng, +Array)// is det.
|
samer@0
|
534 %
|
samer@0
|
535 % Format nested lists as Matlab multidimensional array.
|
samer@0
|
536 % Dims is the number of dimensions of the resulting array and
|
samer@0
|
537 % should equal the nesting level of Array, ie if Array=[1,2,3],
|
samer@0
|
538 % Dims=1; if Array=[[1,2],[3,4]], Dims=2, etc.
|
samer@0
|
539 array(0,I,X) --> !, ml_expr(I,X).
|
samer@0
|
540 array(1,I,L) --> !, "[", seqmap_with_sep(";",ml_expr(I),L), "]".
|
samer@0
|
541 array(2,I,L) --> !, "[", seqmap_with_sep(",",array(1,I),L), "]".
|
samer@0
|
542 array(N,I,L) --> {succ(M,N)}, "cat(", atm(N), ",", seqmap_with_sep(",",array(M,I),L), ")".
|
samer@0
|
543
|
samer@0
|
544 array(0,I,P,X) --> !, ml_expr_with(I,P,X).
|
samer@0
|
545 array(1,I,P,L) --> !, "[", seqmap_with_sep(";",ml_expr_with(I,P),L), "]".
|
samer@0
|
546 array(2,I,P,L) --> !, "[", seqmap_with_sep(",",array(1,I,P),L), "]".
|
samer@0
|
547 array(N,I,P,L) --> {succ(M,N)}, "cat(", atm(N), ",", seqmap_with_sep(",",array(M,I,P),L), ")".
|
samer@0
|
548
|
samer@0
|
549 matrix(h,I,(A,B)) --> !, ml_expr(I,A), ",", matrix(h,I,B).
|
samer@0
|
550 matrix(v,I,(A;B)) --> !, ml_expr(I,A), ";", matrix(v,I,B).
|
samer@0
|
551 matrix(_,I,A) --> !, ml_expr(I,A).
|
samer@0
|
552
|
samer@0
|
553
|
samer@0
|
554 % colon syntax for ranges
|
samer@0
|
555 range(I,A,B:C) --> !, "colon", arglist(I,[A,B,C]).
|
samer@0
|
556 range(I,A,B) --> !, "colon", args(I,A,B).
|
samer@0
|
557
|
samer@0
|
558
|
samer@33
|
559 %% varlist(+Term)// is det.
|
samer@33
|
560 % Format comma separated list of lambda expression arguments.
|
samer@33
|
561 varlist((A,B)) --> !, atm(A), ",", varlist(B).
|
samer@33
|
562 varlist(A) --> !, atm(A).
|
samer@33
|
563
|
samer@33
|
564
|
samer@0
|
565 %% clist(+Id:ml_eng, +Items:list(ml_expr))// is det.
|
samer@0
|
566 % Format list of Matlab expressions in a comma separated list.
|
samer@0
|
567 clist(_,[]) --> [].
|
samer@0
|
568 clist(I,[L1|LX]) --> ml_expr(I,L1), seqmap(do_then_call(",",ml_expr(I)),LX).
|
samer@0
|
569
|
samer@0
|
570
|
samer@0
|
571 %% clist_at(+Id:ml_eng, +Items:list(ml_expr))// is det.
|
samer@0
|
572 % Format list of atoms in a comma separated list.
|
samer@0
|
573 clist_at(_,[]) --> [].
|
samer@0
|
574 clist_at(_,[L1|LX]) --> atm(L1), seqmap(do_then_call(",",atm),LX).
|
samer@0
|
575
|
samer@0
|
576
|
samer@0
|
577 %% arglist(+Id:ml_eng, +Args:list(ml_expr))// is det.
|
samer@0
|
578 % DCG rule to format a list of Matlab expressions as function arguments
|
samer@0
|
579 % including parentheses.
|
samer@0
|
580 arglist(I,X) --> "(", clist(I,X), ")".
|
samer@0
|
581
|
samer@0
|
582
|
samer@0
|
583 %% args(+Id:ml_eng, +A1:ml_expr, +A2:ml_expr)// is det.
|
samer@0
|
584 %% args(+Id:ml_eng, +A1:ml_expr)// is det.
|
samer@0
|
585 %
|
samer@0
|
586 % DCG rule to format one or two Matlab expressions as function arguments
|
samer@0
|
587 % including parentheses.
|
samer@0
|
588 args(I,X,Y) --> "(", ml_expr(I,X), ",", ml_expr(I,Y), ")".
|
samer@0
|
589 args(I,X) --> "(", ml_expr(I,X), ")".
|
samer@0
|
590
|
samer@0
|
591
|
samer@0
|
592 %% atm(+A:atom)// is det.
|
samer@0
|
593 % DCG rule to format an atom using write/1.
|
samer@0
|
594 atm(A,C,T) :- with_output_to(codes(C,T),write(A)).
|
samer@0
|
595
|
samer@0
|
596 varnames(L) :- varnames(1,L).
|
samer@0
|
597 varnames(_,[]).
|
samer@0
|
598 varnames(N,[TN|Rest]) :-
|
samer@0
|
599 atom_concat(p_,N,TN), succ(N,M),
|
samer@0
|
600 varnames(M,Rest).
|
samer@0
|
601
|
samer@0
|
602
|
samer@0
|
603 %% term_mlstring(+Id:ml_eng,+X:ml_expr,-Y:list(code)) is det.
|
samer@0
|
604 % Convert term representing Matlab expression to a list of character codes.
|
samer@0
|
605 term_mlstring(I,Term,String) :- phrase(stmt(I,Term),String), !.
|
samer@0
|
606
|
samer@0
|
607 %% term_texatom(+X:tex_expr,-Y:atom) is det.
|
samer@0
|
608 % Convert term representing TeX expression to a string in atom form.
|
samer@0
|
609 term_texatom(Term,Atom) :- phrase(pl2tex(Term),String), !, atom_codes(Atom,String).
|
samer@0
|
610
|
samer@0
|
611
|
samer@0
|
612
|
samer@0
|
613 % Once the computation has been done, the MATLAB workspace contains
|
samer@0
|
614 % the results which must be transferred in the appropriate form the
|
samer@0
|
615 % specified left-values, in one of several forms, eg mxArray pointer,
|
samer@0
|
616 % a float, an atom, a string or a locator.
|
samer@0
|
617 %
|
samer@0
|
618 % Note that requesting a locator causes a further call
|
samer@0
|
619 % to MATLAB to do a dbsave.
|
samer@0
|
620 %
|
samer@0
|
621 % If no type requestor tag is present, then a unique variable name
|
samer@0
|
622 % is generated to store the result in the Matlab workspace. This name
|
samer@0
|
623 % is returned in the variable as a ws blob.
|
samer@0
|
624 % The idea is to avoid unnecessary traffic over the Matlab engine pipe.
|
samer@0
|
625
|
samer@0
|
626 % conversion between different representations of values
|
samer@0
|
627 % !! FIXME: check memory management of mxArrays here
|
samer@0
|
628
|
samer@0
|
629
|
samer@0
|
630 %% convert_ws( +Type:type, +In:ws_blob, -Out:Type) is det.
|
samer@0
|
631 % Convert value of Matlab workspace variable to representation
|
samer@0
|
632 % determined by Type.
|
samer@0
|
633 convert_ws(ws, Z, ws(Z)) :- !.
|
samer@0
|
634 convert_ws(wsseq, Z, wsseq(Z)) :- !.
|
samer@0
|
635 convert_ws(mx, Z, mx(Y)) :- !, mlWSGET(Z,Y).
|
samer@0
|
636
|
samer@0
|
637 % conversions that go direct from workspace variables to matbase.
|
samer@0
|
638 convert_ws(tmp, Z, Y) :- !, mlWSNAME(Z,_,I), bt_call(db_tmp(I,ws(Z),Y), db_drop(I,Y)).
|
samer@0
|
639 convert_ws(mat, Z, Y) :- !, mlWSNAME(Z,_,I), bt_call(db_save(I,ws(Z),Y), db_drop(I,Y)).
|
samer@0
|
640
|
samer@0
|
641 % return cell array as list of temporary or permanent mat file locators
|
samer@0
|
642 % (this avoids getting whole array from WS to MX).
|
samer@0
|
643 convert_ws(cell(tmp,Size), Z, L) :- !,
|
samer@0
|
644 mlWSNAME(Z,_,I),
|
samer@0
|
645 bt_call(db_tmp_all(I,ws(Z),L,Size), db_drop_all(I,L,Size)).
|
samer@0
|
646
|
samer@0
|
647 convert_ws(cell(mat,Size), Z, L) :- !,
|
samer@0
|
648 mlWSNAME(Z,_,I),
|
samer@0
|
649 bt_call(db_save_all(I,ws(Z),L,Size), db_drop_all(I,L,Size)).
|
samer@0
|
650
|
samer@0
|
651 % Most other conversions from ws(_) go via mx(_)
|
samer@13
|
652 convert_ws(T,Z,A) :-
|
samer@17
|
653 mlWSGET(Z,X),
|
samer@17
|
654 convert_mx(T,X,A).
|
samer@0
|
655
|
samer@0
|
656
|
samer@0
|
657 %% convert_mx( +Type:type, +In:mx_blob, -Out:Type) is det.
|
samer@0
|
658 % Convert value of in-process Matlab array In to representation
|
samer@0
|
659 % determined by Type.
|
samer@0
|
660 convert_mx(atom, X, Y) :- !, mlMX2ATOM(X,Y).
|
samer@0
|
661 convert_mx(bool, X, Y) :- !, mlMX2LOGICAL(X,Y).
|
samer@0
|
662 convert_mx(float, X, Y) :- !, mlMX2FLOAT(X,Y).
|
samer@0
|
663 convert_mx(int, X, Y) :- !, mlMX2FLOAT(X,Z), Y is truncate(Z).
|
samer@0
|
664 convert_mx(string, X, Y) :- !, mlMX2STRING(X,Y).
|
samer@0
|
665 convert_mx(term, X, Y) :- !, mlMX2ATOM(X,Z), term_to_atom(Y,Z).
|
samer@0
|
666 convert_mx(loc, X, mat(Y,W)) :- !, mlMX2ATOM(X,Z), term_to_atom(Y|W,Z).
|
samer@0
|
667
|
samer@0
|
668 convert_mx(mat, X, Y) :- !, % !!! use first engine to save to its matbase
|
samer@28
|
669 current_engine(I),
|
samer@0
|
670 bt_call( db_save(I,mx(X),Y), db_drop(I,Y)).
|
samer@0
|
671 convert_mx(tmp, X, Y) :- !, % !!! use first engine to save to its matbase
|
samer@28
|
672 current_engine(I),
|
samer@0
|
673 bt_call( db_tmp(I,mx(X),Y), db_drop(I,Y)).
|
samer@0
|
674
|
samer@0
|
675 convert_mx(list(float), X, Y) :- !, mlGETREALS(X,Y).
|
samer@0
|
676
|
samer@0
|
677 convert_mx(cell(Type,Size), X, L) :- !,
|
samer@0
|
678 mx_size_type(X,Size,cell),
|
samer@0
|
679 prodlist(Size,1,Elems), % total number of elements
|
samer@0
|
680 mapnats(conv_cref(Type,X),Elems,[],FL),
|
samer@0
|
681 reverse(Size,RSize),
|
samer@0
|
682 unflatten(RSize,FL,L).
|
samer@0
|
683
|
samer@0
|
684 convert_mx(array(Type,Size), X, L) :- !,
|
samer@0
|
685 mx_size_type(X,Size,MXType),
|
samer@0
|
686 compatible(MXType,Type),
|
samer@0
|
687 prodlist(Size,1,Elems), % total number of elements
|
samer@0
|
688 mapnats(conv_aref(Type,X),Elems,[],FL),
|
samer@0
|
689 reverse(Size,RSize),
|
samer@0
|
690 unflatten(RSize,FL,L).
|
samer@0
|
691
|
samer@0
|
692 compatible(double,float).
|
samer@0
|
693 compatible(double,int).
|
samer@0
|
694 compatible(double,bool).
|
samer@0
|
695 compatible(logical,float).
|
samer@0
|
696 compatible(logical,int).
|
samer@0
|
697 compatible(logical,bool).
|
samer@0
|
698
|
samer@0
|
699 % !! Need to worry about non gc mx atoms
|
samer@0
|
700 conv_aref(bool, X,I,Y) :- !, mlGETLOGICAL(X,I,Y).
|
samer@0
|
701 conv_aref(float, X,I,Y) :- !, mlGETFLOAT(X,I,Y).
|
samer@0
|
702 conv_aref(int, X,I,Y) :- !, mlGETFLOAT(X,I,W), Y is truncate(W).
|
samer@0
|
703
|
samer@0
|
704 conv_cref(mx,Z,I,Y) :- !, mlGETCELL(Z,I,Y). % !! non gc mx
|
samer@0
|
705 conv_cref(Ty,Z,I,Y) :- !, conv_cref(mx,Z,I,X), convert_mx(Ty,X,Y).
|
samer@0
|
706
|
samer@0
|
707 %convert(W, field(Z,N,I)) :- convert(mx(X),Z), mlGETFIELD(X,I,N,Y), convert_mx(W,Y).
|
samer@0
|
708 %convert(W, field(Z,N)) :- convert(mx(X),Z), mlGETFIELD(X,1,N,Y), convert_mx(W,Y).
|
samer@0
|
709
|
samer@0
|
710 % Utilities used by convert/2
|
samer@0
|
711
|
samer@0
|
712 mapnats(P,N,L1,L3) :- succ(M,N), !, call(P,N,PN), mapnats(P,M,[PN|L1],L3).
|
samer@0
|
713 mapnats(_,0,L,L) :- !.
|
samer@0
|
714
|
samer@0
|
715 prodlist([],P,P).
|
samer@0
|
716 prodlist([X1|XX],P1,P3) :- P2 is P1*X1, prodlist(XX,P2,P3).
|
samer@0
|
717
|
samer@0
|
718 concat(0,_,[]) --> !, [].
|
samer@0
|
719 concat(N,L,[X1|XX]) --> { succ(M,N), length(X1,L) }, X1, concat(M,L,XX).
|
samer@0
|
720
|
samer@0
|
721 % convert a flat list into a nested-list array representation
|
samer@0
|
722 % using given size specification
|
samer@0
|
723 unflatten([N],Y,Y) :- !, length(Y,N).
|
samer@0
|
724 unflatten([N|NX],Y,X) :-
|
samer@0
|
725 length(Y,M),
|
samer@0
|
726 L is M/N, integer(L), L>=1,
|
samer@0
|
727 phrase(concat(N,L,Z),Y),
|
samer@0
|
728 maplist(unflatten(NX),Z,X).
|
samer@0
|
729
|
samer@0
|
730 % thin wrappers
|
samer@0
|
731 mx_size_type(X,Sz,Type) :- mlMXINFO(X,Sz,Type).
|
samer@0
|
732 mx_sub2ind(X,Subs,Ind) :- mlSUB2IND(X,Subs,Ind).
|
samer@0
|
733
|
samer@0
|
734
|
samer@0
|
735 % these create memory managed arrays, which are not suitable
|
samer@0
|
736 % for putting into a cell array
|
samer@0
|
737
|
samer@0
|
738 % roughly, mx_create :: type -> mxarray.
|
samer@0
|
739 mx_create([Size],mx(X)) :- mlCREATENUMERIC(Size,Z), mlNEWREFGC(Z,X).
|
samer@0
|
740 mx_create({Size},mx(X)) :- mlCREATECELL(Size,Z), mlNEWREFGC(Z,X).
|
samer@0
|
741 mx_string(string(Y),mx(X)) :- mlCREATESTRING(Y,Z), mlNEWREFGC(Z,X).
|
samer@0
|
742
|
samer@0
|
743 % MX as MUTABLE variables
|
samer@0
|
744 mx_put(aref(mx(X),I),float(Y)) :- mlPUTFLOAT(X,I,Y).
|
samer@0
|
745 mx_put(cref(mx(X),I),mx(Y)) :- mlPUTCELL(X,I,Y). % !! ensure that Y is non gc
|
samer@0
|
746 mx_put(mx(X),list(float,Y)) :- mlPUTFLOATS(X,1,Y).
|
samer@0
|
747
|
samer@0
|
748 %% wsvar(+X:ws_blob(A), -Nm:atom, -Id:ml_eng) is semidet.
|
samer@0
|
749 % True if X is a workspace variable in Matlab session Id.
|
samer@0
|
750 % Unifies Nm with the name of the Matlab variable.
|
samer@0
|
751 wsvar(A,Name,Engine) :- mlWSNAME(A,Name,Engine).
|
samer@0
|
752
|
samer@0
|
753 /* __________________________________________________________________________________
|
samer@0
|
754 * Dealing with the Matbase
|
samer@0
|
755 *
|
samer@0
|
756 * The Matbase is a file system tree which contains lots of
|
samer@0
|
757 * MAT files which have been created by using the dbsave
|
samer@0
|
758 * Matlab function.
|
samer@0
|
759 */
|
samer@0
|
760
|
samer@0
|
761
|
samer@0
|
762 %% loc(Dir,File)// is det.
|
samer@0
|
763 % DCG rule for matbase locator strings. Dir must be an atom slash-separated
|
samer@0
|
764 % list of atoms representing a path relative to the matbase root (see Matlab
|
samer@0
|
765 % function dbroot). File must be an atom. Outputs a single-quoted locator
|
samer@0
|
766 % string acceptable to Matlab db functions.
|
samer@0
|
767 loc(X,Y) --> "'", wr(X),"|",atm(Y), "'".
|
samer@0
|
768
|
samer@0
|
769
|
samer@0
|
770 % saving and dropping matbase files
|
samer@0
|
771 db_save(I,Z,Y) :- ml_eval(I,dbsave(Z),[loc],[Y]).
|
samer@0
|
772 db_tmp(I,Z,Y) :- ml_eval(I,dbtmp(Z),[loc],[Y]).
|
samer@0
|
773 db_drop(I,mat(A,B)) :- ml_exec(I,dbdrop(\loc(A,B))).
|
samer@0
|
774
|
samer@9
|
775 db_save_all(I,Z,L,Size) :- ml_eval(I,dbcellmap(@dbsave,Z),[cell(loc,Size)],[L]).
|
samer@9
|
776 db_tmp_all(I,Z,L,Size) :- ml_eval(I,dbcellmap(@dbtmp,Z),[cell(loc,Size)],[L]).
|
samer@0
|
777 db_drop_all(I,L,Size) :-
|
samer@0
|
778 length(Size,Dims),
|
samer@0
|
779 ml_exec(I,hide(foreach(@dbdrop,arr(Dims,L,X\\{loc(X)})))).
|
samer@0
|
780
|
samer@0
|
781
|
samer@0
|
782 %% dropmat(+Id:ml_id, +Mat:ml_loc) is det.
|
samer@0
|
783 % Deleting MAT file from matbase.
|
samer@0
|
784 dropmat(Eng,mat(A,B)) :- db_drop(Eng,mat(A,B)).
|
samer@0
|
785
|
samer@0
|
786 %% exportmat(+Id:ml_id, +Mat:ml_loc, +Dir:atom) is det.
|
samer@0
|
787 % Export specified MAT file from matbase to given directory.
|
samer@0
|
788 exportmat(Eng,mat(A,B),Dir) :- ml_exec(Eng,copyfile(dbpath(\loc(A,B)),\q(wr(Dir)))).
|
samer@0
|
789
|
samer@0
|
790 %% matbase_mat(+Id:ml_eng,-X:ml_loc) is nondet.
|
samer@0
|
791 % Listing mat files actually in matbase at given root directory.
|
samer@0
|
792 matbase_mat(Id,mat(SubDir/File,x)) :-
|
samer@0
|
793 ml_eval(Id,[dbroot,q(/)],[atom],[DBRoot]), % NB with trailing slash
|
samer@0
|
794
|
samer@0
|
795 atom_concat(DBRoot,'*/d*',DirPattern),
|
samer@0
|
796 expand_file_name(DirPattern,Dirs),
|
samer@0
|
797 member(FullDir,Dirs),
|
samer@0
|
798 atom_concat( DBRoot,SubDirAtom,FullDir),
|
samer@0
|
799 term_to_atom(SubDir,SubDirAtom),
|
samer@0
|
800 atom_concat(FullDir,'/m*.mat',FilePattern),
|
samer@0
|
801 expand_file_name(FilePattern,Files),
|
samer@0
|
802 member(FullFile,Files),
|
samer@0
|
803 file_base_name(FullFile,FN),
|
samer@0
|
804 atom_concat(File,'.mat',FN).
|
samer@0
|
805
|
samer@0
|
806
|
samer@0
|
807 %% persist_item(+X:ml_expr(A),-Y:ml_expr(A)) is det.
|
samer@0
|
808 % Convert Matlab expression to persistent form not dependent on
|
samer@0
|
809 % current Matlab workspace or MX arrays in Prolog memory space.
|
samer@0
|
810 % Large values like arrays and structures are saved in the matbase
|
samer@0
|
811 % replaced with matbase locators. Scalar values are converted to
|
samer@0
|
812 % literal numeric values. Character strings are converted to Prolog atoms.
|
samer@0
|
813 % Cell arrays wrapped in the wsseq/1 functor are converted to literal
|
samer@0
|
814 % form.
|
samer@0
|
815 %
|
samer@0
|
816 % NB. any side effects are undone on backtracking -- in particular, any
|
samer@0
|
817 % files created in the matbase are deleted.
|
samer@0
|
818 persist_item($T,$T) :- !.
|
samer@0
|
819 persist_item(mat(A,B),mat(A,B)) :- !.
|
samer@0
|
820
|
samer@0
|
821 persist_item(ws(A),B) :- !,
|
samer@0
|
822 mlWSNAME(A,_,Eng),
|
samer@0
|
823 ml_eval(Eng,typecode(ws(A)),[int,bool,bool],[Numel,IsNum,IsChar]),
|
samer@0
|
824 ( Numel=1, IsNum=1
|
samer@0
|
825 -> convert_ws(float,A,B)
|
samer@0
|
826 ; IsChar=1
|
samer@0
|
827 -> convert_ws(atom,A,AA), B= `AA
|
samer@0
|
828 ; convert_ws(mat,A,B)
|
samer@0
|
829 ).
|
samer@0
|
830
|
samer@0
|
831
|
samer@0
|
832 % !! TODO -
|
samer@0
|
833 % deal with collections - we can either save the aggregate
|
samer@0
|
834 % OR save the elements individually and get a prolog list of the
|
samer@0
|
835 % locators.
|
samer@0
|
836 persist_item(wsseq(A),cell(B)) :-
|
samer@0
|
837 mlWSNAME(A,_,Eng),
|
samer@0
|
838 ml_test(Eng,iscell(ws(A))),
|
samer@0
|
839 ml_eval(Eng,wsseq(A),[cell(mat,_)],[B]).
|
samer@0
|
840
|
samer@0
|
841 persist_item(mx(X),B) :-
|
samer@0
|
842 mx_size_type(X,Size,Type),
|
samer@0
|
843 ( Size=[1], Type=double
|
samer@0
|
844 -> convert_mx(float,X,B)
|
samer@0
|
845 ; Type=char
|
samer@0
|
846 -> convert_mx(atom,X,AA), B= `AA
|
samer@0
|
847 ; convert_mx(mat,X,B)
|
samer@0
|
848 ).
|
samer@0
|
849
|
samer@0
|
850 persist_item(A,A) :- atomic(A).
|
samer@0
|
851
|
samer@0
|
852
|
samer@0
|
853 /* -----------------------------------------------------------------------
|
samer@0
|
854 * From here on, we have straight Matlab utilities
|
samer@0
|
855 * rather than basic infrastructure.
|
samer@0
|
856 */
|
samer@0
|
857
|
samer@0
|
858
|
samer@0
|
859
|
samer@0
|
860 % for dealing with option lists
|
samer@0
|
861
|
samer@0
|
862 %% mhelp(+Name:atom) is det.
|
samer@0
|
863 % Lookup Matlab help on the given name. Equivalent to executing help(`X).
|
samer@0
|
864 mhelp(X) :- ml_exec(ml,help(q(X))).
|
samer@0
|
865
|
samer@0
|
866
|
samer@0
|
867
|
samer@0
|
868 %% compileoptions(+Opts:list(ml_options), -Prefs:ml_expr(options)) is det.
|
samer@0
|
869 %
|
samer@0
|
870 % Convert list of option specifiers into a Matlab expression representing
|
samer@0
|
871 % options (ie a struct). Each specifier can be a Name:Value pair, a name
|
samer@0
|
872 % to be looked up in the optionset/2 predicate, a nested list of ml_options
|
samer@0
|
873 % compileoptions :: list (optionset | atom:value | struct) -> struct.
|
samer@0
|
874 % NB. option types are as follows:
|
samer@0
|
875 % ==
|
samer@0
|
876 % X :: ml_options :- optionset(X,_).
|
samer@0
|
877 % X :: ml_options :- X :: ml_option(_).
|
samer@0
|
878 % X :: ml_options :- X :: list(ml_options).
|
samer@0
|
879 % X :: ml_options :- X :: ml_expr(struct(_)).
|
samer@0
|
880 %
|
samer@0
|
881 % ml_option(A) ---> atom:ml_expr(A).
|
samer@0
|
882 % ==
|
samer@0
|
883 compileoptions(Opts,Prefs) :-
|
samer@0
|
884 rec_optslist(Opts,OptsList),
|
samer@0
|
885 Prefs=..[prefs|OptsList].
|
samer@0
|
886
|
samer@0
|
887 rec_optslist([],[]).
|
samer@0
|
888 rec_optslist([H|T],L) :-
|
samer@0
|
889 ( % mutually exclusive types for H
|
samer@0
|
890 optionset(H,Opts1) -> rec_optslist(Opts1,Opts)
|
samer@0
|
891 ; H=Name:Value -> Opts=[`Name,Value]
|
samer@0
|
892 ; is_list(H) -> rec_optslist(H,Opts)
|
samer@0
|
893 ; /* assume struct */ Opts=[H]
|
samer@0
|
894 ),
|
samer@0
|
895 rec_optslist(T,TT),
|
samer@0
|
896 append(Opts,TT,L).
|
samer@0
|
897
|
samer@0
|
898 rtimes(X,Y,Z) :-
|
samer@0
|
899 ( var(X) -> X is Z/Y
|
samer@0
|
900 ; var(Y) -> Y is Z/X
|
samer@0
|
901 ; Z is X*Y).
|
samer@0
|
902
|
samer@0
|
903
|
samer@0
|
904 % Execute several plots as subplots. The layout can be
|
samer@0
|
905 % vertical, horizontal, or explicity given as Rows*Columns.
|
samer@0
|
906
|
samer@0
|
907
|
samer@0
|
908 % mplot is a private procedure used by multiplot
|
samer@0
|
909 mplot(subplot(H,W),N,Plot,Ax) :- ?? (subplot(H,W,N); Plot), Ax===gca.
|
samer@0
|
910 mplot(figure,N,Plot,Ax) :- ?? (figure(N); Plot), Ax===gca.
|
samer@0
|
911
|
samer@0
|
912 %% multiplot(+Type:ml_plot, +Cmds:list(ml_expr(_))) is det.
|
samer@0
|
913 %% multiplot(+Type:ml_plot, +Cmds:list(ml_expr(_)), -Axes:list(ml_val(handle))) is det.
|
samer@0
|
914 %
|
samer@0
|
915 % Executes plotting commands in Cmds in multiple figures or axes as determined
|
samer@0
|
916 % by Type. Valid types are:
|
samer@0
|
917 % * figs(Range)
|
samer@0
|
918 % Executes each plot in a separate figure, Range must be P..Q where P
|
samer@0
|
919 % and Q are figure numbers.
|
samer@0
|
920 % * vertical
|
samer@0
|
921 % Executes each plot in a subplot;
|
samer@0
|
922 % subplots are arranged vertically top to bottom in the current figure.
|
samer@0
|
923 % * horizontal
|
samer@0
|
924 % Executes each plot in a subplot;
|
samer@0
|
925 % subplots are arranged horizontally left to right in the current figure.
|
samer@0
|
926 % * [Type, link(Axis)]
|
samer@0
|
927 % As for multplot type Type, but link X or Y axis scales as determined by Axis,
|
samer@0
|
928 % which can be `x, `y, or `xy.
|
samer@0
|
929 %
|
samer@0
|
930 % Three argument form returns a list containing the Matlab handles to axes objects,
|
samer@0
|
931 % one for each plot.
|
samer@0
|
932 multiplot(Type,Plots) :- multiplot(Type,Plots,_).
|
samer@0
|
933
|
samer@0
|
934 multiplot([Layout|Opts],Plots,Axes) :- !,
|
samer@0
|
935 multiplot(Layout,Plots,Axes),
|
samer@0
|
936 member(link(A),Opts) ->
|
samer@0
|
937 ?? (linkaxes(Axes,`off); hide(linkaxes(Axes,`A)))
|
samer@0
|
938 ; true.
|
samer@0
|
939
|
samer@0
|
940 multiplot(figs(P..Q),Plots,Axes) :- !,
|
samer@0
|
941 length(Plots,N),
|
samer@0
|
942 between(1,inf,P), Q is P+N-1,
|
samer@0
|
943 numlist(P,Q,PlotNums),
|
samer@0
|
944 maplist(mplot(figure),PlotNums,Plots,Axes).
|
samer@0
|
945
|
samer@0
|
946 multiplot(Layout,Plots,Axes) :-
|
samer@0
|
947 length(Plots,N),
|
samer@0
|
948 member(Layout:H*W,[vertical:N*1, horizontal:1*N, H*W:H*W]),
|
samer@0
|
949 rtimes(H,W,N), % bind any remaining variables
|
samer@0
|
950 numlist(1,N,PlotNums),
|
samer@0
|
951 maplist(mplot(subplot(H,W)),PlotNums,Plots,Axes).
|
samer@0
|
952
|
samer@0
|
953
|
samer@0
|
954 %% optionset( +Key:term, -Opts:list(ml_options)) is semidet.
|
samer@0
|
955 %
|
samer@0
|
956 % Extensible predicate for mapping arbitrary terms to a list of options
|
samer@0
|
957 % to be processed by compileoptions/2.
|
samer@0
|
958
|
samer@0
|
959 %user:portray(A|B) :- print(A), write('|'), print(B).
|
samer@0
|
960 user:portray(Z) :- mlWSNAME(Z,N,ID), format('<~w:~w>',[ID,N]).
|
samer@0
|
961
|
samer@0
|
962 prolog:message(ml_illegal_expression(Expr),[ 'Illegal Matlab expression: ~w'-[Expr] | Z], Z).
|
samer@0
|
963 prolog:message(mlerror(Eng,Msg,Cmd),[
|
samer@0
|
964 'Error in Matlab engine (~w):\n * ~w\n * while executing "~w"'-[Eng,Msg,Cmd] | Z], Z).
|
samer@0
|
965
|
samer@0
|
966
|
samer@0
|
967 %% pl2tex(+Exp:tex_expr)// is det.
|
samer@0
|
968 %
|
samer@0
|
969 % DCG for texifying expressions (useful for matlab text)
|
samer@0
|
970 pl2tex(A=B) --> !, pl2tex(A), "=", pl2tex(B).
|
samer@0
|
971 pl2tex(A+B) --> !, pl2tex(A), "+", pl2tex(B).
|
samer@0
|
972 pl2tex(A-B) --> !, pl2tex(A), "-", pl2tex(B).
|
samer@0
|
973 pl2tex(A*B) --> !, pl2tex(A), "*", pl2tex(B).
|
samer@0
|
974 pl2tex(A.*B) --> !, pl2tex(A), "*", pl2tex(B).
|
samer@0
|
975 pl2tex(A/B) --> !, pl2tex(A), "/", pl2tex(B).
|
samer@0
|
976 pl2tex(A./B) --> !, pl2tex(A), "/", pl2tex(B).
|
samer@0
|
977 pl2tex(A\B) --> !, pl2tex(A), "\\", pl2tex(B).
|
samer@0
|
978 pl2tex(A.\B) --> !, pl2tex(A), "\\", pl2tex(B).
|
samer@0
|
979 pl2tex(A^B) --> !, pl2tex(A), "^", brace(pl2tex(B)).
|
samer@0
|
980 pl2tex(A.^B) --> !, pl2tex(A), "^", brace(pl2tex(B)).
|
samer@0
|
981 pl2tex((A,B))--> !, pl2tex(A), ", ", pl2tex(B).
|
samer@0
|
982 pl2tex(A;B)--> !, pl2tex(A), "; ", pl2tex(B).
|
samer@0
|
983 pl2tex(A:B)--> !, pl2tex(A), ": ", pl2tex(B).
|
samer@0
|
984 pl2tex({A}) --> !, "\\{", pl2tex(A), "\\}".
|
samer@0
|
985 pl2tex([]) --> !, "[]".
|
samer@0
|
986 pl2tex([X|XS]) --> !, "[", seqmap_with_sep(", ",pl2tex,[X|XS]), "]".
|
samer@0
|
987
|
samer@0
|
988 pl2tex(A\\B) --> !, "\\lambda ", pl2tex(A), ".", pl2tex(B).
|
samer@0
|
989 pl2tex(@A) --> !, "@", pl2tex(A).
|
samer@0
|
990 pl2tex(abs(A)) --> !, "|", pl2tex(A), "|".
|
samer@0
|
991 pl2tex(A) --> {atomic(A)}, escape_with(0'\\,0'_,at(A)).
|
samer@0
|
992 pl2tex(A) -->
|
samer@0
|
993 {compound(A), A=..[H|T] },
|
samer@0
|
994 pl2tex(H), paren(seqmap_with_sep(", ",pl2tex,T)).
|
samer@0
|
995
|
samer@37
|
996 hostname(H) :-
|
samer@37
|
997 ( getenv('HOSTNAME',H) -> true
|
samer@37
|
998 ; setup_call_cleanup(open(pipe(hostname),read,S),
|
samer@37
|
999 read_line_to_codes(S,Codes),
|
samer@37
|
1000 close(S)), atom_codes(H,Codes)
|
samer@37
|
1001 ).
|