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('_lsp_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    ;  insert_whitespace_to_indent(State0, [In|InRest], Out) ).
  123correct_indentation(State0, [In|InRest], [In|OutRest]) :-
  124    functor(In, Name, _Arity, _Type),
  125    atom_concat(_, '_begin', Name), !,
  126    % if we've just begun something...
  127    update_alignment(State0, State1),
  128    update_state_column(State1, In, State2),
  129    indent_state_push(State2, begin(State2.column, State1.column), State3),
  130    push_state_open_spaces(State3, InRest, State4),
  131    correct_indentation(State4, InRest, OutRest).
  132correct_indentation(State0, [In|InRest], [In|OutRest]) :-
  133    indent_state_top(State0, defn_head(_, _)),
  134    In = term_end(_, S), S \= toplevel, !,
  135    indent_state_pop(State0, State1),
  136    indent_state_push(State1, defn_head_neck, State2),
  137    update_state_column(State2, In, State3),
  138    pop_state_open_spaces(State3, _, State4),
  139    correct_indentation(State4, InRest, OutRest).
  140correct_indentation(State0, [In|InRest], Out) :-
  141    ending_term(In), !,
  142    indent_state_pop(State0, State1),
  143    update_state_column(State1, In, State2),
  144    pop_state_open_spaces(State2, Spaces, State3),
  145    ( In \= term_end(false, _), In \= term_end(_, toplevel), Spaces > 0
  146    -> Out = [white(Spaces), In|OutRest]
  147    ;  Out = [In|OutRest] ),
  148    correct_indentation(State3, InRest, OutRest).
  149correct_indentation(State0, [In, NextIn|InRest], Out) :-
  150    In = white(_),
  151    ending_term(NextIn), !,
  152    correct_indentation(State0, [NextIn|InRest], Out).
  153correct_indentation(State0, [In|InRest], [In|OutRest]) :-
  154    memberchk(In, [white(_), newline]), !,
  155    update_state_column(State0, In, State1),
  156    correct_indentation(State1, InRest, OutRest).
  157correct_indentation(State0, [In|InRest], [In|OutRest]) :- !,
  158    ( In \= white(_)
  159    -> update_alignment(State0, State1)
  160    ; State1 = State0 ),
  161    update_state_column(State1, In, State2),
  162    correct_indentation(State2, InRest, OutRest).
  163
  164insert_whitespace_to_indent(State0, [In|InRest], Out) :-
  165    indent_state_pop(State0, State1),
  166    ( indent_state_top(State1, begin(_, BeganAt))
  167      % state top = begin means prev line ended with an open paren
  168    -> % so pop that off and align as if one step "back"
  169       indent_state_pop(State1, StateX),
  170       whitespace_indentation_for_state(StateX, PrevIndent),
  171       IncPrevIndent is PrevIndent + 4,
  172       indent_state_push(StateX, align(IncPrevIndent, BeganAt), State2)
  173    ; State2 = State1 ),
  174    update_alignment(State2, State3),
  175    ( ending_term(In)
  176    -> indent_for_end_term(State3, In, State4, Indent)
  177    ;  whitespace_indentation_for_state(State3, Indent),
  178       State4 = State3 ),
  179    Out = [white(Indent)|OutRest],
  180    update_state_column(State4, white(Indent), State5),
  181    correct_indentation(State5, [In|InRest], OutRest).
  182
  183indent_for_end_term(State0, In, State, Indent) :-
  184    % for a paren ending a term, align a level up
  185    In = term_end(true, _), !,
  186    indent_state_pop(State0, State_),
  187    pop_state_open_spaces(State0, _, State1),
  188    push_state_open_spaces(State1, 0, State),
  189    whitespace_indentation_for_state(State_, Indent).
  190indent_for_end_term(State0, In, State, Indent) :-
  191    % for a brace ending a dict, align two levels up level up
  192    In = dict_end, !,
  193    indent_state_pop(State0, State_),
  194    indent_state_pop(State_, State__),
  195    pop_state_open_spaces(State0, _, State1),
  196    push_state_open_spaces(State1, 0, State),
  197    whitespace_indentation_for_state(State__, Indent).
  198indent_for_end_term(State0, _In, State, Indent) :-
  199    % for another ending term, align to the open
  200    % if we have alignment infomation.
  201    indent_state_top(State0, Top),
  202    Top = align(_, Indent), !,
  203    pop_state_open_spaces(State0, _, State1),
  204    push_state_open_spaces(State1, 0, State).
  205indent_for_end_term(State0, _In, State, Indent) :-
  206    % otherwise, at top-level, just pop state.
  207    indent_state_pop(State0, State_),
  208    pop_state_open_spaces(State0, _, State1),
  209    push_state_open_spaces(State1, 0, State),
  210    whitespace_indentation_for_state(State_, Indent).
  211
  212ending_term(Term) :-
  213    functor(Term, Name, _, _),
  214    atom_concat(_, '_end', Name).
  215
  216update_alignment(State0, State2) :-
  217    indent_state_top(State0, begin(Col, BeganAt)), !,
  218    indent_state_pop(State0, State1),
  219    AlignCol is max(Col, State1.column),
  220    indent_state_push(State1, align(AlignCol, BeganAt), State2).
  221update_alignment(State0, State2) :-
  222    indent_state_top(State0, defn_head(Col, false)), !,
  223    indent_state_pop(State0, State1),
  224    AlignCol is max(Col, State1.column),
  225    indent_state_push(State1, defn_head(AlignCol, true), State2).
  226update_alignment(State, State).
  227
  228whitespace_indentation_for_state(State, Indent) :-
  229    indent_state_top(State, align(Indent, _)), !.
  230whitespace_indentation_for_state(State, Indent) :-
  231    indent_state_top(State, defn_head(Indent, _)), !.
  232whitespace_indentation_for_state(State, Indent) :-
  233    get_dict(state, State, Stack),
  234    aggregate_all(count,
  235                  ( member(X, Stack),
  236                    memberchk(X, [parens_begin, braces_begin, term_begin(_, _, _)]) ),
  237                  ParensCount),
  238    ( indent_state_contains(State, defn_body)
  239    -> MoreIndent = #toplevel_indent
  240    ;  MoreIndent = 0 ),
  241    Indent is ParensCount * 2 + MoreIndent.
  242
  243indent_state_top(State, Top) :-
  244    _{state: [Top|_]} :< State.
  245
  246indent_state_contains(State, Needle) :-
  247    _{state: Stack} :< State,
  248    memberchk(Needle, Stack).
  249
  250indent_state_push(State0, NewTop, State1) :-
  251    _{state: Stack} :< State0,
  252    put_dict(state, State0, [NewTop|Stack], State1).
  253
  254indent_state_pop(State0, State1) :-
  255    _{state: [_|Rest]} :< State0,
  256    put_dict(state, State0, Rest, State1).
  257
  258update_state_column(State0, newline, State1) :- !,
  259    put_dict(column, State0, 0, State1).
  260update_state_column(State0, Term, State1) :-
  261    emit_reified(string(S), [Term]),
  262    string_length(S, Len),
  263    NewCol is State0.column + Len,
  264    put_dict(column, State0, NewCol, State1).
  265
  266push_state_open_spaces(State0, Next, State1) :-
  267    _{leading_spaces: PrevSpaces} :< State0,
  268    ( Next = [white(N)|_]
  269    -> put_dict(leading_spaces, State0, [N|PrevSpaces], State1)
  270    ; put_dict(leading_spaces, State0, [0|PrevSpaces], State1) ).
  271
  272pop_state_open_spaces(State0, Top, State1) :-
  273    _{leading_spaces: [Top|Spaces]} :< State0,
  274    put_dict(leading_spaces, State0, Spaces, State1).
  275
  276%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  277% Create a List of Edits from the Original and Formatted Lines
  278%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  279create_edit_list(Orig, Formatted, Edits) :-
  280    create_edit_list(0, Orig, Formatted, Edits).
  281
  282create_edit_list(_, [], [], []) :- !.
  283create_edit_list(LineNum, [Line|Lines], [], [Edit]) :- !,
  284    length(Lines, NLines),
  285    EndLine is LineNum + NLines,
  286    last([Line|Lines], LastLine),
  287    string_length(LastLine, LastLineLen),
  288    Edit = _{range: _{start: _{line: LineNum, character: 0},
  289                      end: _{line: EndLine, character: LastLineLen}},
  290             newText: ""}.
  291create_edit_list(LineNum, [], [NewLine|NewLines], [Edit|Edits]) :- !,
  292    string_length(NewLine, LenLen),
  293    Edit = _{range: _{start: _{line: LineNum, character: 0},
  294                      end: _{line: LineNum, character: LenLen}},
  295             newText: NewLine},
  296    succ(LineNum, LineNum1),
  297    create_edit_list(LineNum1, [], NewLines, Edits).
  298create_edit_list(LineNum, [OrigLine|OrigRest], [FormattedLine|FormattedRest], Edits) :-
  299    (   OrigLine \= FormattedLine  % Only create an edit if the line has changed
  300    -> string_length(OrigLine, LineLen), %TODO: what should this be?
  301       Edit = _{range: _{start: _{line: LineNum, character: 0},
  302                         end: _{line: LineNum, character: LineLen}},
  303                newText: FormattedLine},
  304       Edits = [Edit|EditRest]
  305    ; EditRest = Edits
  306    ),
  307    succ(LineNum, LineNum1),
  308    create_edit_list(LineNum1, OrigRest, FormattedRest, EditRest).
  309
  310% lsp_formatter:file_formatted('/Users/james/Projects/prolog-lsp/prolog/format_test2.pl', Src), lsp_formatter_parser:emit_reified(user_output, Src).
  311
  312% 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)).