1/***************************************************************************** 2 * This file is part of the Prolog Development Tool (PDT) 3 * 4 * WWW: http://sewiki.iai.uni-bonn.de/research/pdt/start 5 * Mail: pdt@lists.iai.uni-bonn.de 6 * Copyright (C): 2004-2012, CS Dept. III, University of Bonn 7 * 8 * All rights reserved. This program is made available under the terms 9 * of the Eclipse Public License v1.0 which accompanies this distribution, 10 * and is available at http://www.eclipse.org/legal/epl-v10.html 11 * 12 ****************************************************************************/ 13 14/* 15 * This module provides the infrastructure for managing CTC data 16 * (PEFs) and CTC programs (CTs and CT sequences) in multiple 17 * modules without having to add a module parameter to each CTC 18 * operation. 19 * 20 * The directive ":- ctc_module(name, F/N_list)." to be added at the 21 * beginning of a CTC program file declares that this file contains 22 * CT and/or CT sequence definitions in the Prolog module 'name' 23 * with their heads' functor/arity according to F/N_list. 24 */ 25 26:- module(ctc_admin_copy,[ 27 % These two rather belong to the interpreter: 28 ctc_id_init_pdt/0, 29 new_node_id_pdt/1 % (-NewId) 30]). 31 32:- use_module(pdt_prolog_library(logging)). 33/***************************************************************** 34 * Predefined predicates: prev_ctc_id/1, ctc_id_init/0, new_node_id/1 35 */ 36 37/* 38 * Identity counter. Initialized to 10000. 39 */ 40:- dynamic prev_ctc_id/1. 41 42ctc_id_init_pdt :- 43 retractall(prev_ctc_id(_)), 44 assert(prev_ctc_id(10000)). 45 46?- ctc_id_init_pdt. 47 48/* 49 * new_node_id(-Id): Bind id to a unique term. 50 */ 51new_node_id_pdt(NewId) :- 52 clause(user:new_id(_),_) % If new_id is defined (=JT is running) 53 -> user:new_id(NewId) % ... use new_id to ensure consistency 54 ; ( var(NewId) % ... otherwise use own implementation 55 -> ( prev_ctc_id(Last), 56 NewId is Last+1, 57 retract(prev_ctc_id(Last)), 58 !, 59 assert(prev_ctc_id(NewId)) 60 ) 61 ; ( term_to_atom(NewId,Id), 62 ctc_warning('Ignored call of operation new_node_id(Id) with non-variable Parameter (Id = ~w).' ,[Id]) 63 ) 64 )