34
35:- module(deref_reexport,
36 [deref_reexport/2,
37 deref_reexport/3
38 ]). 39
40:- use_module(library(lists)). 41:- use_module(library(pairs)). 42:- use_module(library(called_from)). 43:- use_module(library(from_utils)). 44:- use_module(library(infer_alias)). 45:- use_module(library(pretty_decl)). 46:- use_module(library(file_to_module)). 47:- use_module(library(refactor)). 48
49deref_reexport(Alias, Options) :-
50 deref_reexport(Alias, _, Options).
51
52deref_reexport(Alias, Reexported, Options) :-
53 absolute_file_name(Alias, AFile, [file_type(prolog), access(read)]),
54 module_property(M, file(AFile)),
55 module_property(M, exports(ExL)),
56 ( \+ ( member(F/A, ExL),
57 functor(H, F, A),
58 predicate_property(M:H, imported_from(_))
59 )
60 ->print_message(information, format("~w does not have reexports", [Alias]))
61 ; freeze(H1, once((member(F/A, ExL), functor(H1, F, A)))),
62 collect_called_from(H1, Reexported, _, _, Options),
63 findall(File/CM, called_from_w(_, M, Reexported, CM, File), FileCMU),
64 sort(FileCMU, FileCML),
65 findall(File/CM-RMPIG,
66 ( member(File/CM, FileCML),
67 findall((Reexported-F/A),
68 ( called_from_w(H2, M, Reexported, CM, File),
69 functor(H2, F, A),
70 ( Reexported = M
71 ->true
72 ; \+ declared_use_module(F, A, Reexported, CM, _, File)
73 )
74 ), RMPIU),
75 sort(RMPIU, RMPIL),
76 group_pairs_by_key(RMPIL, RMPIG)
77 ), FileRMPIG),
78 forall(member(File/CM-RMPIL, FileRMPIG),
79 update_use_module(AFile, M, RMPIL, File, CM))
80 ).
81
82called_from_w(H, M, RM, CM, File) :-
83 called_from:called_from_db(H, RM, CM, _, From),
84 RM \= CM,
85 ( RM = M
86 ->true
87 ; predicate_property(M:H, imported_from(RM))
88 ),
89 from_to_file(From, File).
90
91update_use_module(AFile, M, RMPIL, File, CM) :-
92 module_property(M, exports(ExL)),
93 replace_sentence((:- use_module(A)),
94 DeclL,
95 collect_decls(AFile, File, RMPIL, CM, A, ExL, ExL, DeclL),
96 [file(File)]),
97 replace_sentence((:- use_module(A, ImS)),
98 DeclL,
99 collect_decls(AFile, File, RMPIL, CM, A, ExL, ImS, DeclL),
100 [file(File)]).
101
102collect_decls(AFile, File, RMPIL, CM, A, ExL, ImS, DeclL) :-
103 absolute_file_name(A, AF, [file_type(prolog), access(read), relative_to(File)]),
104 AF = AFile,
105 ( ImS = except(Exc)
106 ->subtract(ExL, Exc, ImL)
107 ; ImL = ImS
108 ),
109 ImL \= [],
110 findall(PDecl,
111 ( member(RM-RPIL, RMPIL),
112 intersection(RPIL, ImL, PIL),
113 module_property(RM, file(RF)),
114 library_alias(RF, RA),
115 ( \+ ( module_property(RM, exports(ExL)),
116 member(F/A, ExL),
117 \+ member(F/A, PIL),
118 functor(H, F, A),
119 module_property(CM:H, defined)
120 )
121 ->Decl = (:- use_module(RA))
122 ; Decl = (:- use_module(RA, PIL))
123 ),
124 pretty_decl(Decl, PDecl)
125 ), DeclL)