| Did you know ... | Search Documentation: | 
|  | Pack plml -- prolog/plml.pl | 
ml_eng - Any atom identifying a Matlab engine.
ml_stmt - A Matlab statement
X;Y :: ml_stmt :- X::ml_stmt, Y::ml_stmt. X,Y :: ml_stmt :- X::ml_stmt, Y::ml_stmt. X=Y :: ml_stmt :- X::ml_lval, Y::ml_expr. hide(X) :: ml_stmt :- X::ml_stmt.
ml_expr(A) % A Matlab expression, possibly with multiple return values ml_loc ---> mat(atom,atom). % Matbase locator
The Matlab expression syntax adopted by this module allows Prolog terms to represent or denote Matlab expressions. Let T be the domain of recognised Prolog terms (corresponding to the type ml_expr), and M be the domain of Matlab expressions written in Matlab syntax. Then V : T->M is the valuation function which maps Prolog term X to Matlab expression V[X]. These are some of the constructs it recognises:
Constructs valid only in top level statements, not subexpressions:
X;Y % |--> V[X]; V[Y] (sequential evaluation hiding first result) X,Y % |--> V[X], V[Y] (sequential evaluation displaying first result) X=Y % |--> V[X]=V[Y] (assignment, X must denote a valid left-value) hide(X) % |--> V[X]; (execute X but hide return value) if(X,Y) % |--> if V[X], V[Y], end if(X,Y,Z) % |--> if V[X], V[Y], else V[Z], end
Things that look and work like Matlab syntax (more or less):
+X              % |--> uplus(V[X])
-X              % |--> uminus(V[X])
X+Y             % |--> plus(V[X],V[Y])
X-Y             % |--> minus(V[X],V[Y])
X^Y             % |--> mpower(V[X],V[Y])
X*Y             % |--> mtimes(V[X],V[Y])
X/Y             % |--> mrdivide(V[X],V[Y])
X\Y             % |--> mldivide(V[X],V[Y])
X.^Y            % |--> power(V[X],V[Y])
X.*Y            % |--> times(V[X],V[Y])
X./Y            % |--> rdivide(V[X],V[Y])
X.\Y            % |--> ldivide(V[X],V[Y])
X:Y:Z           % |--> colon(V[X],V[Y],V[Z])
X:Z             % |--> colon(V[X],V[Z])
X>Z             % |--> gt(V[X],V[Y])
X>=Z            % |--> ge(V[X],V[Y])
X<Z             % |--> lt(V[X],V[Y])
X=<Z            % |--> le(V[X],V[Y])
X==Z            % |--> eq(V[X],V[Y])
[X1,X2,...]     % |--> [ V[X1], V[X2], ... ]
[X1;X2;...]     % |--> [ V[X1]; V[X2]; ... ]
{X1,X2,...}     % |--> { V[X1], V[X2], ... }
{X1;X2;...}     % |--> { V[X1]; V[X2]; ... }
@X              % |--> @V[X] (function handle)
Things that do not look like Matlab syntax but provide standard Matlab features:
'Infinity' % |--> inf (positive infinity) 'Nan' % |--> nan (not a number) X`` % |--> ctranpose(V[X]) (conjugate transpose, V[X]') X#Y % |--> getfield(V[X],V[q(Y)]) X\\Y % |--> @(V[X])V[Y] (same as lambda(X,Y)) \\Y % |--> @()V[Y] (same as thunk(Y)) lambda(X,Y) % |--> @(V[X])V[Y] (anonymous function with arguments X) thunk(Y) % |--> @()V[Y] (anonymous function with no arguments) vector(X) % |--> horzcat(V[X1],V[X2], ...) atvector(X) % as vector but assumes elements of X are assumed all atomic cell(X) % construct 1xN cell array from elements of X `X % same as q(X) q(X) % wrap V[X] in single quotes (escaping internal quotes) tq(X) % wrap TeX expression in single quotes (escape internal quotes)
Referencing different value representations.
mat(X,Y) % denotes a value in the Matbase using a dbload expression mx(X:mx_blob) % denotes an MX Matlab array in SWI memory ws(X:ws_blob) % denotes a variable in a Matlab workspace wsseq(X:ws_blob) % workspace variable containing list as cell array.
Tricky bits.
apply(X,AX)        % X must denote a function or array, applied to list of arguments AX.
cref(X,Y)          % cell dereference, |--> V[X]{ V[Y1], V[Y2], ... }
arr(Lists)         % multidimensional array from nested lists.
arr(Lists,Dims)    % multidimensional array from nested lists.
Things to bypass default formatting
noeval(_) % triggers a failure when processed atom(X) % write atom X as write/1 term(X) % write term X as write/1 \(P) % escape and call phrase P directly to generate Matlab string $(X) % calls pl2ml_hook/2, denotes V[Y] where plml_hook(X,Y). '$VAR'(N) % gets formatted as p_N where N is assumed to be atomic.
All other Prolog atoms are written using write/1, while other Prolog terms are assumed to be calls to Matlab functions named according to the head functor. Thus V[ <head>( <arg1>, <arg2>, ...) ] = <head>(V[<arg1>, V[<arg2>], ...).
There are some incompatibilities between Matlab syntax and Prolog syntax, that is, syntactic structures that Prolog cannot parse correctly:
save('x','Y')" can be written as "save x Y" in Matlab,
but in Prolog, you must use function call syntax with quoted arguments:
save(`x,`'Y').ctranspose(x)".cref(x,1,2)".ml_val(_), only the first return value is bound.
If Y is a list, multiple return values are processed.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).
The following predicates are exported, but not or incorrectly documented.