1% This file is part of the Attempto Parsing Engine (APE).
    2% Copyright 2013, Attempto Group, University of Zurich (see http://attempto.ifi.uzh.ch).
    3%
    4% The Attempto Parsing Engine (APE) is free software: you can redistribute it and/or modify it
    5% under the terms of the GNU Lesser General Public License as published by the Free Software
    6% Foundation, either version 3 of the License, or (at your option) any later version.
    7%
    8% The Attempto Parsing Engine (APE) is distributed in the hope that it will be useful, but WITHOUT
    9% ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
   10% PURPOSE. See the GNU Lesser General Public License for more details.
   11%
   12% You should have received a copy of the GNU Lesser General Public License along with the Attempto
   13% Parsing Engine (APE). If not, see http://www.gnu.org/licenses/.
   14
   15
   16:- module(transform_anonymous, [
   17		transform_anonymous/2   % +TermIn, -TermOut
   18	]).

Transform Anonymous Individuals

author
- Tobias Kuhn
version
- 2007-10-29 */
 transform_anonymous(+TermIn, -TermOut)
   29transform_anonymous(TermIn, TermOut) :-
   30	transform_anonymous(TermIn, TermOut, [], _).
   31
   32
   33transform_anonymous(Var, Var, Map, Map) :-
   34	var(Var),
   35	!.
   36
   37transform_anonymous(nodeID('$VAR'(LocalID)), nodeID(GlobalID), MapIn, MapOut) :-
   38	!,
   39	( member((LocalID, GID), MapIn) ->
   40		GlobalID = GID,
   41		MapOut = MapIn
   42	;
   43		GlobalID is random(1000000000000000000),
   44		MapOut = [(LocalID, GlobalID)|MapIn]
   45	).
   46
   47transform_anonymous([], [], Map, Map) :-
   48	!.
   49
   50transform_anonymous([H1|T1], [H2|T2], MapIn, MapOut) :-
   51	!,
   52	transform_anonymous(H1, H2, MapIn, MapTemp),
   53	transform_anonymous(T1, T2, MapTemp, MapOut).
   54
   55transform_anonymous(Term, Term, Map, Map) :-
   56	Term =.. [Term],
   57	!.
   58
   59transform_anonymous(Term1, Term2, MapIn, MapOut) :-
   60	!,
   61	Term1 =.. List1,
   62	transform_anonymous(List1, List2, MapIn, MapOut),
   63	Term2 =.. List2