1:- module(pls_index_documents, [
    2  store_document/4,
    3
    4  get_document_properties/2,
    5  add_document_property/2,
    6  set_document_property/2,
    7  get_document_property/2,
    8  clear_document_property/2,
    9  clear_document_properties/1,
   10
   11  get_document_uri/1,
   12  set_document_uri/1,
   13  clear_document_uri/1,
   14
   15  get_document_content/2,
   16  set_document_content/2,
   17  clear_document_content/1,
   18  with_content/3,
   19
   20  add_document_item/3,
   21  get_document_item/3,
   22  clear_document_item/2,
   23  clear_document_items/1,
   24
   25  add_document_line/3,
   26  get_document_line_position/3,
   27  clear_document_line/2,
   28  clear_document_lines/1,
   29  set_document_line_count/2,
   30  get_document_line_count/2,
   31  clear_document_line_count/1  
   32  ]).   33
   34:- dynamic document_content/2.   35:- dynamic document_item/3.   36:- dynamic document_line_count/2.   37:- dynamic document_line_position/3.   38:- dynamic document_property/2.   39:- dynamic document_uri/1.   40
   41store_document(URI, Language, Version, Content) :-
   42  clear_document_properties(URI),
   43  clear_document_items(URI),
   44  clear_document_lines(URI),
   45  clear_document_line_count(URI),
   46  set_document_property(URI, language(Language)),
   47  set_document_property(URI, version(Version)),
   48  set_document_content(URI, Content).
   49
   50get_document_properties(URI, Properties) :-
   51  findall(Property, document_property(URI, Property), Properties).
   52
   53add_document_property(URI, Property) :-
   54  assertz(document_property(URI, Property)).
   55
   56set_document_property(URI, Property) :-
   57  functor(Property, Name, Arity),
   58  functor(Clear, Name, Arity),
   59  clear_document_property(URI, Clear),
   60  assertz(document_property(URI, Property)).
   61
   62get_document_property(URI, Property) :-
   63  document_property(URI, Property).
   64
   65clear_document_properties(URI) :-
   66  clear_document_property(URI, _).
   67
   68clear_document_property(URI, Clear) :-
   69  retractall(document_property(URI, Clear)).
   70
   71set_document_content(URI, Content) :-
   72  clear_document_content(URI),
   73  assertz(document_content(URI, Content)).
   74
   75get_document_content(URI, Content) :-
   76  document_content(URI, Content).
   77
   78clear_document_content(URI) :-
   79  retractall(document_content(URI, _)).
   80
   81% 
   82% document accessors
   83% 
   84
   85% -- URI --
   86
   87set_document_uri(URI) :-
   88  get_document_uri(URI), !.
   89
   90set_document_uri(URI) :-
   91  assertz(document_uri(URI)).
   92
   93get_document_uri(URI) :-
   94  document_uri(URI).
   95
   96clear_document_uri(URI) :-
   97  retractall(document_uri(URI)).
   98
   99% -- content --
 set_content(+URI, +Content) is nondet
Record content for the specified URI; usually for temporary available of content for a document where editing is underway
  107set_content(URI, Content) :-
  108  clear_language(URI),
  109  assertz(document_content(URI, Content)).
 get_content(?URI, ?Content) is det
Retrieve the content of the document associated with the URI as a string.
  116get_content(URI, Content) :-
  117  once(document_content(URI, Content)).
 clear_content(+URI) is det
Flush the content associated with the URI.
  123clear_content(URI) :-
  124  clear_document_content(URI).
  125
  126% --- items --
 add_document_item(?URI, ?Range, ?Value) is nondet
Add a piece of information about a specific range in a specific document. Items are the basis of all cross-referencing, hover info, etc.
  134add_document_item(URI, Range, Value) :-
  135  assertz(document_item(URI, Range, Value)).
 get_document_item(?URI, +Position, -Item) is nondet
