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% Utility used by pdt/src/org/cs3/pdt/internal/editors/PLScanner.java
   15
   16:- module( pdt_editor_highlighting,
   17         [ predicates_with_property/3  
   18         ]).   19:- use_module(library(lists)).   20:- use_module( prolog_connector_pl(split_file_path),
   21             [ split_file_path/5                % (File,Folder,FileName,BaseName,Extension)
   22             ] ).   23
   24:- op(600, xfy, ::).   % Logtalk message sending operator
   25
   26               /************************************************
   27                * PREDICATE PROPERTIES FOR SYNTAX HIGHLIGHTING *
   28                ************************************************/
 predicates_with_property(+Property, ?FileName, -Predicates) is det
Look up all Predicates with property Property, including atomic properties (e.g. dynamic, built_in) AND properties that are functions (e.g. meta_predicate(Head)).

Property = undefined | built_in | dynamic | transparent | meta_predicate(_)

   39% GK, 5. April 2011: Extended the implementation to deal with functors. 
   40% The combination of findall and setof is essential for 
   41% this added functionality. The findall/3 call finds all results
   42%   (even if the arguments are free variables -- note that setof/3
   43%   would return results one by one in such a case, not a full list!). 
   44% Then the setof/3 call eliminates the duplicates from the results
   45% of findall/3. 
   46% DO NOT CHANGE, unless you consider yourself a Prolog expert.
   47
   48% Look for undefined predicates only in the local context 
   49% (of the file whose editor has just been opened):
   50%predicates_with_property(undefined, FileName, Predicates) :-
   51%    !,
   52%    module_of_file(FileName,Module), 
   53%	findall(Name, predicate_name_with_property_(Module,Name,undefined), AllPredicateNames),
   54%	make_duplicate_free_string(AllPredicateNames,Predicates).
   55
   56predicates_with_property(Property, FileName, Predicates) :-
   57	(	split_file_path(FileName, _, _, _, lgt)
   58	;	split_file_path(FileName, _, _, _, logtalk)
   59	),
   60	!,
   61	current_predicate(logtalk_load/1),
   62	logtalk_editor_adapter::predicates_with_property(Property, FileName, AllPredicateNames),
   63	make_duplicate_free_string(AllPredicateNames,Predicates).
   64predicates_with_property(Property, _FileName, Predicates) :-
   65    findall(Name, predicate_name_with_property_(_Module,Name,Property), AllPredicateNames),
   66	make_duplicate_free_string(AllPredicateNames,Predicates).
   67
   68
   69    	
   70predicate_name_with_property_(Module,Name,Property) :-
   71    current_module(Module),
   72    current_predicate(Module:Name/Arity),
   73	Name \== [],
   74	Name \== (:),
   75	\+ atom_concat('$', _, Name),
   76	functor(Head,Name,Arity),
   77	predicate_property(Module:Head,Property).
   78	
   79make_duplicate_free_string(AllPredicateNames,Predicates) :-
   80    setof(Name, member(Name,AllPredicateNames), UniqueNames),
   81	format(atom(Predicates),'~w',[UniqueNames]).
   82
   83
   84% Below this line is apparently dead code. 
   85% TODO: 
   86% Check whether it is better than the one above.
   87% If yes use it, otherwise delete it. 
 predicates_with_unary_property(+Property, ?Predicates, ?PropertyParams) is det
Look up all Predicates with the unary property Property, e.g. meta_predicate(Head) The element at position i in Predicates is the name of a predicate that has the property Property with the parameter at position i in PropertyParams.

Author: GK, 5 April 2011 TODO: Integrate into the editor the ability to show the params as tool tips, e.g. show the metaargument specifications of a metapredicate on mouse over.

   99predicates_with_unary_property(Property,Predicates,PropertyArguments) :-
  100	setof((Name,Arg),
  101	   predicate_name_with_unary_property_(Name,Property,Arg),
  102	   PredArgList),
  103	findall(Pred, member((Pred,_),PredArgList), AllProps),
  104	findall(Arg,  member((_,Arg), PredArgList), AllArgs),
  105	format(atom(Predicates),'~w',[AllProps]),
  106	format(atom(PropertyArguments),'~w',[AllArgs]).
  107	   	  
  108% helper
  109predicate_name_with_unary_property_(Name,Property,Arg) :-
  110    Property =.. [__F,Arg],
  111	predicate_property(_M:Head,Property),
  112	functor(Head,Name,_),
  113	Name \= '[]'