Daniel@0
|
1 /* Part of DML (Digital Music Laboratory)
|
Daniel@0
|
2 Copyright 2014-2015 Samer Abdallah, University of London
|
Daniel@0
|
3
|
Daniel@0
|
4 This program is free software; you can redistribute it and/or
|
Daniel@0
|
5 modify it under the terms of the GNU General Public License
|
Daniel@0
|
6 as published by the Free Software Foundation; either version 2
|
Daniel@0
|
7 of the License, or (at your option) any later version.
|
Daniel@0
|
8
|
Daniel@0
|
9 This program is distributed in the hope that it will be useful,
|
Daniel@0
|
10 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
Daniel@0
|
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
Daniel@0
|
12 GNU General Public License for more details.
|
Daniel@0
|
13
|
Daniel@0
|
14 You should have received a copy of the GNU General Public
|
Daniel@0
|
15 License along with this library; if not, write to the Free Software
|
Daniel@0
|
16 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
|
Daniel@0
|
17 */
|
Daniel@0
|
18
|
Daniel@0
|
19 :- module(jpath, [ jpath/2, op(600,xfy,#) ]).
|
Daniel@0
|
20 :- use_module(library(dcg_core)).
|
Daniel@0
|
21 :- use_module(library(insist)).
|
Daniel@0
|
22
|
Daniel@0
|
23 % :- op(600,fx,#).
|
Daniel@0
|
24 :- op(600,xfy,#).
|
Daniel@0
|
25
|
Daniel@0
|
26 % harvest(M,Tree) :- harvest(M,just(Tree),nothing).
|
Daniel@0
|
27 % harvest(\X,just(X),nothing).
|
Daniel@0
|
28 % harvest(@F,just(X),just(Y)) :- Y=X.F.
|
Daniel@0
|
29 % harvest(#N,just(X),just(Y)) :- nth1(N,X,Y).
|
Daniel@0
|
30 % harvest(F*G) --> harvest(F), harvest(G).
|
Daniel@0
|
31 % harvest((F//G)) --> harvest(F) // harvest(G).
|
Daniel@0
|
32
|
Daniel@0
|
33 % dec(id,X,X).
|
Daniel@0
|
34 % dec([],_,[]).
|
Daniel@0
|
35 % dec([D|Ds],X,[Y|Ys]) :- dec(D,X,Y), dec(Ds,X,Ys).
|
Daniel@0
|
36 % dec(@F,X,Y) :- Y=X.F.
|
Daniel@0
|
37 % dec(F*G,X,Z) :- dec(F,X,Y), dec(G,Y,Z).
|
Daniel@0
|
38 % dec(swap,(X,Y),(Y,X)).
|
Daniel@0
|
39 % dec(dup,X,(X,X)).
|
Daniel@0
|
40 % dec(fst(F),(X,Y),(Z,Y)) :- dec(F,X,Z).
|
Daniel@0
|
41 % dec((F,G),X,(Y,Z)) :- dec(F,X,Y), dec(G,X,Z).
|
Daniel@0
|
42 % dec(item,X,Y) :- member(Y,X).
|
Daniel@0
|
43
|
Daniel@0
|
44 % decode(F, R, X) :- atomic(F), X=R.F.
|
Daniel@0
|
45 % decode(item(D), R, X) :- decode(D,R,Y), member(X,Y).
|
Daniel@0
|
46 % decode(F/G, R, X) :- decode(F,R,Y), decode(G,Y,X).
|
Daniel@0
|
47
|
Daniel@0
|
48 jpath(Y,X) :-
|
Daniel@0
|
49 (complex(X) -> (match(Y,X); Y=(_,_), multi_match(Y,[],X)) ; Y=X).
|
Daniel@0
|
50
|
Daniel@0
|
51 complex(X) :- is_list(X).
|
Daniel@0
|
52 complex(X) :- is_dict(X).
|
Daniel@0
|
53
|
Daniel@0
|
54 match(\X,X).
|
Daniel@0
|
55 match(Y,X) :- var(Y), !,
|
Daniel@0
|
56 ( is_dict(X) -> match_dict(Y,X)
|
Daniel@0
|
57 ; is_list(X) -> match_list(Y,X)
|
Daniel@0
|
58 ).
|
Daniel@0
|
59 match(dict(X),X) :- must_be(dict,X).
|
Daniel@0
|
60 match(list(X),X) :- must_be(list,X).
|
Daniel@0
|
61 match(N#Y,X) :- must_be(list,X), match_member(N,Y,X).
|
Daniel@0
|
62 match(F:Y,X) :- must_be(dict,X), match_field(F,Y,X).
|
Daniel@0
|
63
|
Daniel@0
|
64 match_dict(dict(X),X).
|
Daniel@0
|
65 match_dict(F:V,X) :- match_field(F,V,X).
|
Daniel@0
|
66
|
Daniel@0
|
67 match_list(list(X),X).
|
Daniel@0
|
68 match_list(N#Y,X) :- match_member(N,Y,X).
|
Daniel@0
|
69
|
Daniel@0
|
70 match_field(F,Y,X) :-
|
Daniel@0
|
71 ( var(F) -> get_dict(F,X,Z)
|
Daniel@0
|
72 ; insist(get_dict(F,X,Z),field_not_present(F,X))
|
Daniel@0
|
73 ),
|
Daniel@0
|
74 jpath(Y,Z).
|
Daniel@0
|
75
|
Daniel@0
|
76 match_member(N,Y,X) :-
|
Daniel@0
|
77 ( var(N) -> nth1(N,X,Z)
|
Daniel@0
|
78 ; nth1(N,X,Z) % insist(...),index_out_of_range(N,X))
|
Daniel@0
|
79 ),
|
Daniel@0
|
80 jpath(Y,Z).
|
Daniel@0
|
81
|
Daniel@0
|
82 % multi_match([],_,_).
|
Daniel@0
|
83 % multi_match([S|Ss],Prev,X) :- match1(S,X), \+member(S,Prev), multi_match(Ss,[S|Prev],X).
|
Daniel@0
|
84 multi_match(S,Prev,X) :- match(S,X), \+member(S,Prev).
|
Daniel@0
|
85 multi_match((S,Ss),Prev,X) :- match(S,X), \+member(S,Prev), multi_match(Ss,[S|Prev],X).
|