get_document_item(?URI, ?Range, ?Item) is nondet
When called in its first form, get a document item based on its position, otherwise return a document item by unifying with URI, Range, and Item .
  143get_document_item(URI, Position, Item) :-
  144  nonvar(Position),
  145  Line = Position.get(line),
  146  Character = Position.get(character),
  147  % Must have ground actual position
  148  ground(Line),ground(Character),
  149  get_document_item(
  150    URI,
  151    _{
  152      start: _{line: Line, character: FromCharacter},
  153      end:  _{line: _ToLine, character: ToCharacter}
  154      },
  155    Item
  156    ),
  157  Character >= FromCharacter,
  158  Character =< ToCharacter.
  159
  160get_document_item(URI, Range, Value) :-
  161  document_item(URI, Range, Value).
  162
  163clear_document_item(URI, Value) :-
  164  retractall(document_item(URI, _Range, Value)).
  165
  166clear_document_items(URI) :-
  167  clear_document_item(URI, _).
  168
  169:- meta_predicate with_content(?, ?, :).  170with_content(URI, In, Module:Goal) :-
  171  get_document_content(URI, Content),
  172  !,
  173  setup_call_cleanup(
  174    open_string(Content, In),
  175    call(Module:Goal),
  176    close(In)
  177    ).
  178
  179with_content(URI, In, Module:Goal) :-
  180  uri_file_name(URI, FileName),
  181  setup_call_cleanup(
  182    open(FileName, read, In),
  183    call(Module:Goal),
  184    close(In)
  185    ).
  186
  187% --- lines --
  188
  189add_document_line(URI, Line, Position) :-
  190  assertz(document_line_position(URI, Line, Position)).
 get_document_line_position(+URI, ?Line, +Position) is det
get_document_line_position(?URI, ?Line, ?Position) is det
Given a position with a file, return the line where the position occurs, or the reverse. Can also be useful for iterating over the starting positions of lines within a file.
  199get_document_line_position(URI, Line, Position) :-
  200  ground(Position),
  201  get_document_line_count(URI, Max),
  202  MidPoint is ceiling(Max / 2),
  203  Range is ceiling(MidPoint / 2),
  204  find_line_position(URI, Position, MidPoint, Range, Line),
  205  !.
  206
  207get_document_line_position(URI, Line, Position) :-
  208  document_line_position(URI, Line, Position).
  209
  210clear_document_line(URI, Line) :-
  211  retractall(document_line_position(URI, Line, _)).
  212
  213clear_document_lines(URI) :-
  214  clear_document_line(URI, _).
  215
  216set_document_line_count(URI, LineCount) :-
  217  clear_document_line_count(URI),
  218  assertz(document_line_count(URI, LineCount)).
  219
  220get_document_line_count(URI, LineCount) :-
  221  document_line_count(URI, LineCount).
  222
  223clear_document_line_count(URI) :-
  224  retractall(document_line_count(URI, _)).
  225
  226find_line_position(URI, Position, Start, _Range, Line) :-
  227  position_falls_on_line(URI, Start, Position),
  228  Line = Start.
  229
  230find_line_position(URI, Position, Start, Range, Line) :-
  231  get_document_line_position(URI, Start, LinePosition),
  232  NewRange is ceiling(Range / 2),
  233  UpperStart is Start + NewRange,
  234  LowerStart is Start - NewRange,
  235  (Position < LinePosition
  236    -> find_line_position(URI, Position, LowerStart, NewRange, Line)
  237    ; find_line_position(URI, Position, UpperStart, NewRange, Line)
  238    ).
  239
  240position_falls_on_line(URI, Line, Position) :-
  241  get_document_line_position(URI, Line, LinePosition),
  242  NextLine is Line + 1,
  243  (get_document_line_position(URI, NextLine, NextPosition) 
  244    -> true
  245    ; NextPosition is inf 
  246    ),
  247  ( Position >= LinePosition , Position < NextPosition).
  248
  249% -- language --
  250
  251set_language(URI, Language) :-
  252  clear_language(URI),
  253  set_document_property(URI, language(Language)).
  254
  255get_language(URI, Language) :-
  256  once(get_document_property(URI, language(Language))).
  257
  258clear_language(URI) :-
  259  clear_document_property(URI, language(_)).
  260
  261% -- version --
  262
  263set_version(URI, Version) :-
  264  clear_version(URI),
  265  set_document_property(URI, version(Version)).
  266
  267get_version(URI, Version) :-
  268  once(get_document_property(URI, version(Version))).
  269
  270clear_version(URI) :-
  271  clear_document_property(URI, version(_))