1 % (c) 2009-2019 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5 % term_expansion/6 hook for the debugging_calls module
6 % this file should only be used by the debugging_calls module
7
8 :- use_module(module_information,[module_info/3]).
9
10 :- module_info(debugging_calls_te,group,infrastructure).
11 :- module_info(debugging_calls_te,description,'This sub-module contains the term-expansing code of the debugging call module, to remove ~~ calls').
12
13 :- dynamic current_context/2.
14 current_context(none,none).
15
16 assert_layout(File,Layout,NewPos) :-
17 print('Layout:'),print(Layout),nl,
18 retractall(current_context(_,_)),
19 ( Layout = [NewPos|_] -> true
20 ; otherwise -> NewPos = none),
21 assert(current_context(File,NewPos)).
22
23 logte(_Term,Layout) :-
24 prolog_load_context(file,File),
25 current_context(Before,OldPos),
26 assert_layout(File,Layout,NewPos),
27 ( File=Before ->
28 true
29 ; otherwise ->
30 print('### start: '),
31 print(File),print('/'),print(NewPos),
32 print(', was: '),
33 print(Before),print('/'),print(OldPos),nl).
34
35
36 expand((:- meta_predicate '~~'(_X)),_Layout1,_Term2,_Layout2) :- !,
37 %print(not_removing_in_meta_predicate('~~'(_X))),nl,
38 fail.
39 expand((:- use_module(library(Lib))),Layout1,Term2,Layout2) :-
40 library_to_patch(Lib,PatchedLib),
41 !,
42 Layout2 = Layout1,
43 current_module(CurModule),
44 format('Patching use_module(library(~w)) in ~w to ~w~n',[Lib,CurModule,PatchedLib]),
45 Term2 = (:- use_module(PatchedLib)).
46 expand((:- use_module(library(Lib),Preds)),Layout1,Term2,Layout2) :-
47 library_to_patch(Lib,PatchedLib),
48 Preds \= [], % so that there is a way to bypass the term expander
49 !,
50 Layout2 = Layout1,
51 current_module(CurModule),
52 format('Patching use_module(library(~w),~w) in ~w to ~w~n',[Lib,Preds,CurModule,PatchedLib]),
53 Term2 = (:- use_module(PatchedLib,Preds)).
54 expand(Term1,Layout1,Term2,Layout2) :-
55 % removes terms like ~~ pp_mnf,...
56 debugging_calls:remove_debugging_calls(Layout1,Term1,Layout2,Term2).
57
58 % patch libraries for plspec
59 :- load_files(library(system), [when(compile_time), imports([environ/2])]).
60 :- if(environ(prob_safe_mode,true)).
61 library_to_patch(ordsets,library_plspec(ordsetsp)).
62 library_to_patch(avl,library_plspec(avlp)).
63 :- endif.
64 library_to_patch('~~'(X),library(X)).
65
66 :- multifile user:term_expansion/6.
67 user:term_expansion(Term1, Layout1, Ids, Term2, Layout2, [rm_debug_calls|Ids]) :-
68 nonvar(Term1), nonmember(rm_debug_calls,Ids),
69 expand(Term1,Layout1,Term2,Layout2).
70
71
72