34
35:- module(assrt_comment, []). 36
37:- use_module(library(lists)). 38:- use_module(library(assertions)). 39:- use_module(library(assertions_op)). 40:- use_module(user:library(plprops)). 41:- init_expansors. 42
43:- create_prolog_flag(assrt_comment, yes, [type(atom)]). 44
45:- meta_predicate with_acp(0, -, +). 46
48
49with_acp(Goal, OldFlag, NewFlag) :-
50 setup_call_cleanup(
51 set_prolog_flag(assrt_comment, NewFlag),
52 Goal,
53 set_prolog_flag(assrt_comment, OldFlag)).
54
55ac_head_prop_idx(Head, M, Mode, Det, From) :-
56 current_prolog_flag(assrt_comment, Flag),
57 Flag \= none,
58 59 with_acp(do_ac_head_prop_idx(Head, M, Mode, Det, From), Flag, none).
60
61do_ac_head_prop_idx(Head, M, Mode, Det, From) :-
62 var(Mode),
63 !,
64 ( var(Head)
65 ->module_property(M, class(user)),
66 current_predicate(M:F/A),
67 functor(Head, F, A)
68 ; functor(Head, F, A),
69 module_property(M, class(user)),
70 current_predicate(M:F/A)
71 ),
72 functor(Mode, F, A),
73 '$c_current_predicate'(_, M:'$mode'(_,_)),
74 clause(M:'$mode'(Mode, Det), true, Ref),
75 From = clause(Ref).
76do_ac_head_prop_idx(_, _, _, _, _).
77
78assertions:asr_head_prop(ac_asr(M, H, S, D, F), M, H, check, pred, [], M, F) :-
79 ac_head_prop_idx(H, M, S, D, F).
80assertions:asr_comp(ac_asr(M, H, S, D, F), PM, P, F) :- asrc_prop(comp, M, H, S, D, F, PM, P).
81assertions:asr_call(ac_asr(M, H, S, D, F), PM, P, F) :- asrc_prop(call, M, H, S, D, F, PM, P).
82assertions:asr_succ(ac_asr(M, H, S, D, F), PM, P, F) :- asrc_prop(succ, M, H, S, D, F, PM, P).
83assertions:asr_glob(ac_asr(M, H, S, D, F), PM, P, F) :- asrc_prop(glob, M, H, S, D, F, PM, P).
84
85asrc_prop(Type, M, H, Mode, D, F, PM, P) :-
86 ac_head_prop_idx(H, M, Mode, D, F),
87 assertions:current_decomposed_assertion(pred Mode is D, _, M, M:H, _, _, CpL, CaL, SuL, GlL, _, _, _),
88 ( member(Type-PrL, [comp-CpL, call-CaL, succ-SuL]),
89 member(MPr-_, PrL),
90 strip_module(MPr, PM, P)
91 ; Type = glob,
92 member(MGl-_, GlL),
93 strip_module(MGl, PM, Gl),
94 assertions:add_arg(_, Gl, P, _, _)
95 ).
96