1/* 2* Copyright (c) 2016, University of Texas at Dallas 3* All rights reserved. 4* 5* Redistribution and use in source and binary forms, with or without 6* modification, are permitted provided that the following conditions are met: 7* * Redistributions of source code must retain the above copyright 8* notice, this list of conditions and the following disclaimer. 9* * Redistributions in binary form must reproduce the above copyright 10* notice, this list of conditions and the following disclaimer in the 11* documentation and/or other materials provided with the distribution. 12* * Neither the name of the University of Texas at Dallas nor the 13* names of its contributors may be used to endorse or promote products 14* derived from this software without specific prior written permission. 15* 16* THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" 17* AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE 18* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE 19* DISCLAIMED. IN NO EVENT SHALL THE UNIVERSITY OF TEXAS AT DALLAS BE LIABLE FOR 20* ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES 21* (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 22* LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND 23* ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT 24* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS 25* SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. 26*/ 27 28:- module(scasp_variables, 29 [ is_var/1, 30 is_var/2, 31 body_vars/3, 32 var_list/2, % +N, -Vars 33 revar/3 % +Term,-VarTerm,-Bindings 34 ]). 35:- use_module(library(assoc)). 36:- use_module(library(apply)). 37:- use_module(library(lists)). 38 39/** <module> Variable storage and access 40 41Predicates related to storing, accessing and modifying variables. 42 43@author Kyle Marple 44@version 20170515 45@license BSD-3 46*/ 47 48%! is_var(@Term) is semidet. 49%! is_var(@Term, Name) is semidet. 50% 51% Test an entry to see if it's a variable (the first non-underscore is 52% an upper-case letter. 53% 54% @arg Term is the term to be tested. 55 56is_var($X) :- 57 atom(X). 58 59is_var($X, X) :- 60 atom(X). 61 62%! body_vars(+Head:compound, +Body:list, -BodyVars:list) is det 63% 64% Get the body variables (variables used in the body but not in the 65% head) for a clause. 66 67:- det(body_vars/3). 68 69body_vars(H, B, Bv) :- 70 empty_assoc(Empty), 71 term_vars(H, _, [], Empty, Hv), 72 term_vars(B, Bv, [], Hv, _). 73 74term_vars(Var, Vars0, Vars, Seen0, Seen) :- 75 is_var(Var, Name), 76 !, 77 ( get_assoc(Name, Seen0, _) 78 -> Vars = Vars0, 79 Seen = Seen0 80 ; put_assoc(Name, Seen0, true, Seen), 81 Vars0 = [Var|Vars] 82 ). 83term_vars(Term, Vars0, Vars, Seen0, Seen) :- 84 compound(Term), 85 !, 86 functor(Term, _Name, Arity), 87 term_vars(1, Arity, Term, Vars0, Vars, Seen0, Seen). 88term_vars(_, Vars, Vars, Seen, Seen). 89 90term_vars(I, Arity, Term, Vars0, Vars, Seen0, Seen) :- 91 I =< Arity, 92 !, 93 arg(I, Term, Arg), 94 term_vars(Arg, Vars0, Vars1, Seen0, Seen1), 95 I2 is I+1, 96 term_vars(I2, Arity, Term, Vars1, Vars, Seen1, Seen). 97term_vars(_, _, _, Vars, Vars, Seen, Seen). 98 99%! var_list(+N:int, -Vars:list) is det 100% 101% Get a list of N variables, each of which is different. Basically, 102% just append a counter to '_X'. The '_' prefix ensures they don't 103% overlap with any existing variables in a rule. 104% 105% @arg N The size of the list to return. 106% @arg Vars output list. 107 108:- det(var_list/2). 109 110var_list(0, []) :- 111 !. 112var_list(I, [H|T]) :- 113 I2 is I-1, 114 var_list(I2, T), 115 mk_var(I2, H). 116 117mk_var(I, $Name) :- 118 atom_concat('_X', I, Name). 119 120%! revar(+Term, -VarTerm, -Bindings) is det. 121% 122% If Term is a term that contains atoms using variable syntax 123% ([A-Z].*), VarTerm is a copy of Term with all such atoms replaced by 124% variables. In addition this performs the following rewrites: 125% 126% - A term N/D is translated into rat(N,D) 127% - An atom N/D is translated into rat(N,D) 128% - A quoted atom is translated into its unquoted equivalent 129% 130% @arg Bindings is a list `Name=Var` that contains the variable names. 131 132revar(X,Y,VarNames) :- 133 empty_assoc(Dic0), 134 revar_(X,Y,Dic0,Dic), 135 assoc_to_list(Dic, Pairs), 136 maplist(varname, Pairs, VarNames). 137 138varname(Name-Var, Name=Var). 139 140revar_(X,Y,Dic,Dic) :- 141 var(X), 142 !, 143 Y=X. 144revar_(X,Y,Dic0,Dic) :- 145 is_var(X, Name), 146 !, 147 ( get_assoc(Name, Dic0, Y) 148 -> Dic = Dic0 149 ; put_assoc(Name, Dic0, Y, Dic) 150 ). 151revar_(X,Y,Dic,Dic) :- 152 special_atom(X,Y), 153 !. 154revar_(X,Y,Dic0,Dic) :- 155 X=..[F|As], 156 revars(As,Bs,Dic0,Dic), 157 Y=..[F|Bs]. 158 159special_atom(A/B,Rat) :- 160 integer(A), 161 integer(B), 162 !, 163 Rat is rdiv(A,B). 164special_atom(X,Y) :- 165 atom(X), 166 atom_chars(X,Codes), 167 append(['\''|C_Y],['\''],Codes), 168 atom_chars(Y,C_Y). 169 170revars([],[],Dic,Dic). 171revars([X|Xs],[Y|Ys],Dic0,Dic) :- 172 revar_(X,Y,Dic0,Dic1), 173 revars(Xs, Ys, Dic1, Dic)