1:- module(pls_index_profiles, [
    2  use_language_profile/1,
    3  provide_language_profile/1,
    4  register_language_profile/2,
    5  reindex_for_profile/1,
    6  profile_module/2,
    7  ensure_profile_loaded/1,
    8  get_document_profile/2,
    9  set_document_profile/2,
   10
   11  profile_index_term/4,
   12  profile_index_docs/5,
   13  profile_index_signature/5,
   14  profile_index_goal/5,
   15
   16  index_goals/4,
   17  index_goal/4,
   18
   19  functor_range/3,
   20  functor_range/4,
   21  term_position_range/3,
   22  term_range/4,
   23  argument_positions/2,
   24  symbol_kind/2
   25]).   26
   27:- use_module(library(log4p)).   28:- use_module(documents).   29
   30user:file_search_path(pls_language_profile,library(pls_language_profile)).
   31user:file_search_path(pls_language_profile,LocalPath) :-
   32  working_directory(Cwd, Cwd),
   33  absolute_file_name(pls_language_profile,LocalPath, [relative_to(Cwd)]).
   34
   35user:file_search_path(pls_language_profile,LocalPath) :-
   36  working_directory(Cwd, Cwd),
   37  absolute_file_name(prolog/pls_language_profile,LocalPath, [relative_to(Cwd)]).
   38
   39% 
   40% Interface to profiles
   41% 
   42
   43% profile_index_term(Profile, URI, SubPos, Term)
   44:- multifile profile_index_term/4.
 profile_index_docs(+Profile, +URI, +SubPos, Term, +CommentPos) is nondet
Index the documentation for the term at the indicated SubPos, using the CommentPos from an earlier read_term/3 call.
   51:- multifile profile_index_docs/5.   52
   53% profile_index_signature(Profile, URI, SubPos, Term, Vars)
   54:- multifile profile_index_signature/5.
 profile_index_goal(+Profile, ?URI, ?Caller, ?SubPos, ?Goal) is nondet
Index a goal for cross-referncing
   60:- multifile profile_index_goal/5.
 profile_end_of_file(Profile, URI) is nondet
Allow the profile to cleanup after indexing a file.
   66:- multifile profile_end_of_file/2.
 profile_symbol(+Profile, +URI, +Query, ?Range, ?Name, ?Detail, ?Kind) is nondet
Return details about a symbol in the indicated document
   72:- multifile profile_symbol/7.
 use_language_profile(+Profile) is det
Directive to indicate which language profile to use when indexing source. The specified profile applies to the end of the file, or until the next such directive.
   79use_language_profile(_Profile) :- true.
   80
   81:- meta_predicate use_language_profile(:).
 profile_loaded(+Profile) is det
Dynamic predicate to indicate a profile has been loaded
   86:- dynamic profile_loaded/1.
 provide_language_profile(+Profile) is det
A no-op in regular code, but is a single to the Prolog Language server during indexing that the file being indexed implements the indicated language profile.
   94provide_language_profile(_Profile).
 register_language_profile(+Profile, +ProfileModuleFile) is det
Register the indicated module file as an implementation of the indicated profile.
  101register_language_profile(Profile, ProfileURI) :-
  102  registered_language_profile(Profile, ProfileURI),
  103  info("Language profile %w in %w already registered",[Profile, ProfileURI]).
  104
  105register_language_profile(Profile, ProfileURI) :-
  106  info("Registering language profile %w in %w",[Profile, ProfileURI]),
  107  assertz(registered_language_profile(Profile, ProfileURI)).
 registered_language_profile(+Profile, +ProfileModuleFile) is det
