1:- module(lsp_formatter, [ file_format_edits/2,
2 file_formatted/2 ]).
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 ]). 18file_format_edits(Path, Edits) :-
19 read_file_to_string(Path, OrigText, []),
20 split_string(OrigText, "\n", "", OrigLines),
21 file_formatted(Path, Formatted),
22 with_output_to(string(FormattedText),
23 emit_reified(current_output, Formatted)),
24 split_string(FormattedText, "\n", "", FormattedLines),
25 create_edit_list(OrigLines, FormattedLines, Edits).
26
27file_formatted(Path, Formatted) :-
28 reified_format_for_file(Path, Reified),
29 apply_format_rules(Reified, Formatted).
30
34
35apply_format_rules(Content, Formatted) :-
36 phrase(formatter_rules, Content, Formatted).
37
38formatter_rules -->
39 collapse_whitespace,
40 commas_exactly_one_space,
41 correct_indentation(_{state: [toplevel], column: 0, leading_spaces: [],
42 parens: []}).
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 once((In = term_begin('->', compound, false)
102 ; In = term_begin('*->', compound, false)
103 ; In = term_begin(';', compound, false))),
104 indent_state_top(State0, defn_body_indent), !,
105 indent_state_pop(State0, State1),
106 paren_state_top(State1, Indent),
107 Out = [white(Indent)|OutRest],
108 update_state_column(State1, white(Indent), State4),
109 correct_indentation(State4, [In|InRest], OutRest).
110correct_indentation(State0, [newline|InRest], [newline|Out]) :- !,
111 ( indent_state_top(State0, defn_body_indent)
112 -> State1 = State0
113 ; indent_state_push(State0, defn_body_indent, State1) ),
114 update_state_column(State1, newline, State2),
115 correct_indentation(State2, InRest, Out).
116correct_indentation(State0, [In|InRest], Out) :-
117 indent_state_top(State0, defn_body_indent), !,
118 ( In = white(_)
119 -> correct_indentation(State0, InRest, Out)
120 ; insert_whitespace_to_indent(State0, [In|InRest], Out) ).
121correct_indentation(State0, [In|InRest], [In|OutRest]) :-
122 In = term_begin(';', compound, false), !,
123 update_alignment(State0, State1),
124 update_state_column(State1, In, State2),
126 copy_current_alignment(State2, CurrentAlign),
127 indent_state_push(State2, CurrentAlign, State3),
128 push_state_open_spaces(State3, InRest, State4),
129 correct_indentation(State4, InRest, OutRest)
129.
130correct_indentation(State0, [In|InRest], [In|OutRest]) :-
131 functor(In, Name, _Arity, _Type),
132 atom_concat(_, '_begin', Name), !,
133 134 update_alignment(State0, State1),
135 update_state_column(State1, In, State2),
136 indent_state_push(State2, begin(State2.column, State1.column), State3),
137 push_state_open_spaces(State3, InRest, State4),
138 ( Name == parens_begin
139 -> paren_state_push(State4, State1.column, State5)
140 ; State5 = State4 ),
141 correct_indentation(State5, InRest, OutRest).
142correct_indentation(State0, [In|InRest], [In|OutRest]) :-
143 indent_state_top(State0, defn_head(_, _)),
144 In = term_end(_, S), S \= toplevel, !,
145 indent_state_pop(State0, State1),
146 indent_state_push(State1, defn_head_neck, State2),
147 update_state_column(State2, In, State3),
148 pop_state_open_spaces(State3, _, State4),
149 correct_indentation(State4, InRest, OutRest).
150correct_indentation(State0, [In|InRest], Out) :-
151 ending_term(In), !,
152 indent_state_pop(State0, State1),
153 update_state_column(State1, In, State2),
154 pop_state_open_spaces(State2, Spaces, State3),
155 ( In \= term_end(false, _), In \= term_end(_, toplevel), Spaces > 0
156 -> Out = [white(Spaces), In|OutRest]
157 ; Out = [In|OutRest] ),
158 ( In == parens_end
159 -> paren_state_pop(State3, State4)
160 ; State3 = State4 ),
161 correct_indentation(State4, InRest, OutRest).
162correct_indentation(State0, [In, NextIn|InRest], Out) :-
163 In = white(_),
164 ending_term(NextIn), !,
165 correct_indentation(State0, [NextIn|InRest], Out).
166correct_indentation(State0, [In|InRest], [In|OutRest]) :-
167 memberchk(In, [white(_), newline]), !,
168 update_state_column(State0, In, State1),
169 correct_indentation(State1, InRest, OutRest).
170correct_indentation(State0, [In|InRest], [In|OutRest]) :- !,
171 ( In \= white(_)
172 -> update_alignment(State0, State1)
173 ; State1 = State0 ),
174 update_state_column(State1, In, State2),
175 correct_indentation(State2, InRest, OutRest).
176
177copy_current_alignment(State, Alignment), indent_state_top(State, defn_body) =>
178 Alignment = align(#toplevel_indent, 4).
179copy_current_alignment(State, Alignment), indent_state_top(State, align(_, _)) =>
180 indent_state_top(State, Alignment).
181copy_current_alignment(State, Alignment), indent_state_top(State, begin(Col, BeganAt)) =>
182 Alignment = begin(Col, BeganAt).
183copy_current_alignment(State, Alignment), indent_state_top(State, defn_body_indent) =>
184 Alignment = align(#toplevel_indent, 4).
185copy_current_alignment(State, Alignment), indent_state_top(State, defn_head(Column, _Aligned)) =>
186 Alignment = align(Column, Column).
187copy_current_alignment(State, Alignment), indent_state_top(State, defn_head_neck) =>
188 Alignment = align(#toplevel_indent, 4).
189copy_current_alignment(State, Alignment), indent_state_top(State, declaration) =>
190 Alignment = align(2, 2).
191copy_current_alignment(State, Alignment) =>
192 indent_state_top(State, Alignment).
193
194insert_whitespace_to_indent(State0, [In|InRest], Out) :-
195 indent_state_pop(State0, State1),
196 ( indent_state_top(State1, begin(_, BeganAt))
197 198 -> 199 indent_state_pop(State1, StateX),
200 whitespace_indentation_for_state(StateX, PrevIndent),
201 IncPrevIndent is PrevIndent + 4,
202 indent_state_push(StateX, align(IncPrevIndent, BeganAt), State2)
203 ; State2 = State1 ),
204 update_alignment(State2, State3),
205 ( ending_term(In)
206 -> indent_for_end_term(State3, In, State4, Indent)
207 ; whitespace_indentation_for_state(State3, Indent),
208 State4 = State3 ),
209 Out = [white(Indent)|OutRest],
210 update_state_column(State4, white(Indent), State5),
211 correct_indentation(State5, [In|InRest], OutRest).
212
213indent_for_end_term(State0, In, State, Indent) :-
214 215 In = term_end(true, _), !,
216 indent_state_pop(State0, State_),
217 pop_state_open_spaces(State0, _, State1),
218 push_state_open_spaces(State1, 0, State),
219 whitespace_indentation_for_state(State_, Indent).
220indent_for_end_term(State0, In, State, Indent) :-
221 222 In = dict_end, !,
223 indent_state_pop(State0, State_),
224 indent_state_pop(State_, State__),
225 pop_state_open_spaces(State0, _, State1),
226 push_state_open_spaces(State1, 0, State),
227 whitespace_indentation_for_state(State__, Indent).
228indent_for_end_term(State0, _In, State, Indent) :-
229 230 231 indent_state_top(State0, Top),
232 Top = align(_, Indent), !,
233 pop_state_open_spaces(State0, _, State1),
234 push_state_open_spaces(State1, 0, State).
235indent_for_end_term(State0, _In, State, Indent) :-
236 237 indent_state_pop(State0, State_),
238 pop_state_open_spaces(State0, _, State1),
239 push_state_open_spaces(State1, 0, State),
240 whitespace_indentation_for_state(State_, Indent).
241
242ending_term(Term) :-
243 functor(Term, Name, _, _),
244 atom_concat(_, '_end', Name).
245
246outdent_align(State, Outdented) :-
247 whitespace_indentation_for_state(State, Indent),
248 Outdented is Indent - 2.
249
250update_alignment(State0, State2) :-
251 indent_state_top(State0, begin(Col, BeganAt)), !,
252 indent_state_pop(State0, State1),
253 AlignCol is max(Col, State1.column),
254 indent_state_push(State1, align(AlignCol, BeganAt), State2).
255update_alignment(State0, State2) :-
256 indent_state_top(State0, defn_head(Col, false)), !,
257 indent_state_pop(State0, State1),
258 AlignCol is max(Col, State1.column),
259 indent_state_push(State1, defn_head(AlignCol, true), State2).
260update_alignment(State, State).
261
262whitespace_indentation_for_state(State, Indent) :-
263 indent_state_top(State, align(Indent, _)), !.
264whitespace_indentation_for_state(State, Indent) :-
265 indent_state_top(State, defn_head(Indent, _)), !.
266whitespace_indentation_for_state(State, Indent) :-
267 get_dict(state, State, Stack),
268 aggregate_all(count,
269 ( member(X, Stack),
270 memberchk(X, [parens_begin, braces_begin, term_begin(_, _, _)]) ),
271 ParensCount),
272 ( indent_state_contains(State, defn_body)
273 -> MoreIndent = #toplevel_indent
274 ; MoreIndent = 0 ),
275 Indent is ParensCount * 2 + MoreIndent.
276
277indent_state_top(State, Top) :-
278 _{state: [Top|_]} :< State.
279
280indent_state_contains(State, Needle) :-
281 _{state: Stack} :< State,
282 memberchk(Needle, Stack).
283
284paren_state_push(State0, NewTop, State1) :-
285 _{parens: OldParens} :< State0,
286 put_dict(parens, State0, [NewTop|OldParens], State1).
287
288paren_state_pop(State0, State1) :-
289 _{parens: [_|Parens]} :< State0,
290 put_dict(parens, State0, Parens, State1).
291
292paren_state_top(State0, Top) :-
293 _{parens: [Top|_]} :< State0.
294
295indent_state_push(State0, NewTop, State1) :-
296 _{state: Stack} :< State0,
297 put_dict(state, State0, [NewTop|Stack], State1).
298
299indent_state_pop(State0, State1) :-
300 _{state: [_|Rest]} :< State0,
301 put_dict(state, State0, Rest, State1).
302
303update_state_column(State0, newline, State1) :- !,
304 put_dict(column, State0, 0, State1).
305update_state_column(State0, Term, State1) :-
306 emit_reified(string(S), [Term]),
307 string_length(S, Len),
308 NewCol is State0.column + Len,
309 put_dict(column, State0, NewCol, State1).
310
311push_state_open_spaces(State0, Next, State1) :-
312 _{leading_spaces: PrevSpaces} :< State0,
313 ( Next = [white(N)|_]
314 -> put_dict(leading_spaces, State0, [N|PrevSpaces], State1)
315 ; put_dict(leading_spaces, State0, [0|PrevSpaces], State1) ).
316
317pop_state_open_spaces(State0, Top, State1) :-
318 _{leading_spaces: [Top|Spaces]} :< State0,
319 put_dict(leading_spaces, State0, Spaces, State1).
320
324create_edit_list(Orig, Formatted, Edits) :-
325 create_edit_list(0, Orig, Formatted, Edits).
326
327create_edit_list(_, [], [], []) :- !.
328create_edit_list(LineNum, [Line|Lines], [], [Edit]) :- !,
329 length(Lines, NLines),
330 EndLine is LineNum + NLines,
331 last([Line|Lines], LastLine),
332 string_length(LastLine, LastLineLen),
333 Edit = _{range: _{start: _{line: LineNum, character: 0},
334 end: _{line: EndLine, character: LastLineLen}},
335 newText: ""}.
336create_edit_list(LineNum, [], [NewLine|NewLines], [Edit|Edits]) :- !,
337 string_length(NewLine, LenLen),
338 Edit = _{range: _{start: _{line: LineNum, character: 0},
339 end: _{line: LineNum, character: LenLen}},
340 newText: NewLine},
341 succ(LineNum, LineNum1),
342 create_edit_list(LineNum1, [], NewLines, Edits).
343create_edit_list(LineNum, [OrigLine|OrigRest], [FormattedLine|FormattedRest], Edits) :-
344 ( OrigLine \= FormattedLine 345 -> string_length(OrigLine, LineLen), 346 Edit = _{range: _{start: _{line: LineNum, character: 0},
347 end: _{line: LineNum, character: LineLen}},
348 newText: FormattedLine},
349 Edits = [Edit|EditRest]
350 ; EditRest = Edits
351 ),
352 succ(LineNum, LineNum1),
353 create_edit_list(LineNum1, OrigRest, FormattedRest, EditRest).
354
356
LSP Formatter
Module for formatting Prolog source code
*/