Introduce dedicated node to store markup
[hiphop-php.git] / hphp / hack / src / hackfmt / hack_format.ml
blob349be24d28ebd63b31dc68142ffe6ef4a9bcc252
1 (**
2 * Copyright (c) 2016, Facebook, Inc.
3 * All rights reserved.
5 * This source code is licensed under the BSD-style license found in the
6 * LICENSE file in the "hack" directory of this source tree. An additional grant
7 * of patent rights can be found in the PATENTS file in the same directory.
9 *)
11 module SyntaxKind = Full_fidelity_syntax_kind
12 module Syntax = Full_fidelity_editable_syntax
13 module TriviaKind = Full_fidelity_trivia_kind
14 module Trivia = Full_fidelity_editable_trivia
15 module Token = Full_fidelity_editable_token
16 module Rewriter = Full_fidelity_rewriter.WithSyntax(Syntax)
18 open Core
19 open Syntax
20 open Fmt_node
22 (* TODO: move this to a config file *)
23 let __INDENT_WIDTH = 2
25 let rec transform node =
26 let t = transform in
28 match syntax node with
29 | Missing ->
30 Nothing
31 | Token x ->
32 let open EditableToken in
33 Fmt [
34 transform_leading_trivia (leading x);
35 begin
36 let open TokenKind in
37 match kind x with
38 | SingleQuotedStringLiteral
39 | DoubleQuotedStringLiteral
40 | DoubleQuotedStringLiteralHead
41 | StringLiteralBody
42 | DoubleQuotedStringLiteralTail
43 | HeredocStringLiteral
44 | HeredocStringLiteralHead
45 | HeredocStringLiteralTail
46 | NowdocStringLiteral ->
47 let split_text = (Str.split_delim (Str.regexp "\n") (text x)) in
48 begin match split_text with
49 | [s] -> Text (text x, width x)
50 | _ -> MultilineString (split_text, width x)
51 end
52 | _ -> Text (text x, width x)
53 end;
54 transform_trailing_trivia (trailing x);
56 | SyntaxList _ ->
57 failwith (Printf.sprintf
58 "Error: SyntaxList should never be handled directly;
59 offending text is '%s'." (text node));
60 | EndOfFile x ->
61 let token = get_end_of_file_children x in
62 t token
63 | Script x ->
64 begin match x.script_declarations.syntax with
65 | SyntaxList (header::declarations) when is_markup_section header ->
66 Fmt [
67 t header;
68 Newline;
69 handle_list declarations;
71 | _ ->
72 Fmt [
73 handle_possible_list (get_script_children x);
75 end
76 | LiteralExpression x ->
77 (* Double quoted string literals can create a list *)
78 let children = get_literal_expression_children x in
79 let open EditableToken in
80 let wrap_with_literal_type token transformed =
81 let open TokenKind in
82 match kind token with
83 | HeredocStringLiteral
84 | HeredocStringLiteralHead
85 | HeredocStringLiteralTail
86 | NowdocStringLiteral -> DocLiteral transformed
87 | DecimalLiteral
88 | OctalLiteral
89 | HexadecimalLiteral
90 | BinaryLiteral
91 | FloatingLiteral -> NumericLiteral transformed
92 | _ -> transformed
94 begin match syntax children with
95 | Token tok -> wrap_with_literal_type tok (t children)
96 | SyntaxList l ->
97 let last = trailing_token children in
98 begin match last with
99 | Some tok -> wrap_with_literal_type tok (Fmt (List.map l transform))
100 | _ -> failwith "Expected Token"
102 | _ -> failwith "Expected Token or SyntaxList"
104 | MarkupSection x ->
105 let (prefix, text, suffix, _) = get_markup_section_children x in
106 if is_missing prefix
107 then
108 (* leading markup section
109 for hh files - strip leading whitespaces\newlines - they are not
110 emitted and having them in Hack file is illegal anyways *)
111 let is_hh_script = match suffix.syntax with
112 | MarkupSuffix { markup_suffix_name = {
113 syntax = Token t; _
114 }; _ } ->
115 (EditableToken.text t) = "hh"
116 | _ -> false
118 let rec all_whitespaces s i =
119 i >= String.length s
120 || (match String.get s i with
121 | ' ' | '\t' | '\r' | '\n' -> all_whitespaces s (i + 1)
122 | _ -> false)
124 let text_contains_only_whitespaces = match text.syntax with
125 | Token t -> all_whitespaces (EditableToken.text t) 0
126 | _ -> false
128 if is_hh_script && text_contains_only_whitespaces
129 then t suffix
130 else transform_simple node
131 else transform_simple node
132 | MarkupSuffix _
133 | SimpleTypeSpecifier _
134 | VariableExpression _
135 | QualifiedNameExpression _
136 | PipeVariableExpression _
137 | PropertyDeclarator _
138 | ConstantDeclarator _
139 | DecoratedExpression _
140 | StaticDeclarator _
141 | ScopeResolutionExpression _
142 | EmbeddedMemberSelectionExpression _
143 | EmbeddedSubscriptExpression _
144 | PostfixUnaryExpression _
145 | XHPRequired _
146 | XHPSimpleClassAttribute _
147 | XHPClose _
148 | TypeConstant _
149 | GenericTypeSpecifier _
150 | NullableTypeSpecifier _
151 | SoftTypeSpecifier _
152 | ListItem _ ->
153 transform_simple node
154 | ExpressionStatement _ ->
155 transform_simple_statement node
156 | EnumDeclaration x ->
157 let (attr, kw, name, colon_kw, base, enum_type, left_b, enumerators,
158 right_b) = get_enum_declaration_children x in
159 Fmt [
160 t attr;
161 when_present attr newline;
162 t kw;
163 Space;
164 t name;
165 t colon_kw;
166 Space;
167 SplitWith Cost.Base;
168 Nest [
169 Space;
170 t base;
171 Space;
172 t enum_type;
173 Space;
175 braced_block_nest left_b right_b [
176 handle_possible_list enumerators
178 Newline;
180 | Enumerator x ->
181 let (name, eq_kw, value, semi) = get_enumerator_children x in
182 Fmt [
183 t name;
184 Space;
185 t eq_kw;
186 Space;
187 SplitWith Cost.Base;
188 Nest [t value];
189 t semi;
190 Newline;
192 | AliasDeclaration x ->
193 (* TODO: revisit this for long names *)
194 let (attr, kw, name, generic, type_constraint, eq_kw, alias_type, semi) =
195 get_alias_declaration_children x in
196 Fmt [
197 t attr;
198 when_present attr newline;
199 t kw;
200 Space;
201 t name;
202 t generic;
203 Space;
204 t type_constraint;
205 Space;
206 t eq_kw;
207 Space;
208 SplitWith Cost.Base;
209 Nest [t alias_type];
210 t semi;
211 Newline;
213 | PropertyDeclaration x ->
214 let (modifiers, prop_type, declarators, semi) =
215 get_property_declaration_children x in
216 Fmt [
217 handle_possible_list ~after_each:(fun _ -> Space) modifiers;
218 t prop_type;
219 handle_declarator_list declarators;
220 t semi;
221 Newline;
223 | NamespaceDeclaration x ->
224 let (kw, name, body) = get_namespace_declaration_children x in
225 Fmt [
226 t kw;
227 Space;
228 t name;
229 t body;
230 Newline;
232 | NamespaceBody x ->
233 let (left_b, decls, right_b) = get_namespace_body_children x in
234 Fmt [
235 Space;
236 braced_block_nest left_b right_b [handle_possible_list decls];
238 | NamespaceEmptyBody x ->
239 let semi = get_namespace_empty_body_children x in
240 Fmt [
241 t semi;
243 | NamespaceUseDeclaration x ->
244 let (kw, use_kind, clauses, semi) =
245 get_namespace_use_declaration_children x in
246 Fmt [
247 t kw;
248 Space;
249 t use_kind;
250 when_present use_kind space;
251 WithRule (Rule.Parental, Nest [
252 handle_possible_list clauses ~after_each:after_each_argument;
254 t semi;
255 Newline;
257 | NamespaceGroupUseDeclaration x ->
258 let (kw, use_kind, prefix, left_b, clauses, right_b, semi) =
259 get_namespace_group_use_declaration_children x in
260 Fmt [
261 t kw;
262 Space;
263 t use_kind;
264 when_present use_kind space;
265 t prefix;
266 transform_argish left_b clauses right_b;
267 t semi;
268 Newline;
270 | NamespaceUseClause x ->
271 let (use_kind, name, as_kw, alias) = get_namespace_use_clause_children x in
272 Fmt [
273 t use_kind;
274 t name;
275 when_present as_kw space;
276 t as_kw;
277 when_present alias space;
278 t alias;
280 | FunctionDeclaration x ->
281 let (attr, header, body) = get_function_declaration_children x in
282 Fmt [
283 t attr;
284 when_present attr newline;
285 t header;
286 handle_possible_compound_statement body;
287 Newline;
289 | FunctionDeclarationHeader x ->
290 let (
291 async,
292 coroutine,
294 amp,
295 name,
296 type_params,
297 leftp,
298 params,
299 rightp,
300 colon,
301 ret_type,
302 where
303 ) = get_function_declaration_header_children x
305 Fmt [
306 Span (
307 transform_fn_decl_name async coroutine kw amp name type_params leftp);
308 transform_fn_decl_args params rightp colon ret_type where;
310 | WhereClause x ->
311 let (where, constraints) = get_where_clause_children x in
312 Fmt [
313 t where;
314 Space;
315 handle_possible_list constraints ~after_each:(fun _ -> Space);
317 | WhereConstraint x ->
318 let (left, op, right) = get_where_constraint_children x in
319 Fmt [
320 t left;
321 Space;
322 t op;
323 Space;
324 t right;
326 | MethodishDeclaration x ->
327 let (attr, modifiers, func_decl, body, semi) =
328 get_methodish_declaration_children x
330 Fmt [
331 t attr;
332 when_present attr newline;
334 let mods =
335 handle_possible_list ~after_each:(fun _ -> Space) modifiers
337 let fn_name, args_and_where = match syntax func_decl with
338 | FunctionDeclarationHeader x ->
339 let (
340 async,
341 coroutine,
343 amp,
344 name,
345 type_params,
346 leftp,
347 params,
348 rightp,
349 colon,
350 ret_type,
351 where
352 ) = get_function_declaration_header_children x
354 Fmt (
355 transform_fn_decl_name
356 async
357 coroutine
360 name
361 type_params
362 leftp
364 transform_fn_decl_args params rightp colon ret_type where
365 | _ -> failwith "Expected FunctionDeclarationHeader"
367 Fmt [
368 Span [mods; fn_name];
369 args_and_where;
372 when_present body (fun () -> handle_possible_compound_statement body);
373 t semi;
374 Newline;
376 | ClassishDeclaration x ->
377 let (attr, modifiers, kw, name, type_params, extends_kw, extends,
378 impl_kw, impls, body) = get_classish_declaration_children x
380 let after_each_ancestor is_last =
381 if is_last then Nothing else space_split () in
382 Fmt [
383 t attr;
384 when_present attr newline;
385 Span [
386 handle_possible_list ~after_each:(fun _ -> Space) modifiers;
387 t kw;
388 Space;
389 Split;
390 Nest [
391 t name;
392 t type_params;
396 when_present extends_kw (fun () -> Fmt [
397 Space;
398 Split;
399 WithRule (Rule.Parental, Nest [ Span [
400 t extends_kw;
401 Space;
402 Split;
403 WithRule (Rule.Parental, Nest [
404 handle_possible_list ~after_each:after_each_ancestor extends
409 when_present impl_kw (fun () -> Fmt [
410 Space;
411 Split;
412 WithRule (Rule.Parental, Nest [ Span [
413 t impl_kw;
414 Space;
415 Split;
416 WithRule (Rule.Parental, Nest [
417 handle_possible_list ~after_each:after_each_ancestor impls
421 t body;
423 | ClassishBody x ->
424 let (left_b, body, right_b) = get_classish_body_children x in
425 Fmt [
426 Space;
427 braced_block_nest left_b right_b [
428 handle_possible_list body
430 Newline;
432 | TraitUseConflictResolutionItem x ->
433 let (aliasing_name, kw, aliased_name) =
434 get_trait_use_conflict_resolution_item_children x
436 Fmt [
437 t aliasing_name;
438 Space;
439 t kw;
440 Space;
441 t aliased_name;
442 Newline;
444 | TraitUseConflictResolution x ->
445 let (kw, elements, lb, clauses, rb) =
446 get_trait_use_conflict_resolution_children x
448 Fmt [
449 t kw;
450 WithRule (Rule.Parental, Nest [
451 handle_possible_list ~before_each:space_split elements;
453 t lb;
454 Newline;
455 WithRule (Rule.Parental, Nest [
456 handle_possible_list ~before_each:space_split clauses;
458 Newline;
459 t rb;
461 | TraitUse x ->
462 let (kw, elements, semi) = get_trait_use_children x in
463 Fmt [
464 t kw;
465 WithRule (Rule.Parental, Nest [
466 handle_possible_list ~before_each:space_split elements;
468 t semi;
469 Newline;
471 | RequireClause x ->
472 let (kw, kind, name, semi) = get_require_clause_children x in
473 Fmt [
474 t kw;
475 Space;
476 t kind;
477 Space;
478 Split;
479 t name;
480 t semi;
481 Newline;
483 | ConstDeclaration x ->
484 let (abstr, kw, const_type, declarators, semi) =
485 get_const_declaration_children x in
486 Fmt [
487 t abstr;
488 when_present abstr space;
489 t kw;
490 when_present const_type space;
491 t const_type;
492 WithRule (Rule.Parental, Nest [
493 handle_possible_list ~before_each:space_split declarators;
495 t semi;
496 Newline;
498 | TypeConstDeclaration x ->
499 let (abs, kw, type_kw, name, type_constraint, eq, type_spec, semi) =
500 get_type_const_declaration_children x in
501 Fmt [
502 t abs;
503 Space;
504 t kw;
505 Space;
506 t type_kw;
507 Space;
508 t name;
509 when_present type_constraint space;
510 t type_constraint;
511 when_present eq space;
512 t eq;
513 when_present type_spec (fun _ -> Fmt [
514 Space;
515 SplitWith Cost.Base;
516 Nest [t type_spec];
518 t semi;
519 Newline;
521 | ParameterDeclaration x ->
522 let (attr, visibility, param_type, name, default) =
523 get_parameter_declaration_children x
525 Fmt [
526 t attr;
527 t visibility;
528 when_present visibility space;
529 t param_type;
530 if is_missing visibility && is_missing param_type
531 then t name
532 else Fmt [
533 Space;
534 SplitWith Cost.Base;
535 Nest [t name];
537 t default;
539 | VariadicParameter x ->
540 let ellipsis = get_variadic_parameter_children x in
541 t ellipsis;
542 | AttributeSpecification x ->
543 let (left_da, attrs, right_da) = get_attribute_specification_children x in
544 transform_argish ~allow_trailing:false left_da attrs right_da
545 | Attribute x ->
546 let (name, left_p, values, right_p) = get_attribute_children x in
547 Fmt [
548 t name;
549 transform_argish left_p values right_p;
551 | InclusionExpression x ->
552 let (kw, expr) = get_inclusion_expression_children x in
553 Fmt [
554 t kw;
555 Space;
556 SplitWith Cost.Base;
557 t expr;
559 | InclusionDirective x ->
560 let (expr, semi) = get_inclusion_directive_children x in
561 Fmt [
562 t expr;
563 t semi;
564 Newline;
566 | CompoundStatement x ->
567 handle_possible_compound_statement node
568 | UnsetStatement x ->
569 let (kw, left_p, args, right_p, semi) = get_unset_statement_children x in
570 Fmt [
571 t kw;
572 transform_argish ~allow_trailing:false left_p args right_p;
573 t semi;
574 Newline;
576 | WhileStatement x ->
577 Fmt [
578 t x.while_keyword;
579 Space;
580 t x.while_left_paren;
581 Split;
582 WithRule (Rule.Parental, Fmt [
583 Nest [t x.while_condition];
584 Split;
585 t x.while_right_paren;
587 handle_possible_compound_statement x.while_body;
588 Newline;
590 | IfStatement x ->
591 let (kw, left_p, condition, right_p, if_body, elseif_clauses, else_clause) =
592 get_if_statement_children x in
593 Fmt [
594 t kw;
595 Space;
596 transform_condition left_p condition right_p;
597 handle_possible_compound_statement if_body;
598 handle_possible_list elseif_clauses;
599 t else_clause;
600 Newline;
602 | ElseifClause x ->
603 let (kw, left_p, condition, right_p, body) = get_elseif_clause_children x in
604 Fmt [
605 t kw;
606 Space;
607 transform_condition left_p condition right_p;
608 handle_possible_compound_statement x.elseif_statement;
610 | ElseClause x ->
611 Fmt [
612 t x.else_keyword;
613 match syntax x.else_statement with
614 | IfStatement _ -> Fmt [
615 Space;
616 t x.else_statement;
617 Space;
619 | _ -> handle_possible_compound_statement x.else_statement
621 | TryStatement x ->
622 (* TODO: revisit *)
623 let (kw, body, catch_clauses, finally_clause) =
624 get_try_statement_children x in
625 Fmt [
626 t kw;
627 handle_possible_compound_statement body;
628 handle_possible_list catch_clauses;
629 t finally_clause;
630 Newline;
632 | CatchClause x ->
633 let (kw, left_p, ex_type, var, right_p, body) =
634 get_catch_clause_children x in
635 Fmt [
636 t kw;
637 Space;
638 delimited_nest left_p right_p [
639 t ex_type;
640 Space;
641 SplitWith Cost.Base;
642 Nest [
643 t var;
646 handle_possible_compound_statement body;
648 | FinallyClause x ->
649 let (kw, body) = get_finally_clause_children x in
650 Fmt [
651 t kw;
652 Space;
653 handle_possible_compound_statement body;
655 | DoStatement x ->
656 let (do_kw, body, while_kw, left_p, cond, right_p, semi) =
657 get_do_statement_children x in
658 Fmt [
659 t do_kw;
660 Space;
661 handle_possible_compound_statement body;
662 t while_kw;
663 Space;
664 transform_condition left_p cond right_p;
665 t semi;
666 Newline;
668 | ForStatement x ->
669 let (kw, left_p, init, semi1, control, semi2, after_iter, right_p, body) =
670 get_for_statement_children x in
671 Fmt [
672 t kw;
673 Space;
674 t left_p;
675 WithRule (Rule.Parental, Fmt [
676 Split;
677 Nest [
678 handle_possible_list init;
679 t semi1;
680 Space;
681 Split;
682 handle_possible_list control;
683 t semi2;
684 Space;
685 Split;
686 handle_possible_list after_iter;
688 Split;
689 t right_p;
691 handle_possible_compound_statement body;
692 Newline;
694 | ForeachStatement x ->
695 let (kw, left_p, collection, await_kw, as_kw, key, arrow, value, right_p,
696 body) = get_foreach_statement_children x in
697 Fmt [
698 t kw;
699 Space;
700 delimited_nest left_p right_p [
701 t collection;
702 Space;
703 t await_kw;
704 Space;
705 t as_kw;
706 Space;
707 SplitWith Cost.Base;
708 Nest [
709 Span [
710 t key;
711 Space;
712 t arrow;
713 Space;
714 SplitWith Cost.Base;
715 Nest [
716 t value;
721 handle_possible_compound_statement body;
722 Newline;
724 | SwitchStatement x ->
725 let (kw, left_p, expr, right_p, left_b, sections, right_b) =
726 get_switch_statement_children x in
727 Fmt [
728 t kw;
729 Space;
730 t left_p;
731 Split;
732 WithRule (Rule.Parental, Fmt [
733 Nest [t expr];
734 t right_p;
736 handle_switch_body left_b sections right_b;
737 Newline;
739 | SwitchSection x ->
740 failwith "SwitchSection should be handled by handle_switch_body"
741 | CaseLabel x ->
742 failwith "CaseLabel should be handled by handle_switch_body"
743 | DefaultLabel x ->
744 failwith "DefaultLabel should be handled by handle_switch_body"
745 | SwitchFallthrough x ->
746 failwith "SwitchFallthrough should be handled by handle_switch_body"
747 | ReturnStatement x ->
748 let (kw, expr, semi) = get_return_statement_children x in
749 transform_keyword_expression_statement kw expr semi
750 | GotoLabel { goto_label_name; goto_label_colon } ->
751 Fmt [
752 t goto_label_name;
753 t goto_label_colon;
754 Newline;
756 | GotoStatement {
757 goto_statement_keyword;
758 goto_statement_label_name;
759 goto_statement_semicolon; } ->
760 Fmt [
761 t goto_statement_keyword;
762 Space;
763 t goto_statement_label_name;
764 t goto_statement_semicolon;
765 Newline;
767 | ThrowStatement x ->
768 let (kw, expr, semi) = get_throw_statement_children x in
769 transform_keyword_expression_statement kw expr semi
770 | BreakStatement x ->
771 let (kw, expr, semi) = get_break_statement_children x in
772 transform_keyword_expression_statement kw expr semi
773 | ContinueStatement x ->
774 let (kw, level, semi) = get_continue_statement_children x in
775 transform_keyword_expression_statement kw level semi
776 | FunctionStaticStatement x ->
777 let (static_kw, declarators, semi) =
778 get_function_static_statement_children x in
779 transform_keyword_expr_list_statement static_kw declarators semi
780 | EchoStatement x ->
781 let (kw, expr_list, semi) = get_echo_statement_children x in
782 transform_keyword_expr_list_statement kw expr_list semi
783 | GlobalStatement x ->
784 let (kw, var_list, semi) = get_global_statement_children x in
785 transform_keyword_expr_list_statement kw var_list semi
786 | SimpleInitializer x ->
787 let (eq_kw, value) = get_simple_initializer_children x in
788 Fmt [
789 Space;
790 t eq_kw;
791 Space;
792 SplitWith Cost.Base;
793 Nest [t value];
795 | AnonymousFunction x ->
796 let (
797 async_kw,
798 coroutine_kw,
799 fun_kw,
801 params,
803 colon,
804 ret_type,
805 use,
806 body
807 ) = get_anonymous_function_children x in
808 Fmt [
809 t async_kw;
810 when_present async_kw space;
811 t coroutine_kw;
812 when_present coroutine_kw space;
813 t fun_kw;
814 transform_argish_with_return_type lp params rp colon ret_type;
815 t use;
816 handle_possible_compound_statement ~space:false body;
818 | AnonymousFunctionUseClause x ->
819 (* TODO: Revisit *)
820 let (kw, left_p, vars, right_p) =
821 get_anonymous_function_use_clause_children x in
822 Fmt [
823 Space;
824 t kw;
825 Space;
826 transform_argish left_p vars right_p;
828 | LambdaExpression x ->
829 let (async, coroutine, signature, arrow, body) =
830 get_lambda_expression_children x in
831 Fmt [
832 t async;
833 when_present async space;
834 t coroutine;
835 when_present coroutine space;
836 t signature;
837 Space;
838 t arrow;
839 handle_lambda_body body;
841 | LambdaSignature x ->
842 let (lp, params, rp, colon, ret_type) = get_lambda_signature_children x in
843 transform_argish_with_return_type lp params rp colon ret_type
844 | CastExpression x ->
845 Span (List.map (children node) t)
846 | MemberSelectionExpression x ->
847 handle_possible_chaining
848 (get_member_selection_expression_children x)
849 None
850 | SafeMemberSelectionExpression x ->
851 handle_possible_chaining
852 (get_safe_member_selection_expression_children x)
853 None
854 | YieldExpression x ->
855 let (kw, operand) = get_yield_expression_children x in
856 Fmt [
857 t kw;
858 Space;
859 SplitWith Cost.Base;
860 Nest [t operand];
862 | PrintExpression x ->
863 let (kw, expr) = get_print_expression_children x in
864 Fmt [
865 t kw;
866 Space;
867 SplitWith Cost.Base;
868 Nest [t expr];
870 | PrefixUnaryExpression x ->
871 let (operator, operand) = get_prefix_unary_expression_children x in
872 Fmt [
873 t operator;
874 (match syntax operator with
875 | Token x ->
876 let open EditableToken in
877 if kind x = TokenKind.Await || kind x = TokenKind.Clone then Space
878 else Nothing
879 | _ -> Nothing
881 t operand;
883 | BinaryExpression x ->
884 transform_binary_expression ~is_nested:false x
885 | InstanceofExpression x ->
886 let (left, kw, right) = get_instanceof_expression_children x in
887 Fmt [
888 t left;
889 Space;
890 t kw;
891 Space;
892 SplitWith Cost.Base;
893 Nest [t right];
895 | ConditionalExpression x ->
896 let (test_expr, q_kw, true_expr, c_kw, false_expr) =
897 get_conditional_expression_children x in
898 WithLazyRule (Rule.Parental,
899 t test_expr,
900 Nest [
901 Space;
902 Split;
903 t q_kw;
904 when_present true_expr (fun () -> Fmt [
905 Space;
906 if __INDENT_WIDTH = 2
907 then Nest [t true_expr]
908 else t true_expr;
909 Space;
910 Split;
912 t c_kw;
913 Space;
914 if not (is_missing true_expr) && __INDENT_WIDTH = 2
915 then Nest [t false_expr]
916 else t false_expr;
918 | FunctionCallExpression x ->
919 handle_function_call_expression x
920 | EvalExpression x ->
921 let (kw, left_p, arg, right_p) = get_eval_expression_children x in
922 Fmt [
923 t kw;
924 transform_braced_item left_p arg right_p;
926 | EmptyExpression x ->
927 let (kw, left_p, arg, right_p) = get_empty_expression_children x in
928 Fmt [
929 t kw;
930 transform_braced_item left_p arg right_p;
932 | IssetExpression x ->
933 let (kw, left_p, args, right_p) = get_isset_expression_children x in
934 Fmt [
935 t kw;
936 transform_argish ~allow_trailing:false left_p args right_p;
938 | DefineExpression x ->
939 let (kw, left_p, args, right_p) = get_define_expression_children x in
940 Fmt [
941 t kw;
942 transform_argish left_p args right_p;
944 | ParenthesizedExpression x ->
945 let (left_p, expr, right_p) = get_parenthesized_expression_children x in
946 Fmt [
947 t left_p;
948 Split;
949 WithRule (Rule.Parental, Fmt [
950 Nest [ t expr; ];
951 Split;
952 t right_p
955 | BracedExpression x ->
956 (* TODO: revisit this *)
957 let (left_b, expr, right_b) = get_braced_expression_children x in
958 Fmt [
959 t left_b;
960 Split;
961 let rule =
962 if List.is_empty (trailing_trivia left_b)
963 && List.is_empty (trailing_trivia expr)
964 then Rule.Simple Cost.Base
965 else Rule.Parental
967 WithRule (rule, Fmt [
968 Nest [t expr];
969 Split;
970 t right_b
973 | EmbeddedBracedExpression x ->
974 (* TODO: Consider finding a way to avoid treating these expressions as
975 opportunities for line breaks in long strings:
977 $sql = "DELETE FROM `foo` WHERE `left` BETWEEN {$res->left} AND {$res
978 ->right} ORDER BY `level` DESC";
980 let (left_b, expr, right_b) = get_embedded_braced_expression_children x in
981 Fmt [
982 t left_b;
983 Nest [t expr];
984 t right_b;
986 | ListExpression x ->
987 let (kw, lp, members, rp) = get_list_expression_children x in
988 Fmt [
989 t kw;
990 transform_argish lp members rp;
992 | CollectionLiteralExpression x ->
993 let (name, left_b, initializers, right_b) =
994 get_collection_literal_expression_children x
996 Fmt [
997 t name;
998 Space;
999 transform_argish ~spaces:true left_b initializers right_b;
1001 | ObjectCreationExpression x ->
1002 let (kw, obj_type, left_p, arg_list, right_p) =
1003 get_object_creation_expression_children x
1005 Fmt [
1006 t kw;
1007 Space;
1008 t obj_type;
1009 transform_argish left_p arg_list right_p;
1011 | ArrayCreationExpression x ->
1012 let (left_b, members, right_b) = get_array_creation_expression_children x in
1013 transform_argish left_b members right_b
1014 | ArrayIntrinsicExpression x ->
1015 let (kw, left_p, members, right_p) =
1016 get_array_intrinsic_expression_children x
1018 Fmt [
1019 t kw;
1020 transform_argish left_p members right_p;
1022 | DarrayIntrinsicExpression x ->
1023 let (kw, left_p, members, right_p) =
1024 get_darray_intrinsic_expression_children x in
1025 Fmt [
1026 t kw;
1027 transform_argish left_p members right_p;
1029 | DictionaryIntrinsicExpression x ->
1030 let (kw, left_p, members, right_p) =
1031 get_dictionary_intrinsic_expression_children x
1033 Fmt [
1034 t kw;
1035 transform_argish left_p members right_p;
1037 | KeysetIntrinsicExpression x ->
1038 let (kw, left_p, members, right_p) =
1039 get_keyset_intrinsic_expression_children x
1041 Fmt [
1042 t kw;
1043 transform_argish left_p members right_p;
1045 | VarrayIntrinsicExpression x ->
1046 let (kw, left_p, members, right_p) =
1047 get_varray_intrinsic_expression_children x in
1048 Fmt [
1049 t kw;
1050 transform_argish left_p members right_p;
1052 | VectorIntrinsicExpression x ->
1053 let (kw, left_p, members, right_p) =
1054 get_vector_intrinsic_expression_children x
1056 Fmt [
1057 t kw;
1058 transform_argish left_p members right_p;
1060 | ElementInitializer x ->
1061 let (key, arrow, value) = get_element_initializer_children x in
1062 transform_mapish_entry key arrow value
1063 | SubscriptExpression x ->
1064 let (receiver, lb, expr, rb) = get_subscript_expression_children x in
1065 Fmt [
1066 t receiver;
1067 transform_braced_item lb expr rb;
1069 | AwaitableCreationExpression x ->
1070 let (async_kw, coroutine_kw, body) =
1071 get_awaitable_creation_expression_children x in
1072 Fmt [
1073 t async_kw;
1074 when_present async_kw space;
1075 t coroutine_kw;
1076 when_present coroutine_kw space;
1077 (* TODO: rethink possible one line bodies *)
1078 (* TODO: correctly handle spacing after the closing brace *)
1079 handle_possible_compound_statement ~space:false body;
1081 | XHPChildrenDeclaration x ->
1082 let (kw, expr, semi) = get_xhp_children_declaration_children x in
1083 Fmt [
1084 t kw;
1085 Space;
1086 t expr;
1087 t semi;
1088 Newline;
1090 | XHPChildrenParenthesizedList x ->
1091 let (left_p, expressions, right_p) =
1092 get_xhp_children_parenthesized_list_children x in
1093 Fmt [
1094 transform_argish ~allow_trailing:false left_p expressions right_p;
1096 | XHPCategoryDeclaration x ->
1097 let (kw, categories, semi) = get_xhp_category_declaration_children x in
1098 Fmt [
1099 t kw;
1100 (* TODO: Eliminate code duplication *)
1101 WithRule (Rule.Parental, Nest [
1102 handle_possible_list ~before_each:space_split categories;
1104 t semi;
1105 Newline;
1107 | XHPEnumType x ->
1108 let (kw, left_b, values, right_b) = get_xhp_enum_type_children x in
1109 Fmt [
1110 t kw;
1111 Space;
1112 transform_argish left_b values right_b;
1114 | XHPClassAttributeDeclaration x ->
1115 let (kw, xhp_attributes, semi) =
1116 get_xhp_class_attribute_declaration_children x in
1117 Fmt [
1118 t kw;
1119 WithRule (Rule.Parental, Nest [
1120 handle_possible_list ~before_each:space_split xhp_attributes;
1122 t semi;
1123 Newline;
1125 | XHPClassAttribute x ->
1126 (* TODO: figure out nesting here *)
1127 let (attr_type, name, init, req) = get_xhp_class_attribute_children x in
1128 Fmt [
1129 t attr_type;
1130 Space;
1131 t name;
1132 when_present init space;
1133 t init;
1134 when_present req space;
1135 t req;
1137 | XHPAttribute x ->
1138 let (name, eq, expr) = get_xhp_attribute_children x in
1139 Span [
1140 t name;
1141 t eq;
1142 SplitWith Cost.Base;
1143 Nest [t expr];
1145 | XHPOpen x ->
1146 let (left_a, name, attrs, right_a) = get_xhp_open_children x in
1147 Fmt [
1148 t left_a;
1149 t name;
1150 match syntax attrs with
1151 | Missing -> handle_xhp_open_right_angle_token attrs right_a
1152 | _ ->
1153 Fmt [
1154 Space;
1155 Split;
1156 WithRule (Rule.Parental, Fmt [
1157 Nest [
1158 handle_possible_list ~after_each:(fun is_last ->
1159 if not is_last then space_split () else Nothing
1160 ) attrs;
1162 handle_xhp_open_right_angle_token attrs right_a;
1166 | XHPExpression x ->
1167 let handle_xhp_body body =
1168 match syntax body with
1169 | Missing -> Nothing, true
1170 | SyntaxList xs ->
1171 (* XHP breaks the normal rules of trivia. All trailing trivia (except on
1172 * XHPBody tokens) is lexed as leading trivia for the next token.
1174 * To deal with this, we keep track of whether the last token we added
1175 * was one that trailing trivia is scanned for. If it wasn't, we handle
1176 * the next token's leading trivia with transform_xhp_leading_trivia,
1177 * which treats all trivia up to the first newline as trailing trivia.
1179 let prev_token_scanned_trailing_trivia = ref false in
1180 let prev_token_was_xhpbody = ref false in
1181 let transformed_body = Fmt (List.map xs ~f:begin fun node ->
1182 let leading, node = remove_leading_trivia node in
1183 let transformed_node = Fmt [
1184 (* Whitespace in an XHPBody is only significant when adjacent to an
1185 * XHPBody token, so we are free to add splits between other nodes
1186 * (like XHPExpressions and BracedExpressions). We can also safely
1187 * add splits before XHPBody tokens, but only if they already have
1188 * whitespace in their leading trivia.
1190 * Splits *after* XHPBody tokens are handled below by
1191 * trailing_whitespace, so if the previous token was an XHPBody
1192 * token, we don't need to do anything. *)
1193 if !prev_token_was_xhpbody
1194 then Nothing
1195 else begin
1196 match syntax node with
1197 | Token _ -> if has_invisibles leading then Split else Nothing
1198 | _ -> Split
1199 end;
1200 if !prev_token_scanned_trailing_trivia
1201 then transform_leading_trivia leading
1202 else transform_xhp_leading_trivia leading;
1203 t node;
1204 ] in
1205 (* XHPExpressions currently have trailing trivia when in an
1206 * XHPBody, but they shouldn't--see T16787398.
1207 * Once that issue is resolved, prev_token_scanned_trailing_trivia and
1208 * prev_token_was_xhpbody will be equivalent and one can be removed.
1210 let open EditableToken in
1211 prev_token_scanned_trailing_trivia := begin
1212 match syntax node with
1213 | XHPExpression _ -> true
1214 | Token t -> kind t = TokenKind.XHPBody
1215 | _ -> false
1216 end;
1217 prev_token_was_xhpbody := begin
1218 match syntax node with
1219 | Token t -> kind t = TokenKind.XHPBody
1220 | _ -> false
1221 end;
1222 (* Here, we preserve newlines after XHPBody tokens and don't add
1223 * splits between them. This means that we don't reflow paragraphs in
1224 * XHP to fit in the column limit.
1226 * If we were to split between XHPBody tokens, we'd need a new Rule
1227 * type to govern word-wrap style splitting, since using independent
1228 * splits (e.g. SplitWith Cost.Base) between every token would make
1229 * solving too expensive. *)
1230 let trailing = Syntax.trailing_trivia node in
1231 let trailing_whitespace =
1232 match syntax node with
1233 | Token _ when has_newline trailing -> Newline
1234 | _ when has_whitespace trailing -> Space
1235 | _ -> Nothing
1237 Fmt [transformed_node; trailing_whitespace]
1238 end) in
1239 let leading_token =
1240 match Syntax.leading_token (List.hd_exn xs) with
1241 | None -> failwith "Expected token"
1242 | Some token -> token
1244 let can_split_before_first_token =
1245 let open EditableToken in
1246 kind leading_token <> TokenKind.XHPBody ||
1247 has_invisibles (leading leading_token)
1249 let transformed_body = Fmt [
1250 if can_split_before_first_token then Split else Nothing;
1251 transformed_body;
1252 ] in
1253 let can_split_before_close = not !prev_token_was_xhpbody in
1254 transformed_body, can_split_before_close
1255 | _ -> failwith "Expected SyntaxList"
1258 let (xhp_open, body, close) = get_xhp_expression_children x in
1259 WithPossibleLazyRule (Rule.Parental, t xhp_open,
1260 let transformed_body, can_split_before_close = handle_xhp_body body in
1261 Fmt [
1262 Nest [transformed_body];
1263 when_present close begin fun () ->
1264 let leading, close = remove_leading_trivia close in Fmt [
1265 (* Ignore extra newlines by treating this as trailing trivia *)
1266 ignore_trailing_invisibles leading;
1267 if can_split_before_close then Split else Nothing;
1268 t close;
1270 end;
1272 | VarrayTypeSpecifier x ->
1273 let (kw, left_a, varray_type, _, right_a) =
1274 get_varray_type_specifier_children x in
1275 Fmt [
1276 t kw;
1277 transform_braced_item left_a varray_type right_a;
1279 | VectorArrayTypeSpecifier x ->
1280 let (kw, left_a, vec_type, right_a) =
1281 get_vector_array_type_specifier_children x in
1282 Fmt [
1283 t kw;
1284 transform_braced_item left_a vec_type right_a;
1286 | VectorTypeSpecifier x ->
1287 let (kw, left_a, vec_type, right_a) =
1288 get_vector_type_specifier_children x in
1289 Fmt [
1290 t kw;
1291 transform_braced_item left_a vec_type right_a;
1293 | KeysetTypeSpecifier x ->
1294 let (kw, left_a, ks_type, right_a) =
1295 get_keyset_type_specifier_children x in
1296 Fmt [
1297 t kw;
1298 transform_braced_item left_a ks_type right_a;
1300 | TypeParameter x ->
1301 let (variance, name, constraints) = get_type_parameter_children x in
1302 Fmt [
1303 t variance;
1304 t name;
1305 when_present constraints space;
1306 handle_possible_list constraints;
1308 | TypeConstraint x ->
1309 let (kw, constraint_type) = get_type_constraint_children x in
1310 Fmt [
1311 t kw;
1312 Space;
1313 t constraint_type;
1315 | DarrayTypeSpecifier x ->
1316 let (kw, left_a, key, comma_kw, value, _, right_a) =
1317 get_darray_type_specifier_children x in
1318 let key_list_item = make_list_item key comma_kw in
1319 let val_list_item = make_list_item value (make_missing ()) in
1320 let args = make_list [key_list_item; val_list_item] in
1321 Fmt [
1322 t kw;
1323 transform_argish ~allow_trailing:true left_a args right_a;
1325 | MapArrayTypeSpecifier x ->
1326 let (kw, left_a, key, comma_kw, value, right_a) =
1327 get_map_array_type_specifier_children x in
1328 Fmt [
1329 t kw;
1330 let key_list_item = make_list_item key comma_kw in
1331 let val_list_item = make_list_item value (make_missing ()) in
1332 let args = make_list [key_list_item; val_list_item] in
1333 transform_argish ~allow_trailing:false left_a args right_a;
1335 | DictionaryTypeSpecifier x ->
1336 let (kw, left_a, members, right_a) =
1337 get_dictionary_type_specifier_children x
1339 Fmt [
1340 t kw;
1341 transform_argish left_a members right_a;
1343 | ClosureTypeSpecifier x ->
1344 let (
1345 outer_left_p,
1346 coroutine,
1348 inner_left_p,
1349 param_types,
1350 inner_right_p,
1351 colon,
1352 ret_type,
1353 outer_right_p
1354 ) = get_closure_type_specifier_children x in
1355 Fmt [
1356 t outer_left_p;
1357 t coroutine;
1358 when_present coroutine space;
1359 t kw;
1360 transform_argish_with_return_type
1361 inner_left_p param_types inner_right_p colon ret_type;
1362 t outer_right_p;
1364 | ClassnameTypeSpecifier x ->
1365 let (kw, left_a, class_type, right_a) =
1366 get_classname_type_specifier_children x in
1367 Fmt [
1368 t kw;
1369 transform_braced_item left_a class_type right_a;
1371 | FieldSpecifier x ->
1372 let (question, name, arrow_kw, field_type) =
1373 get_field_specifier_children x in
1374 Fmt [
1375 t question;
1376 transform_mapish_entry name arrow_kw field_type;
1378 | FieldInitializer x ->
1379 let (name, arrow_kw, value) = get_field_initializer_children x in
1380 transform_mapish_entry name arrow_kw value
1381 | ShapeTypeSpecifier x ->
1382 let (shape_kw, left_p, type_fields, ellipsis, right_p) =
1383 get_shape_type_specifier_children x in
1384 let fields = if is_missing ellipsis
1385 then type_fields
1386 else
1387 let missing_separator = make_missing () in
1388 let ellipsis_list = [make_list_item ellipsis missing_separator] in
1389 make_list (children type_fields @ ellipsis_list) in
1390 Fmt [
1391 t shape_kw;
1392 transform_argish
1393 ~allow_trailing:(is_missing ellipsis)
1394 left_p
1395 fields
1396 right_p;
1398 | ShapeExpression x ->
1399 let (shape_kw, left_p, fields, right_p) = get_shape_expression_children x in
1400 Fmt [
1401 t shape_kw;
1402 transform_argish left_p fields right_p;
1404 | TupleExpression x ->
1405 let (kw, left_p, items, right_p) = get_tuple_expression_children x in
1406 Fmt [
1407 t kw;
1408 transform_argish left_p items right_p;
1410 | TypeArguments x ->
1411 let (left_a, type_list, right_a) = get_type_arguments_children x in
1412 transform_argish left_a type_list right_a
1413 | TypeParameters x ->
1414 let (left_a, param_list, right_a) = get_type_parameters_children x in
1415 transform_argish left_a param_list right_a
1416 | TupleTypeSpecifier x ->
1417 let (left_p, types, right_p) = get_tuple_type_specifier_children x in
1418 transform_argish left_p types right_p
1419 | TupleTypeExplicitSpecifier x ->
1420 let (kw, left_a, types, right_a) =
1421 get_tuple_type_explicit_specifier_children x in
1422 Fmt [
1423 t kw;
1424 transform_argish left_a types right_a
1426 | ErrorSyntax _ ->
1427 raise Hackfmt_error.InvalidSyntax
1429 and when_present node f =
1430 match syntax node with
1431 | Missing -> Nothing
1432 | _ -> f ()
1434 and is_present node =
1435 not (is_missing node)
1437 and transform_simple node =
1438 Fmt (List.map (children node) transform)
1440 and transform_simple_statement node =
1441 Fmt ((List.map (children node) transform) @ [Newline])
1443 and braced_block_nest open_b close_b nodes =
1444 (* Remove the closing brace's leading trivia and handle it inside the
1445 * BlockNest, so that comments will be indented correctly. *)
1446 let leading, close_b = remove_leading_trivia close_b in
1447 Fmt [
1448 transform open_b;
1449 Newline;
1450 BlockNest [
1451 Fmt nodes;
1452 transform_leading_trivia leading;
1453 Newline;
1455 transform close_b;
1458 and delimited_nest
1459 ?(spaces=false)
1460 ?(split_when_children_split=true)
1461 left_delim
1462 right_delim
1463 nodes
1465 let rule =
1466 if split_when_children_split
1467 then Rule.Parental
1468 else Rule.Simple Cost.Base
1470 Span [
1471 transform left_delim;
1472 WithRule (rule,
1473 nest ~spaces right_delim nodes
1477 and nest ?(spaces=false) right_delim nodes =
1478 (* Remove the right delimiter's leading trivia and handle it inside the Nest,
1479 * so that comments will be indented correctly. *)
1480 let leading, right_delim = remove_leading_trivia right_delim in
1481 let nested_contents = Nest [Fmt nodes; transform_leading_trivia leading] in
1482 let content_present = has_printable_content nested_contents in
1483 let maybe_split =
1484 match content_present, spaces with
1485 | false, _ -> Nothing
1486 | true, false -> Split
1487 | true, true -> space_split ()
1489 Fmt [
1490 maybe_split;
1491 nested_contents;
1492 maybe_split;
1493 transform right_delim;
1496 and after_each_argument is_last =
1497 if is_last then Split else space_split ()
1499 and handle_lambda_body node =
1500 match syntax node with
1501 | CompoundStatement x ->
1502 handle_compound_statement x;
1503 | _ ->
1504 Fmt [
1505 Space;
1506 SplitWith Cost.Base;
1507 Nest [transform node];
1510 and handle_possible_compound_statement ?space:(space=true) node =
1511 match syntax node with
1512 | CompoundStatement x ->
1513 Fmt [
1514 handle_compound_statement x;
1515 if space then Space else Nothing;
1517 | _ ->
1518 Fmt [
1519 Newline;
1520 BlockNest [
1521 transform node
1525 and handle_compound_statement cs =
1526 let (left_b, statements, right_b) = get_compound_statement_children cs in
1527 Fmt [
1528 Space;
1529 braced_block_nest left_b right_b [
1530 handle_possible_list statements
1535 * Special-case handling for lists of declarators, where we want the splits
1536 * between declarators to break if their children break, but we want a single
1537 * declarator to stay joined with the line preceding it if it fits, even when
1538 * its children break.
1540 and handle_declarator_list declarators =
1541 match syntax declarators with
1542 | Missing -> Nothing
1543 | SyntaxList [declarator] ->
1544 Nest [
1545 Space;
1546 (* Use an independent split, so we don't break just because a line break
1547 * occurs in the declarator. *)
1548 SplitWith Cost.Base;
1549 transform declarator;
1551 | SyntaxList xs ->
1552 (* Use Rule.Parental to break each declarator onto its own line if any line
1553 * break occurs in a declarator, or if they can't all fit onto one line. *)
1554 WithRule (Rule.Parental, Nest (List.map xs (fun declarator -> Fmt [
1555 Space;
1556 Split;
1557 transform declarator;
1558 ])));
1559 | _ -> failwith "SyntaxList expected"
1561 and handle_list
1562 ?(before_each=(fun () -> Nothing))
1563 ?(after_each=(fun is_last -> Nothing))
1564 ?(handle_last=transform)
1565 list =
1566 let rec aux l = (
1567 match l with
1568 | hd :: [] ->
1569 Fmt [
1570 before_each ();
1571 handle_last hd;
1572 after_each true;
1574 | hd :: tl ->
1575 Fmt [
1576 before_each ();
1577 transform hd;
1578 after_each false;
1579 aux tl
1581 | [] -> Nothing
1582 ) in
1583 aux list
1585 and handle_possible_list
1586 ?(before_each=(fun () -> Nothing))
1587 ?(after_each=(fun is_last -> Nothing))
1588 ?(handle_last=transform)
1589 node =
1590 match syntax node with
1591 | Missing -> Nothing
1592 | SyntaxList x -> handle_list x ~before_each ~after_each ~handle_last
1593 | _ -> handle_list [node] ~before_each ~after_each ~handle_last
1595 and handle_xhp_open_right_angle_token attrs t =
1596 match syntax t with
1597 | Token token ->
1598 Fmt [
1599 if EditableToken.text token = "/>"
1600 then Fmt [Space; when_present attrs split]
1601 else Nothing;
1602 transform t
1604 | _ -> failwith "expected xhp_open right_angle token"
1606 and handle_function_call_expression fce =
1607 let (receiver, lp, args, rp) = get_function_call_expression_children fce in
1608 match syntax receiver with
1609 | MemberSelectionExpression mse ->
1610 handle_possible_chaining
1611 (get_member_selection_expression_children mse)
1612 (Some (lp, args, rp))
1613 | SafeMemberSelectionExpression smse ->
1614 handle_possible_chaining
1615 (get_safe_member_selection_expression_children smse)
1616 (Some (lp, args, rp))
1617 | _ ->
1618 Fmt [
1619 transform receiver;
1620 transform_argish lp args rp
1623 and handle_possible_chaining (obj, arrow1, member1) argish =
1624 let rec handle_chaining obj =
1625 let handle_mse_or_smse (obj, arrow, member) fun_paren_args =
1626 let (obj, l) = handle_chaining obj in
1627 obj, l @ [(arrow, member, fun_paren_args)]
1629 match syntax obj with
1630 | FunctionCallExpression x ->
1631 let (receiver, lp, args, rp) =
1632 get_function_call_expression_children x in
1633 (match syntax receiver with
1634 | MemberSelectionExpression mse ->
1635 handle_mse_or_smse
1636 (get_member_selection_expression_children mse)
1637 (Some (lp, args, rp))
1638 | SafeMemberSelectionExpression smse ->
1639 handle_mse_or_smse
1640 (get_safe_member_selection_expression_children smse)
1641 (Some (lp, args, rp))
1642 | _ -> obj, []
1644 | MemberSelectionExpression mse ->
1645 handle_mse_or_smse
1646 (get_member_selection_expression_children mse) None
1647 | SafeMemberSelectionExpression smse ->
1648 handle_mse_or_smse
1649 (get_safe_member_selection_expression_children smse) None
1650 | _ -> obj, []
1653 let (obj, chain_list) = handle_chaining obj in
1654 let chain_list = chain_list @ [(arrow1, member1, argish)] in
1656 let transform_chain (arrow, member, argish) =
1657 Fmt [
1658 transform arrow;
1659 transform member;
1660 Option.value_map argish ~default:Nothing
1661 ~f:(fun (lp, args, rp) -> transform_argish lp args rp);
1664 match chain_list with
1665 | hd :: [] ->
1666 Fmt [
1667 Span [transform obj];
1668 SplitWith Cost.SimpleMemberSelection;
1669 Nest [transform_chain hd];
1671 | hd :: tl ->
1672 WithLazyRule (Rule.Parental,
1673 Fmt [
1674 transform obj;
1675 Split;
1677 Nest [
1678 transform_chain hd;
1679 Fmt (List.map tl ~f:(fun x -> Fmt [Split; transform_chain x]));
1681 | _ -> failwith "Expected a chain of at least length 1"
1683 and handle_switch_body left_b sections right_b =
1684 let handle_fallthrough fallthrough =
1685 match syntax fallthrough with
1686 | SwitchFallthrough x ->
1687 let (kw, semi) = get_switch_fallthrough_children x in
1689 transform kw;
1690 transform semi;
1692 | _ -> []
1694 let handle_label label =
1695 match syntax label with
1696 | CaseLabel x ->
1697 let (kw, expr, colon) = get_case_label_children x in
1698 Fmt [
1699 transform kw;
1700 Space;
1701 Split;
1702 transform expr;
1703 transform colon;
1704 Newline;
1706 | DefaultLabel x ->
1707 let (kw, colon) = get_default_label_children x in
1708 Fmt [
1709 transform kw;
1710 transform colon;
1711 Newline;
1713 | _ -> Nothing
1715 let handle_statement statement =
1716 BlockNest [
1717 transform statement;
1720 let handle_section section =
1721 match syntax section with
1722 | SwitchSection s ->
1723 Fmt (
1724 (List.map
1725 (syntax_node_to_list s.switch_section_labels)
1726 ~f:handle_label)
1727 @ (List.map
1728 (syntax_node_to_list s.switch_section_statements)
1729 ~f:handle_statement)
1730 @ handle_fallthrough s.switch_section_fallthrough
1732 | _ -> Nothing
1734 Fmt [
1735 Space;
1736 braced_block_nest left_b right_b (
1737 List.map (syntax_node_to_list sections) handle_section
1741 and transform_fn_decl_name async coroutine kw amp name type_params leftp =
1743 transform async;
1744 when_present async space;
1745 transform coroutine;
1746 when_present coroutine space;
1747 transform kw;
1748 Space;
1749 transform amp;
1750 transform name;
1751 transform type_params;
1752 transform leftp;
1753 Split;
1756 and transform_fn_decl_args params rightp colon ret_type where =
1757 WithRule (Rule.Parental, Fmt [
1758 transform_possible_comma_list params rightp;
1759 transform colon;
1760 when_present colon space;
1761 transform ret_type;
1762 when_present where space;
1763 transform where;
1766 and transform_argish_with_return_type left_p params right_p colon ret_type =
1767 Fmt [
1768 transform left_p;
1769 when_present params split;
1770 WithRule (Rule.Parental, Span [
1771 Span [ transform_possible_comma_list params right_p ];
1772 transform colon;
1773 when_present colon space;
1774 transform ret_type;
1778 and transform_argish ?(allow_trailing=true) ?(spaces=false)
1779 left_p arg_list right_p =
1780 (* When there is only one argument, with no surrounding whitespace in the
1781 * original source, allow that style to be preserved even when there are line
1782 * breaks within the argument (normally these would force the splits around
1783 * the argument to break). *)
1784 let split_when_children_split =
1785 match spaces, syntax arg_list with
1786 | false, SyntaxList [x] ->
1787 not (
1788 List.is_empty (trailing_trivia left_p) &&
1789 List.is_empty (trailing_trivia x)
1791 | _ -> true
1793 delimited_nest ~spaces ~split_when_children_split left_p right_p [
1794 transform_arg_list ~spaces ~allow_trailing arg_list
1797 and transform_braced_item left_p item right_p =
1798 delimited_nest left_p right_p [transform item]
1800 and transform_arg_list ?(allow_trailing=true) ?(spaces=false) items =
1801 handle_possible_list items
1802 ~after_each:after_each_argument
1803 ~handle_last:(transform_last_arg ~allow_trailing)
1805 and transform_possible_comma_list ?(allow_trailing=true) ?(spaces=false)
1806 items right_p =
1807 nest ~spaces right_p [
1808 transform_arg_list ~spaces ~allow_trailing items
1811 and remove_leading_trivia node =
1812 match Syntax.leading_token node with
1813 | None -> [], node
1814 | Some leading_token ->
1815 let rewritten_node = Rewriter.rewrite_pre (fun rewrite_node ->
1816 match syntax rewrite_node with
1817 | Token t when t == leading_token ->
1818 Rewriter.Replace (Syntax.make_token {t with EditableToken.leading = []})
1819 | _ -> Rewriter.Keep
1820 ) node in
1821 EditableToken.leading leading_token, rewritten_node
1823 and remove_trailing_trivia node =
1824 match Syntax.trailing_token node with
1825 | None -> node, []
1826 | Some trailing_token ->
1827 let rewritten_node = Rewriter.rewrite_pre (fun rewrite_node ->
1828 match syntax rewrite_node with
1829 | Token t when t == trailing_token ->
1830 Rewriter.Replace (Syntax.make_token {t with EditableToken.trailing = []})
1831 | _ -> Rewriter.Keep
1832 ) node in
1833 rewritten_node, EditableToken.trailing trailing_token
1835 and transform_last_arg ~allow_trailing node =
1836 match syntax node with
1837 | ListItem x ->
1838 let (item, separator) = get_list_item_children x in
1839 Fmt (match syntax separator with
1840 | Token x -> [
1841 begin
1842 let item, trailing = remove_trailing_trivia item in
1843 Fmt [
1844 transform item;
1845 if allow_trailing then TrailingComma else Nothing;
1846 transform_trailing_trivia trailing;
1848 end;
1849 let leading = EditableToken.leading x in
1850 let trailing = EditableToken.trailing x in
1851 Fmt [
1852 transform_leading_trivia leading;
1853 Ignore (EditableToken.text x, EditableToken.width x);
1854 transform_trailing_trivia trailing;
1857 | Missing ->
1858 let item, trailing = remove_trailing_trivia item in [
1859 transform item;
1860 if allow_trailing then TrailingComma else Nothing;
1861 transform_trailing_trivia trailing;
1863 | _ -> failwith "Expected separator to be a token"
1865 | _ ->
1866 failwith "Expected ListItem"
1868 and transform_mapish_entry key arrow value =
1869 Fmt [
1870 transform key;
1871 Space;
1872 transform arrow;
1873 Space;
1874 SplitWith Cost.Base;
1875 Nest [transform value];
1878 and transform_keyword_expression_statement kw expr semi =
1879 Fmt [
1880 transform kw;
1881 when_present expr (fun () -> Fmt [
1882 Space;
1883 SplitWith Cost.Base;
1884 Nest [transform expr];
1886 transform semi;
1887 Newline;
1890 and transform_keyword_expr_list_statement kw expr_list semi =
1891 Fmt [
1892 transform kw;
1893 handle_declarator_list expr_list;
1894 transform semi;
1895 Newline;
1898 and transform_condition left_p condition right_p =
1899 Fmt [
1900 transform left_p;
1901 Split;
1902 WithRule (Rule.Parental, Fmt [
1903 Nest [transform condition];
1904 Split;
1905 transform right_p;
1909 and transform_binary_expression ~is_nested expr =
1910 let get_operator_type op =
1911 match syntax op with
1912 | Token t -> Full_fidelity_operator.trailing_from_token
1913 (EditableToken.kind t)
1914 | _ -> failwith "Operator should always be a token"
1916 let is_concat op =
1917 get_operator_type op = Full_fidelity_operator.ConcatenationOperator in
1918 let operator_has_surrounding_spaces op = not (is_concat op) in
1919 let operator_is_leading op =
1920 get_operator_type op = Full_fidelity_operator.PipeOperator in
1922 let (left, operator, right) = get_binary_expression_children expr in
1923 let operator_t = get_operator_type operator in
1925 if Full_fidelity_operator.is_comparison operator_t then
1926 WithLazyRule (Rule.Parental,
1927 Fmt [
1928 transform left;
1929 Space;
1930 transform operator;
1932 Fmt [
1933 Space;
1934 Split;
1935 Nest [transform right];
1937 else if Full_fidelity_operator.is_assignment operator_t then
1938 Fmt [
1939 transform left;
1940 Space;
1941 transform operator;
1942 Space;
1943 SplitWith Cost.Base;
1944 Nest [transform right];
1946 else
1947 Fmt [
1948 let precedence = Full_fidelity_operator.precedence operator_t in
1950 let rec flatten_expression expr =
1951 match syntax expr with
1952 | BinaryExpression x ->
1953 let (left, operator, right) = get_binary_expression_children x in
1954 let operator_t = get_operator_type operator in
1955 let op_precedence = Full_fidelity_operator.precedence operator_t in
1956 if (op_precedence = precedence) then
1957 (flatten_expression left) @ (operator :: flatten_expression right)
1958 else [expr]
1959 | _ -> [expr]
1962 let transform_operand operand =
1963 match syntax operand with
1964 | BinaryExpression x -> transform_binary_expression ~is_nested:true x
1965 | _ -> transform operand
1968 let binary_expression_syntax_list =
1969 flatten_expression (make_binary_expression left operator right) in
1970 match binary_expression_syntax_list with
1971 | hd :: tl ->
1972 WithLazyRule (Rule.Parental,
1973 transform_operand hd,
1974 let expression =
1975 let last_op = ref (List.hd_exn tl) in
1976 List.mapi tl ~f:(fun i x ->
1977 if i mod 2 = 0 then begin
1978 let op = x in
1979 last_op := op;
1980 let op_has_spaces = operator_has_surrounding_spaces op in
1981 let op_is_leading = operator_is_leading op in
1982 Fmt [
1983 if op_is_leading
1984 then (if op_has_spaces then space_split () else Split)
1985 else (if op_has_spaces then Space else Nothing);
1986 if is_concat op
1987 then ConcatOperator (transform op)
1988 else transform op;
1991 else begin
1992 let operand = x in
1993 let op_has_spaces = operator_has_surrounding_spaces !last_op in
1994 let op_is_leading = operator_is_leading !last_op in
1995 Fmt [
1996 if op_is_leading then begin
1997 (* TODO: We only have this split to ensure that range
1998 * formatting works when it starts or ends here. We should
1999 * remove it once we can return an expanded formatting
2000 * range. *)
2001 if op_has_spaces
2002 then Fmt [Space; SplitWith Cost.Base]
2003 else SplitWith Cost.Base
2005 else (if op_has_spaces then space_split () else Split);
2006 transform_operand operand;
2011 if is_nested
2012 then Nest expression
2013 else ConditionalNest expression)
2014 | _ ->
2015 failwith "Expected non empty list of binary expression pieces"
2018 (* True if the trivia list contains WhiteSpace trivia.
2019 * Note that WhiteSpace includes spaces and tabs, but not newlines. *)
2020 and has_whitespace trivia_list =
2021 List.exists trivia_list
2022 ~f:(fun trivia -> Trivia.kind trivia = TriviaKind.WhiteSpace)
2024 (* True if the trivia list contains EndOfLine trivia. *)
2025 and has_newline trivia_list =
2026 List.exists trivia_list
2027 ~f:(fun trivia -> Trivia.kind trivia = TriviaKind.EndOfLine)
2029 (* True if the trivia list contains any "invisible" trivia, meaning spaces,
2030 * tabs, or newlines. *)
2031 and has_invisibles trivia_list =
2032 List.exists trivia_list ~f:begin fun trivia ->
2033 Trivia.kind trivia = TriviaKind.WhiteSpace ||
2034 Trivia.kind trivia = TriviaKind.EndOfLine
2037 and transform_leading_trivia t = transform_trivia ~is_leading:true t
2038 and transform_trailing_trivia t = transform_trivia ~is_leading:false t
2040 and transform_trivia ~is_leading trivia =
2041 let new_line_regex = Str.regexp "\n" in
2042 let indent = ref 0 in
2043 let currently_leading = ref is_leading in
2044 let leading_invisibles = ref [] in
2045 let last_comment = ref None in
2046 let last_comment_was_delimited = ref false in
2047 let newline_followed_last_comment = ref false in
2048 let whitespace_followed_last_comment = ref false in
2049 let trailing_invisibles = ref [] in
2050 let comments = ref [] in
2051 let make_comment _ =
2052 if Option.is_some !last_comment then begin
2053 newline_followed_last_comment := has_newline !trailing_invisibles;
2054 whitespace_followed_last_comment := has_whitespace !trailing_invisibles;
2055 end;
2056 comments :=
2057 (Fmt [
2058 transform_leading_invisibles (List.rev !leading_invisibles);
2059 Option.value !last_comment ~default:Nothing;
2060 ignore_trailing_invisibles (List.rev !trailing_invisibles);
2061 if !last_comment_was_delimited then begin
2062 if !whitespace_followed_last_comment then Space
2063 else if !newline_followed_last_comment then Newline
2064 else Nothing
2066 else if Option.is_some !last_comment
2067 then Newline (* Always add a newline after a single-line comment *)
2068 else Nothing;
2070 :: !comments;
2071 last_comment := None;
2072 leading_invisibles := [];
2073 trailing_invisibles := [];
2075 List.iter trivia ~f:(fun triv ->
2076 match Trivia.kind triv with
2077 | TriviaKind.UnsafeExpression
2078 | TriviaKind.FixMe
2079 | TriviaKind.IgnoreError
2080 | TriviaKind.DelimitedComment ->
2081 let preceded_by_whitespace =
2082 if !currently_leading
2083 then has_whitespace !leading_invisibles
2084 else has_whitespace !trailing_invisibles
2086 make_comment ();
2087 let delimited_lines = Str.split new_line_regex (Trivia.text triv) in
2088 let map_tail str =
2089 let prefix_space_count str =
2090 let len = String.length str in
2091 let rec aux i =
2092 if i = len || str.[i] <> ' '
2093 then 0
2094 else 1 + (aux (i + 1))
2096 aux 0
2098 (* If we're dealing with trailing trivia, then we don't have a good
2099 signal for the indent level, so we just cut all leading spaces.
2100 Otherwise, we cut a number of spaces equal to the indent before
2101 the delimited comment opener. *)
2102 let start_index = if is_leading
2103 then min !indent (prefix_space_count str)
2104 else prefix_space_count str
2106 let len = String.length str - start_index in
2107 let dc = Trivia.make_delimited_comment @@
2108 String.sub str start_index len in
2109 Fmt [
2110 Newline;
2111 Ignore ("\n", 1);
2112 Ignore ((String.make start_index ' '), start_index);
2113 Comment ((Trivia.text dc), (Trivia.width dc));
2117 let hd = List.hd_exn delimited_lines in
2118 let tl = List.tl_exn delimited_lines in
2119 let hd = Comment (hd, (String.length hd)) in
2121 last_comment := Some (Fmt [
2122 if !currently_leading then Newline
2123 else if preceded_by_whitespace then Space
2124 else Nothing;
2125 Fmt (hd :: List.map tl ~f:map_tail);
2127 last_comment_was_delimited := true;
2128 currently_leading := false;
2129 | TriviaKind.Unsafe
2130 | TriviaKind.FallThrough
2131 | TriviaKind.SingleLineComment ->
2132 make_comment ();
2133 last_comment := Some (Fmt [
2134 if !currently_leading then Newline else Space;
2135 Comment ((Trivia.text triv), (Trivia.width triv));
2137 last_comment_was_delimited := false;
2138 currently_leading := false;
2139 | TriviaKind.EndOfLine ->
2140 indent := 0;
2141 if !currently_leading then
2142 leading_invisibles := triv :: !leading_invisibles
2143 else begin
2144 trailing_invisibles := triv :: !trailing_invisibles;
2145 make_comment ();
2146 end;
2147 currently_leading := true;
2148 | TriviaKind.WhiteSpace ->
2149 if !currently_leading then begin
2150 indent := Trivia.width triv;
2151 leading_invisibles := triv :: !leading_invisibles
2153 else
2154 trailing_invisibles := triv :: !trailing_invisibles;
2156 if List.is_empty !comments then begin
2157 if is_leading
2158 then transform_leading_invisibles trivia
2159 else ignore_trailing_invisibles trivia
2161 else begin
2162 make_comment ();
2163 Fmt (List.rev !comments)
2166 and _MAX_CONSECUTIVE_BLANK_LINES = 2
2168 and transform_leading_invisibles triv =
2169 let newlines = ref 0 in
2170 Fmt (List.map triv ~f:(fun t ->
2171 let ignored = Ignore ((Trivia.text t), (Trivia.width t)) in
2172 match Trivia.kind t with
2173 | TriviaKind.EndOfLine ->
2174 newlines := !newlines + 1;
2175 Fmt [
2176 ignored;
2177 if !newlines <= _MAX_CONSECUTIVE_BLANK_LINES
2178 then BlankLine
2179 else Nothing
2181 | _ -> ignored;
2184 and ignore_trailing_invisibles triv =
2185 Fmt (List.map triv ~f:(fun t -> Ignore ((Trivia.text t), (Trivia.width t))))
2187 and transform_xhp_leading_trivia triv =
2188 let (up_to_first_newline, after_newline, _) =
2189 List.fold triv
2190 ~init:([], [], false)
2191 ~f:begin fun (upto, after, seen) t ->
2192 if seen then upto, t :: after, true
2193 else t :: upto, after, Trivia.kind t = TriviaKind.EndOfLine
2196 Fmt [
2197 ignore_trailing_invisibles up_to_first_newline;
2198 transform_leading_invisibles after_newline;