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:- module(listing, [ 15 listing_if_defined/1, 16 listing_if_defined/1, 17 list_defined_pred_if_logging_enabled/2 18]). 19 20:- if(current_prolog_flag(dialect, swi)). 21:- use_module(library(listing)). 22:- endif. 23 24:- use_module(logging). 25:- use_module(general). 26:- use_module(utils4modules). 27 28/* 29 * listing*(?Module,+FunctorSubstring,?Arity) 30 * 31 * Call listing(Module:Functor/Arity) for each currently defined 32 * predicate whose functor contains the substring FunctorSubstring. 33 * Throws an exception "secondArgumentNotAtomic(Call)" if 34 * +FunctorSubstring is not atomic. 35 */ 36listing*(Module,FunctorSubstring,Arity) :- 37 atomic(FunctorSubstring) 38 -> all( ( 39 current_predicate(Module:Functor/Arity), 40 sub_atom(Functor, _Start, _Length, _After, FunctorSubstring), 41 listing(Module:Functor/Arity) 42 ) ) 43 ; throw( secondArgumentNotAtomic( listing*(Module,FunctorSubstring,Arity) ) ) 44 . 45 46/* 47 * listing_if_defined(+Functor) 48 * listing_if_defined(+Functor/+Arity) 49 * listing_if_defined(+Head) 50 * 51 * If a predicate corresponding to Arg1 is defined, its current 52 * definition is listed with the built-in predicate listing/1. 53 * Otherwise, this call simply succeeds instead of throwing an 54 * exception (unlike listing/1). 55 */ 56listing_if_defined(Pred) :- 57 catch(listing(Pred),_AnyException,true). 58 59/* 60 * As above but only list clauses in specified module. 61 */ 62listing_if_defined_in_module(Module,Pred) :- 63% term_to_atom(Pred,P), 64% format('~n Clauses of predicate ~a in module ~a: ',[P, Module]), 65 catch(listing_in_module(Module,Pred),_AnyException,true). 66 67/* 68 * As above but only list clauses if logging enabled. 69 */ 70list_defined_pred_if_logging_enabled(Module,Pred) :- 71 do_if_logging_enabled(listing_if_defined_in_module(Module,Pred))