1:- module(lsp_formatter, [ file_format_edits/2,
    2                           file_formatted/2 ]).

LSP Formatter

Module for formatting Prolog source code

author
- James Cash

*/

   12:- use_module(library(readutil), [ read_file_to_string/3 ]).   13:- use_module(library(macros)).   14
   15:- include('path_add.pl').   16:- use_module(lsp(lsp_formatter_parser), [ reified_format_for_file/2,
   17                                           emit_reified/2 ]).   18
   19file_format_edits(Path, Edits) :-
   20    read_file_to_string(Path, OrigText, []),
   21    split_string(OrigText, "\n", "", OrigLines),
   22    file_formatted(Path, Formatted),
   23    with_output_to(string(FormattedText),
   24                   emit_reified(current_output, Formatted)),
   25    split_string(FormattedText, "\n", "", FormattedLines),
   26    create_edit_list(OrigLines, FormattedLines, Edits).
   27
   28file_formatted(Path, Formatted) :-
   29    reified_format_for_file(Path, Reified),
   30    apply_format_rules(Reified, Formatted).
   31
   32%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   33% Formatting rules
   34%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   35
   36apply_format_rules(Content, Formatted) :-
   37    phrase(formatter_rules, Content, Formatted).
   38
   39formatter_rules -->
   40    collapse_whitespace,
   41    commas_exactly_one_space,
   42    correct_indentation(_{state: [toplevel], column: 0, leading_spaces: []}).
   43
   44collapse_whitespace([], []) :- !.
   45collapse_whitespace([white(A), white(B)|InRest], [white(AB)|OutRest]) :- !,
   46    AB is A + B,
   47    collapse_whitespace(InRest, OutRest).
   48collapse_whitespace([In|InRest], [In|OutRest]) :-
   49    collapse_whitespace(InRest, OutRest).
   50
   51commas_exactly_one_space([], Out) => Out = [].
   52commas_exactly_one_space([white(_), comma|InRest], Out) =>
   53    commas_exactly_one_space([comma|InRest], Out).
   54commas_exactly_one_space([comma, white(_)|InRest], Out) =>
   55    Out = [comma, white(1)|OutRest],
   56    commas_exactly_one_space(InRest, OutRest).
   57commas_exactly_one_space([comma, Next|InRest], Out), Next \= white(_), Next \= newline =>
   58    Out = [comma, white(1), Next|OutRest],
   59    commas_exactly_one_space(InRest, OutRest).
   60commas_exactly_one_space([Other|Rest], Out) =>
   61    Out = [Other|OutRest],
   62    commas_exactly_one_space(Rest, OutRest).
   63
   64#define(toplevel_indent, 4).
   65
   66% TODO: alignment special-case rule for ->;
   67correct_indentation(_, [], []) :- !.
   68correct_indentation(State0,
   69                    [term_begin(Func, Type, Parens)|InRest],
   70                    [term_begin(Func, Type, Parens)|OutRest]) :-
   71    indent_state_top(State0, toplevel),
   72    Func = ':-', !,
   73    indent_state_push(State0, declaration, State1),
   74    update_state_column(State1, term_begin(Func, Type, Parens), State2),
   75    push_state_open_spaces(State2, InRest, State3),
   76    correct_indentation(State3, InRest, OutRest).
   77correct_indentation(State0,
   78                    [term_begin(Func, Type, Parens)|InRest],
   79                    [term_begin(Func, Type, Parens)|OutRest]) :-
   80    indent_state_top(State0, toplevel), !,
   81    update_state_column(State0, term_begin(Func, Type, Parens), State1),
   82    indent_state_push(State1, defn_head(State1.column, false), State2),
   83    push_state_open_spaces(State2, InRest, State3),
   84    correct_indentation(State3, InRest, OutRest).
   85correct_indentation(State0, [In|InRest], [In|OutRest]) :-
   86    indent_state_top(State0, toplevel),
   87    In = simple(_), !,
   88    indent_state_push(State0, defn_head_neck, State1),
   89    update_state_column(State1, In, State2),
   90    correct_indentation(State2, InRest, OutRest).
   91correct_indentation(State0,
   92                    [term_begin(Neckish, T, P)|InRest],
   93                    [term_begin(Neckish, T, P)|OutRest]) :-
   94    memberchk(Neckish, [':-', '=>', '-->']),
   95    indent_state_top(State0, defn_head_neck), !,
   96    indent_state_pop(State0, State1),
   97    indent_state_push(State1, defn_body, State2),
   98    update_state_column(State2, term_begin(Neckish, T, P), State3),
   99    push_state_open_spaces(State3, InRest, State4),
  100    correct_indentation(State4, InRest, OutRest).
  101correct_indentation(State0, [In|InRest], Out) :-
  102    In = term_begin('->', compound, false),
  103    indent_state_top(State0, defn_body_indent), !,
  104    indent_state_pop(State0, State1),
  105    % if should align with the open paren, not the first term
  106    indent_state_pop(State1, State2),
  107    indent_state_top(State2, Top), % Copy the previous top
  108    indent_state_push(State2, Top, State3),
  109    whitespace_indentation_for_state(State3, Indent),
  110    Out = [white(Indent)|OutRest],
  111    update_state_column(State3, white(Indent), State4),
  112    correct_indentation(State4, [In|InRest], OutRest).
  113correct_indentation(State0, [newline|InRest], [newline|Out]) :- !,
  114    ( indent_state_top(State0, defn_body_indent)
  115    -> State1 = State0
  116    ; indent_state_push(State0, defn_body_indent, State1) ),
  117    update_state_column(State1, newline, State2),
  118    correct_indentation(State2, InRest, Out).
  119correct_indentation(State0, [In|InRest], Out) :-
  120    indent_state_top(State0, defn_body_indent), !,
  121    ( In = white(_)
  122    -> correct_indentation(State0, InRest, Out)
  123    ;  ( indent_state_pop(State0, State1),
  124         ( indent_state_top(State1, begin(_, _))
  125           % state top = begin means prev line ended with an open paren
  126         -> indent_state_pop(State1, StateX),
  127            % so pop that off and align as if one step "back"
  128            whitespace_indentation_for_state(StateX, PrevIndent),
  129            IncPrevIndent is PrevIndent + 4,
  130            indent_state_push(StateX, align(IncPrevIndent), State2)
  131         ; State2 = State1 ),
  132         update_alignment(State2, State3),
  133         ( ending_term(In)
  134           % TODO: this needs some more special casing to act the way I'd like
  135           % (that is, when the ending )/]/} is on its own line)
  136         -> indent_state_pop(State3, State_),
  137            pop_state_open_spaces(State3, _, State4),
  138            push_state_open_spaces(State4, 0, State5),
  139            whitespace_indentation_for_state(State_, Indent)
  140         ; ( whitespace_indentation_for_state(State3, Indent),
  141             State5 = State3 ) ),
  142         Out = [white(Indent)|OutRest],
  143         update_state_column(State5, white(Indent), State6),
  144         correct_indentation(State6, [In|InRest], OutRest) ) ).
  145correct_indentation(State0, [In|InRest], [In|OutRest]) :-
  146    functor(In, Name, _Arity, _Type),
  147    atom_concat(_, '_begin', Name), !,
  148    % if we've just begun something...
  149    update_alignment(State0, State1),
  150    update_state_column(State1, In, State2),
  151    indent_state_push(State2, begin(State2.column, In), State3),
  152    push_state_open_spaces(State3, InRest, State4),
  153    correct_indentation(State4, InRest, OutRest).
  154correct_indentation(State0, [In|InRest], [In|OutRest]) :-
  155    indent_state_top(State0, defn_head(_, _)),
  156    In = term_end(_, S), S \= toplevel, !,
  157    indent_state_pop(State0, State1),
  158    indent_state_push(State1, defn_head_neck, State2),
  159    update_state_column(State2, In, State3),
  160    pop_state_open_spaces(State3, _, State4),
  161    correct_indentation(State4, InRest, OutRest).
  162correct_indentation(State0, [In|InRest], Out) :-
  163    ending_term(In), !,
  164    indent_state_pop(State0, State1),
  165    update_state_column(State1, In, State2),
  166    pop_state_open_spaces(State2, Spaces, State3),
  167    ( In \= term_end(false, _), In \= term_end(_, toplevel), Spaces > 0
  168    -> Out = [white(Spaces), In|OutRest]
  169    ;  Out = [In|OutRest] ),
  170    correct_indentation(State3, InRest, OutRest).
  171correct_indentation(State0, [In, NextIn|InRest], Out) :-
  172    In = white(_),
  173    ending_term(NextIn), !,
  174    correct_indentation(State0, [NextIn|InRest], Out).
  175correct_indentation(State0, [In|InRest], [In|OutRest]) :-
  176    memberchk(In, [white(_), newline]), !,
  177    update_state_column(State0, In, State1),
  178    correct_indentation(State1, InRest, OutRest).
  179correct_indentation(State0, [In|InRest], [In|OutRest]) :- !,
  180    ( In \= white(_)
  181    -> update_alignment(State0, State1)
  182    ; State1 = State0 ),
  183    update_state_column(State1, In, State2),
  184    correct_indentation(State2, InRest, OutRest).
  185
  186ending_term(Term) :-
  187    functor(Term, Name, _, _),
  188    atom_concat(_, '_end', Name).
  189
  190update_alignment(State0, State2) :-
  191    indent_state_top(State0, begin(Col, _)), !,
  192    indent_state_pop(State0, State1),
  193    AlignCol is max(Col, State1.column),
  194    indent_state_push(State1, align(AlignCol), State2).
  195update_alignment(State0, State2) :-
  196    indent_state_top(State0, defn_head(Col, false)), !,
  197    indent_state_pop(State0, State1),
  198    AlignCol is max(Col, State1.column),
  199    indent_state_push(State1, defn_head(AlignCol, true), State2).
  200update_alignment(State, State).
  201
  202whitespace_indentation_for_state(State, Indent) :-
  203    indent_state_top(State, align(Indent)), !.
  204whitespace_indentation_for_state(State, Indent) :-
  205    indent_state_top(State, defn_head(Indent, _)), !.
  206whitespace_indentation_for_state(State, Indent) :-
  207    get_dict(state, State, Stack),
  208    aggregate_all(count,
  209                  ( member(X, Stack),
  210                    memberchk(X, [parens_begin, braces_begin, term_begin(_, _, _)]) ),
  211                  ParensCount),
  212    ( indent_state_contains(State, defn_body)
  213    -> MoreIndent = #toplevel_indent
  214    ;  MoreIndent = 0 ),
  215    Indent is ParensCount * 2 + MoreIndent.
  216
  217indent_state_top(State, Top) :-
  218    _{state: [Top|_]} :< State.
  219
  220indent_state_contains(State, Needle) :-
  221    _{state: Stack} :< State,
  222    memberchk(Needle, Stack).
  223
  224indent_state_push(State0, NewTop, State1) :-
  225    _{state: Stack} :< State0,
  226    put_dict(state, State0, [NewTop|Stack], State1).
  227
  228indent_state_pop(State0, State1) :-
  229    _{state: [_|Rest]} :< State0,
  230    put_dict(state, State0, Rest, State1).
  231
  232update_state_column(State0, newline, State1) :- !,
  233    put_dict(column, State0, 0, State1).
  234update_state_column(State0, Term, State1) :-
  235    emit_reified(string(S), [Term]),
  236    string_length(S, Len),
  237    NewCol is State0.column + Len,
  238    put_dict(column, State0, NewCol, State1).
  239
  240push_state_open_spaces(State0, Next, State1) :-
  241    _{leading_spaces: PrevSpaces} :< State0,
  242    ( Next = [white(N)|_]
  243    -> put_dict(leading_spaces, State0, [N|PrevSpaces], State1)
  244    ; put_dict(leading_spaces, State0, [0|PrevSpaces], State1) ).
  245
  246pop_state_open_spaces(State0, Top, State1) :-
  247    _{leading_spaces: [Top|Spaces]} :< State0,
  248    put_dict(leading_spaces, State0, Spaces, State1).
  249
  250%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  251% Create a List of Edits from the Original and Formatted Lines
  252%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  253create_edit_list(Orig, Formatted, Edits) :-
  254    create_edit_list(0, Orig, Formatted, Edits).
  255
  256create_edit_list(_, [], [], []) :- !.
  257create_edit_list(LineNum, [Line|Lines], [], [Edit]) :- !,
  258    length(Lines, NLines),
  259    EndLine is LineNum + NLines,
  260    last([Line|Lines], LastLine),
  261    string_length(LastLine, LastLineLen),
  262    Edit = _{range: _{start: _{line: LineNum, character: 0},
  263                      end: _{line: EndLine, character: LastLineLen}},
  264             newText: ""}.
  265create_edit_list(LineNum, [], [NewLine|NewLines], [Edit|Edits]) :- !,
  266    string_length(NewLine, LenLen),
  267    Edit = _{range: _{start: _{line: LineNum, character: 0},
  268                      end: _{line: LineNum, character: LenLen}},
  269             newText: NewLine},
  270    succ(LineNum, LineNum1),
  271    create_edit_list(LineNum1, [], NewLines, Edits).
  272create_edit_list(LineNum, [OrigLine|OrigRest], [FormattedLine|FormattedRest], Edits) :-
  273    (   OrigLine \= FormattedLine  % Only create an edit if the line has changed
  274    -> string_length(OrigLine, LineLen), %TODO: what should this be?
  275       Edit = _{range: _{start: _{line: LineNum, character: 0},
  276                         end: _{line: LineNum, character: LineLen}},
  277                newText: FormattedLine},
  278       Edits = [Edit|EditRest]
  279    ; EditRest = Edits
  280    ),
  281    succ(LineNum, LineNum1),
  282    create_edit_list(LineNum1, OrigRest, FormattedRest, EditRest).
  283
  284% lsp_formatter:file_formatted('/Users/james/Projects/prolog-lsp/prolog/format_test2.pl', Src), lsp_formatter_parser:emit_reified(user_output, Src).
  285
  286% lsp_formatter:file_formatted('/Users/james/Projects/prolog-lsp/prolog/format_test.pl', Src), setup_call_cleanup(open('/Users/james/tmp/formatted_out.pl', write, S), lsp_formatter_parser:emit_reified(S, Src), close(S)).