1:- module(pls_index_terms, [
2 index_terms/1
3 ]). 4
5:- use_module(library(http/json)). 6:- use_module(library(log4p)). 7:- use_module(library(prolog_stack)). 8
9:- use_module(library(prolog_source)). 10
11:- use_module(documents). 12:- use_module(docs). 13:- use_module(profiles). 14
18index_terms(URI) :-
19 clear_document_items(URI),
20 forall(index_term(URI), true).
26index_term(URI) :-
27 with_content(URI, In, (
28 repeat,
29 get_document_profile(URI, Profile),
30 profile_module(Profile, ProfileModule),
31 ( ProfileModule = pls_language_profile_base
32 -> true
33 ; info("Using profile %w in %w for %w",[Profile, ProfileModule, URI])
34 ),
35 read_term(In, Term, [
36 syntax_errors(dec10),
37 subterm_positions(SubPos),
38 module(ProfileModule),
39 comments(CommentPos),
40 variable_names(Vars)
41 ]),
42 ( Term \== end_of_file
43 -> process_term(URI, SubPos, Term, CommentPos, Vars)
44 ; (try_process_end_of_file(URI), !, fail)
45 )
46 )).
47
48process_term(URI, _SubPos, (:- use_language_profile(Profile)), _CommentPos, _Vars) :-
49 profile_module(Profile, ProfileModule),
50 info("Using profile %w for %w in %w",[Profile, URI, ProfileModule]),
51 set_document_profile(URI, Profile),
52 ensure_profile_loaded(Profile),
53 !.
54
55process_term(URI, SubPos, Term, CommentPos, Vars) :-
56 get_document_profile(URI, Profile),
57 58 try_profile_index_term(Profile, URI, SubPos, Term),
59 try_profile_index_docs(Profile, URI, SubPos, Term, CommentPos),
60 try_profile_index_signature(Profile, URI, SubPos, Term, Vars),
61 !.
62
63try_profile_index_term(Profile, URI, SubPos, Term) :-
64 pls_index_profiles:profile_index_term(Profile, URI, SubPos, Term),
65 !.
66
67try_profile_index_term(_Profile, URI, SubPos, Term) :-
68 pls_index_profiles:profile_index_term(base, URI, SubPos, Term).
69
70try_profile_index_docs(Profile, URI, SubPos, Term, CommentPos) :-
71 pls_index_profiles:profile_index_docs(Profile, URI, SubPos, Term, CommentPos),
72 !.
73
74try_profile_index_docs(_Profile, URI, SubPos, Term, CommentPos) :-
75 pls_index_profiles:profile_index_docs(base, URI, SubPos, Term, CommentPos).
76
77try_profile_index_signature(Profile, URI, SubPos, Term, Vars) :-
78 pls_index_profiles:profile_index_signature(Profile, URI, SubPos, Term, Vars),
79 !.
80
81try_profile_index_signature(_Profile, URI, SubPos, Term, Vars) :-
82 pls_index_profiles:profile_index_signature(base, URI, SubPos, Term, Vars).
83
84try_process_end_of_file(URI) :-
85 get_document_profile(URI, Profile),
86 ensure_profile_loaded(Profile),
87 pls_index_profiles:profile_end_of_file(Profile, URI),
88 !.
89
90try_process_end_of_file(URI) :-
91 pls_index_profiles:profile_end_of_file(base, URI)