diff cpack/dml/lib/jpath.pl @ 0:718306e29690 tip

commiting public release
author Daniel Wolff
date Tue, 09 Feb 2016 21:05:06 +0100
parents
children
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/lib/jpath.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,85 @@
+/* Part of DML (Digital Music Laboratory)
+	Copyright 2014-2015 Samer Abdallah, University of London
+	 
+	This program is free software; you can redistribute it and/or
+	modify it under the terms of the GNU General Public License
+	as published by the Free Software Foundation; either version 2
+	of the License, or (at your option) any later version.
+
+	This program is distributed in the hope that it will be useful,
+	but WITHOUT ANY WARRANTY; without even the implied warranty of
+	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+	GNU General Public License for more details.
+
+	You should have received a copy of the GNU General Public
+	License along with this library; if not, write to the Free Software
+	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+*/
+
+:- module(jpath, [ jpath/2, op(600,xfy,#) ]).
+:- use_module(library(dcg_core)).
+:- use_module(library(insist)).
+
+% :- op(600,fx,#).
+:- op(600,xfy,#).
+
+% harvest(M,Tree) :- harvest(M,just(Tree),nothing).
+% harvest(\X,just(X),nothing).
+% harvest(@F,just(X),just(Y)) :- Y=X.F.
+% harvest(#N,just(X),just(Y)) :- nth1(N,X,Y).
+% harvest(F*G) --> harvest(F), harvest(G).
+% harvest((F//G)) --> harvest(F) // harvest(G).
+
+% dec(id,X,X).
+% dec([],_,[]).
+% dec([D|Ds],X,[Y|Ys]) :- dec(D,X,Y), dec(Ds,X,Ys).
+% dec(@F,X,Y) :- Y=X.F.
+% dec(F*G,X,Z) :- dec(F,X,Y), dec(G,Y,Z).
+% dec(swap,(X,Y),(Y,X)).
+% dec(dup,X,(X,X)).
+% dec(fst(F),(X,Y),(Z,Y)) :- dec(F,X,Z).
+% dec((F,G),X,(Y,Z)) :- dec(F,X,Y), dec(G,X,Z).
+% dec(item,X,Y) :- member(Y,X).
+
+% decode(F, R, X) :- atomic(F), X=R.F.
+% decode(item(D), R, X) :- decode(D,R,Y), member(X,Y).
+% decode(F/G, R, X) :- decode(F,R,Y), decode(G,Y,X).
+
+jpath(Y,X) :- 
+   (complex(X) -> (match(Y,X); Y=(_,_), multi_match(Y,[],X)) ; Y=X).
+
+complex(X) :- is_list(X).
+complex(X) :- is_dict(X).
+
+match(\X,X).
+match(Y,X) :- var(Y), !, 
+   (  is_dict(X) -> match_dict(Y,X)
+   ;  is_list(X) -> match_list(Y,X)
+   ).
+match(dict(X),X) :- must_be(dict,X).
+match(list(X),X) :- must_be(list,X).
+match(N#Y,X) :- must_be(list,X), match_member(N,Y,X).
+match(F:Y,X) :- must_be(dict,X), match_field(F,Y,X).
+
+match_dict(dict(X),X).
+match_dict(F:V,X) :- match_field(F,V,X).
+
+match_list(list(X),X).
+match_list(N#Y,X) :- match_member(N,Y,X).
+
+match_field(F,Y,X) :- 
+   (  var(F) -> get_dict(F,X,Z)
+   ;  insist(get_dict(F,X,Z),field_not_present(F,X))
+   ), 
+   jpath(Y,Z).
+
+match_member(N,Y,X) :- 
+   (  var(N) -> nth1(N,X,Z)
+   ;  nth1(N,X,Z) % insist(...),index_out_of_range(N,X))
+   ),
+   jpath(Y,Z).
+
+% multi_match([],_,_).
+% multi_match([S|Ss],Prev,X) :- match1(S,X), \+member(S,Prev), multi_match(Ss,[S|Prev],X).
+multi_match(S,Prev,X) :- match(S,X), \+member(S,Prev).
+multi_match((S,Ss),Prev,X) :- match(S,X), \+member(S,Prev), multi_match(Ss,[S|Prev],X).