1/*  Part of Refactoring Tools for SWI-Prolog
    2
    3    Author:        Edison Mera
    4    E-mail:        efmera@gmail.com
    5    WWW:           https://github.com/edisonm/refactor
    6    Copyright (C): 2015, Process Design Center, Breda, The Netherlands.
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(file_to_module,
   36          [file_to_module/1, % +Alias
   37           file_to_module/2, % +Alias, +Options
   38           declared_use_module/6
   39          ]).   40
   41:- use_module(library(lists)).   42:- use_module(library(option)).   43:- use_module(library(pairs)).   44:- use_module(library(prolog_metainference)).   45:- use_module(library(solution_sequences)).   46:- use_module(library(clambda)).   47:- use_module(library(infer_alias)).   48:- use_module(library(list_sequence)).   49:- use_module(library(sequence_list)).   50:- use_module(library(codewalk)).   51:- use_module(library(extra_location)).   52:- use_module(library(from_utils)).   53:- use_module(library(location_utils)).   54:- use_module(library(module_files)).   55:- use_module(library(pretty_decl)).   56:- use_module(library(infer_meta)).   57:- use_module(library(refactor)).   58:- init_expansors.
 module_to_import_db(F, A, M, CM, File)
Predicate M:F/A used in File, in context CM
   64:- dynamic
   65    module_to_import_db/5.   66
   67file_to_module(Alias) :-
   68    file_to_module(Alias, []).
   69
   70implementation_decl(dynamic).
   71implementation_decl(multifile).
   72implementation_decl(discontiguous).
   73implementation_decl(volatile).
   74implementation_decl(thread_local).
   75implementation_decl(clause(_)).
   76
   77files_to_move(M, File, [File|FileL]) :-
   78    file_modules(File, MU),
   79    sort(MU, ML),
   80    member(M, ML),
   81    findall(IFile, file_includes(File, IFile), FileL).
   82
   83file_includes(File, IFile) :-
   84    distinct(Incl, source_file_property(File, includes(Incl, _))),
   85    ( IFile = Incl
   86    ; file_includes(Incl, IFile)
   87    ).
   88
   89collect_def_files(M, PIL, FileL) :-
   90    findall(File,
   91            ( member(F/A, PIL),
   92              functor(H, F, A),
   93              property_from((M:H)/_, _, From),
   94              from_to_file(From, File)
   95            ), FileU),
   96    sort(FileU, FileL).
   97
   98file_to_module(Alias, Options1) :-
   99    select_option(module(M),         Options1, Options2, M),
  100    select_option(exclude(ExcludeL), Options2, Options3, []),
  101    select_option(addcl(AddL),       Options3, Options4, []),
  102    select_option(near2(Nr2L),       Options4, Options5, []),
  103    select_option(delcl(DelL),       Options5, _, []),
  104    absolute_file_name(Alias, File, [file_type(prolog), access(read)]),
  105    files_to_move(M, File, FileL),
  106    format('% from context ~a~n', [M]),
  107    collect_movable(M, FileL, ExcludeL, PIMo),
  108    collect_fixable(M, FileL, ExcludeL, PIFx, PIRn),
  109    directory_file_path(_, Name, File),
  110    file_name_extension(NewM, _, Name),
  111    add_qualification_head(M, PIFx, [module(M), files(FileL)]),
  112    add_qualification_decl(M, PIFx, [module(M), files(FileL)]),
  113    collect_def_files(M, PIRn, FileD),
  114    subtract(FileD, FileL, FileR),
  115    add_qualification_head(NewM, PIRn, [files(FileR)]),
  116    add_qualification_decl(NewM, PIRn, [files(FileR)]),
  117    ren_qualification_head(M, NewM, PIRn, [files(FileD)]),
  118    ren_qualification_decl(M, NewM, PIRn, [files(FileD)]),
  119    subtract(PIMo, PIFx, PIL1),
  120    subtract(PIL1, PIRn, PIL),
  121    report_dispersed_assertions(PIL1, FileL, M),
  122    collect_to_reexport(M, FileL, PIL1, ReexportL),
  123    collect_export_decl_files(M, ExFileL),
  124    del_modexp_decl(M, ReexportL),
  125    del_export_decl(M, ExFileL, ReexportL),
  126    del_export_decl(M, FileL, PIFx),
  127    add_modexp_decl(M, PIFx),
  128    add_modmeta_decl(M, PIFx),
  129    append([PIL1, PIRn, ExcludeL], ExU2),
  130    sort(ExU2, ExL2),
  131    phrase(( AddL,
  132             collect_import_decls(M, FileL, ExL2),
  133             collect_dynamic_decls(M, FileL),
  134             collect_meta_decls(M, PIL)
  135           ), MDL, []),
  136    add_declarations(MDL, File),
  137    decl_to_use_module(consult, M, PIL1, Alias, ReexportL),
  138    decl_to_use_module(include, M, PIL1, Alias, ReexportL),
  139    append(ExcludeL, PIFx, ExTL),
  140    add_use_module(M, FileL, Alias, Nr2L, AddL, ExTL),
  141    add_use_module_ex(M, DelL, FileL),
  142    del_use_module_ex(M, FileL),
  143    add_module_decl(NewM, PIL1, File),
  144    forall(member(C, DelL), replace_sentence(C, [], [files(FileL)])).
  145
  146add_module_decl(NewM, PIL1, File) :-
  147    pretty_decl((:- module(NewM, PIL2)), PDecl2),
  148    replace_sentence(Term, PDecl2,
  149                     ( Term = (:- export(ExS))
  150                     ->sequence_list(ExS, ExL, []),
  151                       subtract(PIL1, ExL, PILD),
  152                       append(ExL, PILD, PIL2)
  153                     ),
  154                     [max_tries(1), changes(N), file(File)]),
  155    ( N = 0
  156    ->pretty_decl((:- module(NewM, PIL1)), PDecl1),
  157      replace_sentence([],
  158                       PDecl1,
  159                       [max_changes(1), file(File)])
  160    ; true
  161    ).
  162
  163collect_meta_decls(M, PIL, MDL, Tail) :-
  164    collect_meta_specs(M, PIL, SpecL),
  165    ( SpecL = []
  166    ->MDL = Tail
  167    ; MDL = [(:- meta_predicate('$LIST,NL'(SpecL)))|Tail]
  168    ).
  169
  170collect_meta_specs(M, PIL, SpecL) :-
  171    findall(Spec, ( member(F/A, PIL),
  172                    functor(H, F, A),
  173                    \+ predicate_property(M:H, meta_predicate(Spec)),
  174                    inferred_meta_predicate(M:H, Spec)
  175                  ), SpecL).
  176
  177add_modmeta_decl(M, PIFx) :-
  178    collect_meta_specs(M, PIFx, SpecL),
  179    ( SpecL \= [] ->
  180      replace_sentence((:- module(M, MEL)),
  181                       [(:- module(M, MEL)),
  182                        (:- meta_predicate('$LIST,NL'(SpecL)))
  183                       ], [max_changes(1), module(M)])
  184    ; true
  185    ).
  186
  187add_modexp_decl(M, PIFx) :-
  188    module_property(M, file(MFile)),
  189    pretty_decl((:- module(M, NMExL)), PDecl),
  190    replace_sentence((:- module(M, MEL)),
  191                     PDecl,
  192                     ( subtract(PIFx, MEL, NExL),
  193                       NExL \= [],
  194                       ( MEL = []
  195                       ->pretty_decl((:- module(M, PIFx)), PDecl)
  196                       ; append(MEL, '$LIST,NL'(NExL,'$1'+1), NMExL),
  197                         PDecl = (:- $@(module('$POS'('$1', M),
  198                                               '$NL'(NMExL$@MEL, '$1'))))                       )                     ), [file(MFile)]).
 collect_fixable(M, FileL, ExcludeL, PIM) is det
Collect the predicates that preserves its implementation module, even if they have clauses in the file being modularized. That includes multifile predicates whose multifile declaration is outside FileL
  208collect_fixable(M, FileL, ExcludeL, PIM, PIR) :-
  209    findall(F/A,
  210            ( current_predicate(M:F/A),
  211              functor(H, F, A),
  212              \+ memberchk(F/A, ExcludeL),
  213              \+ predicate_property(M:H, imported_from(_)),
  214              once(( implemented_in_file(F, A, M, InFile),
  215                     memberchk(InFile, FileL),
  216                     implemented_in_file(F, A, M, ExFile),
  217                     \+ memberchk(ExFile, FileL)
  218                   ))
  219            ), PIU),
  220    sort(PIU, PIF),
  221    partition(preserve_module(M, FileL), PIF, PIM, PIR).
  222
  223preserve_module(M, FileL, F/A) :-
  224    functor(H, F, A),
  226    once(( loc_declaration(H, M, multifile, MFrom),
  227           from_to_file(MFrom, MFile),
  228           \+ memberchk(MFile, FileL)
  229         ))
  229.
  230
  231add_qualification_head(M, PIM, Options) :-
  232    forall(member(F/A, PIM),
  233           ( functor(H, F, A),
  234             replace_head(H, M:H, Options)
  235           )).
  236
  237add_qualification_decl(M, PIM, Options) :-
  238    forall(( implementation_decl(DeclN),
  239             DeclN \= clause(_)
  240           ),
  241           ( functor(Decl, DeclN, 1),
  242             replace_term(F/A, M:F/A, ( atom(F),
  243                                        integer(A),
  244                                        memberchk(F/A, PIM)
  245                                      ),
  246                          [sentence((:- Decl))|Options])
  247           )).
  248
  249ren_qualification_head(M, NewM, PIL, Options) :-
  250    forall(member(F/A, PIL),
  251           ( functor(H, F, A),
  252             replace_head(M:H, NewM:H, Options)
  253           )).
  254
  255ren_qualification_decl(M, NewM, PIL, Options) :-
  256    forall(( implementation_decl(DeclN),
  257             DeclN \= clause(_)
  258           ),
  259           ( functor(Decl, DeclN, 1),
  260             replace_term(M:F/A, NewM:F/A, ( atom(F),
  261                                             integer(A),
  262                                             memberchk(F/A, PIL)
  263                                           ),
  264                          [sentence((:- Decl))|Options])
  265           )).
  266
  267add_use_module(M, FileL, Alias, Nr2L, AddL, ExcludeL) :-
  268    findall(CM-(F/A),
  269            ( ( module_to_import_db(F, A, M, CM, _File),
  270                implemented_in_file(F, A, M, File),
  271                memberchk(File, FileL)
  272              ; implem_to_export(FileL, F, A, M, CM)
  273              ),
  274              \+ memberchk(F/A, ExcludeL),
  275              CM \= M
  276            ),
  277            CMPIU),
  278    sort(CMPIU, CMPIL),
  279    group_pairs_by_key(CMPIL, CMPIG),
  280    forall(member(CM-PIL, CMPIG),
  281           add_use_module_cm(M, Alias, Nr2L, AddL, CM, PIL)).
  282
  283add_use_module1_file(Alias, MFile, TermL) :-
  284    once(( member(Term, TermL),
  285           replace_sentence(Term,
  286                            [Term,
  287                             (:- use_module(Alias))],
  288                            [max_changes(1), changes(C), file(MFile)]),
  289           C \= 0
  290         )).
  291
  292add_use_module_cm(M, Alias, Nr2L, AddL, CM, PIL) :-
  293    ( module_property(CM, file(MFile))
  294    ->reverse(AddL, AddR),
  295      append([Nr2L, AddR, [(:- module(CM, _))]], TermL),
  296      add_use_module1_file(Alias, MFile, TermL),
  297      module_property(M, file(MainF)),
  298      replace_sentence((:- use_module(MainA, ExL)),
  299                       [],
  300                       ( absolute_file_name(MainA,
  301                                            MainF1,
  302                                            [file_type(prolog),
  303                                             access(read)]),
  304                         MainF1=MainF,
  305                         subtract(ExL, PIL, ExL2),
  306                         ExL2 = []
  307                       ),
  308                       [module(CM)]),
  309      pretty_decl(:- use_module(MainA, ExL2), PDecl),
  310      replace_sentence((:- use_module(MainA, ExL)), PDecl,
  311                       ( absolute_file_name(MainA,
  312                                            MainF1,
  313                                            [file_type(prolog),
  314                                             access(read)]),
  315                         MainF1=MainF,
  316                         subtract(ExL, PIL, ExL2),
  317                         ExL2 \= []
  318                       ),
  319                       [module(CM)])
  320    ; print_message(warning, format('Module ~w will require :- use_module(~w)', [CM, Alias]))
  321    ).
  322
  323declared_use_module(F, A, IM, M, EA, File) :-
  324    module_property(IM, file(ImplFile)),
  325    ( module_property(IM, exports(ExL)),
  326      loc_declaration(EA, M, use_module, From)
  327    ; loc_declaration(use_module(EA, Ex), M, use_module_2, From),
  328      ( is_list(Ex)
  329      ->ExL = Ex
  330      ; Ex = except(NotExL)
  331      ->module_property(IM, exports(ExA)),
  332        subtract(ExA, NotExL, ExL)
  333      )
  334    ),
  335    from_to_file(From, File),
  336    absolute_file_name(EA, EFile, [file_type(prolog), access(read), relative_to(File)]),
  337    EFile = ImplFile,
  338    memberchk(F/A, ExL).
  339
  340del_use_module_ex(M, FileL) :-
  341    replace_sentence((:- use_module(EA)),
  342                     [],
  343                     ( absolute_file_name(EA,
  344                                          ImplementFile,
  345                                          [file_type(prolog),
  346                                           access(read)]),
  347                       module_property(IM, file(ImplementFile)),
  348                       \+ module_property(IM, exports([])),
  349                       \+ ( module_to_import_db(F, A, IM, M, File),
  350                            memberchk(File, FileL)
  351                          )
  352                     ),
  353                     [files(FileL)]),
  354    replace_sentence((:- use_module(EA, IL)),
  355                     [],
  356                     ( IL = [_|_],
  357                       absolute_file_name(EA,
  358                                          ImplementFile,
  359                                          [file_type(prolog),
  360                                           access(read)]),
  361                       module_property(IM, file(ImplementFile)),
  362                       \+ module_property(IM, exports([])),
  363                       findall(F/A,
  364                               ( module_to_import_db(F, A, IM, M, File),
  365                                 memberchk(File, FileL)
  366                               ), PIL),
  367                       intersection(IL, PIL, NIL),
  368                       NIL = []
  369                     ),
  370                     [files(FileL)]),
  371    pretty_decl((:- use_module(EA, NIL)), PDecl),
  372    replace_sentence((:- use_module(EA, IL)), PDecl,
  373                     ( IL = [_|_],
  374                       absolute_file_name(EA,
  375                                          ImplementFile,
  376                                          [file_type(prolog),
  377                                           access(read)]),
  378                       module_property(IM, file(ImplementFile)),
  379                       findall(F/A,
  380                               ( module_to_import_db(F, A, IM, M, File),
  381                                 memberchk(File, FileL)
  382                               ), PIL),
  383                       intersection(IL, PIL, NIL),
  384                       NIL \= []
  385                     ),
  386                     [files(FileL)]).
  387
  388add_use_module_ex(M, DelL, FileL) :-
  389    findall(ImportingFile-((IM:EA)-(F/A)),
  390            [M, FileL, ImportingFile, IM, EA, F, A] +\
  391            ( module_to_import_db(F, A, IM, M, ImportingFile),
  392              IM \= M,
  393              \+ module_file(IM, ImportingFile),
  394              \+ declared_use_module(F, A, IM, M, _, ImportingFile),
  395              declared_use_module(F, A, IM, M, EA, File),
  396              memberchk(File, FileL)
  397            ),
  398            FileAliasPIU),
  399    sort(FileAliasPIU, FileAliasPIL),
  400    group_pairs_by_key(FileAliasPIL, FileAliasPIG),
  401    forall(member(ImFile-AliasPIL, FileAliasPIG),
  402           add_use_module_ex_1(M, DelL, ImFile, AliasPIL)).
  403
  404add_umexdecl_each(ImFile, M, AliasPIG, (:- Decl)) :-
  405    member((IM:Alias)-PIL, AliasPIG),
  406    get_use_module_decl(ImFile, M, IM, Alias, PIL, Decl).
  407
  408add_declarations(DeclL, ImFile) :-
  409    ( DeclL = []
  410    ->true
  411    ; findall(NDecl,
  412              ( member(NDecl, DeclL),
  413                ( NDecl = (:- use_module(A))
  414                ->( replace_sentence(NDecl, (:- use_module(A)),
  415                                     [max_changes(1), changes(C), file(ImFile)]),
  416                    C \= 0
  417                  ->fail
  418                  ; replace_sentence((:- use_module(A, _)), (:- use_module(A)),
  419                                     [max_changes(1), changes(0), file(ImFile)])
  420                  )
  421                ; NDecl = (:- use_module(A, L1))
  422                ->( replace_sentence((:- use_module(A)), (:- use_module(A)),
  423                                     [max_changes(1), changes(C), file(ImFile)]),
  424                    C \= 0
  425                  ->fail
  426                  ; pretty_decl((:- use_module(A, L)), PDecl),
  427                    replace_sentence((:- use_module(A, L2)), PDecl,
  428                                     ( is_list(L2),
  429                                       subtract(L1, L2, L3),
  430                                       append(L2, '$LIST,NL'(L3,'$1'(1)+1), L)
  431                                     ),
  432                                     [max_changes(1), changes(0), file(ImFile)])
  433                  )
  434                ; true
  435                )
  436              ), DeclL2),
  437      ( DeclL2 = []
  438      ->true
  439      ; foldl(pretty_decl, DeclL2, DeclL3, 1, _),
  440        ( Term = (:- Decl),
  441          append(DeclL3, [(:- Decl)], DeclL4),
  442          replace_sentence(Term, DeclL4,
  443                           memberchk(Decl, [use_module(_), use_module(_,_)]),
  444                           [max_changes(1), changes(C), file(ImFile)]),
  445          C \= 0
  446        ->true
  447        ; ( replace_sentence((:- module(ImM, Ex)),
  448                             [(:- module(ImM, Ex))|DeclL3],
  449                             [max_changes(1), changes(C), file(ImFile)]),
  450            C \= 0
  451          ->true
  452          ; replace_sentence([], DeclL3, [max_changes(1), file(ImFile)])
  453          )
  454        )
  455      )
  456    ).
  457
  458add_use_module_ex_1(M, DelL, ImFile, AliasPIL) :-
  459    group_pairs_by_key(AliasPIL, AliasPIG),
  460    findall(Decl, ( add_umexdecl_each(ImFile, M, AliasPIG, Decl),
  461                    \+ memberchk(Decl, DelL)
  462                  ), DeclL),
  463    add_declarations(DeclL, ImFile).
  464
  465collect_to_reexport(M, FileL, PIL, ReexportL) :-
  466    module_property(M, exports(EL1)),
  467    findall(PI,
  468            ( PI=F/A,
  469              member(PI, EL1),
  470              functor(H, F, A),
  471              loc_declaration(H, M, export, From),
  472              from_to_file(From, FileX),
  473              \+ memberchk(FileX, FileL)
  474            ), EL),
  475    intersection(PIL, EL, ReexportL).
  476
  477alias_location(Alias, M, Decl, IAlias-File) :-
  478    ( extra_location(Alias, M, Decl, From),
  479      from_to_file(From, File)
  480    ->IAlias = Alias
  481    ; absolute_file_name(Alias, IFile, [file_type(prolog), access(read)]),
  482      extra_location(IAlias, M, Decl, From),
  483      from_to_file(From, File),
  484      absolute_file_name(IAlias, IFile,
  485                         [file_type(prolog), access(read),
  486                          file_errors(fail), relative_to(File)]),
  487      !
  488    ).
  489
  490decl_to_use_module(Decl, M, PIL, Alias, ReexportL) :-
  491    findall(DFile, alias_location(Alias, M, Decl, DFile), DAFileU),
  492    sort(DAFileU, DAFileL),
  493    ( ReexportL = []
  494    ->Into = (:- use_module(Alias))
  495    ; ( PIL = ReexportL
  496      ->Into = (:- reexport(Alias))
  497      ; subtract(PIL, ReexportL, ExportL),
  498        pretty_decl((:- reexport(Alias, ReexportL)), PDecl, 1),
  499        ( ExportL = []
  500        ->Into = PDecl
  501        ; Into = [(:- use_module(Alias)), PDecl]
  502        )
  503      )
  504    ),
  505    Patt =.. [Decl, IAlias],
  506    group_pairs_by_key(DAFileL, DAFileG),
  507    forall(member(IAlias-DFileL, DAFileG),
  508           replace_sentence((:- Patt), Into, [files(DFileL)])).
  509
  510collect_export_decl_files(M, ExFileL) :-
  511    module_property(M, exports(Ex)),
  512    findall(ExFile, ( PI=F/A,
  513                      member(PI, Ex),
  514                      functor(H, F, A),
  515                      loc_declaration(H, M, export, From),
  516                      from_to_file(From, ExFile)
  517                    ), ExFileU),
  518    sort(ExFileU, ExFileL).
  519
  520del_modexp_decl(M, DelExpDeclL) :-
  521    module_property(M, file(MFile)),
  522    pretty_decl((:- module(M, NL)), PDecl),
  523    replace_sentence((:- module(M, MEL)), PDecl,
  524                     ( subtract(MEL, DelExpDeclL, NL),
  525                       NL \= MEL
  526                     ), [file(MFile)]).
  527
  528del_export_decl(M, ExFileL, DelExpDeclL) :-
  529    pretty_decl((:- export(ExNL)), ExDecl),
  530    replace_sentence((:- export(ExS)), Exp,
  531                     ( sequence_list(ExS, ExL, []),
  532                       subtract(ExL, DelExpDeclL, ExNL),
  533                       ExNL \= ExL,
  534                       ( ExNL = []
  535                       ->Exp = []
  536                       ; Exp = ExDecl
  537                       )
  538                     ), [module(M), files(ExFileL)]),
  539    pretty_decl((:- M:export(ExNL)), MExDecl),
  540    replace_sentence((:- M:export(ExS)),
  541                     MExp,
  542                     ( sequence_list(ExS, ExL, []),
  543                       subtract(ExL, DelExpDeclL, ExNL),
  544                       ExNL \= ExL,
  545                       ( ExNL = []
  546                       ->MExp = []
  547                       ; MExp = MExDecl
  548                       )
  549                     ), [files(ExFileL)]).
 implem_to_export(FileL, F, A, M, CM)
Predicate M:F/A implemented in FileL, is called outside FileL and therefore should be exported
  556implem_to_export(FileL, F, A, M, CM) :-
  557    ( loc_dynamic(H, M, dynamic(_, CM, _), FromD),
  558      from_to_file(FromD, FileD),
  559      \+ memberchk(FileD, FileL),
  560      ( loc_declaration(H, M, D, From),
  561        implementation_decl(D),
  562        from_to_file(From, File),
  563        memberchk(File, FileL)
  564      ->true
  565      ; loc_declaration(H, M, D, From),
  566        implementation_decl(D),
  567        from_to_file(From, FileE),
  568        \+ memberchk(FileE, FileL)
  569      ->fail
  570      ; loc_dynamic(H, M, dynamic(_, M, _), From),
  571        from_to_file(From, File),
  572        memberchk(File, FileL)
  573      ->true
  574      )
  575    ; loc_declaration(H, M, export, From),
  576      from_to_file(From, FileX),
  577      \+ memberchk(FileX, FileL),
  578      once(( property_from((M:H)/_, clause(_), PFrom),
  579             from_to_file(PFrom, File),
  580             memberchk(File, FileL)
  581           )),
  582      M=CM
  583    ),
  584    functor(H, F, A).
  585
  586report_dispersed_assertions(PIL, FileL, M) :-
  587    collect_dispersed_assertions(PIL, FileL, M, PIA),
  588    ( PIA \= []
  589    ->print_message(warning,
  590                    format('Assertions for ~w needs to be relocated', [PIA]))
  591    ; true
  592    ).
  593
  594collect_dispersed_assertions(PIL, FileL, M, PIA) :-
  595    findall(F/A, ( member(F/A, PIL),
  596                   functor(H, F, A),
  597                   once(( implemented_in_file(F, A, M, File),
  598                          memberchk(File, FileL)
  599                        )),
  600                   loc_declaration(H, M, assertion(_, _), FromD),
  601                   from_to_file(FromD, FileD),
  602                   \+ memberchk(FileD, FileL)
  603                 ), PIUA),
  604    sort(PIUA, PIA).
  605
  606collect_movable(M, FileL, ExcludeL, PIL) :-
  607    Options = [source(false), trace_reference(_)],
  608    retractall(module_to_import_db(_, _, _, _, _)),
  609    infer_meta_if_required,
  610    walk_code([on_trace(collect_file_to_module)|Options]),
  611    findall(F/A, ( module_to_import_db(F, A, M, _, IFile),
  612                   \+ memberchk(IFile, FileL),
  613                   implemented_in_file(F, A, M, File),
  614                   memberchk(File, FileL)
  615                 ), PIU, PIT),
  616    findall(F/A, implem_to_export(FileL, F, A, M, _), PIT),
  617    sort(PIU, PIS),
  618    subtract(PIS, ExcludeL, PIL).
  619
  620implemented_in_file(F, A, M, File) :-
  621    functor(Goal, F, A),
  622    property_from((M:Goal)/_, Decl, PFrom),
  623    implementation_decl(Decl),
  624    from_to_file(PFrom, File).
  625
  626collect_used_outside(M, FileL, ExcludeL, UOL, T) :-
  627    findall(EM-(F/A),
  628            ( module_to_import_db(F, A, EM, M, File),
  629              memberchk(File, FileL),
  630              implemented_in_file(F, A, EM, IFile),
  631              \+ memberchk(IFile, FileL),
  632              \+ memberchk(F/A, ExcludeL)
  633            ), UOL, T).
  634
  635collect_decl_outside(M, FileL, ExcludeL, DOL, T) :-
  636    findall(EM-(F/A),
  637            ( loc_dynamic(H, EM, dynamic(_, M, _), From),
  638              from_to_file(From, File),
  639              memberchk(File, FileL),
  640              ( loc_declaration(H, EM, D, FromD),
  641                implementation_decl(D),
  642                from_to_file(FromD, FileD),
  643                memberchk(FileD, FileL)
  644              ->fail
  645              ; ( loc_declaration(H, EM, D, FromD),
  646                  implementation_decl(D)
  647                ; loc_dynamic(H, EM, dynamic(Type, _, _), FromD),
  648                  memberchk(Type, [retract, def, dec])
  649                ),
  650                from_to_file(FromD, FileD),
  651                \+ memberchk(FileD, FileL)
  652              ->true
  653              ),
  654              functor(H, F, A),
  655              \+ memberchk(F/A, ExcludeL)
  656            ), DOL, T).
  657
  658collect_requires_dyn_decl(M, FileL, PID) :-
  659    findall(F/A,
  660            ( loc_dynamic(H, M, dynamic(_, _, _), FromD),
  661              from_to_file(FromD, FileD),
  662              \+ memberchk(FileD, FileL),
  663              ( loc_declaration(H, M, D, _),
  664                implementation_decl(D)
  665              ->fail
  666              ; loc_dynamic(H, M, dynamic(_, M, _), From),
  667                from_to_file(From, File),
  668                memberchk(File, FileL)
  669              ->true
  670              ),
  671              functor(H, F, A)
  672            ), PIUD),
  673    sort(PIUD, PID).
  674
  675collect_dynamic_decls(M, FileL, DYL, Tail) :-
  676    collect_requires_dyn_decl(M, FileL, PID),
  677    ( PID = []
  678    ->DYL = Tail
  679    ; DYL = [(:- dynamic('$LIST,NL'(PID)))|Tail]
  680    ).
  681
  682% collect_import_decls(+atm,+list(atm),+list,+list,-list,?list) is det.
  683%
  684collect_import_decls(M, FileL, ExcludeL, MDL, Tail) :-
  685    collect_used_outside(M, FileL, ExcludeL, UOL, DOL),
  686    collect_decl_outside(M, FileL, ExcludeL, DOL, []),
  687    sort(UOL, ML),
  688    group_pairs_by_key(ML, GL),
  689    findall((:- Decl),
  690            ( member(EM-PEL, GL),
  691              findall(PPI,
  692                      ( PPI=FF/AA,
  693                        member(PPI, PEL),
  694                        functor(HH, FF, AA),
  695                        % \+ predicate_property(EM:HH, exported),
  696                        \+ ( extra_location(HH, EM, export, EFrom),
  697                             from_to_file(EFrom, EFile),
  698                             ( memberchk(EFile, FileL)
  699                             ; module_property(M, file(EFile))
  700                             )
  701                           ),
  702                        ( predicate_property(EM:HH, D),
  703                          implementation_decl(D)
  704                        ->true
  705                        ; implemented_in_file(FF, AA, EM, _PFile)
  706                        ->true
  707                        )
  708                      ), REL),
  709              module_property(EM, file(EF)),
  710              library_alias(EF, EA),
  711              \+ black_list_um(EA),
  712              ( EM=M, REL \= []
  713              ->list_sequence(REL, RES),
  714                print_message(warning,
  715                              format("Back imports is a bad sign: ~w",
  716                                     [(:- EM:export(RES))]))
  717              ; true
  718              ),
  719              ( ( EM = M,
  720                  % PEL \= REL,
  721                  REL \= []
  722                ->Decl = EM:export(REL) % Explicit exports --EMM
  723                ; fail
  724                )
  725              ; \+ ( loc_declaration(EA, _, use_module, UMFrom),
  726                     from_to_file(UMFrom, UFile),
  727                     memberchk(UFile, FileL)
  728                   ),
  729                get_use_module_decl('', M, EM, EA, REL, Decl)
  730
  731              )
  732            ), MDL, Tail).
  733
  734get_use_module_decl(ImFile, M, IM, EA, REL, Decl) :-
  735    ( IM \= M,
  736      module_property(IM, exports(ExL)),
  737      member(F/A, ExL),
  738      functor(H, F, A),
  739      predicate_property(M:H, defined),
  740      ( module_to_import_db(F, A, OM, M, ImFile),
  741        OM \= IM,
  742        \+ predicate_property(IM:H, imported_from(OM))
  743      ; \+ ( predicate_property(M:H, imported_from(MM)),
  744             ( MM = IM
  745             ; predicate_property(IM:H, imported_from(MM)),
  746               predicate_property(IM:H, exported)
  747             )
  748           )
  749      )
  750    ->Decl = use_module(EA, REL)
  751    ; Decl = use_module(EA)
  752    ).
  753
  754black_list_um(swi(_)).          % Ignore internal SWI modules
  755black_list_um(library(dialect/_)).
  756
  757:- public collect_file_to_module/3.  758collect_file_to_module(Callee, _Caller, From) :-
  759    record_location_meta(Callee, _, From, all_call_refs, cu_caller_hook).
  760
  761cu_caller_hook(Head, CM, Type, Goal, _, From) :-
  762    callable(Head),
  763    nonvar(CM),
  764    predicate_property(CM:Head, implementation_module(M)),
  765    ( Type \= lit
  766    ->record_location(Head, M, dynamic(Type, CM, Goal), From)
  767    ; true
  768    ),
  769    record_calls_to(Head, M, CM, From).
  770
  771record_calls_to(Head, M, CM, From) :-
  772    functor(Head, F, A),
  773    from_to_file(From, File),
  774    ( module_to_import_db(F, A, M, CM, File) -> true
  775    ; assertz(module_to_import_db(F, A, M, CM, File))
  776    )