Used to record that the indicated module file implements the specified language profile. The Prolog Language Server uses this track registration through register_language_profile/1, and dyamically load the profile from index source.
  116:- dynamic registered_language_profile/2.  117
  118profile_module(Profile, Module) :-
  119  profile_module_file(Profile, ProfileURI),
  120  get_document_item(ProfileURI, _Range, module(Module, _Exports)),
  121  info("Profile %w is in module %w",[Profile, Module]),
  122  !.
  123
  124profile_module(_Profile, Module) :-
  125  Module = pls_language_profile_base.
  126
  127profile_module_file(Profile, ProfileURI) :-
  128  registered_language_profile(Profile, ProfileURI).
  129
  130profile_module_file(Profile, ProfileURI) :-
  131  exists_source(pls_language_profile(Profile), ProfileURI).
  132
  133ensure_profile_loaded(Profile) :-
  134  profile_loaded(Profile), 
  135  !.
  136
  137ensure_profile_loaded(Profile) :-
  138  once(profile_module_file(Profile, ProfileURI)),
  139  uri_file_name(ProfileURI, ProfileModuleFile),
  140  ensure_loaded(ProfileModuleFile),
  141  assertz(profile_loaded(Profile)).
  142
  143get_document_profile(URI, Profile) :-
  144  get_document_property(URI,profile(Profile)),
  145  !.
  146
  147get_document_profile(_URI, base).
  148
  149set_document_profile(URI, Profile) :-
  150  set_document_property(URI, profile(Profile)).
  151
  152reindex_for_profile(base).
  153
  154reindex_for_profile(Profile) :-
  155  forall(
  156    get_document_profile(URI, Profile),
  157    % This is a little sketch, as we
  158    % are explicitly calling to avoid circular references
  159    (
  160      info("Reindexing %w for profile %w",[URI, Profile]),
  161      pls_index_indexing:index_text(URI)
  162      )
  163    ).
  164
  165% f
  166% goals
  167% 
  168index_goals(URI, Caller, GoalPos, Goal) :-
  169  forall(index_goal(URI, Caller, GoalPos, Goal), true).
  170
  171index_goal(URI, Caller, GoalPos, Goal) :-
  172  get_document_profile(URI, Profile),
  173  try_profile_index_goal(Profile, URI, Caller, GoalPos, Goal).
  174
  175try_profile_index_goal(Profile, URI, Caller, GoalPos, Goal) :-
  176  pls_index_profiles:profile_index_goal(Profile, URI, Caller, GoalPos, Goal),
  177  !.
  178
  179try_profile_index_goal(_Profile, URI, Caller, GoalPos, Goal) :-
  180  pls_index_profiles:profile_index_goal(base, URI, Caller, GoalPos, Goal).
  181
  182% 
  183%  -- position helpers --
  184% 
 functor_range(+URI, +Pos, -Range) is det
Given the position of a term, return the range for the functor.
  190functor_range(URI, term_position(_From, _To, FFrom, FTo, _Subpos), Range) :-
  191  term_range(URI, FFrom, FTo, Range).
  192
  193functor_range(URI, FFrom, FTo, Range) :-
  194  term_range(URI, FFrom, FTo, Range).
  195
  196term_position_range(URI, term_position(From, To, _FFrom, _FTo, _Subpos), Range) :-
  197  term_range(URI, From, To, Range).
 term_range(+URI, +From, +To, -Range) is det
Given a From position and To position in the text of the document specified by URI, return a Ranage, which expresses as a start / end pair of locations. Each location has a line number and character offset.
  205term_range(URI, From, To, Range) :-
  206  get_document_line_position(URI, FromLine, From),
  207  get_document_line_position(URI, FromLine, FromStart),
  208  get_document_line_position(URI, ToLine, To),
  209  get_document_line_position(URI, ToLine, ToStart),
  210  FromPosition is From - FromStart,
  211  ToPosition is To - ToStart,
  212  Range = range{
  213    start: position{
  214      line: FromLine,
  215      character: FromPosition
  216      }, 
  217    end: position{
  218      line: ToLine, 
  219      character: ToPosition
  220      }
  221    }.
  222
  223argument_positions(term_position(_From, _To, _FFrom, _FTo, Subpos), Subpos).
 symbol_kind(+Kind, -Code) is det
Transalte a known symbol kind into a pre-defined code.
  229symbol_kind(file, 1).
  230symbol_kind(module, 2).
  231symbol_kind(namespace, 3).
  232symbol_kind(package, 4).
  233symbol_kind(class, 5).
  234symbol_kind(method, 6).
  235symbol_kind(property, 7).
  236symbol_kind(field, 8).
  237symbol_kind(constructor, 9).
  238symbol_kind(enum, 10).
  239symbol_kind(interface, 11).
  240symbol_kind(function, 12).
  241symbol_kind(variable, 13).
  242symbol_kind(constant, 14).
  243symbol_kind(string, 15).
  244symbol_kind(number, 16).
  245symbol_kind(boolean, 17).
  246symbol_kind(array, 18)