1/*  Part of Extended Tools for SWI-Prolog
    2
    3    Author:        Edison Mera
    4    E-mail:        efmera@gmail.com
    5    WWW:           https://github.com/edisonm/xtools
    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(codewalk_prolog, []).   36
   37:- use_module(library(apply)).   38:- use_module(library(lists)).   39:- use_module(library(option)).   40:- use_module(library(prolog_codewalk)).   41:- use_module(library(assertions)).   42:- use_module(library(extra_location)).   43:- use_module(library(option_utils)).   44:- use_module(library(from_utils)).   45:- init_expansors.   46
   47:- thread_local
   48    issues/1.
 extra_walk_module_body(-Module, +Options) is det
   52extra_walk_module_body(Options) :-
   53    ( option(module(M), Options)
   54    ->findall(Ref, current_clause_module_body(M, Ref), RefU),
   55      sort(RefU, RefL),
   56      prolog_walk_code([source(false), clauses(RefL)|Options])
   57    ; true
   58    ).
   59
   60:- multifile
   61    codewalk:walk_code/2.   62
   63codewalk:walk_code(prolog, Options1) :-
   64    extra_wcsetup(Options1, Options2, MFileD),
   65    foldl(select_option_default,
   66          [source(S)-false,
   67           walkextras(Extras)-[declaration, asrparts([body])],
   68           on_trace(ETracer)-ETracer
   69          ], Options2, Options3),
   70    Options = [on_trace(codewalk_prolog:pcw_trace(1, ETracer, MFileD))|Options3],
   71    extra_walk_module_body(Options),
   72    optimized_walk_code(S, Stage, codewalk_prolog:pcw_trace(Stage, ETracer, MFileD), Options3),
   73    prolog_codewalk:make_walk_option(Options, OTerm),
   74    maplist(walk_extras_p(OTerm, MFileD), Extras).
   75
   76:- public pcw_trace/6.   77:- meta_predicate pcw_trace(+,3,+,+,+,+).   78pcw_trace(1, ETracer, MFileD, M:Goal, Caller, From) :-
   79    get_dict(M, MFileD, FileD),
   80    from_to_file(From, File),
   81    get_dict(File, FileD, _),
   82    '$set_source_module'(M),
   83    call(ETracer, M:Goal, Caller, From),
   84    ( From = clause(CRef)
   85    ->record_issues(CRef)
   86    ; true
   87    ).
   88pcw_trace(2, ETracer, _, Goal, Caller, From) :-
   89    call(ETracer, Goal, Caller, From).
   90
   91walk_extras_p(OTerm, MFileD, Extra) :- walk_extras_(Extra, OTerm, MFileD).
   92
   93walk_extras_(declaration, OTerm, MFileD) :- walk_from_loc_declaration(OTerm, MFileD).
   94walk_extras_(asrparts(L), OTerm, MFileD) :- walk_from_assertion(OTerm, MFileD, L).
   95
   96current_clause_module_body(CM, Ref) :-
   97    MH = M:_,
   98    current_predicate(_, MH),
   99    M \= CM,
  100    \+ predicate_property(MH, imported_from(_)),
  101    ( catch(clause(MH, Body, Ref), _, fail),
  102      clause_property(Ref, module(HM)),
  103      strip_module(HM:Body, CM, _)
  104    ).
  105
  106optimized_walk_code(false, 1, Tracer, Options) :-
  107    prolog_walk_code([source(false), on_trace(Tracer)|Options]).
  108optimized_walk_code(true, Stage, Tracer, Options) :-
  109    optimized_walk_code_true(Stage, Tracer, Options).
  110
  111optimized_walk_code_true(1, Tracer, Options) :-
  112    prolog_walk_code([source(false), on_trace(Tracer)|Options]),
  113    fail.
  114optimized_walk_code_true(2, Tracer, Options) :-
  115    findall(CRef, retract(issues(CRef)), ClausesU),
  116    sort(ClausesU, Clauses),
  117    ( Clauses==[]
  118    ->true
  119    ; prolog_walk_code([clauses(Clauses), on_trace(Tracer)|Options])
  120    ).
  121
  122extra_wcsetup(Options1, Options, MFileD) :-
  123    option_module_files(MFileD, Options1, Options2),
  124    merge_options(Options2,
  125                  [infer_meta_predicates(false),
  126                   autoload(false),
  127                   evaluate(false),
  128                   trace_reference(_),
  129                   module_class([user, system, library])
  130                  ], Options).
  131
  132walk_from_loc_declaration(OTerm, MFileD) :-
  133    forall(( prolog_codewalk:walk_option_caller(OTerm, '<declaration>'),
  134             clause(loc_declaration(Head, M, goal, From), _, Ref),
  135             get_dict(M, MFileD, FileD),
  136             from_to_file(From, File),
  137             get_dict(File, FileD, _)
  138           ),
  139           walk_from_goal(Head, M, Ref, OTerm)).
  140
  141walk_from_goal(Head, M, Ref, OTerm) :-
  142    prolog_codewalk:( scan_module(M, OTerm),
  143                      walk_option_clause(OTerm, Ref),
  144                      walk_called_by_body(no_positions, Head, M, OTerm)
  145                    ).
  146
  147walk_from_assertion(OTerm, MFileD, AsrPartL) :-
  148    option_files([module_files(MFileD)], FileD),
  149    forall(( AHead = assertions:asr_head_prop(Asr, HM, Head, _, _, _, _, From),
  150             clause(AHead, Body, Ref),
  151             module_property(Ref, module(M)),
  152             call(M:Body),
  153             from_to_file(From, File),
  154             get_dict(File, FileD, _),
  155             predicate_property(HM:Head, implementation_module(M)),
  156             prolog_codewalk:walk_option_caller(OTerm, '<assertion>'(M:Head)),
  157             member(AsrPart, AsrPartL),
  158             assertion_goal(AsrPart, Head, HM, Asr, Goal, CM)
  159           ),
  160           walk_from_goal(Goal, CM, Ref, OTerm)).
  161
  162assertion_goal(head, Head, HM, _, Head, HM).
  163assertion_goal(body, _, _, Asr, Prop, PM) :-
  164    member(Part, [comp, call, succ, glob]),
  165    % For glob, actually is arg(1, Prop, HM:Head), but we keep it uninstantiated for optimization
  166    curr_prop_asr(Part, PM:Prop, _, Asr).
  167
  168record_issues(CRef) :-
  169    assertz(issues(CRef))