34
35:- module(from_utils, [from_to_file/2,
36 from_to_line/2,
37 from_to_module/2,
38 from_to_file_line_pos/5,
39 file_termpos_line/4,
40 update_fact_from/2,
41 subsumes_from/2]). 42
43:- use_module(library(prolog_clause), []). 44:- use_module(library(extra_messages), []). 45:- use_module(library(assertions)). 46:- use_module(library(plprops)). 47:- use_module(library(extend_args)). 48:- use_module(library(filepos_line)). 49:- init_expansors.
53from_to_file_line_pos(clause_term_position(ClauseRef, TermPos),
54 File, CLine, TLine, Pos) :-
55 clause_property(ClauseRef, file(File)),
56 clause_property(ClauseRef, line_count(CLine)),
57 file_termpos_line(File, TermPos, TLine, Pos).
58from_to_file_line_pos(clause(ClauseRef), File, CLine, _, _) :-
59 clause_property(ClauseRef, file(File)),
60 clause_property(ClauseRef, line_count(CLine)).
61from_to_file_line_pos(file(File, Line, Pos, _), File, _, Line, Pos).
62from_to_file_line_pos(file_term_position(File, TermPos), File, _, Line, Pos) :-
63 file_termpos_line(File, TermPos, Line, Pos).
64
65file_termpos_line(File, TermPos, Line, Pos) :-
66 ( compound(TermPos),
67 arg(1, TermPos, CharCount),
68 integer(CharCount)
69 ->filepos_line(File, CharCount, Line, Pos)
70 ; true
71 ).
72
73subsumes_from(From1, From2) :-
74 from_to_file_line_pos(From1, File1, CLine1, TLine1, Pos1),
75 from_to_file_line_pos(From2, File2, CLine2, TLine2, Pos2),
76 subsumes_term(flp(File1, CLine1, TLine1, Pos1),
77 flp(File2, CLine2, TLine2, Pos2)).
78
79from_to_file(clause_term_position(ClauseRef, _), File) :-
80 clause_property(ClauseRef, file(File)).
81from_to_file(clause(ClauseRef), File) :-
82 clause_property(ClauseRef, file(File)).
83from_to_file(file_term_position(File, _), File).
84from_to_file(file(File, _, _, _), File).
85
86clause_module(ClauseRef, Module) :-
87 88 89 clause_property(ClauseRef, file(File)),
90 module_property(Module, file(File)).
91
92from_to_module(clause_term_position(ClauseRef, _), Module) :-
93 clause_module(ClauseRef, Module).
94from_to_module(clause(ClauseRef), Module) :-
95 clause_module(ClauseRef, Module).
96from_to_module(file_term_position(File, _), Module) :-
97 module_property(Module, file(File)).
98from_to_module(file(File, _, _, _), Module) :-
99 module_property(Module, file(File)).
100
101from_to_line(clause_term_position(ClauseRef, _), Line) :-
102 clause_property(ClauseRef, line_count(Line)).
103from_to_line(clause(ClauseRef), Line) :-
104 clause_property(ClauseRef, line_count(Line)).
105from_to_line(file_term_position(File, TermPos), Line) :-
106 file_termpos_line(File, TermPos, Line, _).
107from_to_line(file(_, Line, _, _), Line).
108
109:- meta_predicate update_fact_from(1, ?). 110:- pred update_fact_from/2 + database.
111update_fact_from(Fact, From) :-
112 extend_args(Fact, [From1], FactFrom),
113 functor(Fact, F, A),
114 atomic_list_concat(['__mutex_', F, '/', A], Mutex),
115 with_mutex(Mutex, update_fact_from(FactFrom, From1, From)).
116
117update_fact_from(FactFrom, From1, From) :-
118 forall(( clause(FactFrom, _, Ref),
119 subsumes_from(From1, From)
120 ),
121 erase(Ref)),
122 ( \+ ( call(FactFrom),
123 subsumes_from(From, From1)
124 )
125 ->From = From1,
126 assertz(FactFrom)
127 ; true
128 )