1/*****************************************************************************
    2 * This file is part of the Prolog Development Tool (PDT)
    3 * 
    4 * Author: G�nter Kniesel (among others)
    5 * WWW: http://sewiki.iai.uni-bonn.de/research/pdt/start
    6 * Mail: pdt@lists.iai.uni-bonn.de
    7 * Copyright (C): 2004-2012, 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% Date: 25.06.2006
   16
   17/*
   18 * This file contains predicates for working with SWI-Prolog modules.
   19 */
   20:- module( utils4modules, [
   21
   22           assert_in_module/2,             % Module, Head
   23           assert_in_module/3,             % Module, Head, Body
   24           clause_in_module/2,             % Module, Head
   25           clause_in_module/3,             % Module, Head, Body
   26           retract_in_module/2,            % Module, Head
   27           retract_in_module/3,            % Module, Head, Body
   28           retractall_in_module/2,         % Module, Head
   29           call_in_module/2,               % Module, Goal
   30           call_and_report_contex_module/1,% Goal
   31           report_contex_module/1,         % Module        
   32           listing_in_module/2,            % Module, FunctorOrHeadOrFkt/Arity
   33           
   34           copy_module_predicate/3,        % SrcMod, TargetMod, Head
   35           move_module_predicate/3         % SrcMod, TargetMod, Head
   36           ]
   37 ).   38 
   39:- use_module(library(lists)).   40:- use_module(pdt_support, [pdt_support/1]).   41:- use_module(logging).   42:- use_module(database).   43:- use_module(utils4modules_visibility).   44
   45:- module_transparent(call_and_report_contex_module/1).   46call_and_report_contex_module(Goal) :- 
   47    context_module(M),
   48    log_on_stdout('Calling ~w.~n',[M:Goal]),
   49    call(M:Goal).
   50
   51:- module_transparent(report_contex_module/1).   52report_contex_module(M) :- context_module(M),
   53    log_on_stdout('Context module = ~w.~n',[M]).
   54    
   55   
   56    
   57/*
   58 * call_in_module(+Module, +Head) is nondet
   59 * 
   60 * Call Head in Module regardless whether Head is locally defined or
   61 * imported from another module. 
   62 */
   63call_in_module(Module,Goal) :- 
   64   nonvar(Module)
   65   -> call( Module:Goal )
   66    ; ctc_error('Goal called in variable module: ~w:~w.', 
   67                 [Module,Goal]
   68   ).
   69
   70   
   71/*
   72 * assert_in_module(?Mod,?Head      ) is det
   73 *
   74 * Assert clauses in an explicitly specified module. 
   75 * 
   76 * CAUTION: Due to the semantics of modules in SWI-Prolog, the  
   77 * clause ends up in the module from which the explicitly specified 
   78 * module imports the declaration of the predicate to be asserted.
   79 * 
   80 * assert_in_module/2,3 differs from a normal assert called in a 
   81 * module, which would assert the fact into the module containing
   82 * the invocation of assert (unless the predicate containing the 
   83 * invocation and all its parents on the stack were "module_transparent"
   84 * and the invoking module was loaded via use_module ...). 
   85 */
   86assert_in_module(Mod,Head      ) :- assert( :(Mod,Head) ).
   87assert_in_module(Mod,Head,Body ) :- not(is_list(Body)), !, assert( :(Mod,':-'(Head,Body)) ).
   88
   89assert_in_module(Mod,Head, []) :- assert_in_module(Mod,Head ).
   90    
   91assert_in_module(Mod,Head, [Opt]) :- 
   92   (  Opt == unique
   93   -> assert_unique( :(Mod,Head))
   94   ;  assert(        :(Mod,Head))
   95   ).
   96   
   97assert_in_module(Mod,Head,Body, [Opt]) :- 
   98   (  Opt == unique
   99   -> assert_unique( :(Mod,':-'(Head,Body)))
  100   ;  assert(        :(Mod,':-'(Head,Body)))
  101   ).
  102
  103
  104/*
  105 * Get or retract clauses from an explicitly specified module.
  106 * The Module argument must not be a variable! 
  107 * These predicates never access clauses imported from other modules.
  108 * They only get or delete clauses that are actually asserted in the
  109 * specified module. This appears to be standard SWI Prolog behaviour
  110 * meanwhile but it sometimes changed, so for safety we prefer to 
  111 * enforce it ourselves. 
  112 */
  113clause_in_module(Mod,Head	)   :- defined_in_module(Mod, Head), clause( :(Mod,Head),_ ) .
  114clause_in_module(Mod,Head,Body) :- defined_in_module(Mod, Head), clause( :(Mod,Head),Body ) .
  115
  116retract_in_module(Mod,Head   )  :- defined_in_module(Mod, Head), retract( :(Mod,Head) ) .
  117retract_in_module(Mod,Head,Body):- defined_in_module(Mod, Head), retract( :(Mod,':-'(Head,Body)) ) .
  118
  119retractall_in_module(Mod,Head)  :- defined_in_module(Mod, Head) -> retractall( :(Mod,Head) ) ; true.
  120
  121listing_in_module(Module,Goal)  :- listing( Module:Goal ).
  122   
  123/*
  124 * Copy all clauses whose head unifies Arg3 from module Arg1 to 
  125 * module Arg2 without deleting the original clauses.
  126 */   
  127copy_module_predicate(InpMod, OutMod, Head) :-
  128   copy_predicate_clauses(InpMod:Head, OutMod:Head).  % SWI-PL
  129%
  130%   NON-SWIPL implementation:
  131% 
  132%   all( copy_module_clause(InpMod, OutMod, Head) ).
  133%  
  134%
  135%copy_module_clause(InpMod, OutMod, Head) :-
  136%   clause_in_module(InpMod,Head,Body),
  137%   assert_in_module(OutMod,Head,Body).  
  138   
  139/*
  140 * Move all clauses whose head unifies Arg3 from module Arg1 to 
  141 * module Arg2, deleting the original clauses.
  142 */   
  143move_module_predicate(FromModule, ToModule,Head) :-
  144   copy_module_predicate(FromModule, ToModule, Head),
  145   retractall_in_module(FromModule,Head).
  146
  147/*
  148 * Replace all clauses whose old head unifies Arg2 from module Arg1  
  149 * and whose head unifies Arg2 .
  150 */       
  151replace_module_predicate(Module, Old, New) :-
  152	retract_in_module(Module, Old),
  153	assert_in_module(Module, New).    
  154	
  155/*
  156 * Tests:
  157 
  158assert_in_module(Mod,Head     , Goal) :- assert( :(Mod,Head)      ), call(Goal).
  159assert_in_module(Mod,Head,Body, Goal) :- assert( :(Mod,Head,Body) ), call(Goal).
  160
  161% :- Dynamically created contents of user module globally visible (without module prefix): 
  162%       Mod = user, Head=uuu(1), Goal=uuu(X), assert_in_module(Mod,Head, Goal).
  163
  164% :- Contents of other modules not visible without module prefix: 
  165%       Mod = mmmm, Head=uuu(2), Goal=uuu(X), assert_in_module(Mod,Head, Goal).
  166
  167% :- Contents of other modules visible with explicit module prefix: 
  168%       Mod = mmmm, Head=uuu(3), Goal=mmmm:uuu(X), assert_in_module(Mod,Head, Goal).
  169
  170% :- Dynamic creation of explicit module prefix: 
  171%       Mod = mmmm, Head=uuu(4), Goal=':'(mmmm,uuu(X)), assert_in_module(Mod,Head, Goal).
  172
  173*/