Reduce max_consecutive_blank_lines to 1
[hiphop-php.git] / hphp / hack / src / hackfmt / hack_format.ml
blob3940b07d7f1ea14d6b2fb523d0ef6fac86bb8d55
1 (*
2 * Copyright (c) 2018, Facebook, Inc.
3 * All rights reserved.
5 * This source code is licensed under the MIT license found in the
6 * LICENSE file in the "hack" directory of this source tree.
8 *)
10 open Hh_prelude
11 module Env = Format_env
12 module SourceText = Full_fidelity_source_text
13 module Syntax = Full_fidelity_editable_syntax
14 module SyntaxKind = Full_fidelity_syntax_kind
15 module Token = Full_fidelity_editable_token
16 module TokenKind = Full_fidelity_token_kind
17 module Trivia = Full_fidelity_editable_trivia
18 module TriviaKind = Full_fidelity_trivia_kind
19 module Rewriter = Full_fidelity_rewriter.WithSyntax (Syntax)
20 open Doc
22 let is_trivia_kind_fallthrough = function
23 | TriviaKind.FallThrough -> true
24 | _ -> false
26 let is_trivia_kind_end_of_line = function
27 | TriviaKind.EndOfLine -> true
28 | _ -> false
30 let is_trivia_kind_white_space = function
31 | TriviaKind.WhiteSpace -> true
32 | _ -> false
34 let is_syntax_kind_parenthesized_exprression = function
35 | SyntaxKind.ParenthesizedExpression -> true
36 | _ -> false
38 let is_token_kind_xhp_body = function
39 | TokenKind.XHPBody -> true
40 | _ -> false
42 let is_token_kind_in_out = function
43 | TokenKind.Inout -> true
44 | _ -> false
46 let make_list = Syntax.make_list SourceText.empty 0
48 let make_missing () = Syntax.make_missing SourceText.empty 0
50 (* Main transform function, which takes a full-fidelity CST node and produces a
51 * Doc.t node (the IR which is fed to Chunk_builder.build).
53 * Exported via the `transform` alias below. *)
54 let rec t (env : Env.t) (node : Syntax.t) : Doc.t =
55 (* Leave this node as it was in the original source if it is preceded by a
56 hackfmt-ignore comment. *)
57 match transform_node_if_ignored node with
58 | Some doc -> doc
59 | None ->
60 (match Syntax.syntax node with
61 | Syntax.Missing -> Nothing
62 | Syntax.Token x ->
63 let token_kind = Token.kind x in
64 Concat
66 begin
67 match token_kind with
68 | TokenKind.EndOfFile ->
69 let leading_trivia = Token.leading x in
70 let trivia_without_trailing_invisibles =
71 let reversed = List.rev leading_trivia in
72 List.rev (List.drop_while reversed ~f:is_invisible)
74 transform_leading_trivia trivia_without_trailing_invisibles
75 | _ -> transform_leading_trivia (Token.leading x)
76 end;
77 begin
78 match token_kind with
79 | TokenKind.EndOfFile -> Nothing
80 | TokenKind.SingleQuotedStringLiteral
81 | TokenKind.DoubleQuotedStringLiteral
82 | TokenKind.DoubleQuotedStringLiteralHead
83 | TokenKind.StringLiteralBody
84 | TokenKind.DoubleQuotedStringLiteralTail
85 | TokenKind.HeredocStringLiteral
86 | TokenKind.HeredocStringLiteralHead
87 | TokenKind.HeredocStringLiteralTail
88 | TokenKind.NowdocStringLiteral ->
89 make_string (Token.text x) (Token.width x)
90 | TokenKind.XHPStringLiteral when Env.version_gte env 2 ->
91 make_string (Token.text x) (Token.width x)
92 | _ -> Text (Token.text x, Token.width x)
93 end;
94 transform_trailing_trivia (Token.trailing x);
96 | Syntax.SyntaxList _ ->
97 failwith
98 (Printf.sprintf
99 "Error: SyntaxList should never be handled directly;
100 offending text is '%s'."
101 (Syntax.text node))
102 | Syntax.EndOfFile x -> t env x.end_of_file_token
103 | Syntax.Script x -> Concat [handle_possible_list env x.script_declarations]
104 | Syntax.LiteralExpression { literal_expression } ->
105 (* Double quoted string literals can create a list *)
106 let wrap_with_literal_type token transformed =
107 match Token.kind token with
108 | TokenKind.HeredocStringLiteral
109 | TokenKind.HeredocStringLiteralHead
110 | TokenKind.HeredocStringLiteralTail
111 | TokenKind.NowdocStringLiteral ->
112 DocLiteral transformed
113 | TokenKind.DecimalLiteral
114 | TokenKind.OctalLiteral
115 | TokenKind.HexadecimalLiteral
116 | TokenKind.BinaryLiteral
117 | TokenKind.FloatingLiteral ->
118 NumericLiteral transformed
119 | _ -> transformed
121 begin
122 match Syntax.syntax literal_expression with
123 | Syntax.Token tok ->
124 wrap_with_literal_type tok (t env literal_expression)
125 | Syntax.SyntaxList l ->
126 let last = Syntax.trailing_token literal_expression in
127 begin
128 match last with
129 | Some tok ->
130 wrap_with_literal_type tok (Concat (List.map l ~f:(t env)))
131 | _ -> failwith "Expected Token"
133 | _ -> failwith "Expected Token or SyntaxList"
135 | Syntax.PrefixedStringExpression
136 { prefixed_string_name = name; prefixed_string_str = str } ->
137 Concat [t env name; t env str]
138 | Syntax.MarkupSection
139 { markup_hashbang = hashbang; markup_suffix = suffix; _ } ->
140 if Syntax.is_missing hashbang then
141 t env suffix
142 else
143 Concat [t env hashbang; Newline; t env suffix]
144 | Syntax.MarkupSuffix _ -> transform_simple_statement env node
145 | Syntax.SimpleTypeSpecifier _
146 | Syntax.VariableExpression _
147 | Syntax.PipeVariableExpression _
148 | Syntax.PropertyDeclarator _
149 | Syntax.ConstantDeclarator _
150 | Syntax.ScopeResolutionExpression _
151 | Syntax.EmbeddedMemberSelectionExpression _
152 | Syntax.EmbeddedSubscriptExpression _
153 | Syntax.PostfixUnaryExpression _
154 | Syntax.XHPRequired _
155 | Syntax.XHPLateinit _
156 | Syntax.XHPSimpleClassAttribute _
157 | Syntax.XHPClose _
158 | Syntax.TypeConstant _
159 | Syntax.GenericTypeSpecifier _
160 | Syntax.NullableTypeSpecifier _
161 | Syntax.LikeTypeSpecifier _
162 | Syntax.SoftTypeSpecifier _
163 | Syntax.ListItem _ ->
164 transform_simple env node
165 | Syntax.ReifiedTypeArgument
166 { reified_type_argument_reified; reified_type_argument_type } ->
167 Concat
169 t env reified_type_argument_reified;
170 Space;
171 t env reified_type_argument_type;
173 | Syntax.QualifiedName { qualified_name_parts } ->
174 handle_possible_list env qualified_name_parts
175 | Syntax.ModuleName { module_name_parts } ->
176 handle_possible_list env module_name_parts
177 | Syntax.ExpressionStatement _ -> transform_simple_statement env node
178 | Syntax.EnumDeclaration
180 enum_attribute_spec = attr;
181 enum_modifiers = modifiers;
182 enum_keyword = kw;
183 enum_name = name;
184 enum_colon = colon_kw;
185 enum_base = base;
186 enum_type;
187 enum_left_brace = left_b;
188 enum_use_clauses;
189 enum_enumerators = enumerators;
190 enum_right_brace = right_b;
191 } ->
192 Concat
194 t env attr;
195 when_present attr newline;
196 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
197 t env kw;
198 Space;
199 t env name;
200 t env colon_kw;
201 Space;
202 SplitWith Cost.Base;
203 Nest [Space; t env base; Space; t env enum_type; Space];
204 braced_block_nest
206 left_b
207 right_b
209 handle_possible_list env enum_use_clauses;
210 handle_possible_list env enumerators;
212 Newline;
214 | Syntax.Enumerator
216 enumerator_name = name;
217 enumerator_equal = eq_kw;
218 enumerator_value = value;
219 enumerator_semicolon = semi;
220 } ->
221 let value = t env value in
222 Concat
224 t env name;
225 Space;
226 t env eq_kw;
227 Space;
228 (if has_split value then
229 SplitWith Cost.Base
230 else
231 Nothing);
232 Nest [value];
233 t env semi;
234 Newline;
236 | Syntax.EnumUse
238 enum_use_keyword = kw;
239 enum_use_names = elements;
240 enum_use_semicolon = semi;
241 } ->
242 Concat
244 t env kw;
245 (match Syntax.syntax elements with
246 | Syntax.SyntaxList [x] -> Concat [Space; t env x]
247 | Syntax.SyntaxList _ ->
248 WithRule
249 ( Rule.Parental,
250 Nest
251 [handle_possible_list env ~before_each:space_split elements]
253 | _ -> Concat [Space; t env elements]);
254 t env semi;
255 Newline;
257 | Syntax.AliasDeclaration
259 alias_attribute_spec = attr;
260 alias_modifiers = modifiers;
261 alias_module_kw_opt = mkw_opt;
262 alias_keyword = kw;
263 alias_name = name;
264 alias_generic_parameter = generic;
265 alias_constraint = type_constraint;
266 alias_equal = eq_kw;
267 alias_type = ty;
268 alias_semicolon = semi;
269 } ->
270 (* TODO: revisit this for long names *)
271 Concat
273 t env attr;
274 when_present attr newline;
275 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
276 t env mkw_opt;
277 when_present mkw_opt space;
278 t env kw;
279 Space;
280 t env name;
281 t env generic;
282 Space;
283 handle_possible_list env type_constraint;
284 when_present eq_kw (function () ->
285 Concat
287 Space; t env eq_kw; Space; SplitWith Cost.Base; Nest [t env ty];
289 t env semi;
290 Newline;
292 | Syntax.ContextAliasDeclaration
294 ctx_alias_attribute_spec = attr;
295 ctx_alias_keyword = kw;
296 ctx_alias_name = name;
297 ctx_alias_generic_parameter = generic;
298 ctx_alias_as_constraint = type_constraint;
299 ctx_alias_equal = eq_kw;
300 ctx_alias_context = ty;
301 ctx_alias_semicolon = semi;
302 } ->
303 (* TODO: revisit this for long names *)
304 Concat
306 t env attr;
307 when_present attr newline;
308 t env kw;
309 Space;
310 t env name;
311 t env generic;
312 Space;
313 handle_possible_list env type_constraint;
314 when_present eq_kw (function () ->
315 Concat
317 Space; t env eq_kw; Space; SplitWith Cost.Base; Nest [t env ty];
319 t env semi;
320 Newline;
322 | Syntax.PropertyDeclaration
324 property_attribute_spec = attr;
325 property_modifiers = modifiers;
326 property_type = prop_type;
327 property_declarators = declarators;
328 property_semicolon = semi;
329 } ->
330 let declaration =
331 Concat
333 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
334 t env prop_type;
335 handle_declarator_list env declarators;
336 t env semi;
337 Newline;
340 if Syntax.is_missing attr then
341 declaration
342 else
343 WithLazyRule
344 ( Rule.Parental,
345 handle_attribute_spec env attr ~always_split:false,
346 Concat [Space; Split; declaration] )
347 | Syntax.NamespaceDeclaration
348 { namespace_header = header; namespace_body = body } ->
349 Concat [t env header; t env body; Newline]
350 | Syntax.NamespaceDeclarationHeader
351 { namespace_keyword = kw; namespace_name = name } ->
352 Concat [t env kw; Space; t env name]
353 | Syntax.NamespaceBody
355 namespace_left_brace = left_b;
356 namespace_declarations = decls;
357 namespace_right_brace = right_b;
358 } ->
359 Concat
361 Space;
362 braced_block_nest env left_b right_b [handle_possible_list env decls];
364 | Syntax.NamespaceEmptyBody { namespace_semicolon = semi } ->
365 Concat [t env semi]
366 | Syntax.NamespaceUseDeclaration
368 namespace_use_keyword = kw;
369 namespace_use_kind = use_kind;
370 namespace_use_clauses = clauses;
371 namespace_use_semicolon = semi;
372 } ->
373 Concat
375 t env kw;
376 Space;
377 t env use_kind;
378 when_present use_kind space;
379 WithRule
380 ( Rule.Parental,
381 Nest
383 handle_possible_list
385 clauses
386 ~after_each:after_each_argument;
387 ] );
388 t env semi;
389 Newline;
391 | Syntax.NamespaceGroupUseDeclaration
393 namespace_group_use_keyword = kw;
394 namespace_group_use_kind = use_kind;
395 namespace_group_use_prefix = prefix;
396 namespace_group_use_left_brace = left_b;
397 namespace_group_use_clauses = clauses;
398 namespace_group_use_right_brace = right_b;
399 namespace_group_use_semicolon = semi;
400 } ->
401 Concat
403 t env kw;
404 Space;
405 t env use_kind;
406 when_present use_kind space;
407 t env prefix;
408 transform_argish env left_b clauses right_b;
409 t env semi;
410 Newline;
412 | Syntax.NamespaceUseClause
414 namespace_use_clause_kind = use_kind;
415 namespace_use_name = name;
416 namespace_use_as = as_kw;
417 namespace_use_alias = alias;
418 } ->
419 Concat
421 t env use_kind;
422 when_present use_kind space;
423 t env name;
424 when_present as_kw space;
425 t env as_kw;
426 when_present alias space;
427 t env alias;
429 | Syntax.FunctionDeclaration
431 function_attribute_spec = attr;
432 function_declaration_header = header;
433 function_body = body;
434 } ->
435 Concat
437 t env attr;
438 when_present attr newline;
439 t env header;
440 handle_possible_compound_statement env ~allow_collapse:true body;
441 Newline;
443 | Syntax.FunctionDeclarationHeader
445 function_modifiers = modifiers;
446 function_keyword = kw;
447 function_name = name;
448 function_type_parameter_list = type_params;
449 function_left_paren = leftp;
450 function_parameter_list = params;
451 function_right_paren = rightp;
452 function_contexts = ctxs;
453 function_colon = colon;
454 function_readonly_return = readonly_return;
455 function_type = ret_type;
456 function_where_clause = where;
457 } ->
458 Concat
460 Span (transform_fn_decl_name env modifiers kw name type_params leftp);
461 transform_fn_decl_args env params rightp;
462 t env ctxs;
463 t env colon;
464 when_present colon space;
465 t env readonly_return;
466 when_present readonly_return space;
467 t env ret_type;
468 when_present where space;
469 t env where;
471 | Syntax.WhereClause
472 { where_clause_keyword = where; where_clause_constraints = constraints }
474 Concat
476 WithRule
477 ( Rule.Parental,
478 Concat
480 Space;
481 Split;
482 t env where;
483 Nest
485 handle_possible_list
487 constraints
488 ~before_each:space_split
489 ~handle_last:
490 (transform_last_arg env ~allow_trailing:false)
491 ~handle_element:(transform_argish_item env);
493 ] );
495 | Syntax.WhereConstraint
497 where_constraint_left_type = left;
498 where_constraint_operator = op;
499 where_constraint_right_type = right;
500 } ->
501 Concat [t env left; Space; t env op; Space; t env right]
502 | Syntax.TypeRefinement
504 type_refinement_type = ty;
505 type_refinement_keyword = kw;
506 type_refinement_left_brace = left;
507 type_refinement_members = members;
508 type_refinement_right_brace = right;
509 } ->
510 Concat
512 t env ty;
513 Space;
514 t env kw;
515 Space;
516 Nest
518 Span
520 t env left;
521 handle_possible_list
523 ~before_each:space_split
524 ~after_each:(fun last ->
525 if last then
526 Space
527 else
528 Nothing)
529 members;
530 t env right;
534 | Syntax.TypeInRefinement
536 type_in_refinement_keyword = kw;
537 type_in_refinement_name = name;
538 type_in_refinement_type_parameters = type_params;
539 type_in_refinement_constraints = constraints;
540 type_in_refinement_equal = eq;
541 type_in_refinement_type = eq_bound;
543 | Syntax.CtxInRefinement
545 ctx_in_refinement_keyword = kw;
546 ctx_in_refinement_name = name;
547 ctx_in_refinement_type_parameters = type_params;
548 ctx_in_refinement_constraints = constraints;
549 ctx_in_refinement_equal = eq;
550 ctx_in_refinement_ctx_list = eq_bound;
551 } ->
552 Span
554 t env kw;
555 Space;
556 t env name;
557 t env type_params;
558 handle_possible_list env ~before_each:(fun _ -> Space) constraints;
559 when_present eq space;
560 t env eq;
561 when_present eq_bound (fun _ ->
562 Concat [Space; SplitWith Cost.Moderate; Nest [t env eq_bound]]);
564 | Syntax.Contexts
566 contexts_left_bracket = lb;
567 contexts_types = tys;
568 contexts_right_bracket = rb;
569 } ->
570 transform_argish env lb tys rb
571 | Syntax.FunctionCtxTypeSpecifier
572 { function_ctx_type_keyword = kw; function_ctx_type_variable = var } ->
573 Concat [t env kw; Space; t env var]
574 | Syntax.MethodishDeclaration
576 methodish_attribute = attr;
577 methodish_function_decl_header = func_decl;
578 methodish_function_body = body;
579 methodish_semicolon = semi;
580 } ->
581 Concat
583 t env attr;
584 when_present attr newline;
585 t env func_decl;
586 when_present body (fun () ->
587 handle_possible_compound_statement env ~allow_collapse:true body);
588 t env semi;
589 Newline;
591 | Syntax.MethodishTraitResolution
593 methodish_trait_attribute = attr;
594 methodish_trait_function_decl_header = func_decl;
595 methodish_trait_equal = equal;
596 methodish_trait_name = name;
597 methodish_trait_semicolon = semi;
598 } ->
599 Concat
601 t env attr;
602 when_present attr newline;
603 t env func_decl;
604 t env equal;
605 t env name;
606 t env semi;
607 Newline;
609 | Syntax.ClassishDeclaration
611 classish_attribute = attr;
612 classish_modifiers = modifiers;
613 classish_xhp = xhp;
614 classish_keyword = kw;
615 classish_name = name;
616 classish_type_parameters = type_params;
617 classish_extends_keyword = extends_kw;
618 classish_extends_list = extends;
619 classish_implements_keyword = impl_kw;
620 classish_implements_list = impls;
621 classish_where_clause = where;
622 classish_body = body;
623 } ->
624 let after_each_ancestor is_last =
625 if is_last then
626 Nothing
627 else
628 space_split ()
630 Concat
632 t env attr;
633 when_present attr newline;
634 Span
636 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
637 t env xhp;
638 when_present xhp space;
639 t env kw;
640 Space;
641 t env name;
642 t env type_params;
644 WithRule
645 ( Rule.Parental,
646 Concat
648 when_present extends_kw (fun () ->
649 Nest
651 Space;
652 Split;
653 t env extends_kw;
654 WithRule
655 ( Rule.Parental,
656 Nest
658 Span
660 Space;
661 (if list_length extends = 1 then
662 SplitWith Cost.Base
663 else
664 Split);
665 Nest
667 handle_possible_list
669 ~after_each:after_each_ancestor
670 extends;
673 ] );
675 when_present impl_kw (fun () ->
676 Nest
678 Space;
679 Split;
680 t env impl_kw;
681 WithRule
682 ( Rule.Parental,
683 Nest
685 Span
687 Space;
688 (if list_length impls = 1 then
689 SplitWith Cost.Base
690 else
691 Split);
692 Nest
694 handle_possible_list
696 ~after_each:after_each_ancestor
697 impls;
700 ] );
702 when_present where space;
703 t env where;
704 ] );
705 t env body;
707 | Syntax.ClassishBody
709 classish_body_left_brace = left_b;
710 classish_body_elements = body;
711 classish_body_right_brace = right_b;
712 } ->
713 Concat
715 Space;
716 braced_block_nest env left_b right_b [handle_possible_list env body];
717 Newline;
719 | Syntax.TraitUse
721 trait_use_keyword = kw;
722 trait_use_names = elements;
723 trait_use_semicolon = semi;
724 } ->
725 Concat
727 t env kw;
728 (match Syntax.syntax elements with
729 | Syntax.SyntaxList [x] -> Concat [Space; t env x]
730 | Syntax.SyntaxList _ ->
731 WithRule
732 ( Rule.Parental,
733 Nest
734 [handle_possible_list env ~before_each:space_split elements]
736 | _ -> Concat [Space; t env elements]);
737 t env semi;
738 Newline;
740 | Syntax.RequireClause
742 require_keyword = kw;
743 require_kind = kind;
744 require_name = name;
745 require_semicolon = semi;
746 } ->
747 let name = t env name in
748 Concat
750 t env kw;
751 Space;
752 t env kind;
753 Space;
754 (if has_split name then
755 SplitWith Cost.High
756 else
757 Nothing);
758 Nest [name; t env semi];
759 Newline;
761 | Syntax.ConstDeclaration
763 const_attribute_spec = attr;
764 const_modifiers = modifiers;
765 const_keyword = kw;
766 const_type_specifier = const_type;
767 const_declarators = declarators;
768 const_semicolon = semi;
769 } ->
770 Concat
772 t env attr;
773 when_present attr newline;
774 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
775 t env kw;
776 when_present const_type space;
777 t env const_type;
778 handle_declarator_list env declarators;
779 t env semi;
780 Newline;
782 | Syntax.TypeConstDeclaration
784 type_const_attribute_spec = attr;
785 type_const_modifiers = modifiers;
786 type_const_keyword = kw;
787 type_const_type_keyword = type_kw;
788 type_const_name = name;
789 type_const_type_parameters = type_params;
790 type_const_type_constraints = type_constraints;
791 type_const_equal = eq;
792 type_const_type_specifier = type_spec;
793 type_const_semicolon = semi;
794 } ->
795 Concat
797 t env attr;
798 when_present attr newline;
799 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
800 Space;
801 t env kw;
802 Space;
803 t env type_kw;
804 Space;
805 t env name;
806 t env type_params;
807 handle_possible_list
809 ~before_each:(fun _ -> Space)
810 type_constraints;
811 when_present eq space;
812 t env eq;
813 when_present type_spec (fun _ ->
814 Concat [Space; SplitWith Cost.Base; Nest [t env type_spec]]);
815 t env semi;
816 Newline;
818 | Syntax.ContextConstDeclaration
820 context_const_modifiers = modifiers;
821 context_const_const_keyword = kw;
822 context_const_ctx_keyword = ctx_kw;
823 context_const_name = name;
824 context_const_type_parameters = type_params;
825 context_const_constraint = constraint_list;
826 context_const_equal = eq;
827 context_const_ctx_list = ctx_list;
828 context_const_semicolon = semi;
829 } ->
830 Concat
832 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
833 Space;
834 t env kw;
835 Space;
836 t env ctx_kw;
837 Space;
838 t env name;
839 t env type_params;
840 when_present constraint_list space;
841 handle_possible_list
843 ~after_each:(fun is_last ->
844 if is_last then
845 Nothing
846 else
847 Space)
848 constraint_list;
849 when_present eq space;
850 t env eq;
851 when_present ctx_list (fun _ ->
852 Concat [Space; SplitWith Cost.Base; Nest [t env ctx_list]]);
853 t env semi;
854 Newline;
856 | Syntax.ParameterDeclaration
858 parameter_attribute = attr;
859 parameter_visibility = visibility;
860 parameter_call_convention = callconv;
861 parameter_readonly = readonly;
862 parameter_type = param_type;
863 parameter_name = name;
864 parameter_default_value = default;
865 } ->
866 Concat
868 handle_attribute_spec env attr ~always_split:false;
869 when_present attr (fun _ -> Concat [Space; SplitWith Cost.Base]);
870 t env visibility;
871 when_present visibility space;
872 t env callconv;
873 when_present callconv space;
874 t env readonly;
875 when_present readonly space;
876 t env param_type;
878 Syntax.is_missing visibility
879 && Syntax.is_missing callconv
880 && Syntax.is_missing param_type
881 then
882 t env name
883 else
884 Concat [Space; SplitWith Cost.Moderate; Nest [t env name]]);
885 t env default;
887 | Syntax.VariadicParameter
889 variadic_parameter_call_convention = callconv;
890 variadic_parameter_type = type_var;
891 variadic_parameter_ellipsis = ellipsis;
892 } ->
893 Concat
895 t env callconv;
896 when_present callconv space;
897 t env type_var;
898 t env ellipsis;
900 | Syntax.FileAttributeSpecification
902 file_attribute_specification_left_double_angle = left_da;
903 file_attribute_specification_keyword = keyword;
904 file_attribute_specification_colon = colon;
905 file_attribute_specification_attributes = attrs;
906 file_attribute_specification_right_double_angle = right_da;
907 } ->
908 Concat
910 t env left_da;
911 t env keyword;
912 t env colon;
913 when_present colon space;
914 transform_possible_comma_list env ~allow_trailing:false attrs right_da;
915 Newline;
917 | Syntax.OldAttributeSpecification _
918 | Syntax.AttributeSpecification _ ->
919 handle_attribute_spec env node ~always_split:true
920 | Syntax.Attribute { attribute_at = at; attribute_attribute_name = attr } ->
921 Concat [t env at; t env attr]
922 | Syntax.AttributizedSpecifier
924 attributized_specifier_attribute_spec = attr_spec;
925 attributized_specifier_type = attr_type;
926 } ->
927 Concat
929 handle_attribute_spec env attr_spec ~always_split:false;
930 Space;
931 t env attr_type;
933 | Syntax.InclusionExpression
934 { inclusion_require = kw; inclusion_filename = expr } ->
935 Concat
937 t env kw;
938 (match Syntax.syntax expr with
939 | Syntax.ParenthesizedExpression _ -> Nothing
940 | _ -> Space);
941 SplitWith Cost.Base;
942 t env expr;
944 | Syntax.InclusionDirective
945 { inclusion_expression = expr; inclusion_semicolon = semi } ->
946 Concat [t env expr; t env semi; Newline]
947 | Syntax.CompoundStatement
948 { compound_left_brace; compound_statements; compound_right_brace } ->
949 Concat
951 handle_compound_statement
953 compound_left_brace
954 compound_statements
955 compound_right_brace;
956 Newline;
958 | Syntax.UnsetStatement
960 unset_keyword = kw;
961 unset_left_paren = left_p;
962 unset_variables = args;
963 unset_right_paren = right_p;
964 unset_semicolon = semi;
965 } ->
966 Concat
968 t env kw;
969 transform_argish env ~allow_trailing:false left_p args right_p;
970 t env semi;
971 Newline;
973 | Syntax.WhileStatement x ->
974 Concat
976 t env x.while_keyword;
977 Space;
978 t env x.while_left_paren;
979 Split;
980 WithRule
981 ( Rule.Parental,
982 Concat
984 Nest [t env x.while_condition];
985 Split;
986 t env x.while_right_paren;
987 ] );
988 handle_possible_compound_statement env x.while_body;
989 Newline;
991 | Syntax.UsingStatementBlockScoped x ->
992 Concat
994 t env x.using_block_await_keyword;
995 when_present x.using_block_await_keyword space;
996 t env x.using_block_using_keyword;
997 Space;
998 t env x.using_block_left_paren;
999 Split;
1000 WithRule
1001 ( Rule.Parental,
1002 Concat
1004 Nest
1006 handle_possible_list
1008 ~after_each:separate_with_space_split
1009 x.using_block_expressions;
1011 Split;
1012 t env x.using_block_right_paren;
1013 ] );
1014 handle_possible_compound_statement env x.using_block_body;
1015 Newline;
1017 | Syntax.UsingStatementFunctionScoped x ->
1018 Concat
1020 t env x.using_function_await_keyword;
1021 when_present x.using_function_await_keyword space;
1022 t env x.using_function_using_keyword;
1023 Space;
1024 t env x.using_function_expression;
1025 t env x.using_function_semicolon;
1026 Newline;
1028 | Syntax.IfStatement
1030 if_keyword = kw;
1031 if_left_paren = left_p;
1032 if_condition = condition;
1033 if_right_paren = right_p;
1034 if_statement = if_body;
1035 if_else_clause = else_clause;
1036 } ->
1037 Concat
1039 t env kw;
1040 Space;
1041 transform_condition env left_p condition right_p;
1042 transform_consequence t env if_body right_p;
1043 t env else_clause;
1044 Newline;
1046 | Syntax.ElseClause x ->
1047 Concat
1049 t env x.else_keyword;
1050 (match Syntax.syntax x.else_statement with
1051 | Syntax.IfStatement _ ->
1052 Concat [Space; t env x.else_statement; Space]
1053 | _ -> transform_consequence t env x.else_statement x.else_keyword);
1055 | Syntax.TryStatement
1057 try_keyword = kw;
1058 try_compound_statement = body;
1059 try_catch_clauses = catch_clauses;
1060 try_finally_clause = finally_clause;
1061 } ->
1062 (* TODO: revisit *)
1063 Concat
1065 t env kw;
1066 handle_possible_compound_statement env body;
1067 handle_possible_list env catch_clauses;
1068 t env finally_clause;
1069 Newline;
1071 | Syntax.CatchClause
1073 catch_keyword = kw;
1074 catch_left_paren = left_p;
1075 catch_type = ex_type;
1076 catch_variable = var;
1077 catch_right_paren = right_p;
1078 catch_body = body;
1079 } ->
1080 Concat
1082 t env kw;
1083 Space;
1084 delimited_nest
1086 left_p
1087 right_p
1088 [t env ex_type; Space; SplitWith Cost.Base; Nest [t env var]];
1089 handle_possible_compound_statement env body;
1091 | Syntax.FinallyClause { finally_keyword = kw; finally_body = body } ->
1092 Concat [t env kw; Space; handle_possible_compound_statement env body]
1093 | Syntax.DoStatement
1095 do_keyword = do_kw;
1096 do_body = body;
1097 do_while_keyword = while_kw;
1098 do_left_paren = left_p;
1099 do_condition = cond;
1100 do_right_paren = right_p;
1101 do_semicolon = semi;
1102 } ->
1103 Concat
1105 t env do_kw;
1106 Space;
1107 handle_possible_compound_statement env body;
1108 t env while_kw;
1109 Space;
1110 transform_condition env left_p cond right_p;
1111 t env semi;
1112 Newline;
1114 | Syntax.ForStatement
1116 for_keyword = kw;
1117 for_left_paren = left_p;
1118 for_initializer = init;
1119 for_first_semicolon = semi1;
1120 for_control = control;
1121 for_second_semicolon = semi2;
1122 for_end_of_loop = after_iter;
1123 for_right_paren = right_p;
1124 for_body = body;
1125 } ->
1126 Concat
1128 t env kw;
1129 Space;
1130 t env left_p;
1131 WithRule
1132 ( Rule.Parental,
1133 Concat
1135 Split;
1136 Nest
1138 handle_possible_list
1140 ~after_each:separate_with_space_split
1141 init;
1142 t env semi1;
1143 Space;
1144 Split;
1145 handle_possible_list
1147 ~after_each:separate_with_space_split
1148 control;
1149 t env semi2;
1150 Space;
1151 Split;
1152 handle_possible_list
1154 ~after_each:separate_with_space_split
1155 after_iter;
1157 Split;
1158 t env right_p;
1159 ] );
1160 handle_possible_compound_statement env body;
1161 Newline;
1163 | Syntax.ForeachStatement
1165 foreach_keyword = kw;
1166 foreach_left_paren = left_p;
1167 foreach_collection = collection;
1168 foreach_await_keyword = await_kw;
1169 foreach_as = as_kw;
1170 foreach_key = key;
1171 foreach_arrow = arrow;
1172 foreach_value = value;
1173 foreach_right_paren = right_p;
1174 foreach_body = body;
1175 } ->
1176 Concat
1178 t env kw;
1179 Space;
1180 delimited_nest
1182 left_p
1183 right_p
1185 t env collection;
1186 Space;
1187 t env await_kw;
1188 Space;
1189 t env as_kw;
1190 Space;
1191 SplitWith Cost.Base;
1192 Nest
1194 Span
1196 t env key;
1197 Space;
1198 t env arrow;
1199 Space;
1200 SplitWith Cost.Base;
1201 Nest [t env value];
1205 handle_possible_compound_statement env body;
1206 Newline;
1208 | Syntax.SwitchStatement
1210 switch_keyword = kw;
1211 switch_left_paren = left_p;
1212 switch_expression = expr;
1213 switch_right_paren = right_p;
1214 switch_left_brace = left_b;
1215 switch_sections = sections;
1216 switch_right_brace = right_b;
1217 } ->
1218 let sections = Syntax.syntax_node_to_list sections in
1219 Concat
1221 t env kw;
1222 Space;
1223 delimited_nest env left_p right_p [t env expr];
1224 Space;
1225 braced_block_nest env left_b right_b (List.map sections ~f:(t env));
1226 Newline;
1228 | Syntax.SwitchSection
1230 switch_section_labels = labels;
1231 switch_section_statements = statements;
1232 switch_section_fallthrough = fallthrough;
1233 } ->
1234 (* If there is FallThrough trivia leading the first case label, handle it
1235 * in a BlockNest so that it is indented to the same level as the previous
1236 * SwitchSection's statements. *)
1237 let (labels_leading, labels) = remove_leading_trivia labels in
1238 let (after_fallthrough, upto_fallthrough) =
1239 List.split_while (List.rev labels_leading) ~f:(fun t ->
1240 not (is_trivia_kind_fallthrough (Trivia.kind t)))
1242 let upto_fallthrough = List.rev upto_fallthrough in
1243 let after_fallthrough = List.rev after_fallthrough in
1244 let labels = Syntax.syntax_node_to_list labels in
1245 let statements = Syntax.syntax_node_to_list statements in
1246 (* When the statements in the SwitchSection are wrapped in a single
1247 * CompoundStatement, special-case the opening curly brace to appear on
1248 * the same line as the case label. *)
1249 let is_scoped_section =
1250 match statements with
1251 | [Syntax.{ syntax = CompoundStatement _; _ }] -> true
1252 | _ -> false
1254 Concat
1256 (if List.is_empty upto_fallthrough then
1257 transform_leading_trivia after_fallthrough
1258 else
1259 Concat
1261 BlockNest [transform_leading_trivia upto_fallthrough; Newline];
1262 transform_trailing_trivia after_fallthrough;
1264 handle_list env labels ~after_each:(fun is_last_label ->
1265 if is_last_label && is_scoped_section then
1266 Nothing
1267 else
1268 Newline);
1269 (if is_scoped_section then
1270 handle_list env statements
1271 else
1272 BlockNest [handle_list env statements]);
1273 t env fallthrough;
1275 | Syntax.CaseLabel
1276 { case_keyword = kw; case_expression = expr; case_colon = colon } ->
1277 Concat [t env kw; Space; t env expr; t env colon]
1278 | Syntax.DefaultLabel { default_keyword = kw; default_colon = colon } ->
1279 Concat [t env kw; t env colon]
1280 | Syntax.SwitchFallthrough
1281 { fallthrough_keyword = kw; fallthrough_semicolon = semi } ->
1282 Concat [t env kw; t env semi]
1283 | Syntax.ReturnStatement
1285 return_keyword = kw;
1286 return_expression = expr;
1287 return_semicolon = semi;
1288 } ->
1289 transform_keyword_expression_statement env kw expr semi
1290 | Syntax.YieldBreakStatement
1292 yield_break_keyword = kw;
1293 yield_break_break = y;
1294 yield_break_semicolon = semi;
1295 } ->
1296 Concat [t env kw; Space; t env y; t env semi]
1297 | Syntax.ThrowStatement
1298 { throw_keyword = kw; throw_expression = expr; throw_semicolon = semi }
1300 transform_keyword_expression_statement env kw expr semi
1301 | Syntax.BreakStatement { break_keyword = kw; break_semicolon = semi }
1302 | Syntax.ContinueStatement
1303 { continue_keyword = kw; continue_semicolon = semi } ->
1304 Concat [t env kw; t env semi; Newline]
1305 | Syntax.EchoStatement
1307 echo_keyword = kw;
1308 echo_expressions = expr_list;
1309 echo_semicolon = semi;
1310 } ->
1311 (match Syntax.syntax expr_list with
1312 | Syntax.SyntaxList
1313 [Syntax.{ syntax = ListItem { list_item = expr; _ }; _ }]
1314 when is_syntax_kind_parenthesized_exprression (Syntax.kind expr) ->
1315 Concat [t env kw; t env expr; t env semi; Newline]
1316 | _ -> transform_keyword_expr_list_statement env kw expr_list semi)
1317 | Syntax.ConcurrentStatement
1318 { concurrent_keyword = kw; concurrent_statement = statement } ->
1319 Concat
1321 t env kw;
1322 Space;
1323 handle_possible_compound_statement env statement;
1324 Newline;
1326 | Syntax.SimpleInitializer
1327 { simple_initializer_equal = eq_kw; simple_initializer_value = value }
1329 Concat
1330 [Space; t env eq_kw; Space; SplitWith Cost.Base; Nest [t env value]]
1331 | Syntax.AnonymousFunction
1333 anonymous_attribute_spec = attr;
1334 anonymous_async_keyword = async_kw;
1335 anonymous_function_keyword = fun_kw;
1336 anonymous_left_paren = lp;
1337 anonymous_parameters = params;
1338 anonymous_right_paren = rp;
1339 anonymous_ctx_list = ctx_list;
1340 anonymous_colon = colon;
1341 anonymous_readonly_return = readonly_ret;
1342 anonymous_type = ret_type;
1343 anonymous_use = use;
1344 anonymous_body = body;
1345 } ->
1346 Concat
1348 handle_attribute_spec env attr ~always_split:false;
1349 when_present attr space;
1350 t env async_kw;
1351 when_present async_kw space;
1352 t env fun_kw;
1353 transform_argish_with_return_type
1356 params
1358 ctx_list
1359 colon
1360 readonly_ret
1361 ret_type;
1362 t env use;
1363 handle_possible_compound_statement
1365 ~space:false
1366 ~allow_collapse:true
1367 body;
1369 | Syntax.AnonymousFunctionUseClause
1371 anonymous_use_keyword = kw;
1372 anonymous_use_left_paren = left_p;
1373 anonymous_use_variables = vars;
1374 anonymous_use_right_paren = right_p;
1375 } ->
1376 (* TODO: Revisit *)
1377 Concat [Space; t env kw; Space; transform_argish env left_p vars right_p]
1378 | Syntax.LambdaExpression
1380 lambda_attribute_spec = attr;
1381 lambda_async = async;
1382 lambda_signature = signature;
1383 lambda_arrow = arrow;
1384 lambda_body = body;
1385 } ->
1386 Concat
1388 handle_attribute_spec env attr ~always_split:false;
1389 when_present attr space;
1390 t env async;
1391 when_present async space;
1392 t env signature;
1393 Space;
1394 t env arrow;
1395 handle_lambda_body env body;
1397 | Syntax.LambdaSignature
1399 lambda_left_paren = lp;
1400 lambda_parameters = params;
1401 lambda_right_paren = rp;
1402 lambda_contexts = ctxs;
1403 lambda_colon = colon;
1404 lambda_readonly_return = readonly;
1405 lambda_type = ret_type;
1406 } ->
1407 Concat
1409 t env lp;
1410 when_present params split;
1411 transform_fn_decl_args env params rp;
1412 t env ctxs;
1413 t env colon;
1414 when_present colon space;
1415 t env readonly;
1416 when_present readonly space;
1417 t env ret_type;
1419 | Syntax.CastExpression _ ->
1420 Span (List.map (Syntax.children node) ~f:(t env))
1421 | Syntax.MemberSelectionExpression _
1422 | Syntax.SafeMemberSelectionExpression _ ->
1423 handle_possible_chaining env node
1424 | Syntax.YieldExpression { yield_keyword = kw; yield_operand = operand } ->
1425 Concat [t env kw; Space; SplitWith Cost.Base; Nest [t env operand]]
1426 | Syntax.PrefixUnaryExpression
1427 { prefix_unary_operator = operator; prefix_unary_operand = operand } ->
1428 Concat
1430 t env operator;
1431 (match Syntax.syntax operator with
1432 | Syntax.Token x ->
1433 let is_parenthesized =
1434 match Syntax.syntax operand with
1435 | Syntax.ParenthesizedExpression _ -> true
1436 | _ -> false
1438 TokenKind.(
1439 (match Token.kind x with
1440 | Await
1441 | Readonly
1442 | Clone ->
1443 Space
1444 | Print ->
1445 if is_parenthesized then
1446 Nothing
1447 else
1448 Space
1449 | _ -> Nothing))
1450 | _ -> Nothing);
1451 t env operand;
1453 | Syntax.BinaryExpression
1454 { binary_left_operand; binary_operator; binary_right_operand } ->
1455 transform_binary_expression
1457 ~is_nested:false
1458 (binary_left_operand, binary_operator, binary_right_operand)
1459 | Syntax.IsExpression
1460 { is_left_operand = left; is_operator = kw; is_right_operand = right }
1461 | Syntax.AsExpression
1462 { as_left_operand = left; as_operator = kw; as_right_operand = right }
1463 | Syntax.NullableAsExpression
1465 nullable_as_left_operand = left;
1466 nullable_as_operator = kw;
1467 nullable_as_right_operand = right;
1469 | Syntax.UpcastExpression
1471 upcast_left_operand = left;
1472 upcast_operator = kw;
1473 upcast_right_operand = right;
1474 } ->
1475 Concat
1477 t env left;
1478 Space;
1479 SplitWith Cost.Base;
1480 Nest [t env kw; Space; t env right];
1482 | Syntax.ConditionalExpression
1484 conditional_test = test_expr;
1485 conditional_question = q_kw;
1486 conditional_consequence = true_expr;
1487 conditional_colon = c_kw;
1488 conditional_alternative = false_expr;
1489 } ->
1490 WithLazyRule
1491 ( Rule.Parental,
1492 t env test_expr,
1493 Nest
1495 Space;
1496 Split;
1497 t env q_kw;
1498 when_present true_expr (fun () ->
1499 Concat
1501 Space;
1502 (if env.Env.indent_width = 2 then
1503 Nest [t env true_expr]
1504 else
1505 t env true_expr);
1506 Space;
1507 Split;
1509 t env c_kw;
1510 Space;
1512 (not (Syntax.is_missing true_expr)) && env.Env.indent_width = 2
1513 then
1514 Nest [t env false_expr]
1515 else
1516 t env false_expr);
1518 | Syntax.FunctionCallExpression _ -> handle_possible_chaining env node
1519 | Syntax.FunctionPointerExpression _ -> transform_simple env node
1520 | Syntax.EvalExpression
1522 eval_keyword = kw;
1523 eval_left_paren = left_p;
1524 eval_argument = arg;
1525 eval_right_paren = right_p;
1526 } ->
1527 Concat [t env kw; transform_braced_item env left_p arg right_p]
1528 | Syntax.IssetExpression
1530 isset_keyword = kw;
1531 isset_left_paren = left_p;
1532 isset_argument_list = args;
1533 isset_right_paren = right_p;
1534 } ->
1535 Concat
1537 t env kw;
1538 transform_argish env ~allow_trailing:false left_p args right_p;
1540 | Syntax.ParenthesizedExpression
1542 parenthesized_expression_left_paren = left_p;
1543 parenthesized_expression_expression = expr;
1544 parenthesized_expression_right_paren = right_p;
1545 } ->
1546 Concat
1548 t env left_p;
1549 Split;
1550 WithRule
1551 (Rule.Parental, Concat [Nest [t env expr]; Split; t env right_p]);
1553 | Syntax.ETSpliceExpression
1555 et_splice_expression_dollar = dollar;
1556 et_splice_expression_left_brace = left_p;
1557 et_splice_expression_expression = expr;
1558 et_splice_expression_right_brace = right_p;
1559 } ->
1560 Concat
1562 t env dollar;
1563 t env left_p;
1564 Split;
1565 WithRule
1566 (Rule.Parental, Concat [Nest [t env expr]; Split; t env right_p]);
1568 | Syntax.BracedExpression
1570 braced_expression_left_brace = left_b;
1571 braced_expression_expression = expr;
1572 braced_expression_right_brace = right_b;
1573 } ->
1574 (* TODO: revisit this *)
1575 Concat
1577 t env left_b;
1578 Split;
1579 (let rule =
1581 List.is_empty (Syntax.trailing_trivia left_b)
1582 && List.is_empty (Syntax.trailing_trivia expr)
1583 then
1584 Rule.Simple Cost.Base
1585 else
1586 Rule.Parental
1588 WithRule (rule, Concat [Nest [t env expr]; Split; t env right_b]));
1590 | Syntax.EmbeddedBracedExpression
1592 embedded_braced_expression_left_brace = left_b;
1593 embedded_braced_expression_expression = expr;
1594 embedded_braced_expression_right_brace = right_b;
1595 } ->
1596 (* TODO: Consider finding a way to avoid treating these expressions as
1597 opportunities for line breaks in long strings:
1599 $sql = "DELETE FROM `foo` WHERE `left` BETWEEN {$res->left} AND {$res
1600 ->right} ORDER BY `level` DESC";
1602 Concat [t env left_b; Nest [t env expr]; t env right_b]
1603 | Syntax.ListExpression
1605 list_keyword = kw;
1606 list_left_paren = lp;
1607 list_members = members;
1608 list_right_paren = rp;
1609 } ->
1610 Concat [t env kw; transform_argish env lp members rp]
1611 | Syntax.CollectionLiteralExpression
1613 collection_literal_name = name;
1614 collection_literal_left_brace = left_b;
1615 collection_literal_initializers = initializers;
1616 collection_literal_right_brace = right_b;
1617 } ->
1618 transform_container_literal
1620 ~space:true
1621 name
1622 left_b
1623 initializers
1624 right_b
1625 | Syntax.ObjectCreationExpression
1626 { object_creation_new_keyword = newkw; object_creation_object = what }
1628 Concat [t env newkw; Space; t env what]
1629 | Syntax.ConstructorCall
1631 constructor_call_type = obj_type;
1632 constructor_call_left_paren = left_p;
1633 constructor_call_argument_list = arg_list;
1634 constructor_call_right_paren = right_p;
1635 } ->
1636 Concat [t env obj_type; transform_argish env left_p arg_list right_p]
1637 | Syntax.AnonymousClass
1639 anonymous_class_class_keyword = classkw;
1640 anonymous_class_left_paren = left_p;
1641 anonymous_class_argument_list = arg_list;
1642 anonymous_class_right_paren = right_p;
1643 anonymous_class_extends_keyword = extends_kw;
1644 anonymous_class_extends_list = extends;
1645 anonymous_class_implements_keyword = impl_kw;
1646 anonymous_class_implements_list = impls;
1647 anonymous_class_body = body;
1648 } ->
1649 let after_each_ancestor is_last =
1650 if is_last then
1651 Nothing
1652 else
1653 space_split ()
1655 Concat
1657 t env classkw;
1658 transform_argish env left_p arg_list right_p;
1659 when_present extends_kw (fun () ->
1660 Concat
1662 Space;
1663 Split;
1664 WithRule
1665 ( Rule.Parental,
1666 Nest
1668 Span
1670 t env extends_kw;
1671 Space;
1672 Split;
1673 WithRule
1674 ( Rule.Parental,
1675 Nest
1677 handle_possible_list
1679 ~after_each:after_each_ancestor
1680 extends;
1681 ] );
1683 ] );
1685 when_present impl_kw (fun () ->
1686 Concat
1688 Space;
1689 Split;
1690 WithRule
1691 ( Rule.Parental,
1692 Nest
1694 Span
1696 t env impl_kw;
1697 Space;
1698 Split;
1699 WithRule
1700 ( Rule.Parental,
1701 Nest
1703 handle_possible_list
1705 ~after_each:after_each_ancestor
1706 impls;
1707 ] );
1709 ] );
1711 t env body;
1713 | Syntax.DarrayIntrinsicExpression
1715 darray_intrinsic_keyword = kw;
1716 darray_intrinsic_explicit_type = explicit_type;
1717 darray_intrinsic_left_bracket = left_p;
1718 darray_intrinsic_members = members;
1719 darray_intrinsic_right_bracket = right_p;
1721 | Syntax.DictionaryIntrinsicExpression
1723 dictionary_intrinsic_keyword = kw;
1724 dictionary_intrinsic_explicit_type = explicit_type;
1725 dictionary_intrinsic_left_bracket = left_p;
1726 dictionary_intrinsic_members = members;
1727 dictionary_intrinsic_right_bracket = right_p;
1729 | Syntax.KeysetIntrinsicExpression
1731 keyset_intrinsic_keyword = kw;
1732 keyset_intrinsic_explicit_type = explicit_type;
1733 keyset_intrinsic_left_bracket = left_p;
1734 keyset_intrinsic_members = members;
1735 keyset_intrinsic_right_bracket = right_p;
1737 | Syntax.VarrayIntrinsicExpression
1739 varray_intrinsic_keyword = kw;
1740 varray_intrinsic_explicit_type = explicit_type;
1741 varray_intrinsic_left_bracket = left_p;
1742 varray_intrinsic_members = members;
1743 varray_intrinsic_right_bracket = right_p;
1745 | Syntax.VectorIntrinsicExpression
1747 vector_intrinsic_keyword = kw;
1748 vector_intrinsic_explicit_type = explicit_type;
1749 vector_intrinsic_left_bracket = left_p;
1750 vector_intrinsic_members = members;
1751 vector_intrinsic_right_bracket = right_p;
1752 } ->
1753 transform_container_literal env kw ~explicit_type left_p members right_p
1754 | Syntax.ElementInitializer
1755 { element_key = key; element_arrow = arrow; element_value = value } ->
1756 transform_mapish_entry env key arrow value
1757 | Syntax.SubscriptExpression
1759 subscript_receiver = receiver;
1760 subscript_left_bracket = lb;
1761 subscript_index = expr;
1762 subscript_right_bracket = rb;
1763 } ->
1764 Concat [t env receiver; transform_braced_item env lb expr rb]
1765 | Syntax.AwaitableCreationExpression
1767 awaitable_attribute_spec = attr;
1768 awaitable_async = async_kw;
1769 awaitable_compound_statement = body;
1770 } ->
1771 Concat
1773 handle_attribute_spec env attr ~always_split:false;
1774 when_present attr space;
1775 t env async_kw;
1776 when_present async_kw space;
1777 (* TODO: rethink possible one line bodies *)
1778 (* TODO: correctly handle spacing after the closing brace *)
1779 handle_possible_compound_statement env ~space:false body;
1781 | Syntax.XHPChildrenDeclaration
1783 xhp_children_keyword = kw;
1784 xhp_children_expression = expr;
1785 xhp_children_semicolon = semi;
1786 } ->
1787 Concat [t env kw; Space; t env expr; t env semi; Newline]
1788 | Syntax.XHPChildrenParenthesizedList
1790 xhp_children_list_left_paren = left_p;
1791 xhp_children_list_xhp_children = expressions;
1792 xhp_children_list_right_paren = right_p;
1793 } ->
1794 Concat
1795 [transform_argish env ~allow_trailing:false left_p expressions right_p]
1796 | Syntax.XHPCategoryDeclaration
1798 xhp_category_keyword = kw;
1799 xhp_category_categories = categories;
1800 xhp_category_semicolon = semi;
1801 } ->
1802 Concat
1804 t env kw;
1805 (* TODO: Eliminate code duplication *)
1806 WithRule
1807 ( Rule.Parental,
1808 Nest
1809 [handle_possible_list env ~before_each:space_split categories]
1811 t env semi;
1812 Newline;
1814 | Syntax.XHPEnumType
1816 xhp_enum_like = l;
1817 xhp_enum_keyword = kw;
1818 xhp_enum_left_brace = left_b;
1819 xhp_enum_values = values;
1820 xhp_enum_right_brace = right_b;
1821 } ->
1822 Concat
1823 [t env l; t env kw; Space; transform_argish env left_b values right_b]
1824 | Syntax.XHPClassAttributeDeclaration
1826 xhp_attribute_keyword = kw;
1827 xhp_attribute_attributes = xhp_attributes;
1828 xhp_attribute_semicolon = semi;
1829 } ->
1830 Concat
1832 t env kw;
1833 (match Syntax.syntax xhp_attributes with
1834 | Syntax.Missing -> Nothing
1835 | Syntax.SyntaxList [attr] ->
1836 WithRule (Rule.Parental, Nest [Space; Split; t env attr])
1837 | Syntax.SyntaxList attrs ->
1838 Nest [handle_list env ~before_each:newline attrs]
1839 | _ -> failwith "Expected SyntaxList");
1840 t env semi;
1841 Newline;
1843 | Syntax.XHPClassAttribute
1845 xhp_attribute_decl_type = attr_type;
1846 xhp_attribute_decl_name = name;
1847 xhp_attribute_decl_initializer = init;
1848 xhp_attribute_decl_required = req;
1849 } ->
1850 (* TODO: figure out nesting here *)
1851 Concat
1853 t env attr_type;
1854 Space;
1855 t env name;
1856 when_present init space;
1857 t env init;
1858 when_present req space;
1859 t env req;
1861 | Syntax.XHPSimpleAttribute
1863 xhp_simple_attribute_name = name;
1864 xhp_simple_attribute_equal = eq;
1865 xhp_simple_attribute_expression = expr;
1866 } ->
1867 Span [t env name; t env eq; SplitWith Cost.Base; Nest [t env expr]]
1868 | Syntax.XHPSpreadAttribute
1870 xhp_spread_attribute_left_brace = l_brace;
1871 xhp_spread_attribute_spread_operator = spread;
1872 xhp_spread_attribute_expression = expr;
1873 xhp_spread_attribute_right_brace = r_brace;
1874 } ->
1875 Span
1877 t env l_brace;
1878 t env spread;
1879 SplitWith Cost.Base;
1880 Nest [t env expr];
1881 t env r_brace;
1883 | Syntax.XHPOpen
1885 xhp_open_left_angle = left_a;
1886 xhp_open_name = name;
1887 xhp_open_attributes = attrs;
1888 xhp_open_right_angle = right_a;
1889 } ->
1890 Concat
1892 t env left_a;
1893 t env name;
1894 (match Syntax.syntax attrs with
1895 | Syntax.Missing ->
1896 handle_xhp_open_right_angle_token env attrs right_a
1897 | _ ->
1898 Concat
1900 Space;
1901 Split;
1902 WithRule
1903 ( Rule.Parental,
1904 Concat
1906 Nest
1908 handle_possible_list
1910 ~after_each:(fun is_last ->
1911 if not is_last then
1912 space_split ()
1913 else
1914 Nothing)
1915 attrs;
1917 handle_xhp_open_right_angle_token env attrs right_a;
1918 ] );
1921 | Syntax.XHPExpression { xhp_open; xhp_body = body; xhp_close = close } ->
1922 let handle_xhp_body body =
1923 match Syntax.syntax body with
1924 | Syntax.Missing -> when_present close split
1925 | Syntax.SyntaxList xs ->
1926 (* Trivia is lexed differently within an XHP body because whitespace is
1927 semantically significant in an XHP body when it is adjacent to an
1928 XHPBody token. Any number of whitespaces or newlines adjacent to an
1929 XHPBody token will be rendered as a single space. In order to make it
1930 easier to determine whether a space character should be rendered next
1931 to an XHPBody token, all trailing trivia in an XHP body is lexed as
1932 leading trivia for the next token (except on XHPBody tokens, where
1933 trailing trivia is lexed normally). This ensures that any time
1934 semantically-significant whitespace is present, at least some of it
1935 occurs in the leading or trailing trivia list of an adjacent XHPBody
1936 token.
1938 To deal with this, we keep track of whether the last token we
1939 transformed was one that trailing trivia is scanned for. If it
1940 wasn't, we handle the next token's leading trivia list using
1941 transform_xhp_leading_trivia, which treats all trivia up to the first
1942 newline as trailing trivia. *)
1943 let prev_token_was_xhpbody = ref false in
1944 let transformed_body =
1945 Concat
1946 (List.map xs ~f:(fun node ->
1947 let node_is_xhpbody =
1948 match Syntax.syntax node with
1949 | Syntax.Token t -> is_token_kind_xhp_body (Token.kind t)
1950 | _ -> false
1953 (* Here, we preserve newlines after XHPBody tokens and don't otherwise
1954 add splits between them. This means that we don't reflow paragraphs
1955 in XHP to fit in the desired line length. It would be nice to do
1956 so, but this is not possible with the current set of Rule types.
1958 If we were to add a split between each XHPBody token instead of
1959 splitting only where newlines were already present, we'd need a new
1960 Rule type to govern word-wrap style splitting, since using
1961 independent splits (e.g. SplitWith Cost.Base) between every token
1962 would make solving too expensive. *)
1963 let preserve_xhpbody_whitespace trivia =
1964 if node_is_xhpbody then
1965 if has_newline trivia then
1966 Newline
1967 else if has_whitespace trivia then
1968 Space
1969 else
1970 Nothing
1971 else
1972 Nothing
1974 let (leading, node) = remove_leading_trivia node in
1975 let trailing = Syntax.trailing_trivia node in
1976 let leading_whitespace =
1977 Concat
1979 (* Whitespace in an XHP body is *only* significant when adjacent to
1980 an XHPBody token, so we are free to add splits between other
1981 nodes (like XHPExpressions and BracedExpressions). *)
1983 (not !prev_token_was_xhpbody) && not node_is_xhpbody
1984 then
1985 Split
1986 else
1987 Nothing);
1988 (* If the previous token was an XHPBody token, the lexer will have
1989 scanned trailing trivia for it, so we can handle the leading
1990 trivia for this node normally. Otherwise, handle the trivia up to
1991 the first newline as trailing trivia. *)
1992 (if !prev_token_was_xhpbody then
1993 transform_leading_trivia leading
1994 else
1995 transform_xhp_leading_trivia leading);
1998 prev_token_was_xhpbody := node_is_xhpbody;
1999 Concat
2001 leading_whitespace;
2002 preserve_xhpbody_whitespace leading;
2003 t env node;
2004 preserve_xhpbody_whitespace trailing;
2007 Concat
2009 transformed_body;
2010 (if !prev_token_was_xhpbody then
2011 Nothing
2012 else if
2013 (* Don't collapse XHPExpressions onto a single line if they were
2014 intentionally split across multiple lines in the original source.
2015 If there is a newline in the body's leading trivia, we consider
2016 that a signal that this expression was intended to be split
2017 across multiple lines. *)
2018 has_newline (Syntax.leading_trivia body)
2019 then
2020 Newline
2021 else
2022 Split);
2024 | _ -> failwith "Expected SyntaxList"
2026 WithOverridingParentalRule
2027 (Concat
2029 t env xhp_open;
2030 Nest [handle_xhp_body body];
2031 when_present close (fun () ->
2032 let (leading, close) = remove_leading_trivia close in
2033 Concat
2035 (* Ignore extra newlines by treating this as trailing trivia *)
2036 ignore_trailing_invisibles leading;
2037 t env close;
2040 | Syntax.VarrayTypeSpecifier
2042 varray_keyword = kw;
2043 varray_left_angle = left_a;
2044 varray_type;
2045 varray_trailing_comma = trailing_comma;
2046 varray_right_angle = right_a;
2047 } ->
2048 Concat
2050 t env kw;
2051 transform_braced_item_with_trailer
2053 left_a
2054 varray_type
2055 trailing_comma
2056 right_a;
2058 | Syntax.VectorTypeSpecifier
2060 vector_type_keyword = kw;
2061 vector_type_left_angle = left_a;
2062 vector_type_type = vec_type;
2063 vector_type_trailing_comma = trailing_comma;
2064 vector_type_right_angle = right_a;
2065 } ->
2066 Concat
2068 t env kw;
2069 transform_braced_item_with_trailer
2071 left_a
2072 vec_type
2073 trailing_comma
2074 right_a;
2076 | Syntax.KeysetTypeSpecifier
2078 keyset_type_keyword = kw;
2079 keyset_type_left_angle = left_a;
2080 keyset_type_type = ks_type;
2081 keyset_type_trailing_comma = trailing_comma;
2082 keyset_type_right_angle = right_a;
2083 } ->
2084 Concat
2086 t env kw;
2087 transform_braced_item_with_trailer
2089 left_a
2090 ks_type
2091 trailing_comma
2092 right_a;
2094 | Syntax.TypeParameter
2096 type_attribute_spec = attr;
2097 type_reified = reified;
2098 type_variance = variance;
2099 type_name = name;
2100 type_param_params = params;
2101 type_constraints = constraints;
2102 } ->
2103 Concat
2105 handle_attribute_spec env attr ~always_split:false;
2106 when_present attr space;
2107 t env reified;
2108 when_present reified space;
2109 t env variance;
2110 t env name;
2111 t env params;
2112 when_present constraints space;
2113 handle_possible_list env constraints ~after_each:(fun is_last ->
2114 if is_last then
2115 Nothing
2116 else
2117 Space);
2119 | Syntax.TypeConstraint { constraint_keyword = kw; constraint_type } ->
2120 Concat [t env kw; Space; t env constraint_type]
2121 | Syntax.ContextConstraint
2122 { ctx_constraint_keyword = kw; ctx_constraint_ctx_list = ctx_list } ->
2123 Concat [t env kw; Space; t env ctx_list]
2124 | Syntax.DarrayTypeSpecifier
2126 darray_keyword = kw;
2127 darray_left_angle = left_a;
2128 darray_key = key;
2129 darray_comma = comma_kw;
2130 darray_value = value;
2131 darray_trailing_comma = trailing_comma;
2132 darray_right_angle = right_a;
2133 } ->
2134 let key_list_item = Syntax.make_list_item key comma_kw in
2135 let val_list_item = Syntax.make_list_item value trailing_comma in
2136 let args = make_list [key_list_item; val_list_item] in
2137 Concat
2139 t env kw; transform_argish env ~allow_trailing:true left_a args right_a;
2141 | Syntax.DictionaryTypeSpecifier
2143 dictionary_type_keyword = kw;
2144 dictionary_type_left_angle = left_a;
2145 dictionary_type_members = members;
2146 dictionary_type_right_angle = right_a;
2147 } ->
2148 Concat [t env kw; transform_argish env left_a members right_a]
2149 | Syntax.ClosureTypeSpecifier
2151 closure_outer_left_paren = outer_left_p;
2152 closure_readonly_keyword = ro;
2153 closure_function_keyword = kw;
2154 closure_inner_left_paren = inner_left_p;
2155 closure_parameter_list = param_list;
2156 closure_inner_right_paren = inner_right_p;
2157 closure_contexts = ctxs;
2158 closure_colon = colon;
2159 closure_readonly_return = readonly;
2160 closure_return_type = ret_type;
2161 closure_outer_right_paren = outer_right_p;
2162 } ->
2163 Concat
2165 t env outer_left_p;
2166 t env ro;
2167 when_present ro space;
2168 t env kw;
2169 t env inner_left_p;
2170 when_present param_list split;
2171 transform_fn_decl_args env param_list inner_right_p;
2172 t env ctxs;
2173 t env colon;
2174 when_present colon space;
2175 t env readonly;
2176 when_present readonly space;
2177 t env ret_type;
2178 t env outer_right_p;
2180 | Syntax.ClosureParameterTypeSpecifier
2182 closure_parameter_call_convention = callconv;
2183 closure_parameter_readonly = readonly;
2184 closure_parameter_type = cp_type;
2185 } ->
2186 Concat
2188 t env callconv;
2189 when_present callconv space;
2190 t env readonly;
2191 when_present readonly space;
2192 t env cp_type;
2194 | Syntax.ClassnameTypeSpecifier
2196 classname_keyword = kw;
2197 classname_left_angle = left_a;
2198 classname_type = class_type;
2199 classname_trailing_comma = trailing_comma;
2200 classname_right_angle = right_a;
2201 } ->
2202 Concat
2204 t env kw;
2205 transform_braced_item_with_trailer
2207 left_a
2208 class_type
2209 trailing_comma
2210 right_a;
2212 | Syntax.FieldSpecifier
2214 field_question = question;
2215 field_name = name;
2216 field_arrow = arrow_kw;
2217 field_type;
2218 } ->
2219 Concat
2220 [t env question; transform_mapish_entry env name arrow_kw field_type]
2221 | Syntax.FieldInitializer
2223 field_initializer_name = name;
2224 field_initializer_arrow = arrow_kw;
2225 field_initializer_value = value;
2226 } ->
2227 transform_mapish_entry env name arrow_kw value
2228 | Syntax.ShapeTypeSpecifier
2230 shape_type_keyword = shape_kw;
2231 shape_type_left_paren = left_p;
2232 shape_type_fields = type_fields;
2233 shape_type_ellipsis = ellipsis;
2234 shape_type_right_paren = right_p;
2235 } ->
2236 let fields =
2237 if Syntax.is_missing ellipsis then
2238 type_fields
2239 else
2240 let missing_separator = make_missing () in
2241 let ellipsis_list =
2242 [Syntax.make_list_item ellipsis missing_separator]
2244 make_list (Syntax.children type_fields @ ellipsis_list)
2246 transform_container_literal
2248 shape_kw
2249 left_p
2250 fields
2251 right_p
2252 ~allow_trailing:(Syntax.is_missing ellipsis)
2253 | Syntax.ShapeExpression
2255 shape_expression_keyword = shape_kw;
2256 shape_expression_left_paren = left_p;
2257 shape_expression_fields = fields;
2258 shape_expression_right_paren = right_p;
2259 } ->
2260 transform_container_literal env shape_kw left_p fields right_p
2261 | Syntax.TupleExpression
2263 tuple_expression_keyword = kw;
2264 tuple_expression_left_paren = left_p;
2265 tuple_expression_items = items;
2266 tuple_expression_right_paren = right_p;
2267 } ->
2268 Concat [t env kw; transform_argish env left_p items right_p]
2269 | Syntax.TypeArguments
2271 type_arguments_left_angle = left_a;
2272 type_arguments_types = type_list;
2273 type_arguments_right_angle = right_a;
2274 } ->
2275 transform_argish env left_a type_list right_a
2276 | Syntax.TypeParameters
2278 type_parameters_left_angle = left_a;
2279 type_parameters_parameters = param_list;
2280 type_parameters_right_angle = right_a;
2281 } ->
2282 transform_argish env left_a param_list right_a
2283 | Syntax.TupleTypeSpecifier
2285 tuple_left_paren = left_p;
2286 tuple_types = types;
2287 tuple_right_paren = right_p;
2288 } ->
2289 transform_argish env left_p types right_p
2290 | Syntax.UnionTypeSpecifier
2292 union_left_paren = left_p;
2293 union_types = types;
2294 union_right_paren = right_p;
2295 } ->
2296 delimited_nest
2298 left_p
2299 right_p
2301 handle_possible_list
2303 types
2304 ~after_each:(fun is_last ->
2305 if is_last then
2306 Split
2307 else
2308 space_split ())
2309 ~handle_element:(fun node ->
2310 match Syntax.syntax node with
2311 | Syntax.ListItem { list_item; list_separator } ->
2312 Concat
2314 t env list_item;
2315 when_present list_separator space;
2316 t env list_separator;
2318 | _ -> t env node);
2320 | Syntax.IntersectionTypeSpecifier
2322 intersection_left_paren = left_p;
2323 intersection_types = types;
2324 intersection_right_paren = right_p;
2325 } ->
2326 delimited_nest
2328 left_p
2329 right_p
2331 handle_possible_list
2333 types
2334 ~after_each:(fun is_last ->
2335 if is_last then
2336 Split
2337 else
2338 space_split ())
2339 ~handle_element:(fun node ->
2340 match Syntax.syntax node with
2341 | Syntax.ListItem { list_item; list_separator } ->
2342 Concat
2344 t env list_item;
2345 when_present list_separator space;
2346 t env list_separator;
2348 | _ -> t env node);
2350 | Syntax.TupleTypeExplicitSpecifier
2352 tuple_type_keyword = kw;
2353 tuple_type_left_angle = left_a;
2354 tuple_type_types = types;
2355 tuple_type_right_angle = right_a;
2356 } ->
2357 Concat [t env kw; transform_argish env left_a types right_a]
2358 | Syntax.PrefixedCodeExpression
2360 prefixed_code_prefix = prefix;
2361 prefixed_code_left_backtick = left_bt;
2362 prefixed_code_expression = expression;
2363 prefixed_code_right_backtick = right_bt;
2364 } ->
2365 Concat
2366 [t env prefix; transform_braced_item env left_bt expression right_bt]
2367 | Syntax.DecoratedExpression
2369 decorated_expression_decorator = op;
2370 decorated_expression_expression = expr;
2371 } ->
2372 Concat
2374 t env op;
2375 begin
2376 match Syntax.syntax op with
2377 | Syntax.Token t when is_token_kind_in_out (Token.kind t) -> Space
2378 | _ -> Nothing
2379 end;
2380 t env expr;
2382 | Syntax.ErrorSyntax _ -> raise Hackfmt_error.InvalidSyntax
2383 | Syntax.EnumClassDeclaration
2385 enum_class_attribute_spec = attr_spec;
2386 enum_class_modifiers = modifiers;
2387 enum_class_enum_keyword = enum_kw;
2388 enum_class_class_keyword = class_kw;
2389 enum_class_name = name;
2390 enum_class_colon = colon;
2391 enum_class_base = base;
2392 enum_class_extends = extends_kw;
2393 enum_class_extends_list = extends_list;
2394 enum_class_left_brace = left_brace;
2395 enum_class_elements = elements;
2396 enum_class_right_brace = right_brace;
2397 } ->
2398 let after_each_ancestor is_last =
2399 if is_last then
2400 Nothing
2401 else
2402 space_split ()
2404 Concat
2406 t env attr_spec;
2407 when_present attr_spec newline;
2408 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
2409 t env enum_kw;
2410 Space;
2411 t env class_kw;
2412 Space;
2413 t env name;
2414 t env colon;
2415 Space;
2416 SplitWith Cost.Base;
2417 Nest [Space; t env base; Space];
2418 when_present extends_kw (fun () ->
2419 Nest
2421 Space;
2422 Split;
2423 t env extends_kw;
2424 WithRule
2425 ( Rule.Parental,
2426 Nest
2428 Span
2430 Space;
2431 (if list_length extends_list = 1 then
2432 SplitWith Cost.Base
2433 else
2434 Split);
2435 Nest
2437 handle_possible_list
2439 ~after_each:after_each_ancestor
2440 extends_list;
2443 ] );
2445 Space;
2446 braced_block_nest
2448 left_brace
2449 right_brace
2450 [handle_possible_list env elements];
2451 Newline;
2453 | Syntax.EnumClassEnumerator
2455 enum_class_enumerator_modifiers = modifiers;
2456 enum_class_enumerator_type = type_;
2457 enum_class_enumerator_name = name;
2458 enum_class_enumerator_initializer = init;
2459 enum_class_enumerator_semicolon = semicolon;
2460 } ->
2461 Concat
2463 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
2464 t env type_;
2465 when_present type_ space;
2466 t env name;
2467 t env init;
2468 t env semicolon;
2469 Newline;
2471 | Syntax.EnumClassLabelExpression _ -> transform_simple env node
2472 | Syntax.ModuleDeclaration
2474 module_declaration_attribute_spec = attr;
2475 module_declaration_new_keyword = new_kw;
2476 module_declaration_module_keyword = mod_kw;
2477 module_declaration_name = name;
2478 module_declaration_left_brace = lb;
2479 module_declaration_exports = exports;
2480 module_declaration_imports = imports;
2481 module_declaration_right_brace = rb;
2482 } ->
2483 Concat
2485 t env attr;
2486 when_present attr newline;
2487 t env new_kw;
2488 Space;
2489 t env mod_kw;
2490 Space;
2491 t env name;
2492 Space;
2493 t env lb;
2494 Newline;
2495 t env exports;
2496 when_present exports newline;
2497 t env imports;
2498 when_present imports newline;
2499 t env rb;
2500 Newline;
2502 | Syntax.ModuleExports
2504 module_exports_exports_keyword = exports_kw;
2505 module_exports_left_brace = lb;
2506 module_exports_exports = exports;
2507 module_exports_right_brace = rb;
2508 } ->
2509 Concat
2511 t env exports_kw;
2512 Space;
2513 t env lb;
2514 Newline;
2515 WithRule
2516 ( Rule.Parental,
2517 Nest
2519 handle_possible_list
2521 exports
2522 ~after_each:after_each_argument;
2523 ] );
2524 t env rb;
2525 Newline;
2527 | Syntax.ModuleImports
2529 module_imports_imports_keyword = imports_kw;
2530 module_imports_left_brace = lb;
2531 module_imports_imports = imports;
2532 module_imports_right_brace = rb;
2533 } ->
2534 Concat
2536 t env imports_kw;
2537 Space;
2538 t env lb;
2539 Newline;
2540 WithRule
2541 ( Rule.Parental,
2542 Nest
2544 handle_possible_list
2546 imports
2547 ~after_each:after_each_argument;
2548 ] );
2549 t env rb;
2550 Newline;
2552 | Syntax.ModuleMembershipDeclaration
2554 module_membership_declaration_module_keyword = mod_kw;
2555 module_membership_declaration_name = name;
2556 module_membership_declaration_semicolon = semicolon;
2557 } ->
2558 Concat [t env mod_kw; Space; t env name; t env semicolon; Newline])
2560 and when_present node f =
2561 match Syntax.syntax node with
2562 | Syntax.Missing -> Nothing
2563 | _ -> f ()
2565 and transform_simple env node =
2566 Concat (List.map (Syntax.children node) ~f:(t env))
2568 and transform_simple_statement env node =
2569 Concat (List.map (Syntax.children node) ~f:(t env) @ [Newline])
2571 and braced_block_nest env ?(allow_collapse = true) open_b close_b nodes =
2572 let nodes = Concat nodes in
2573 match (allow_collapse, has_printable_content nodes, Syntax.syntax open_b) with
2574 | (true, false, Syntax.Token ob)
2575 when List.for_all (Token.trailing ob) ~f:(fun t ->
2576 not (is_trivia_kind_end_of_line (Trivia.kind t))) ->
2577 Concat [t env open_b; t env close_b]
2578 | (true, false, Syntax.Missing) -> Concat [t env open_b; t env close_b]
2579 | _ ->
2580 (* Remove the closing brace's leading trivia and handle it inside the
2581 * BlockNest, so that comments will be indented correctly. *)
2582 let (leading, close_b) = remove_leading_trivia close_b in
2583 Concat
2585 t env open_b;
2586 Newline;
2587 BlockNest [nodes; transform_leading_trivia leading; Newline];
2588 t env close_b;
2591 and delimited_nest
2593 ?(split_when_children_split = true)
2594 ?(force_newlines = false)
2595 left_delim
2596 right_delim
2597 nodes =
2598 let rule =
2599 match () with
2600 | _ when force_newlines -> Rule.Always
2601 | _ when split_when_children_split -> Rule.Parental
2602 | _ -> Rule.Simple Cost.Base
2604 Span [t env left_delim; WithRule (rule, nest env right_delim nodes)]
2606 and nest env ?(spaces = false) right_delim nodes =
2607 (* Remove the right delimiter's leading trivia and handle it inside the
2608 * Nest, so that comments will be indented correctly. *)
2609 let (leading, right_delim) = remove_leading_trivia right_delim in
2610 let nested_contents = Nest [Concat nodes; transform_leading_trivia leading] in
2611 let content_present = has_printable_content nested_contents in
2612 let maybe_split =
2613 match (content_present, spaces) with
2614 | (false, _) -> Nothing
2615 | (true, false) -> Split
2616 | (true, true) -> space_split ()
2618 Concat [maybe_split; nested_contents; maybe_split; t env right_delim]
2620 and after_each_argument is_last =
2621 if is_last then
2622 Split
2623 else
2624 space_split ()
2626 and separate_with_space_split is_last =
2627 if is_last then
2628 Nothing
2629 else
2630 space_split ()
2632 and handle_attribute_spec env node ~always_split =
2633 match Syntax.syntax node with
2634 | Syntax.OldAttributeSpecification
2636 old_attribute_specification_left_double_angle = left_da;
2637 old_attribute_specification_attributes = attrs;
2638 old_attribute_specification_right_double_angle = right_da;
2639 } ->
2640 transform_argish env left_da attrs right_da
2641 | Syntax.AttributeSpecification { attribute_specification_attributes = attrs }
2643 handle_possible_list
2645 ~after_each:(fun _ ->
2646 if always_split then
2647 Newline
2648 else
2649 Space)
2650 attrs
2651 | Syntax.Missing -> Nothing
2652 | _ -> failwith "Attribute specification expected"
2654 and handle_lambda_body env node =
2655 match Syntax.syntax node with
2656 | Syntax.CompoundStatement
2657 { compound_left_brace; compound_statements; compound_right_brace } ->
2658 handle_compound_statement
2660 ~allow_collapse:true
2661 compound_left_brace
2662 compound_statements
2663 compound_right_brace
2664 | Syntax.XHPExpression _ ->
2665 WithRule (Rule.Parental, Concat [Space; Split; Nest [t env node]])
2666 | _ -> Concat [Space; SplitWith Cost.Base; Nest [t env node]]
2668 and handle_possible_compound_statement
2669 env ?(space = true) ?(allow_collapse = false) node =
2670 match Syntax.syntax node with
2671 | Syntax.CompoundStatement
2672 { compound_left_brace; compound_statements; compound_right_brace } ->
2673 Concat
2675 handle_compound_statement
2677 ~allow_collapse
2678 compound_left_brace
2679 compound_statements
2680 compound_right_brace;
2681 (if space then
2682 Space
2683 else
2684 Nothing);
2686 | Syntax.Token _ -> t env node
2687 | _ -> Concat [Newline; BlockNest [t env node]]
2689 and handle_compound_statement
2690 env ?(allow_collapse = false) left_b statements right_b =
2691 Concat
2693 Space;
2694 braced_block_nest
2696 ~allow_collapse
2697 left_b
2698 right_b
2699 [handle_possible_list env statements];
2703 * Special-case handling for lists of declarators, where we want the splits
2704 * between declarators to break if their children break, but we want a single
2705 * declarator to stay joined with the line preceding it if it fits, even when
2706 * its children break.
2708 and handle_declarator_list env declarators =
2709 match Syntax.syntax declarators with
2710 | Syntax.Missing -> Nothing
2711 | Syntax.SyntaxList [declarator] ->
2712 Nest
2714 Space;
2715 (* Use an independent split, so we don't break just because a line break
2716 * occurs in the declarator. *)
2717 SplitWith Cost.Base;
2718 t env declarator;
2720 | Syntax.SyntaxList xs ->
2721 (* Use Rule.Parental to break each declarator onto its own line if any
2722 * line break occurs in a declarator, or if they can't all fit onto one
2723 * line. *)
2724 WithRule
2725 ( Rule.Parental,
2726 Nest
2727 (List.map xs ~f:(fun declarator ->
2728 Concat [Space; Split; t env declarator])) )
2729 | _ -> failwith "SyntaxList expected"
2731 and handle_list
2733 ?(before_each = (fun () -> Nothing))
2734 ?(after_each = (fun _is_last -> Nothing))
2735 ?(handle_element = t env)
2736 ?(handle_last = handle_element)
2737 list =
2738 let rec aux l =
2739 match l with
2740 | [hd] -> Concat [before_each (); handle_last hd; after_each true]
2741 | hd :: tl ->
2742 Concat [before_each (); handle_element hd; after_each false; aux tl]
2743 | [] -> Nothing
2745 aux list
2747 and list_length node =
2748 match Syntax.syntax node with
2749 | Syntax.Missing -> 0
2750 | Syntax.SyntaxList x -> List.length x
2751 | _ -> 1
2753 and handle_possible_list
2754 env ?before_each ?after_each ?handle_element ?handle_last node =
2755 match Syntax.syntax node with
2756 | Syntax.Missing -> Nothing
2757 | Syntax.SyntaxList x ->
2758 handle_list env x ?before_each ?after_each ?handle_element ?handle_last
2759 | _ ->
2760 handle_list env [node] ?before_each ?after_each ?handle_element ?handle_last
2762 and handle_xhp_open_right_angle_token env attrs node =
2763 match Syntax.syntax node with
2764 | Syntax.Token token ->
2765 Concat
2767 (if String.equal (Token.text token) "/>" then
2768 Concat [Space; when_present attrs split]
2769 else
2770 Nothing);
2771 t env node;
2773 | _ -> failwith "expected xhp_open right_angle token"
2775 and handle_possible_chaining env node =
2776 let rec handle_member_selection acc (receiver, arrow, member, targs) args =
2777 let (first_receiver, acc) = handle_chaining acc receiver in
2778 (first_receiver, (arrow, member, targs, args) :: acc)
2779 and handle_fun_call acc node receiver targs lp args rp =
2780 match Syntax.syntax receiver with
2781 | Syntax.MemberSelectionExpression
2782 { member_object = obj; member_operator = arrow; member_name = member }
2783 | Syntax.SafeMemberSelectionExpression
2785 safe_member_object = obj;
2786 safe_member_operator = arrow;
2787 safe_member_name = member;
2788 } ->
2789 handle_member_selection
2791 ( obj,
2792 arrow,
2793 member,
2794 if Syntax.is_missing targs then
2795 None
2796 else
2797 Some targs )
2798 (Some (lp, args, rp))
2799 | _ -> (node, [])
2800 and handle_chaining acc node =
2801 match Syntax.syntax node with
2802 | Syntax.FunctionCallExpression
2804 function_call_receiver = receiver;
2805 function_call_type_args = targs;
2806 function_call_left_paren = lp;
2807 function_call_argument_list = args;
2808 function_call_right_paren = rp;
2809 } ->
2810 handle_fun_call acc node receiver targs lp args rp
2811 | Syntax.MemberSelectionExpression
2812 { member_object = obj; member_operator = arrow; member_name = member }
2813 | Syntax.SafeMemberSelectionExpression
2815 safe_member_object = obj;
2816 safe_member_operator = arrow;
2817 safe_member_name = member;
2818 } ->
2819 handle_member_selection acc (obj, arrow, member, None) None
2820 | _ -> (node, [])
2822 (* It's easy to end up with an infinite loop by passing an unexpected node
2823 kind here, so confirm that we have an expected kind in hand. *)
2824 let () =
2825 match Syntax.kind node with
2826 | SyntaxKind.FunctionCallExpression
2827 | SyntaxKind.MemberSelectionExpression
2828 | SyntaxKind.SafeMemberSelectionExpression ->
2830 | kind ->
2831 failwith
2832 ("Unexpected SyntaxKind in handle_possible_chaining: "
2833 ^ SyntaxKind.show kind)
2835 (* Flatten nested member selection expressions into the first receiver and a
2836 list of member selections.
2837 E.g., transform $x->a->b->c into ($x, [->a; ->b; ->c]) *)
2838 let (first_receiver, chain_list) = handle_chaining [] node in
2839 let chain_list = List.rev chain_list in
2840 let transform_chain (arrow, member, targs, argish) =
2841 Concat
2843 t env arrow;
2844 t env member;
2845 Option.value_map targs ~default:Nothing ~f:(t env);
2846 Option.value_map argish ~default:Nothing ~f:(fun (lp, args, rp) ->
2847 transform_argish env lp args rp);
2850 (* The actual transform for function call expressions (the default transform
2851 just calls into [handle_possible_chaining]). *)
2852 let transform_first_receiver node =
2853 match Syntax.syntax node with
2854 | Syntax.FunctionCallExpression
2856 function_call_receiver = receiver;
2857 function_call_type_args = targs;
2858 function_call_left_paren = lp;
2859 function_call_argument_list = args;
2860 function_call_right_paren = rp;
2861 } ->
2862 Concat [t env receiver; t env targs; transform_argish env lp args rp]
2863 | Syntax.MemberSelectionExpression _
2864 | Syntax.SafeMemberSelectionExpression _ ->
2865 failwith
2866 "Should not be possible for a member selection expression to be considered first_receiver"
2867 | _ -> t env node
2869 let first_receiver_has_trailing_newline =
2870 node_has_trailing_newline first_receiver
2872 match chain_list with
2873 | [] -> transform_first_receiver first_receiver
2874 | [hd] ->
2875 Concat
2877 Span [transform_first_receiver first_receiver];
2878 (if first_receiver_has_trailing_newline then
2879 Newline
2880 else
2881 SplitWith Cost.High);
2882 Nest [transform_chain hd];
2884 | hd :: tl ->
2885 let transformed_hd = transform_chain hd in
2886 let tl = List.map tl ~f:transform_chain in
2887 let rule_type =
2888 match hd with
2889 | (_, trailing, None, None)
2890 | (_, _, Some trailing, None)
2891 | (_, _, _, Some (_, _, trailing)) ->
2892 if node_has_trailing_newline trailing then
2893 Rule.Always
2894 else if first_receiver_has_trailing_newline then
2895 Rule.Parental
2896 else
2897 (* If we have a chain where only the final item contains internal
2898 splits, use a Simple rule instead of a Parental one.
2899 This allows us to preserve this style:
2901 return $this->fooGenerator->generateFoo(
2902 $argument_one,
2903 $argument_two,
2904 $argument_three,
2907 let rev_tl_except_last = List.rev tl |> List.tl_exn in
2908 let items_except_last = transformed_hd :: rev_tl_except_last in
2909 if List.exists items_except_last ~f:has_split then
2910 Rule.Parental
2911 else
2912 Rule.Simple Cost.NoCost
2914 Span
2916 WithLazyRule
2917 ( rule_type,
2918 Concat
2920 transform_first_receiver first_receiver;
2921 (if first_receiver_has_trailing_newline then
2922 Newline
2923 else
2924 SplitWith Cost.Base);
2926 Concat
2928 (* This needs to be nested separately due to the above SplitWith *)
2929 Nest [transformed_hd];
2930 Nest (List.map tl ~f:(fun x -> Concat [Split; x]));
2931 ] );
2934 and transform_fn_decl_name env modifiers kw name type_params leftp =
2935 let mods = handle_possible_list env ~after_each:(fun _ -> Space) modifiers in
2936 [mods; t env kw; Space; t env name; t env type_params; t env leftp; Split]
2938 and transform_fn_decl_args env params rightp =
2939 (* It is a syntax error to follow a variadic parameter with a trailing
2940 * comma, so suppress trailing commas in that case. *)
2941 let allow_trailing =
2942 match Syntax.syntax params with
2943 | Syntax.SyntaxList params ->
2944 let last_param =
2945 match Syntax.syntax (List.last_exn params) with
2946 | Syntax.ListItem { list_item; _ } -> list_item
2947 | _ -> failwith "Expected ListItem"
2949 begin
2950 match Syntax.syntax last_param with
2951 | Syntax.VariadicParameter _
2952 | Syntax.(
2953 ParameterDeclaration
2955 parameter_name =
2957 syntax =
2958 DecoratedExpression
2960 decorated_expression_decorator =
2962 syntax =
2963 Token { Token.kind = TokenKind.DotDotDot; _ };
2971 }) ->
2972 false
2973 | _ -> true
2975 | _ -> true
2977 WithRule
2978 ( Rule.Parental,
2979 Concat [transform_possible_comma_list env ~allow_trailing params rightp]
2982 and transform_argish_with_return_type
2983 env left_p params right_p ctx_list colon readonly_ret ret_type =
2984 Concat
2986 t env left_p;
2987 when_present params split;
2988 transform_fn_decl_args env params right_p;
2989 t env ctx_list;
2990 t env colon;
2991 when_present colon space;
2992 t env readonly_ret;
2993 when_present readonly_ret space;
2994 t env ret_type;
2997 and transform_argish
2999 ?(allow_trailing = true)
3000 ?(force_newlines = false)
3001 ?(spaces = false)
3002 left_p
3003 arg_list
3004 right_p =
3005 (* It is a syntax error to follow a splat argument with a trailing comma, so
3006 suppress trailing commas in that case. *)
3007 let allow_trailing =
3008 match Syntax.syntax arg_list with
3009 | Syntax.SyntaxList args ->
3010 let last_arg =
3011 match Syntax.syntax (List.last_exn args) with
3012 | Syntax.ListItem { list_item; _ } -> list_item
3013 | _ -> failwith "Expected ListItem"
3015 begin
3016 match Syntax.syntax last_arg with
3017 | Syntax.(
3018 DecoratedExpression
3020 decorated_expression_decorator =
3021 { syntax = Token { Token.kind = TokenKind.DotDotDot; _ }; _ };
3023 }) ->
3024 false
3025 | _ -> allow_trailing
3027 | _ -> allow_trailing
3030 (* When the last argument breaks across multiple lines, we want to allow the
3031 arg list rule to stay unbroken even though the last argument contains
3032 splits that may be broken on.
3034 For example:
3036 // We do not want to break f's rule even though its child splits:
3037 f(vec[
3038 $foo, // single-line comment forces the vec's rule to split
3039 $bar,
3042 // We do not want to break map's rule even though the lambda has splits:
3043 map($vec, $element ==> {
3044 // ...
3047 let split_when_children_split =
3048 if spaces then
3049 true
3050 else
3051 let unwrap_list_item x =
3052 match Syntax.syntax x with
3053 | Syntax.ListItem { list_item; _ } -> list_item
3054 | _ -> x
3056 let is_doc_string_literal x =
3057 let x = unwrap_list_item x in
3058 match Syntax.syntax x with
3059 | Syntax.LiteralExpression { literal_expression } ->
3060 (match Syntax.syntax literal_expression with
3061 | Syntax.Token t ->
3062 (match Token.kind t with
3063 | TokenKind.(HeredocStringLiteral | NowdocStringLiteral) -> true
3064 | _ -> false)
3065 | Syntax.SyntaxList (x :: _) ->
3066 (match Syntax.syntax x with
3067 | Syntax.Token t ->
3068 (match Token.kind t with
3069 | TokenKind.HeredocStringLiteralHead -> true
3070 | _ -> false)
3071 | _ -> false)
3072 | _ -> false)
3073 | _ -> false
3075 let leading_trivia_is_all_whitespace x =
3076 List.for_all (Syntax.leading_trivia x) ~f:(fun t ->
3077 match Trivia.kind t with
3078 | TriviaKind.WhiteSpace -> true
3079 | _ -> false)
3081 match Syntax.syntax arg_list with
3082 | Syntax.SyntaxList [] -> true
3083 | Syntax.SyntaxList [x] ->
3084 let has_surrounding_whitespace =
3086 (List.is_empty (Syntax.trailing_trivia left_p)
3087 && (List.is_empty (Syntax.trailing_trivia arg_list)
3088 || Env.version_gte env 3
3089 && is_doc_string_literal x
3090 && leading_trivia_is_all_whitespace right_p))
3092 if has_surrounding_whitespace then
3093 true
3094 else
3095 looks_bad_in_non_parental_braces x
3096 | Syntax.SyntaxList items ->
3097 let last = List.last_exn items in
3098 let has_surrounding_whitespace =
3100 (List.is_empty (Syntax.leading_trivia last)
3101 && (List.is_empty (Syntax.trailing_trivia arg_list)
3102 || Env.version_gte env 3
3103 && is_doc_string_literal last
3104 && leading_trivia_is_all_whitespace right_p))
3106 if has_surrounding_whitespace then
3107 true
3108 else (
3109 (* When there are multiple arguments, opt into this behavior only when we
3110 have no splits in any of the arguments except the last. *)
3111 match List.rev items with
3112 | [] -> assert false
3113 | last :: rest ->
3114 let prev_args_may_split =
3115 rest |> List.map ~f:(t env) |> List.exists ~f:has_split
3117 if prev_args_may_split then
3118 true
3119 else
3120 looks_bad_in_non_parental_braces last
3122 | _ -> true
3124 delimited_nest
3126 ~split_when_children_split
3127 ~force_newlines
3128 left_p
3129 right_p
3130 [transform_arg_list env ~allow_trailing arg_list]
3132 (** Sometimes, we want to use a non-Parental rule for function call argument
3133 lists and other similar constructs when not breaking around the argument
3134 list looks reasonable. For example:
3136 f($x ==> {
3137 return do_something_with($x);
3140 Some constructs don't look so great when we do this:
3142 f($x ==>
3143 do_something_with($x));
3145 f($x
3146 ? $y
3147 : $z);
3149 This function blacklists those constructs. *)
3150 and looks_bad_in_non_parental_braces item =
3151 let item =
3152 match Syntax.syntax item with
3153 | Syntax.ListItem { list_item; _ } -> list_item
3154 | _ -> item
3156 match Syntax.syntax item with
3157 | Syntax.(
3158 LambdaExpression { lambda_body = { syntax = CompoundStatement _; _ }; _ })
3160 false
3161 | Syntax.FunctionCallExpression { function_call_receiver; _ } ->
3162 Syntax.is_member_selection_expression function_call_receiver
3163 | Syntax.ConditionalExpression _
3164 | Syntax.BinaryExpression _
3165 | Syntax.MemberSelectionExpression _
3166 | Syntax.FieldSpecifier _
3167 | Syntax.FieldInitializer _
3168 | Syntax.ElementInitializer _
3169 | Syntax.LambdaExpression _
3170 | Syntax.XHPExpression _
3171 | Syntax.IsExpression _
3172 | Syntax.AsExpression _
3173 | Syntax.NullableAsExpression _ ->
3174 true
3175 | _ -> false
3177 and transform_braced_item env left_p item right_p =
3178 let has_no_surrounding_trivia =
3179 List.is_empty (Syntax.trailing_trivia left_p)
3180 && List.is_empty (Syntax.leading_trivia item)
3181 && List.is_empty (Syntax.trailing_trivia item)
3182 && List.is_empty (Syntax.leading_trivia right_p)
3184 if has_no_surrounding_trivia && not (looks_bad_in_non_parental_braces item)
3185 then
3186 Concat (List.map [left_p; item; right_p] ~f:(t env))
3187 else
3188 delimited_nest env left_p right_p [t env item]
3190 and transform_argish_item env x =
3191 match Syntax.syntax x with
3192 | Syntax.ListItem { list_item; list_separator } ->
3193 Concat [transform_argish_item env list_item; t env list_separator]
3194 | Syntax.BinaryExpression
3196 binary_left_operand = left;
3197 binary_operator = op;
3198 binary_right_operand = right;
3200 when not (is_concat op) ->
3201 transform_binary_expression env ~is_nested:true (left, op, right)
3202 | _ -> t env x
3204 and transform_trailing_comma env ~allow_trailing item comma =
3205 (* PHP does not permit trailing commas in function calls. Rather than try to
3206 * account for where PHP's parser permits trailing commas, we just never add
3207 * them in PHP files. *)
3208 let allow_trailing = allow_trailing && env.Env.add_trailing_commas in
3209 match Syntax.syntax comma with
3210 | Syntax.Token tok ->
3211 Concat
3213 transform_argish_item env item;
3214 transform_leading_trivia (Token.leading tok);
3215 (if allow_trailing then
3216 TrailingComma true
3217 else
3218 Nothing);
3219 Ignore (Token.text tok, Token.width tok);
3220 transform_trailing_trivia (Token.trailing tok);
3222 | Syntax.Missing ->
3223 let (item, item_trailing) = remove_trailing_trivia item in
3224 Concat
3226 transform_argish_item env item;
3227 (if allow_trailing then
3228 TrailingComma false
3229 else
3230 Nothing);
3231 transform_trailing_trivia item_trailing;
3233 | _ -> failwith "Expected Token"
3235 and transform_braced_item_with_trailer env left_p item comma right_p =
3236 let has_no_surrounding_trivia =
3237 List.is_empty (Syntax.trailing_trivia left_p)
3238 && List.is_empty (Syntax.leading_trivia item)
3239 && List.is_empty (Syntax.trailing_trivia item)
3240 && List.is_empty (Syntax.leading_trivia comma)
3241 && List.is_empty (Syntax.trailing_trivia comma)
3242 && List.is_empty (Syntax.leading_trivia right_p)
3244 (* TODO: turn allow_trailing:true when HHVM versions that don't support
3245 trailing commas in all these places reach end-of-life. *)
3246 let item_and_comma =
3247 transform_trailing_comma env ~allow_trailing:false item comma
3249 if has_no_surrounding_trivia && not (looks_bad_in_non_parental_braces item)
3250 then
3251 Concat [t env left_p; item_and_comma; t env right_p]
3252 else
3253 delimited_nest env left_p right_p [item_and_comma]
3255 and transform_arg_list env ?(allow_trailing = true) items =
3256 handle_possible_list
3258 items
3259 ~after_each:after_each_argument
3260 ~handle_last:(transform_last_arg env ~allow_trailing)
3261 ~handle_element:(transform_argish_item env)
3263 and transform_possible_comma_list env ?(allow_trailing = true) items right_p =
3264 nest env right_p [transform_arg_list env ~allow_trailing items]
3266 and transform_container_literal
3268 ?(space = false)
3269 ?allow_trailing
3270 ?explicit_type
3272 left_p
3273 members
3274 right_p =
3275 let force_newlines = node_has_trailing_newline left_p in
3276 let ty =
3277 match explicit_type with
3278 | Some ex_ty -> t env ex_ty
3279 | None -> Nothing
3281 Concat
3283 t env kw;
3285 (if space then
3286 Space
3287 else
3288 Nothing);
3289 transform_argish
3291 ~force_newlines
3292 ?allow_trailing
3293 left_p
3294 members
3295 right_p;
3298 and replace_leading_trivia node new_leading_trivia =
3299 match Syntax.leading_token node with
3300 | None -> node
3301 | Some leading_token ->
3302 let rewritten_node =
3303 Rewriter.rewrite_pre
3304 (fun node_to_rewrite ->
3305 match Syntax.syntax node_to_rewrite with
3306 | Syntax.Token t when phys_equal t leading_token ->
3307 Rewriter.Replace
3308 (Syntax.make_token { t with Token.leading = new_leading_trivia })
3309 | _ -> Rewriter.Keep)
3310 node
3312 rewritten_node
3314 and remove_leading_trivia node =
3315 match Syntax.leading_token node with
3316 | None -> ([], node)
3317 | Some leading_token ->
3318 let rewritten_node =
3319 Rewriter.rewrite_pre
3320 (fun rewrite_node ->
3321 match Syntax.syntax rewrite_node with
3322 | Syntax.Token t when phys_equal t leading_token ->
3323 Rewriter.Replace (Syntax.make_token { t with Token.leading = [] })
3324 | _ -> Rewriter.Keep)
3325 node
3327 (Token.leading leading_token, rewritten_node)
3329 and remove_trailing_trivia node =
3330 match Syntax.trailing_token node with
3331 | None -> (node, [])
3332 | Some trailing_token ->
3333 let rewritten_node =
3334 Rewriter.rewrite_pre
3335 (fun rewrite_node ->
3336 match Syntax.syntax rewrite_node with
3337 | Syntax.Token t when phys_equal t trailing_token ->
3338 Rewriter.Replace (Syntax.make_token { t with Token.trailing = [] })
3339 | _ -> Rewriter.Keep)
3340 node
3342 (rewritten_node, Token.trailing trailing_token)
3344 and transform_last_arg env ~allow_trailing node =
3345 match Syntax.syntax node with
3346 | Syntax.ListItem { list_item = item; list_separator = separator } ->
3347 transform_trailing_comma env ~allow_trailing item separator
3348 | _ -> failwith "Expected ListItem"
3350 and transform_mapish_entry env key arrow value =
3351 Concat
3353 t env key;
3354 Space;
3355 t env arrow;
3356 Space;
3357 SplitWith Cost.Base;
3358 Nest [t env value];
3361 and transform_keyword_expression_statement env kw expr semi =
3362 Concat
3364 t env kw;
3365 when_present expr (fun () ->
3366 Concat
3368 Space;
3369 SplitWith
3370 (if Env.version_gte env 1 then
3371 Cost.Base
3372 else
3373 Cost.Moderate);
3374 Nest [t env expr];
3376 t env semi;
3377 Newline;
3380 and transform_keyword_expr_list_statement env kw expr_list semi =
3381 Concat [t env kw; handle_declarator_list env expr_list; t env semi; Newline]
3383 and transform_condition env left_p condition right_p =
3384 Concat
3386 t env left_p;
3387 Split;
3388 WithRule
3389 (Rule.Parental, Concat [Nest [t env condition]; Split; t env right_p]);
3392 and get_operator_type op =
3393 match Syntax.syntax op with
3394 | Syntax.Token t -> Full_fidelity_operator.trailing_from_token (Token.kind t)
3395 | _ -> failwith "Operator should always be a token"
3397 and is_concat op =
3398 match get_operator_type op with
3399 | Full_fidelity_operator.ConcatenationOperator -> true
3400 | _ -> false
3402 and transform_binary_expression env ~is_nested (left, operator, right) =
3403 let operator_has_surrounding_spaces op = not (is_concat op) in
3404 let operator_is_leading op =
3405 match get_operator_type op with
3406 | Full_fidelity_operator.PipeOperator -> true
3407 | _ -> false
3409 let operator_preserves_newlines op =
3410 match get_operator_type op with
3411 | Full_fidelity_operator.PipeOperator -> true
3412 | _ -> false
3414 let operator_t = get_operator_type operator in
3415 if Full_fidelity_operator.is_comparison operator_t then
3416 WithLazyRule
3417 ( Rule.Parental,
3418 Concat [t env left; Space; t env operator],
3419 Concat [Space; Split; Nest [t env right]] )
3420 else if Full_fidelity_operator.is_assignment operator_t then
3421 Concat
3423 t env left;
3424 Space;
3425 t env operator;
3426 Space;
3427 SplitWith
3428 (if Env.version_gte env 1 then
3429 Cost.Base
3430 else
3431 Cost.Moderate);
3432 Nest [t env right];
3434 else
3435 Concat
3437 (let penv = Full_fidelity_parser_env.default in
3438 let precedence = Full_fidelity_operator.precedence penv operator_t in
3439 let rec flatten_expression expr =
3440 match Syntax.syntax expr with
3441 | Syntax.BinaryExpression
3443 binary_left_operand = left;
3444 binary_operator = operator;
3445 binary_right_operand = right;
3446 } ->
3447 let operator_t = get_operator_type operator in
3448 let op_precedence =
3449 Full_fidelity_operator.precedence penv operator_t
3451 if op_precedence = precedence then
3452 flatten_expression left @ operator :: flatten_expression right
3453 else
3454 [expr]
3455 | _ -> [expr]
3457 let transform_operand operand =
3458 match Syntax.syntax operand with
3459 | Syntax.BinaryExpression
3460 { binary_left_operand; binary_operator; binary_right_operand } ->
3461 transform_binary_expression
3463 ~is_nested:true
3464 (binary_left_operand, binary_operator, binary_right_operand)
3465 | _ -> t env operand
3467 let binary_expression_syntax_list =
3468 flatten_expression
3469 (Syntax.make_binary_expression left operator right)
3471 match binary_expression_syntax_list with
3472 | hd :: tl ->
3473 WithLazyRule
3474 ( Rule.Parental,
3475 transform_operand hd,
3476 let expression =
3477 let last_operand = ref hd in
3478 let last_op = ref (List.hd_exn tl) in
3479 List.mapi tl ~f:(fun i x ->
3480 if i mod 2 = 0 then (
3481 let op = x in
3482 last_op := op;
3483 let op_has_spaces = operator_has_surrounding_spaces op in
3484 let op_is_leading = operator_is_leading op in
3485 let newline_before_op =
3486 operator_preserves_newlines op
3487 && node_has_trailing_newline !last_operand
3489 Concat
3491 (if newline_before_op then
3492 Newline
3493 else if op_is_leading then
3494 if op_has_spaces then
3495 space_split ()
3496 else
3497 Split
3498 else if op_has_spaces then
3499 Space
3500 else
3501 Nothing);
3502 (if is_concat op then
3503 ConcatOperator (t env op)
3504 else
3505 t env op);
3507 ) else
3508 let operand = x in
3509 last_operand := x;
3510 let op_has_spaces =
3511 operator_has_surrounding_spaces !last_op
3513 let op_is_leading = operator_is_leading !last_op in
3514 Concat
3516 (if op_is_leading then
3517 if op_has_spaces then
3518 Space
3519 else
3520 Nothing
3521 else if op_has_spaces then
3522 space_split ()
3523 else
3524 Split);
3525 transform_operand operand;
3528 if is_nested then
3529 Nest expression
3530 else
3531 ConditionalNest expression )
3532 | _ -> failwith "Expected non empty list of binary expression pieces");
3535 and make_string text width =
3536 let split_text = Str.split_delim (Str.regexp "\n") text in
3537 match split_text with
3538 | [_] -> Text (text, width)
3539 | _ -> MultilineString (split_text, width)
3541 (* Check the leading trivia of the node's leading token.
3542 Treat the node's text as a multiline string if the leading trivia contains
3543 an ignore comment. *)
3544 and transform_node_if_ignored node =
3545 let (leading_before, leading_including_and_after) =
3546 leading_ignore_comment (Syntax.leading_trivia node)
3548 if List.length leading_including_and_after = 0 then
3549 None
3550 else
3551 let node = replace_leading_trivia node leading_including_and_after in
3552 let (node, trailing_trivia) = remove_trailing_trivia node in
3553 let is_fixme =
3554 match Trivia.kind (List.hd_exn leading_including_and_after) with
3555 | TriviaKind.(FixMe | IgnoreError) -> true
3556 | _ -> false
3558 Some
3559 (Concat
3561 transform_leading_trivia leading_before;
3562 (* If we have a non-error-suppression comment here, then we want to
3563 ensure that we don't join it up onto the preceding line. Since we
3564 only scan leading trivia for hackfmt-ignore comments, and joining
3565 the comment onto the preceding line would make it trailing trivia,
3566 we would make the ignore comment useless if we joined it with the
3567 preceding line (breaking idempotence of hackfmt). Adding [Newline]
3568 here ensures a line break.
3570 Error-suppression comments are different--they are specially
3571 handled by the lexer to ensure that they always appear in leading
3572 trivia. *)
3573 (if is_fixme then
3574 Nothing
3575 else
3576 Newline);
3577 make_string (Syntax.text node) (Syntax.width node);
3578 transform_trailing_trivia trailing_trivia;
3579 (if has_newline trailing_trivia then
3580 Newline
3581 else
3582 Nothing);
3585 and ignore_re = Str.regexp_string "hackfmt-ignore"
3587 and is_ignore_comment trivia =
3588 match Trivia.kind trivia with
3589 (* We don't format the node after a comment containing "hackfmt-ignore". *)
3590 | TriviaKind.(DelimitedComment | SingleLineComment) ->
3591 begin
3592 try Str.search_forward ignore_re (Trivia.text trivia) 0 >= 0 with
3593 | Caml.Not_found -> false
3595 | _ -> false
3597 and leading_ignore_comment trivia_list =
3598 let before = List.take_while trivia_list ~f:(Fn.non is_ignore_comment) in
3599 let (_, including_and_after) =
3600 List.split_n trivia_list (List.length before)
3602 (before, including_and_after)
3604 (* True if the trivia list contains WhiteSpace trivia.
3605 * Note that WhiteSpace includes spaces and tabs, but not newlines. *)
3606 and has_whitespace trivia_list =
3607 List.exists trivia_list ~f:(fun trivia ->
3608 is_trivia_kind_white_space (Trivia.kind trivia))
3610 (* True if the trivia list contains EndOfLine trivia. *)
3611 and has_newline trivia_list =
3612 List.exists trivia_list ~f:(fun trivia ->
3613 is_trivia_kind_end_of_line (Trivia.kind trivia))
3615 and is_invisible trivia =
3616 match Trivia.kind trivia with
3617 | TriviaKind.WhiteSpace
3618 | TriviaKind.EndOfLine ->
3619 true
3620 | _ -> false
3622 and transform_leading_trivia t = transform_trivia ~is_leading:true t
3624 and transform_trailing_trivia t = transform_trivia ~is_leading:false t
3626 and transform_trivia ~is_leading trivia =
3627 let new_line_regex = Str.regexp "\n" in
3628 let indent = ref 0 in
3629 let currently_leading = ref is_leading in
3630 let leading_invisibles = ref [] in
3631 let last_comment = ref None in
3632 let last_comment_was_delimited = ref false in
3633 let newline_followed_last_comment = ref false in
3634 let whitespace_followed_last_comment = ref false in
3635 let trailing_invisibles = ref [] in
3636 let comments = ref [] in
3637 let make_comment _ =
3638 if Option.is_some !last_comment then (
3639 newline_followed_last_comment := has_newline !trailing_invisibles;
3640 whitespace_followed_last_comment := has_whitespace !trailing_invisibles
3642 comments :=
3643 Concat
3645 transform_leading_invisibles (List.rev !leading_invisibles);
3646 Option.value !last_comment ~default:Nothing;
3647 ignore_trailing_invisibles (List.rev !trailing_invisibles);
3648 (if !last_comment_was_delimited && !whitespace_followed_last_comment
3649 then
3650 Space
3651 else if !newline_followed_last_comment then
3652 Newline
3653 else
3654 Nothing);
3656 :: !comments;
3657 last_comment := None;
3658 leading_invisibles := [];
3659 trailing_invisibles := []
3661 List.iter trivia ~f:(fun triv ->
3662 match Trivia.kind triv with
3663 | TriviaKind.ExtraTokenError
3664 | TriviaKind.FixMe
3665 | TriviaKind.IgnoreError
3666 | TriviaKind.DelimitedComment ->
3667 let preceded_by_whitespace =
3668 if !currently_leading then
3669 has_whitespace !leading_invisibles
3670 else
3671 has_whitespace !trailing_invisibles
3673 make_comment ();
3674 let delimited_lines = Str.split new_line_regex (Trivia.text triv) in
3675 let map_tail str =
3676 let prefix_space_count str =
3677 let len = String.length str in
3678 let rec aux i =
3679 if i = len || Char.(str.[i] <> ' ' && str.[i] <> '\t') then
3681 else
3682 1 + aux (i + 1)
3684 aux 0
3686 (* If we're dealing with trailing trivia, then we don't have a good
3687 signal for the indent level, so we just cut all leading spaces.
3688 Otherwise, we cut a number of spaces equal to the indent before
3689 the delimited comment opener. *)
3690 let start_index =
3691 if is_leading then
3692 min !indent (prefix_space_count str)
3693 else
3694 prefix_space_count str
3696 let len = String.length str - start_index in
3697 let dc =
3698 Trivia.create_delimited_comment
3699 @@ String.sub str ~pos:start_index ~len
3701 Concat
3703 Ignore ("\n", 1);
3704 Newline;
3705 Ignore (String.make start_index ' ', start_index);
3706 Comment (Trivia.text dc, Trivia.width dc);
3709 let hd = List.hd_exn delimited_lines in
3710 let tl = List.tl_exn delimited_lines in
3711 let hd = Comment (hd, String.length hd) in
3712 let should_break =
3713 match Trivia.kind triv with
3714 | TriviaKind.FixMe
3715 | TriviaKind.IgnoreError ->
3716 false
3717 | _ -> !currently_leading
3719 last_comment :=
3720 Some
3721 (Concat
3723 (if should_break then
3724 Newline
3725 else if preceded_by_whitespace then
3726 Space
3727 else
3728 Nothing);
3729 Concat (hd :: List.map tl ~f:map_tail);
3731 last_comment_was_delimited := true;
3732 currently_leading := false
3733 | TriviaKind.FallThrough
3734 | TriviaKind.SingleLineComment ->
3735 make_comment ();
3736 last_comment :=
3737 Some
3738 (Concat
3740 (if !currently_leading then
3741 Newline
3742 else
3743 Space);
3744 SingleLineComment (Trivia.text triv, Trivia.width triv);
3746 last_comment_was_delimited := false;
3747 currently_leading := false
3748 | TriviaKind.EndOfLine ->
3749 indent := 0;
3750 if !currently_leading then
3751 leading_invisibles := triv :: !leading_invisibles
3752 else (
3753 trailing_invisibles := triv :: !trailing_invisibles;
3754 make_comment ()
3756 currently_leading := true
3757 | TriviaKind.WhiteSpace ->
3758 if !currently_leading then (
3759 indent := Trivia.width triv;
3760 leading_invisibles := triv :: !leading_invisibles
3761 ) else
3762 trailing_invisibles := triv :: !trailing_invisibles);
3763 if List.is_empty !comments then
3764 if is_leading then
3765 transform_leading_invisibles trivia
3766 else
3767 ignore_trailing_invisibles trivia
3768 else (
3769 make_comment ();
3770 Concat (List.rev !comments)
3773 and max_consecutive_blank_lines = 1
3775 and transform_leading_invisibles triv =
3776 let newlines = ref 0 in
3777 Concat
3778 (List.map triv ~f:(fun t ->
3779 let ignored = Ignore (Trivia.text t, Trivia.width t) in
3780 match Trivia.kind t with
3781 | TriviaKind.EndOfLine ->
3782 newlines := !newlines + 1;
3783 Concat
3785 ignored;
3786 (if !newlines <= max_consecutive_blank_lines then
3787 BlankLine
3788 else
3789 Nothing);
3791 | _ -> ignored))
3793 and ignore_trailing_invisibles triv =
3794 Concat (List.map triv ~f:(fun t -> Ignore (Trivia.text t, Trivia.width t)))
3796 and transform_xhp_leading_trivia triv =
3797 let (up_to_first_newline, after_newline, _) =
3798 List.fold triv ~init:([], [], false) ~f:(fun (upto, after, seen) t ->
3799 if seen then
3800 (upto, t :: after, true)
3801 else
3802 (t :: upto, after, is_trivia_kind_end_of_line (Trivia.kind t)))
3804 Concat
3806 ignore_trailing_invisibles up_to_first_newline;
3807 transform_leading_invisibles after_newline;
3810 and node_has_trailing_newline node =
3811 let trivia = Syntax.trailing_trivia node in
3812 List.exists trivia ~f:(fun x -> is_trivia_kind_end_of_line (Trivia.kind x))
3814 and transform_consequence
3815 t (env : Env.t) (node_body : Syntax.t) (node_newline : Syntax.t) =
3816 match Syntax.syntax node_body with
3817 | Syntax.CompoundStatement _ ->
3818 handle_possible_compound_statement env node_body
3819 | _ ->
3820 Concat
3822 Space;
3823 (if has_newline (Syntax.trailing_trivia node_newline) then
3824 Concat [Newline; Nest [t env node_body]]
3825 else
3826 WithRule (Rule.Parental, Nest [Span [Space; Split; t env node_body]]));
3829 let transform (env : Env.t) (node : Syntax.t) : Doc.t = t env node