1/*****************************************************************************
    2 * This file is part of the Prolog Development Tool (PDT)
    3 * 
    4 * Author: Andreas Becker
    5 * WWW: http://sewiki.iai.uni-bonn.de/research/pdt/start
    6 * Mail: pdt@lists.iai.uni-bonn.de
    7 * Copyright (C): 2014, CS Dept. III, University of Bonn
    8 * 
    9 * All rights reserved. This program is  made available under the terms
   10 * of the Eclipse Public License v1.0 which accompanies this distribution,
   11 * and is available at http://www.eclipse.org/legal/epl-v10.html
   12 * 
   13 ****************************************************************************/
   14
   15:- module(pdt_call_hierarchy, [
   16	find_predicate_declaration_and_visibility/5,
   17	find_caller/9,
   18	find_callee/9,
   19	find_call_location/9
   20]).   21
   22:- use_module(pdt_prolog_library(utils4modules_visibility), [
   23	declared_in_module/4,
   24	visible_in_module/3,
   25	module_of_file/2
   26]).   27
   28:- use_module(pdt_call_graph, [
   29	ensure_call_graph_generated/0,
   30	calls/7,
   31	calls_multifile/8,
   32	pdt_walk_code/1
   33]).   34
   35:- use_module(library(lists), [
   36	sum_list/2
   37]).
 find_predicate_declaration_and_visibility(ModuleOrFile, Name, Arity, DeclaringModule, Visibility)
   40find_predicate_declaration_and_visibility(ModuleOrFile, Name, Arity, DeclaringModule, Visibility) :-
   41	(	ModuleOrFile = module(Module)
   42	->	true
   43	;	ModuleOrFile = file(File),
   44		source_file(File),
   45		once(module_of_file(File, Module))
   46	),
   47	(	declared_in_module(Module, Name, Arity, DeclaringModule)
   48	->	true
   49	;	DeclaringModule = Module
   50	),
   51	predicate_visibility(DeclaringModule, Name, Arity, Visibility).
 predicate_visibility(Module, Name, Arity, Visibility)
   54predicate_visibility(Module, Name, Arity, Visibility) :-
   55	(	visible_in_module(Module, Name, Arity)
   56	->	(	(	Module == user
   57			;	functor(Head, Name, Arity),
   58				predicate_property(Module:Head, exported)
   59			)
   60		->	Visibility = exported
   61		;	Visibility = non_exported
   62		)
   63	;	Visibility = undefined
   64	).
 find_caller(Module, Name, Arity, Root, CallerModule, CallerName, CallerArity, Count, Visibility)
   67find_caller(Module, Name, Arity, Root, CallerModule, CallerName, CallerArity, Count, Visibility) :-
   68	ensure_call_graph_generated,
   69	(	var(Root)
   70	->	calls(Module, Name, Arity, CallerModule, CallerName, CallerArity, Count)
   71	;	(	functor(Head, Name, Arity),	
   72			predicate_property(Module:Head, multifile)
   73		->	bagof(
   74				NumberOfCalls,
   75				Module^Name^Arity^File^(	
   76					calls_multifile(Module, Name, Arity, CallerModule, CallerName, CallerArity, File, NumberOfCalls),
   77					atom_concat(Root, _, File)
   78				),
   79				Counts
   80			),
   81			sum_list(Counts, Count)
   82		;	calls(Module, Name, Arity, CallerModule, CallerName, CallerArity, Count),
   83			functor(CallerHead, CallerName, CallerArity),
   84			predicate_property(CallerModule:CallerHead, file(File)),
   85			atom_concat(Root, _, File)
   86		)
   87	),
   88	predicate_visibility(CallerModule, CallerName, CallerArity, Visibility).
 find_callee(Module, Name, Arity, Root, CalleeModule, CalleeName, CalleeArity, Count, Visibility)
   91find_callee(Module, Name, Arity, Root, CalleeModule, CalleeName, CalleeArity, Count, Visibility) :-
   92	ensure_call_graph_generated,
   93	(	var(Root)
   94	->	calls(CalleeModule, CalleeName, CalleeArity, Module, Name, Arity, Count)
   95	;	functor(Head, Name, Arity),
   96		(	predicate_property(Module:Head, multifile)
   97		->	bagof(
   98				NumberOfCalls,
   99				Module^Name^Arity^File^(	
  100					calls_multifile(CalleeModule, CalleeName, CalleeArity, Module, Name, Arity, File, NumberOfCalls),
  101					atom_concat(Root, _, File)
  102				),
  103				Counts
  104			),
  105			sum_list(Counts, Count)
  106		;	predicate_property(Module:Head, file(File)),
  107			atom_concat(Root, _, File),
  108			calls(CalleeModule, CalleeName, CalleeArity, Module, Name, Arity, Count)
  109		)
  110	),
  111	predicate_visibility(CalleeModule, CalleeName, CalleeArity, Visibility).
 find_call_location(CallerModule, CallerName, CallerArity, CalleeModule, CalleeName, CalleeArity, Root, File, Location)
  114find_call_location(CallerModule, CallerName, CallerArity, CalleeModule, CalleeName, CalleeArity, Root, File, Location) :-
  115	retractall(result(_, _, _, _)),
  116	functor(CalleeHead, CalleeName, CalleeArity),
  117	pdt_walk_code([trace_reference(CalleeModule:CalleeHead), predicates([CallerModule:CallerName/CallerArity]), on_trace(pdt_call_hierarchy:assert_result)]),
  118	!,
  119	retract(result(_Goal, Ref, TermPosition, _Kind)),
  120	(	(	TermPosition = term_position(Start, End, _, _, _)
  121		;	TermPosition = Start-End
  122		)
  123	->	format(atom(Location), '~w-~w', [Start, End])
  124	;	clause_property(Ref, line_count(Location))
  125	),
  126	clause_property(Ref, file(File)),
  127	(	nonvar(Root)
  128	->	sub_atom(File, 0, _, _, Root)
  129	;	true
  130	).
  131
  132:- dynamic(result/4).  133
  134assert_result(Goal, _, clause(Ref), Kind) :-
  135    (	result(Goal, Ref, [], Kind)
  136    ->	true
  137    ;	assertz(result(Goal, Ref, [], Kind))
  138    ),
  139    !.
  140assert_result(Goal, _, clause_term_position(Ref, TermPosition), Kind) :-
  141    (	result(Goal, Ref, TermPosition, Kind)
  142    ->	true
  143    ;	assertz(result(Goal, Ref, TermPosition, Kind))
  144    ),
  145    !.
  146assert_result(_,_,_,_)