Mercurial > hg > plml
diff prolog/plml.pl @ 37:89688ebc447f tip
Deprecating this repository.
author | samer |
---|---|
date | Mon, 05 Jan 2015 17:42:03 +0000 |
parents | af5fa681278e |
children |
line wrap: on
line diff
--- a/prolog/plml.pl Thu Feb 06 16:26:30 2014 +0000 +++ b/prolog/plml.pl Mon Jan 05 17:42:03 2015 +0000 @@ -36,8 +36,8 @@ , multiplot/2 , mhelp/1 - , op(650,fy,`) % quoting things - , op(160,xf,``) % postfix transpose operator + , op(650,fy,'`') % quoting things + , op(160,xf,'``') % postfix transpose operator , op(100,fy,@) % function handles % note slightly reduced precedence of array operators - @@ -57,6 +57,7 @@ % exported after being imported from ops , op(1100,xfx,::) % type specification (esp for arrays) + , op(550,xfx,..) % range of integers ]). @@ -218,11 +219,12 @@ Remove I from ml_expr//2 and add to mx type? */ -:- use_module(library(debug)). :- use_module(library(apply_macros)). -:- use_module(library(utils), [hostname/1]). -:- use_module(library(dcgu)). -:- use_module(library(ops)). +:- use_module(library(dcg_core)). +:- use_module(library(dcg_codes)). + +:- set_prolog_flag(back_quotes,symbol_char). +:- set_prolog_flag(double_quotes,codes). :- op(700,xfx,===). % variable binding/assignment in matlab query :- op(951,fx,??). % evaluate term as matlab @@ -246,6 +248,10 @@ forall(current_engine(Id), ml_close(Id)). +% from utils.pl +bt_call(Do,Undo) :- Do, (true ; once(Undo), fail). +user:goal_expansion( bt_call(Do,Undo), (Do, (true; once(Undo), fail))). + %% matlab_init( -Key, -Cmd:ml_expr) is nondet. % Each user-defined clause of matlab_init/2 causes Cmd to be executed % whenever a new Matlab session is started. @@ -285,7 +291,7 @@ % 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 +% 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 @@ -429,7 +435,7 @@ %% ml_expr(+Id:ml_eng,+X:ml_expr(A))// is nondet. % Convert Matlab expression as a Prolog term to string representation. -ml_expr(_,\X) --> !, X. +ml_expr(_,\X) --> !, phrase(X). ml_expr(I,$X) --> !, {pl2ml_hook(X,Y)}, ml_expr(I,Y). ml_expr(I,q(X)) --> !, q(stmt(I,X)). ml_expr(I,qq(X)) --> !, qq(stmt(I,X)). @@ -509,6 +515,7 @@ % these are the catch-all clauses which will deal with matlab names, and literals % should we filter on the head functor? +ml_expr(_,A) --> {string(A)}, !, q(str(A)). ml_expr(_,A) --> {atomic(A)}, !, atm(A). ml_expr(I,F) --> {F=..[H|AX]}, atm(H), arglist(I,AX). @@ -986,3 +993,9 @@ {compound(A), A=..[H|T] }, pl2tex(H), paren(seqmap_with_sep(", ",pl2tex,T)). +hostname(H) :- + ( getenv('HOSTNAME',H) -> true + ; setup_call_cleanup(open(pipe(hostname),read,S), + read_line_to_codes(S,Codes), + close(S)), atom_codes(H,Codes) + ).