Mercurial > hg > plml
comparison prolog/plml.pl @ 37:89688ebc447f tip
Deprecating this repository.
author | samer |
---|---|
date | Mon, 05 Jan 2015 17:42:03 +0000 |
parents | af5fa681278e |
children |
comparison
equal
deleted
inserted
replaced
36:a1094b51a6c4 | 37:89688ebc447f |
---|---|
34 % Utilities | 34 % Utilities |
35 , compileoptions/2 | 35 , compileoptions/2 |
36 , multiplot/2 | 36 , multiplot/2 |
37 , mhelp/1 | 37 , mhelp/1 |
38 | 38 |
39 , op(650,fy,`) % quoting things | 39 , op(650,fy,'`') % quoting things |
40 , op(160,xf,``) % postfix transpose operator | 40 , op(160,xf,'``') % postfix transpose operator |
41 , op(100,fy,@) % function handles | 41 , op(100,fy,@) % function handles |
42 | 42 |
43 % note slightly reduced precedence of array operators - | 43 % note slightly reduced precedence of array operators - |
44 % hope this doesn't break everything... | 44 % hope this doesn't break everything... |
45 , op(210,xfy,.^) % array exponentiation | 45 , op(210,xfy,.^) % array exponentiation |
55 , op(750,fy,\\) % thunk abdstraction | 55 , op(750,fy,\\) % thunk abdstraction |
56 , op(750,xfy,\\) % lambda abdstraction | 56 , op(750,xfy,\\) % lambda abdstraction |
57 | 57 |
58 % exported after being imported from ops | 58 % exported after being imported from ops |
59 , op(1100,xfx,::) % type specification (esp for arrays) | 59 , op(1100,xfx,::) % type specification (esp for arrays) |
60 , op(550,xfx,..) % range of integers | |
60 ]). | 61 ]). |
61 | 62 |
62 | 63 |
63 :- multifile(user:optionset/2). | 64 :- multifile(user:optionset/2). |
64 :- multifile(user:matlab_path/2). | 65 :- multifile(user:matlab_path/2). |
216 Deprecate old array(Vals::Type) and cell(Vals::Type) left-value syntax. | 217 Deprecate old array(Vals::Type) and cell(Vals::Type) left-value syntax. |
217 | 218 |
218 Remove I from ml_expr//2 and add to mx type? | 219 Remove I from ml_expr//2 and add to mx type? |
219 */ | 220 */ |
220 | 221 |
221 :- use_module(library(debug)). | |
222 :- use_module(library(apply_macros)). | 222 :- use_module(library(apply_macros)). |
223 :- use_module(library(utils), [hostname/1]). | 223 :- use_module(library(dcg_core)). |
224 :- use_module(library(dcgu)). | 224 :- use_module(library(dcg_codes)). |
225 :- use_module(library(ops)). | 225 |
226 :- set_prolog_flag(back_quotes,symbol_char). | |
227 :- set_prolog_flag(double_quotes,codes). | |
226 | 228 |
227 :- op(700,xfx,===). % variable binding/assignment in matlab query | 229 :- op(700,xfx,===). % variable binding/assignment in matlab query |
228 :- op(951,fx,??). % evaluate term as matlab | 230 :- op(951,fx,??). % evaluate term as matlab |
229 :- op(951,fx,???). % evaluate term as matlab boolean | 231 :- op(951,fx,???). % evaluate term as matlab boolean |
230 :- op(650,fy,`). % quoting things | 232 :- op(650,fy,`). % quoting things |
244 | 246 |
245 ml_closeall :- | 247 ml_closeall :- |
246 forall(current_engine(Id), ml_close(Id)). | 248 forall(current_engine(Id), ml_close(Id)). |
247 | 249 |
248 | 250 |
251 % from utils.pl | |
252 bt_call(Do,Undo) :- Do, (true ; once(Undo), fail). | |
253 user:goal_expansion( bt_call(Do,Undo), (Do, (true; once(Undo), fail))). | |
254 | |
249 %% matlab_init( -Key, -Cmd:ml_expr) is nondet. | 255 %% matlab_init( -Key, -Cmd:ml_expr) is nondet. |
250 % Each user-defined clause of matlab_init/2 causes Cmd to be executed | 256 % Each user-defined clause of matlab_init/2 causes Cmd to be executed |
251 % whenever a new Matlab session is started. | 257 % whenever a new Matlab session is started. |
252 | 258 |
253 %% matlab_path( -Key, -Path:list(atom)) is nondet. | 259 %% matlab_path( -Key, -Path:list(atom)) is nondet. |
283 % * debug(In,Out) | 289 % * debug(In,Out) |
284 % if present, Matlab is started in a script which captures standard | 290 % if present, Matlab is started in a script which captures standard |
285 % input and output to files In and Out respectively. (tbd) | 291 % input and output to files In and Out respectively. (tbd) |
286 % * cmd(Cmd:atom) | 292 % * cmd(Cmd:atom) |
287 % Call Cmd as the matlab executable. Default is 'matlab' (i.e. search | 293 % Call Cmd as the matlab executable. Default is 'matlab' (i.e. search |
288 % for matlab on the PATH).. Can be used to select a different executable | 294 % for matlab on the PATH). Can be used to select a different executable |
289 % or to add command line options. | 295 % or to add command line options. |
290 % * awt(Flag:bool) | 296 % * awt(Flag:bool) |
291 % If false (default), call Matlab with -noawt option. Otherwise, Java graphics | 297 % If false (default), call Matlab with -noawt option. Otherwise, Java graphics |
292 % will be available. | 298 % will be available. |
293 | 299 |
427 stmt(I,Expr) --> !, ml_expr(I,Expr). | 433 stmt(I,Expr) --> !, ml_expr(I,Expr). |
428 | 434 |
429 | 435 |
430 %% ml_expr(+Id:ml_eng,+X:ml_expr(A))// is nondet. | 436 %% ml_expr(+Id:ml_eng,+X:ml_expr(A))// is nondet. |
431 % Convert Matlab expression as a Prolog term to string representation. | 437 % Convert Matlab expression as a Prolog term to string representation. |
432 ml_expr(_,\X) --> !, X. | 438 ml_expr(_,\X) --> !, phrase(X). |
433 ml_expr(I,$X) --> !, {pl2ml_hook(X,Y)}, ml_expr(I,Y). | 439 ml_expr(I,$X) --> !, {pl2ml_hook(X,Y)}, ml_expr(I,Y). |
434 ml_expr(I,q(X)) --> !, q(stmt(I,X)). | 440 ml_expr(I,q(X)) --> !, q(stmt(I,X)). |
435 ml_expr(I,qq(X)) --> !, qq(stmt(I,X)). | 441 ml_expr(I,qq(X)) --> !, qq(stmt(I,X)). |
436 ml_expr(_,tq(X)) --> !, q(pl2tex(X)). | 442 ml_expr(_,tq(X)) --> !, q(pl2tex(X)). |
437 ml_expr(_,atom(X)) --> !, atm(X). | 443 ml_expr(_,atom(X)) --> !, atm(X). |
507 ml_expr(_,(A,B)) --> {throw(ml_illegal_expression((A,B)))}. | 513 ml_expr(_,(A,B)) --> {throw(ml_illegal_expression((A,B)))}. |
508 ml_expr(_,A=B) --> {throw(ml_illegal_expression(A=B))}. | 514 ml_expr(_,A=B) --> {throw(ml_illegal_expression(A=B))}. |
509 | 515 |
510 % these are the catch-all clauses which will deal with matlab names, and literals | 516 % these are the catch-all clauses which will deal with matlab names, and literals |
511 % should we filter on the head functor? | 517 % should we filter on the head functor? |
518 ml_expr(_,A) --> {string(A)}, !, q(str(A)). | |
512 ml_expr(_,A) --> {atomic(A)}, !, atm(A). | 519 ml_expr(_,A) --> {atomic(A)}, !, atm(A). |
513 ml_expr(I,F) --> {F=..[H|AX]}, atm(H), arglist(I,AX). | 520 ml_expr(I,F) --> {F=..[H|AX]}, atm(H), arglist(I,AX). |
514 | 521 |
515 ml_expr_with(I,Lambda,Y) --> {copy_term(Lambda,Y\\PY)}, ml_expr(I,PY). | 522 ml_expr_with(I,Lambda,Y) --> {copy_term(Lambda,Y\\PY)}, ml_expr(I,PY). |
516 | 523 |
984 pl2tex(A) --> {atomic(A)}, escape_with(0'\\,0'_,at(A)). | 991 pl2tex(A) --> {atomic(A)}, escape_with(0'\\,0'_,at(A)). |
985 pl2tex(A) --> | 992 pl2tex(A) --> |
986 {compound(A), A=..[H|T] }, | 993 {compound(A), A=..[H|T] }, |
987 pl2tex(H), paren(seqmap_with_sep(", ",pl2tex,T)). | 994 pl2tex(H), paren(seqmap_with_sep(", ",pl2tex,T)). |
988 | 995 |
996 hostname(H) :- | |
997 ( getenv('HOSTNAME',H) -> true | |
998 ; setup_call_cleanup(open(pipe(hostname),read,S), | |
999 read_line_to_codes(S,Codes), | |
1000 close(S)), atom_codes(H,Codes) | |
1001 ). |