Types
ml_eng - Any atom identifying a Matlab engine.
See plml_dcg.pl for information about Matlab term language.
@tbd
Use mat(I) and tmp(I) as types to include engine Id.
Clarify relationship between return values and valid Matlab denotation.
Reshape/2 array representation: reshape([ ... ],Size)
Expression language: arr(Vals,Shape,InnerFunctor) - allows efficient
representation of arrays of arbitrary things. Will require more strict
nested list form.
Deprecate old array(Vals::Type) and cell(Vals::Type) left-value syntax.
Remove I from ml_expr//2 and add to mx type?
- ml_open(+Id:ml_eng, +Host:atom, +Options:list(_)) is det
- ml_open(+Id:ml_eng, +Host:atom) is det
- ml_open(+Id:ml_eng) is det
- Start a Matlab session on the given host. If Host=localhost
or the name of the current current host as returned by hostname/1,
then a Matlab process is started directly. Otherwise, it is
started remotely via SSH. Options defaults to []. Host defaults to
localhost.
Start a Matlab session on the specified host using default options.
If Host is not given, it defaults to localhost. Session will be
associated with the given Id, which should be an atom. See ml_open/3.
Valid options are below. Note that matlab is always called with
the -nodesktop and -nosplash options.
- noinit
- If present, do not run initialisation commands specified by
matlab_path/2 and matlab_init/2 clauses. Otherwise, do run them.
- debug(In, Out)
- if present, Matlab is started in a script which captures standard
input and output to files In and Out respectively. (tbd)
- cmd(Cmd:atom)
- Call Cmd as the matlab executable. Default is 'matlab' (i.e. search
for matlab on the PATH). Can be used to select a different executable
or to add command line options.
- awt(Flag:bool)
- If false (default), call Matlab with -noawt option. Otherwise, Java graphics
will be available.
- ml_close(+Id:ml_eng) is det
- Close Matlab session associated with Id.
- ml_exec(+Id:ml_eng, +Expr:ml_expr) is det
- Execute Matlab expression without returning any values.
- ml_eval(+Id:ml_eng, +Expr:ml_expr, +Types:list(type), -Res:list(ml_val)) is det
- Evaluate Matlab expression binding return values to results list Res. This new
form uses an explicit output types list, so Res can be completely unbound on entry
even when multiple values are required.
- ml_test(+Id:ml_eng, +X:ml_expr(bool)) is semidet
- Succeeds if X evaluates to true in Matlab session Id.
- ??(X:ml_expr(_)) is det
- Execute Matlab expression X as with ml_exec/2, without returning any values.
- ???(X:ml_expr(bool)) is semidet
- Evaluate Matlab boolean expression X as with ml_test/2.
- ===(Y:ml_vals(A), X:ml_expr(A)) is det
- Evaluate Matlab expression X as in ml_eval/4, binding one or more return values
to Y. If Y is unbound or a single
ml_val(_)
, only the first return value is bound.
If Y is a list, multiple return values are processed.
- leftval(+TVal:tagged(T), -T:type, -Val:T) is det
- True if TVal is a tagged value whos type is T and value is Val.
- wsvar(+X:ws_blob(A), -Nm:atom, -Id:ml_eng) is semidet
- True if X is a workspace variable in Matlab session Id.
Unifies Nm with the name of the Matlab variable.
- dropmat(+Id:ml_id, +Mat:ml_loc) is det
- Deleting MAT file from matbase.
- exportmat(+Id:ml_id, +Mat:ml_loc, +Dir:atom) is det
- Export specified MAT file from matbase to given directory.
- matbase_mat(+Id:ml_eng, -X:ml_loc) is nondet
- Listing mat files actually in matbase at given root directory.
- persist_item(+X:ml_expr(A), -Y:ml_expr(A)) is det
- Convert Matlab expression to persistent form not dependent on
current Matlab workspace or MX arrays in Prolog memory space.
Large values like arrays and structures are saved in the matbase
replaced with matbase locators. Scalar values are converted to
literal numeric values. Character strings are converted to Prolog atoms.
Cell arrays wrapped in the wsseq/1 functor are converted to literal
form.
NB. any side effects are undone on backtracking -- in particular, any
files created in the matbase are deleted.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
- ml_open(Arg1)
- ml_open(Arg1, Arg2)
- ml_ws_name(Arg1, Arg2, Arg3)