1:- module(pls_index_indexing, [
    2  index_text/1,
    3
    4  begin_indexing/1,
    5  start_index_roots/1,
    6
    7  index_roots/1,
    8  index_root/1
    9  ]).   10
   11:- use_module(library(log4p)).   12:- use_module(library(option)).   13:- use_module(library(prolog_source)).   14:- use_module(library(prolog_stack)).   15:- use_module(library(uri)).   16
   17:- use_module(documents).   18:- use_module(lines).   19:- use_module(terms).   20
   21with_input_from(String, Goal) :-
   22  setup_and_call_cleanup(
   23    open_string(String, In),
   24    setup_and_call_cleanup(
   25      current_input(SaveIn),
   26      ( set_input(In), Goal ), 
   27      set_input(SaveIn)
   28      ),
   29    close(In)
   30    ).
   36begin_indexing(Params) :-
   37  RootURI = Params.get(rootUri),
   38  (Folders = Params.get(workspaceFolders,[])
   39    -> true
   40       41    ; Folders = []
   42    ),
   43  findall(
   44    URI,
   45    ( member(Folder, Folders), URI = Folder.uri ),
   46    FolderURIs
   47    ),
   48    swi_root(SwiRootURI),
   49    pack_roots(PackRoots),
   50    append([
   51      [RootURI],
   52      [SwiRootURI],
   53      PackRoots,
   54      FolderURIs
   55      ],
   56      AllRoots),
   57    list_to_set(AllRoots, RootURIs),
   58       59    index_roots(RootURIs).
   60
   61begin_indexing(_).
   68start_index_roots(Roots) :-
   69  thread_create(index_roots(Roots), _Id, [detached(true)]).
   76index_roots(Roots) :-
   77  debug("Starting indexing of files in all roots: %w", [Roots]),
   78  forall(member(Root, Roots), index_root(Root)),
   79  debug("Finished indexing of files in all roots: %w", [Roots]).
   85index_root(URI) :-
   86  debug("Starting index of files in root %w", [URI]),
   87  uri_file_name(URI, Directory),
   88  directory_source_files(Directory, Files, [recursive(true)]),
   89  forall(member(File, Files), index_file(File)),
   90  debug("Finished index of files in root %w", [URI]).
   96index_file(Source) :-
   97  debug("Starting index of file %w", [Source]),
   98  file_name_extension(_Base, Extension, Source),
   99  prolog_extension(Extension),
  100  uri_file_name(URI, Source),
  101  catch_with_backtrace(
  102    index_text(URI),
  103    Error,
  104    error(Error)
  105    ),
  106  debug("Finished index of file %w", [Source]).
  114index_text(URI) :-
  115  uri_file_name(URI,FileName),
  116  set_document_uri(URI), 
  117  xref_source(FileName),
  118  index_lines(URI),
  119  index_terms(URI),
  120  !.
  126swi_root(SwiRootURI) :-
  127  absolute_file_name(swi(library),SwiRoot, [file_type(directory)]),
  128  uri_file_name(SwiRootURI, SwiRoot).
  134pack_roots(PackRoots) :-
  135  findall(
  136    PackRoot,
  137    (
  138      pack_property(_Pack, directory(PackDirectory)),
  139      directory_file_path(PackDirectory,'prolog',PackPrologDirectory),
  140      uri_file_name(PackRoot, PackPrologDirectory)
  141      ),
  142    PackRoots
  143    ).
  144  
  145prolog_extension(Extension) :-
  146  member(Extension, [
  147    pl,
  148    plt,
  149    pro,
  150    prolog
  151    ])