1:- module(lsp_highlights, [ highlights_at_position/3 ]).    2
    3:- include('path_add.pl').    4
    5:- use_module(library(apply), [maplist/2]).    6:- use_module(library(apply_macros)).    7:- use_module(library(yall)).    8
    9:- use_module(lsp(lsp_reading_source), [ file_lines_start_end/2,
   10                                         read_term_positions/2,
   11                                         file_offset_line_position/4 ]).   12
   13highlights_at_position(Path, Position, Highlights) :-
   14    highlights_at_position(Path, Position, _, Highlights).
   15
   16highlights_at_position(Path, line_char(Line1, Char0), Leaf, Highlights) :-
   17    file_lines_start_end(Path, LineCharRange),
   18    read_term_positions(Path, TermsWithPositions),
   19    % find the top-level term that the offset falls within
   20    file_offset_line_position(LineCharRange, Offset, Line1, Char0),
   21    % find the specific sub-term containing the point
   22    member(TermInfo, TermsWithPositions),
   23    SubTermPoses = TermInfo.subterm,
   24    arg(1, SubTermPoses, TermFrom),
   25    arg(2, SubTermPoses, TermTo),
   26    between(TermFrom, TermTo, Offset), !,
   27    subterm_leaf_position(TermInfo.term, Offset, SubTermPoses, Leaf),
   28    ( Leaf = '$var'(_)
   29      % if it's a variable, only look inside the containing term
   30    -> find_occurrences_of_var(Leaf, TermInfo, Matches)
   31    % if it's the functor of a term, find all occurrences in the file
   32    ; functor(Leaf, FuncName, Arity),
   33      find_occurrences_of_func(FuncName, Arity, TermsWithPositions, Matches)
   34    ),
   35    maplist(position_to_match(LineCharRange), Matches, Highlights).
   36
   37position_to_match(LineCharRange, found_at(_, From-To), Match) :- !,
   38    file_offset_line_position(LineCharRange, From, FromLine1, FromCharacter),
   39    file_offset_line_position(LineCharRange, To, ToLine1, ToCharacter),
   40    succ(FromLine0, FromLine1),
   41    succ(ToLine0, ToLine1),
   42    Match = _{range: _{start: _{line: FromLine0, character: FromCharacter},
   43                       end: _{line: ToLine0, character: ToCharacter}}}.
   44position_to_match(LineCharRange, found_at(_, term_position(_, _, FFrom, FTo, _)), Match) :-
   45    file_offset_line_position(LineCharRange, FFrom, FromLine1, FromCharacter),
   46    file_offset_line_position(LineCharRange, FTo, ToLine1, ToCharacter),
   47    succ(FromLine0, FromLine1),
   48    succ(ToLine0, ToLine1),
   49    Match = _{range: _{start: _{line: FromLine0, character: FromCharacter},
   50                       end: _{line: ToLine0, character: ToCharacter}}}.
   51
   52find_occurrences_of_func(FuncName, Arity, TermInfos, Matches) :-
   53    find_occurrences_of_func(FuncName, Arity, TermInfos, Matches, []).
   54
   55find_occurrences_of_func(_, _, [], Tail, Tail).
   56find_occurrences_of_func(FuncName, Arity, [TermInfo|Rest], Matches, Tail) :-
   57    find_in_term_with_positions({FuncName, Arity}/[X]>>( nonvar(X),
   58                                                         functor(X, FuncName, Arity) ),
   59                                TermInfo.term, TermInfo.subterm, Matches, Tail0),
   60    find_occurrences_of_func(FuncName, Arity, Rest, Tail0, Tail).
   61
   62find_occurrences_of_var(Var, TermInfo, Matches) :-
   63    Var = '$var'(Name), ground(Name), % wrapped term; otherwise it's anonymous & matches nothing
   64    Term = TermInfo.term,
   65    Poses = TermInfo.subterm,
   66    find_in_term_with_positions({Var}/[X]>>( ground(X), X = Var ), Term, Poses,
   67                                Matches, []).
   68
   69:- meta_predicate find_in_term_with_positions(1, +, +, -, -).   70
   71find_in_term_with_positions(Needle, Term, Position, Matches, Tail) :-
   72    call(Needle, Term), !, % recurse?
   73    Matches = [found_at(Term, Position)|Tail].
   74find_in_term_with_positions(Needle, Term, term_position(_, _, _, _, SubPoses), Matches, Tail) :- !,
   75    find_in_term_subterm(Needle, Term, 1, SubPoses, Matches, Tail).
   76find_in_term_with_positions(Needle, Term, list_position(_, _, Elms, TailPos), Matches, Tail) :- !,
   77    find_in_term_list(Needle, Term, Elms, TailPos, Matches, Tail).
   78find_in_term_with_positions(Needle, Term, brace_term_position(_, _, ArgPos), Matches, Tail) :- !,
   79    Term = {Term0},
   80    find_in_term_with_positions(Needle, Term0, ArgPos, Matches, Tail).
   81find_in_term_with_positions(Needle, Term, parentheses_term_position(_, _, ContentPos), Matches, Tail) :- !,
   82    find_in_term_with_positions(Needle, Term, ContentPos, Matches, Tail).
   83find_in_term_with_positions(Needle, Term, dict_position(_, _, _, _, ContentPos), Matches, Tail) :- !,
   84    find_in_term_dict(Needle, Term, ContentPos, Matches, Tail).
   85find_in_term_with_positions(_, _Term, _Pos, Tail, Tail).
   86
   87find_in_term_dict(_, _, [], Tail, Tail) :- !.
   88find_in_term_dict(Needle, Term, [Pos|Poses], Matches, Tail) :-
   89    key_value_position(_KVFrom, _KVTo, _SF, _ST, Key, _KeyPos, ValuePos) = Pos,
   90    get_dict(Key, Term, Value),
   91    find_in_term_with_positions(Needle, Value, ValuePos, Matches, Tail0),
   92    find_in_term_dict(Needle, Term, Poses, Tail0, Tail).
   93
   94find_in_term_list(_, _, [], none, Tail, Tail) :- !.
   95find_in_term_list(Needle, TailElt, [], TailPos, Matches, Tail) :- !,
   96    find_in_term_with_positions(Needle, TailElt, TailPos, Matches, Tail).
   97find_in_term_list(Needle, [X|Xs], [Pos|Poses], TailPos, Matches, Tail) :-
   98    find_in_term_with_positions(Needle, X, Pos, Matches, Tail0),
   99    find_in_term_list(Needle, Xs, Poses, TailPos, Tail0, Tail).
  100
  101find_in_term_subterm(_, _, _, [], Tail, Tail) :- !.
  102find_in_term_subterm(Needle, Term, Arg, [Position|Positions], Matches, Tail) :-
  103    arg(Arg, Term, SubTerm),
  104    NextArg is Arg + 1,
  105    find_in_term_with_positions(Needle, SubTerm, Position, Matches, Matches0),
  106    find_in_term_subterm(Needle, Term, NextArg, Positions, Matches0, Tail).
 subterm_leaf_position(Term, Offset, SubTermPoses, Leaf) is semidet
  109subterm_leaf_position(Term, Offset, From-To, Term) :- between(From, To, Offset), !.
  110subterm_leaf_position(Term, Offset, term_position(_, _, FFrom, FTo, _), Term) :-
  111    between(FFrom, FTo, Offset), !.
  112subterm_leaf_position(Term, Offset, term_position(From, To, _, _, Subterms), Leaf) :-
  113    between(From, To, Offset), !,
  114    functor(Term, _, Arity, _),
  115    between(1, Arity, Arg),
  116    arg(Arg, Term, Subterm),
  117    nth1(Arg, Subterms, SubtermPos),
  118    subterm_leaf_position(Subterm, Offset, SubtermPos, Leaf), !.
  119subterm_leaf_position(Term, Offset, list_position(From, To, Elms, _), Leaf) :-
  120    between(From, To, Offset),
  121    length(Elms, NElms),
  122    between(1, NElms, Idx),
  123    nth1(Idx, Term, Elm),
  124    nth1(Idx, Elms, ElmPos),
  125    subterm_leaf_position(Elm, Offset, ElmPos, Leaf), !.
  126subterm_leaf_position(Term, Offset, list_position(From, To, Elms, TailPos), Leaf) :-
  127    between(From, To, Offset), TailPos \= none, !,
  128    length(Elms, NElms),
  129    length(Head, NElms),
  130    append(Head, Tail, Term),
  131    subterm_leaf_position(Tail, Offset, TailPos, Leaf), !.
  132subterm_leaf_position(Term, Offset, brace_term_position(From, To, BracesPos), Leaf) :-
  133    between(From, To, Offset), !,
  134    Term = {Term0},
  135    subterm_leaf_position(Term0, Offset, BracesPos, Leaf).
  136subterm_leaf_position(Term, Offset, parentheses_term_position(From, To, ContentPos), Leaf) :-
  137    between(From, To, Offset), !,
  138    subterm_leaf_position(Term, Offset, ContentPos, Leaf).
  139subterm_leaf_position(Term, Offset, dict_position(_From, _To, TagFrom, TagTo, _KVPoses), Leaf) :-
  140    between(TagFrom, TagTo, Offset), !,
  141    is_dict(Term, Leaf).
  142subterm_leaf_position(Term, Offset, dict_position(From, To, _TagFrom, _TagTo, KVPoses), Leaf) :-
  143    between(From, To, Offset), !,
  144    member(key_value_position(KVFrom, KVTo, _SF, _ST, Key, _KeyPos, ValuePos), KVPoses),
  145    between(KVFrom, KVTo, Offset), !,
  146    % keys of a literal dict aren't of interest, I think?
  147    get_dict(Key, Term, Value),
  148    subterm_leaf_position(Value, Offset, ValuePos, Leaf)