YAP 7.1.0
matlab.yap
Go to the documentation of this file.
1/**
2 * @file matlab.yap
3 * @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
4 * @date Tue Nov 17 22:51:48 2015
5 *
6 * @brief YAP Matlab interface.
7 *
8 *
9*/
10
11
12:- module(matlab,
13 [start_matlab/1,
14 close_matlab/0,
15 matlab_on/0,
25 matlab_vector/2,
34 matlab_call/2]).
35
36/** @defgroup matlab MATLAB Package Interface
37@ingroup YAPLibrary
38@{
39
40The MathWorks MATLAB is a widely used package for array
41processing. YAP now includes a straightforward interface to MATLAB. To
42actually use it, you need to install YAP calling `configure` with
43the `--with-matlab=DIR` option, and you need to call
44`use_module(library(lists))` command.
45
46Accessing the matlab dynamic libraries can be complicated. In Linux
47machines, to use this interface, you may have to set the environment
48variable <tt>LD_LIBRARY_PATH</tt>. Next, follows an example using bash in a
4964-bit Linux PC:
50
51```
52export LD_LIBRARY_PATH=''$MATLAB_HOME"/sys/os/glnxa64:''$MATLAB_HOME"/bin/glnxa64:''$LD_LIBRARY_PATH"
53```
54where `MATLAB_HOME` is the directory where matlab is installed
55at. Please replace `ax64` for `x86` on a 32-bit PC.
56
57*/
58
59/*
60
61 @pred start_matlab(+ _Options_)
62
63
64Start a matlab session. The argument _Options_ may either be the
65empty string/atom or the command to call matlab. The command may fail.
66
67
68*/
69
70/** @pred close_matlab
71
72
73Stop the current matlab session.
74
75
76*/
77/** @pred matlab_cells(+ _SizeX_, + _SizeY_, ? _Array_)
78
79MATLAB will create an empty array of cells of size _SizeX_ and
80 _SizeY_, and if _Array_ is bound to an atom, store the array
81in the matlab variable with name _Array_. Corresponds to the
82MATLAB command `cells`.
83
84
85*/
86/** @pred matlab_cells(+ _Size_, ? _Array_)
87
88
89MATLAB will create an empty vector of cells of size _Size_, and if
90 _Array_ is bound to an atom, store the array in the matlab
91variable with name _Array_. Corresponds to the MATLAB command `cells`.
92
93
94*/
95/** @pred matlab_eval_string(+ _Command_)
96
97
98Holds if matlab evaluated successfully the command _Command_.
99
100
101*/
102/** @pred matlab_eval_string(+ _Command_, - _Answer_)
103
104MATLAB will evaluate the command _Command_ and unify _Answer_
105with a string reporting the result.
106
107
108*/
109/** @pred matlab_get_variable(+ _MatVar_, - _List_)
110
111
112Unify MATLAB variable _MatVar_ with the List _List_.
113
114
115*/
116/** @pred matlab_initialized_cells(+ _SizeX_, + _SizeY_, + _List_, ? _Array_)
117
118
119MATLAB will create an array of cells of size _SizeX_ and
120 _SizeY_, initialized from the list _List_, and if _Array_
121is bound to an atom, store the array in the matlab variable with name
122 _Array_.
123
124
125*/
126/** @pred matlab_item(+ _MatVar_, + _X_, + _Y_, ? _Val_)
127
128Read or set MATLAB _MatVar_( _X_, _Y_) from/to _Val_. Use
129`C` notation for matrix access (ie, starting from 0).
130
131
132*/
133/** @pred matlab_item(+ _MatVar_, + _X_, ? _Val_)
134
135
136Read or set MATLAB _MatVar_( _X_) from/to _Val_. Use
137`C` notation for matrix access (ie, starting from 0).
138
139
140*/
141/** @pred matlab_item1(+ _MatVar_, + _X_, + _Y_, ? _Val_)
142
143Read or set MATLAB _MatVar_( _X_, _Y_) from/to _Val_. Use
144MATLAB notation for matrix access (ie, starting from 1).
145
146
147*/
148/** @pred matlab_item1(+ _MatVar_, + _X_, ? _Val_)
149
150
151Read or set MATLAB _MatVar_( _X_) from/to _Val_. Use
152MATLAB notation for matrix access (ie, starting from 1).
153
154
155*/
156/** @pred matlab_matrix(+ _SizeX_, + _SizeY_, + _List_, ? _Array_)
157
158
159MATLAB will create an array of floats of size _SizeX_ and _SizeY_,
160initialized from the list _List_, and if _Array_ is bound to
161an atom, store the array in the matlab variable with name _Array_.
162
163
164*/
165/** @pred matlab_on
166
167
168Holds if a matlab session is on.
169
170
171*/
172/** @pred matlab_sequence(+ _Min_, + _Max_, ? _Array_)
173
174
175MATLAB will create a sequence going from _Min_ to _Max_, and
176if _Array_ is bound to an atom, store the sequence in the matlab
177variable with name _Array_.
178
179
180*/
181/** @pred matlab_set(+ _MatVar_, + _X_, + _Y_, + _Value_)
182
183
184Call MATLAB to set element _MatVar_( _X_, _Y_) to
185 _Value_. Notice that this command uses the MATLAB array access
186convention.
187
188
189*/
190/** @pred matlab_vector(+ _Size_, + _List_, ? _Array_)
191
192
193MATLAB will create a vector of floats of size _Size_, initialized
194from the list _List_, and if _Array_ is bound to an atom,
195store the array in the matlab variable with name _Array_.
196
197
198*/
199/** @pred matlab_zeros(+ _SizeX_, + _SizeY_, + _SizeZ_, ? _Array_)
200
201MATLAB will create an array of zeros of size _SizeX_, _SizeY_,
202and _SizeZ_. If _Array_ is bound to an atom, store the array
203in the matlab variable with name _Array_. Corresponds to the
204MATLAB command `zeros`.
205
206
207
208
209 */
210/** @pred matlab_zeros(+ _SizeX_, + _SizeY_, ? _Array_)
211
212MATLAB will create an array of zeros of size _SizeX_ and
213 _SizeY_, and if _Array_ is bound to an atom, store the array
214in the matlab variable with name _Array_. Corresponds to the
215MATLAB command `zeros`.
216
217
218*/
219/** @pred matlab_zeros(+ _Size_, ? _Array_)
220
221
222MATLAB will create a vector of zeros of size _Size_, and if
223 _Array_ is bound to an atom, store the array in the matlab
224variable with name _Array_. Corresponds to the MATLAB command
225`zeros`.
226
227
228*/
229
230:- ensure_loaded(library(lists)).
231
232ensure_loaded :-
233 print_message(warning,functionality(matlab)).
234
235:- ( catch(load_foreign_files([matlab], ['eng','mx','ut'], init_matlab),_,fail) -> catch ; catch).
236
237matlab_eval_sequence(S) :-
238 atomic_concat(S,S1),
240
241matlab_eval_sequence(S,O) :-
242 atomic_concat(S,S1),
243 matlab_eval_string(S1,O).
244
245matlab_vector( Vec, L) :-
246 length(Vec, LV),
247 matlab_vector(LV, Vec, L).
248
249matlab_sequence(Min,Max,L) :-
250 mksequence(Min,Max,Vector),
251 Dim is (Max-Min)+1,
252 matlab_matrix(1,Dim,Vector,L).
253
254mksequence(Min,Min,[Min]) :- mksequence.
255mksequence(Min,Max,[Min|Vector]) :-
256 Min1 is Min+1,
257 mksequence(Min1,Max,Vector).
258
259matlab_call(S,Out) :-
260 S=..[Func|Args],
261 build_args(Args,L0,[]),
262 process_arg_entry(L0,L),
263 build_output(Out,Lf,['= ',Func|L]),
264 atomic_concat(Lf,Command),
265 matlab_eval_string(Command).
266
267matlab_call(S,Out,Result) :-
268 S=..[Func|Args],
269 build_args(Args,L0,[]),
270 process_arg_entry(L0,L),
271 build_output(Out,Lf,[' = ',Func|L]),
272 atomic_concat(Lf,Command),
273 matlab_eval_string(Command,Result).
274
275build_output(Out,['[ '|L],L0) :-
276 is_list(Out), is_list,
277 build_outputs(Out,L,[']'|L0]).
278build_output(Out,Lf,L0) :-
279 build_arg(Out,Lf,L0).
280
281build_outputs([],L,L).
282build_outputs([Out|Outs],[Out,' '|L],L0) :-
283 build_outputs(Outs,L,L0).
284
285build_args([],L,L).
286build_args([Arg],Lf,L0) :- build_args,
287 build_arg(Arg,Lf,[')'|L0]).
288build_args([Arg|Args],L,L0) :-
289 build_arg(Arg,L,[', '|L1]),
290 build_args(Args,L1,L0).
291
292build_arg(V,_,_) :- var(V), var,
293 throw(error(instantiation_error)).
294build_arg(Arg,[Arg|L],L) :- atomic(Arg), atomic.
295build_arg(\S0,['\'',S0,'\''|L],L) :-
296 atom(S0), atom.
297build_arg([S1|S2],['['|L],L0) :-
298 is_list(S2), is_list,
299 build_arglist([S1|S2],L,L0).
300build_arg([S1|S2],L,L0) :- build_arg,
301 build_arg(S1,L,['.'|L1]),
302 build_arg(S2,L1,L0).
303build_arg(S1:S2,L,L0) :- build_arg,
304 build_arg(S1,L,[':'|L1]),
305 build_arg(S2,L1,L0).
306build_arg(F,[N,'{'|L],L0) :- %N({A}) = N{A}
307 F=..[N,{A}], =..,
308 build_arg(A,L,['}'|L0]).
309build_arg(F,[N,'('|L],L0) :-
310 F=..[N|As],
311 build_args(As,L,L0).
312
313build_arglist([A],L,L0) :- build_arglist,
314 build_arg(A,L,[' ]'|L0]).
315build_arglist([A|As],L,L0) :-
316 build_arg(A,L,[' ,'|L1]),
317 build_arglist(As,L1,L0).
318
319build_string([],['\''|L],L).
320build_string([S0|S],[C|Lf],L0) :-
321 char_code(C,S0),
322 build_string(S,Lf,L0).
323
324
325process_arg_entry([],[]) :- process_arg_entry.
326process_arg_entry(L,['('|L]).
327/** @} */
328
329
catch( : Goal,+ Exception,+ Action)
is_list( ?_List_ )
throw(+ Ball)
char_code(? A,? I)
print_message(+ Severity, +Term)
ensure_loaded(+ F)
atom( T)
atomic(T)
var( T)
length(? L,? S)
matlab_cells(+ Size, ? Array)
matlab_cells(+ SizeX, + SizeY, ? Array)
matlab_eval_string(+ Command)
matlab_eval_string(+ Command, - Answer)
matlab_get_variable(+ MatVar, - List)
matlab_initialized_cells(+ SizeX, + SizeY, + List, ? Array)
matlab_item1(+ MatVar, + X, ? Val)
matlab_item1(+ MatVar, + X, + Y, ? Val)
matlab_item(+ MatVar, + X, ? Val)
matlab_item(+ MatVar, + X, + Y, ? Val)
matlab_matrix(+ SizeX, + SizeY, + List, ? Array)
matlab_sequence(+ Min, + Max, ? Array)
matlab_set(+ MatVar, + X, + Y, + Value)
matlab_vector(+ Size, + List, ? Array)
matlab_zeros(+ Size, ? Array)
matlab_zeros(+ SizeX, + SizeY, ? Array)
matlab_zeros(+ SizeX, + SizeY, + SizeZ, ? Array)