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