Add an upcast expression
[hiphop-php.git] / hphp / hack / src / hackfmt / hack_format.ml
blobe288cdb0ba0630e8bbfd5e0d67ddbf80b192b6f4
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 | _ -> Text (Token.text x, Token.width x)
91 end;
92 transform_trailing_trivia (Token.trailing x);
94 | Syntax.SyntaxList _ ->
95 failwith
96 (Printf.sprintf
97 "Error: SyntaxList should never be handled directly;
98 offending text is '%s'."
99 (Syntax.text node))
100 | Syntax.EndOfFile x -> t env x.end_of_file_token
101 | Syntax.Script x ->
102 begin
103 match Syntax.syntax x.script_declarations with
104 | Syntax.SyntaxList (header :: declarations)
105 when Syntax.is_markup_section header ->
106 Concat [t env header; Newline; handle_list env declarations]
107 | _ -> Concat [handle_possible_list env x.script_declarations]
109 | Syntax.LiteralExpression { literal_expression } ->
110 (* Double quoted string literals can create a list *)
111 let wrap_with_literal_type token transformed =
112 match Token.kind token with
113 | TokenKind.HeredocStringLiteral
114 | TokenKind.HeredocStringLiteralHead
115 | TokenKind.HeredocStringLiteralTail
116 | TokenKind.NowdocStringLiteral ->
117 DocLiteral transformed
118 | TokenKind.DecimalLiteral
119 | TokenKind.OctalLiteral
120 | TokenKind.HexadecimalLiteral
121 | TokenKind.BinaryLiteral
122 | TokenKind.FloatingLiteral ->
123 NumericLiteral transformed
124 | _ -> transformed
126 begin
127 match Syntax.syntax literal_expression with
128 | Syntax.Token tok ->
129 wrap_with_literal_type tok (t env literal_expression)
130 | Syntax.SyntaxList l ->
131 let last = Syntax.trailing_token literal_expression in
132 begin
133 match last with
134 | Some tok ->
135 wrap_with_literal_type tok (Concat (List.map l ~f:(t env)))
136 | _ -> failwith "Expected Token"
138 | _ -> failwith "Expected Token or SyntaxList"
140 | Syntax.PrefixedStringExpression
141 { prefixed_string_name = name; prefixed_string_str = str } ->
142 Concat [t env name; t env str]
143 | Syntax.MarkupSection
144 { markup_hashbang = hashbang; markup_suffix = suffix; _ } ->
145 let is_hh_script =
146 match Syntax.syntax suffix with
147 | Syntax.MarkupSuffix
148 { markup_suffix_name = Syntax.{ syntax = Token t; _ }; _ } ->
149 String.equal (Token.text t) "hh"
150 | _ -> false
152 let rec all_whitespaces s i =
153 i >= String.length s
155 match s.[i] with
156 | ' '
157 | '\t'
158 | '\r'
159 | '\n' ->
160 all_whitespaces s (i + 1)
161 | _ -> false
163 let text_contains_only_whitespaces =
164 match Syntax.syntax hashbang with
165 | Syntax.Token t -> all_whitespaces (Token.text t) 0
166 | _ -> false
168 if is_hh_script && text_contains_only_whitespaces then
169 t env suffix
170 else
171 transform_simple env node
172 | Syntax.MarkupSuffix _
173 | Syntax.SimpleTypeSpecifier _
174 | Syntax.VariableExpression _
175 | Syntax.PipeVariableExpression _
176 | Syntax.PropertyDeclarator _
177 | Syntax.ConstantDeclarator _
178 | Syntax.ScopeResolutionExpression _
179 | Syntax.EmbeddedMemberSelectionExpression _
180 | Syntax.EmbeddedSubscriptExpression _
181 | Syntax.PostfixUnaryExpression _
182 | Syntax.XHPRequired _
183 | Syntax.XHPLateinit _
184 | Syntax.XHPSimpleClassAttribute _
185 | Syntax.XHPClose _
186 | Syntax.TypeConstant _
187 | Syntax.GenericTypeSpecifier _
188 | Syntax.NullableTypeSpecifier _
189 | Syntax.LikeTypeSpecifier _
190 | Syntax.SoftTypeSpecifier _
191 | Syntax.ListItem _ ->
192 transform_simple env node
193 | Syntax.ReifiedTypeArgument
194 { reified_type_argument_reified; reified_type_argument_type } ->
195 Concat
197 t env reified_type_argument_reified;
198 Space;
199 t env reified_type_argument_type;
201 | Syntax.QualifiedName { qualified_name_parts } ->
202 handle_possible_list env qualified_name_parts
203 | Syntax.ExpressionStatement _ -> transform_simple_statement env node
204 | Syntax.EnumDeclaration
206 enum_attribute_spec = attr;
207 enum_keyword = kw;
208 enum_name = name;
209 enum_colon = colon_kw;
210 enum_base = base;
211 enum_type;
212 enum_left_brace = left_b;
213 enum_use_clauses;
214 enum_enumerators = enumerators;
215 enum_right_brace = right_b;
216 } ->
217 Concat
219 t env attr;
220 when_present attr newline;
221 t env kw;
222 Space;
223 t env name;
224 t env colon_kw;
225 Space;
226 SplitWith Cost.Base;
227 Nest [Space; t env base; Space; t env enum_type; Space];
228 braced_block_nest
230 left_b
231 right_b
233 handle_possible_list env enum_use_clauses;
234 handle_possible_list env enumerators;
236 Newline;
238 | Syntax.Enumerator
240 enumerator_name = name;
241 enumerator_equal = eq_kw;
242 enumerator_value = value;
243 enumerator_semicolon = semi;
244 } ->
245 let value = t env value in
246 Concat
248 t env name;
249 Space;
250 t env eq_kw;
251 Space;
252 (if has_split value then
253 SplitWith Cost.Base
254 else
255 Nothing);
256 Nest [value];
257 t env semi;
258 Newline;
260 | Syntax.EnumUse
262 enum_use_keyword = kw;
263 enum_use_names = elements;
264 enum_use_semicolon = semi;
265 } ->
266 Concat
268 t env kw;
269 (match Syntax.syntax elements with
270 | Syntax.SyntaxList [x] -> Concat [Space; t env x]
271 | Syntax.SyntaxList _ ->
272 WithRule
273 ( Rule.Parental,
274 Nest
275 [handle_possible_list env ~before_each:space_split elements]
277 | _ -> Concat [Space; t env elements]);
278 t env semi;
279 Newline;
281 | Syntax.RecordDeclaration
283 record_attribute_spec = attr;
284 record_modifier = modifier;
285 record_keyword = kw;
286 record_name = name;
287 record_extends_keyword = extends_kw;
288 record_extends_opt = extends;
289 record_left_brace = left_b;
290 record_fields = fields;
291 record_right_brace = right_b;
292 } ->
293 let after_each_ancestor is_last =
294 if is_last then
295 Nothing
296 else
297 space_split ()
299 Concat
301 t env attr;
302 when_present attr newline;
303 t env modifier;
304 Space;
305 t env kw;
306 Space;
307 t env name;
308 Space;
309 when_present extends_kw (fun () ->
310 Concat
312 Space;
313 Split;
314 WithRule
315 ( Rule.Parental,
316 Nest
318 Span
320 t env extends_kw;
321 Space;
322 Split;
323 WithRule
324 ( Rule.Parental,
325 Nest
327 handle_possible_list
329 ~after_each:after_each_ancestor
330 extends;
331 ] );
333 ] );
335 braced_block_nest env left_b right_b [handle_possible_list env fields];
336 Newline;
338 | Syntax.RecordField
340 record_field_type;
341 record_field_name = name;
342 record_field_init;
343 record_field_semi = semi_kw;
344 } ->
345 Concat
347 t env record_field_type;
348 Space;
349 t env name;
350 t env record_field_init;
351 t env semi_kw;
352 Newline;
354 | Syntax.AliasDeclaration
356 alias_attribute_spec = attr;
357 alias_keyword = kw;
358 alias_name = name;
359 alias_generic_parameter = generic;
360 alias_constraint = type_constraint;
361 alias_equal = eq_kw;
362 alias_type = ty;
363 alias_semicolon = semi;
365 | Syntax.ContextAliasDeclaration
367 ctx_alias_attribute_spec = attr;
368 ctx_alias_keyword = kw;
369 ctx_alias_name = name;
370 ctx_alias_generic_parameter = generic;
371 ctx_alias_as_constraint = type_constraint;
372 ctx_alias_equal = eq_kw;
373 ctx_alias_context = ty;
374 ctx_alias_semicolon = semi;
375 } ->
376 (* TODO: revisit this for long names *)
377 Concat
379 t env attr;
380 when_present attr newline;
381 t env kw;
382 Space;
383 t env name;
384 t env generic;
385 Space;
386 t env type_constraint;
387 Space;
388 t env eq_kw;
389 Space;
390 SplitWith Cost.Base;
391 Nest [t env ty];
392 t env semi;
393 Newline;
395 | Syntax.PropertyDeclaration
397 property_attribute_spec = attr;
398 property_modifiers = modifiers;
399 property_type = prop_type;
400 property_declarators = declarators;
401 property_semicolon = semi;
402 } ->
403 let declaration =
404 Concat
406 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
407 t env prop_type;
408 handle_declarator_list env declarators;
409 t env semi;
410 Newline;
413 if Syntax.is_missing attr then
414 declaration
415 else
416 WithLazyRule
417 ( Rule.Parental,
418 handle_attribute_spec env attr ~always_split:false,
419 Concat [Space; Split; declaration] )
420 | Syntax.NamespaceDeclaration
421 { namespace_header = header; namespace_body = body } ->
422 Concat [t env header; t env body; Newline]
423 | Syntax.NamespaceDeclarationHeader
424 { namespace_keyword = kw; namespace_name = name } ->
425 Concat [t env kw; Space; t env name]
426 | Syntax.NamespaceBody
428 namespace_left_brace = left_b;
429 namespace_declarations = decls;
430 namespace_right_brace = right_b;
431 } ->
432 Concat
434 Space;
435 braced_block_nest env left_b right_b [handle_possible_list env decls];
437 | Syntax.NamespaceEmptyBody { namespace_semicolon = semi } ->
438 Concat [t env semi]
439 | Syntax.NamespaceUseDeclaration
441 namespace_use_keyword = kw;
442 namespace_use_kind = use_kind;
443 namespace_use_clauses = clauses;
444 namespace_use_semicolon = semi;
445 } ->
446 Concat
448 t env kw;
449 Space;
450 t env use_kind;
451 when_present use_kind space;
452 WithRule
453 ( Rule.Parental,
454 Nest
456 handle_possible_list
458 clauses
459 ~after_each:after_each_argument;
460 ] );
461 t env semi;
462 Newline;
464 | Syntax.NamespaceGroupUseDeclaration
466 namespace_group_use_keyword = kw;
467 namespace_group_use_kind = use_kind;
468 namespace_group_use_prefix = prefix;
469 namespace_group_use_left_brace = left_b;
470 namespace_group_use_clauses = clauses;
471 namespace_group_use_right_brace = right_b;
472 namespace_group_use_semicolon = semi;
473 } ->
474 Concat
476 t env kw;
477 Space;
478 t env use_kind;
479 when_present use_kind space;
480 t env prefix;
481 transform_argish env left_b clauses right_b;
482 t env semi;
483 Newline;
485 | Syntax.NamespaceUseClause
487 namespace_use_clause_kind = use_kind;
488 namespace_use_name = name;
489 namespace_use_as = as_kw;
490 namespace_use_alias = alias;
491 } ->
492 Concat
494 t env use_kind;
495 when_present use_kind space;
496 t env name;
497 when_present as_kw space;
498 t env as_kw;
499 when_present alias space;
500 t env alias;
502 | Syntax.FunctionDeclaration
504 function_attribute_spec = attr;
505 function_declaration_header = header;
506 function_body = body;
507 } ->
508 Concat
510 t env attr;
511 when_present attr newline;
512 t env header;
513 handle_possible_compound_statement env ~allow_collapse:true body;
514 Newline;
516 | Syntax.FunctionDeclarationHeader
518 function_modifiers = modifiers;
519 function_keyword = kw;
520 function_name = name;
521 function_type_parameter_list = type_params;
522 function_left_paren = leftp;
523 function_parameter_list = params;
524 function_right_paren = rightp;
525 function_contexts = ctxs;
526 function_colon = colon;
527 function_readonly_return = readonly_return;
528 function_type = ret_type;
529 function_where_clause = where;
530 } ->
531 Concat
533 Span (transform_fn_decl_name env modifiers kw name type_params leftp);
534 transform_fn_decl_args env params rightp;
535 t env ctxs;
536 t env colon;
537 when_present colon space;
538 t env readonly_return;
539 when_present readonly_return space;
540 t env ret_type;
541 when_present where space;
542 t env where;
544 | Syntax.WhereClause
545 { where_clause_keyword = where; where_clause_constraints = constraints }
547 Concat
549 WithRule
550 ( Rule.Parental,
551 Concat
553 Space;
554 Split;
555 t env where;
556 Nest
558 handle_possible_list
560 constraints
561 ~before_each:space_split
562 ~handle_last:
563 (transform_last_arg env ~allow_trailing:false)
564 ~handle_element:(transform_argish_item env);
566 ] );
568 | Syntax.WhereConstraint
570 where_constraint_left_type = left;
571 where_constraint_operator = op;
572 where_constraint_right_type = right;
573 } ->
574 Concat [t env left; Space; t env op; Space; t env right]
575 | Syntax.Contexts
577 contexts_left_bracket = lb;
578 contexts_types = tys;
579 contexts_right_bracket = rb;
580 } ->
581 transform_argish env lb tys rb
582 | Syntax.FunctionCtxTypeSpecifier
583 { function_ctx_type_keyword = kw; function_ctx_type_variable = var } ->
584 Concat [t env kw; Space; t env var]
585 | Syntax.MethodishDeclaration
587 methodish_attribute = attr;
588 methodish_function_decl_header = func_decl;
589 methodish_function_body = body;
590 methodish_semicolon = semi;
591 } ->
592 Concat
594 t env attr;
595 when_present attr newline;
596 t env func_decl;
597 when_present body (fun () ->
598 handle_possible_compound_statement env ~allow_collapse:true body);
599 t env semi;
600 Newline;
602 | Syntax.MethodishTraitResolution
604 methodish_trait_attribute = attr;
605 methodish_trait_function_decl_header = func_decl;
606 methodish_trait_equal = equal;
607 methodish_trait_name = name;
608 methodish_trait_semicolon = semi;
609 } ->
610 Concat
612 t env attr;
613 when_present attr newline;
614 t env func_decl;
615 t env equal;
616 t env name;
617 t env semi;
618 Newline;
620 | Syntax.ClassishDeclaration
622 classish_attribute = attr;
623 classish_modifiers = modifiers;
624 classish_xhp = xhp;
625 classish_keyword = kw;
626 classish_name = name;
627 classish_type_parameters = type_params;
628 classish_extends_keyword = extends_kw;
629 classish_extends_list = extends;
630 classish_implements_keyword = impl_kw;
631 classish_implements_list = impls;
632 classish_where_clause = where;
633 classish_body = body;
634 } ->
635 let after_each_ancestor is_last =
636 if is_last then
637 Nothing
638 else
639 space_split ()
641 Concat
643 t env attr;
644 when_present attr newline;
645 Span
647 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
648 t env xhp;
649 when_present xhp space;
650 t env kw;
651 Space;
652 SplitWith Cost.Base;
653 Nest [t env name; t env type_params];
655 WithRule
656 ( Rule.Parental,
657 Concat
659 when_present extends_kw (fun () ->
660 Nest
662 Space;
663 Split;
664 t env extends_kw;
665 WithRule
666 ( Rule.Parental,
667 Nest
669 Span
671 Space;
672 (if list_length extends = 1 then
673 SplitWith Cost.Base
674 else
675 Split);
676 Nest
678 handle_possible_list
680 ~after_each:after_each_ancestor
681 extends;
684 ] );
686 when_present impl_kw (fun () ->
687 Nest
689 Space;
690 Split;
691 t env impl_kw;
692 WithRule
693 ( Rule.Parental,
694 Nest
696 Span
698 Space;
699 (if list_length impls = 1 then
700 SplitWith Cost.Base
701 else
702 Split);
703 Nest
705 handle_possible_list
707 ~after_each:after_each_ancestor
708 impls;
711 ] );
713 when_present where space;
714 t env where;
715 ] );
716 t env body;
718 | Syntax.ClassishBody
720 classish_body_left_brace = left_b;
721 classish_body_elements = body;
722 classish_body_right_brace = right_b;
723 } ->
724 Concat
726 Space;
727 braced_block_nest env left_b right_b [handle_possible_list env body];
728 Newline;
730 | Syntax.TraitUsePrecedenceItem
732 trait_use_precedence_item_name = name;
733 trait_use_precedence_item_keyword = kw;
734 trait_use_precedence_item_removed_names = removed_names;
735 } ->
736 Concat
738 t env name;
739 Space;
740 t env kw;
741 Space;
742 WithRule
743 ( Rule.Parental,
744 Nest
746 handle_possible_list env ~before_each:space_split removed_names;
747 ] );
749 | Syntax.TraitUseAliasItem
751 trait_use_alias_item_aliasing_name = aliasing_name;
752 trait_use_alias_item_keyword = kw;
753 trait_use_alias_item_modifiers = visibility;
754 trait_use_alias_item_aliased_name = aliased_name;
755 } ->
756 Concat
758 t env aliasing_name;
759 Space;
760 t env kw;
761 Space;
762 t env visibility;
763 Space;
764 t env aliased_name;
766 | Syntax.TraitUseConflictResolution
768 trait_use_conflict_resolution_keyword = kw;
769 trait_use_conflict_resolution_names = elements;
770 trait_use_conflict_resolution_left_brace = lb;
771 trait_use_conflict_resolution_clauses = clauses;
772 trait_use_conflict_resolution_right_brace = rb;
773 } ->
774 Concat
776 t env kw;
777 WithRule
778 ( Rule.Parental,
779 Nest [handle_possible_list env ~before_each:space_split elements]
781 Space;
782 t env lb;
783 Newline;
784 Nest [handle_possible_list env ~before_each:newline clauses];
785 Newline;
786 t env rb;
788 | Syntax.TraitUse
790 trait_use_keyword = kw;
791 trait_use_names = elements;
792 trait_use_semicolon = semi;
793 } ->
794 Concat
796 t env kw;
797 (match Syntax.syntax elements with
798 | Syntax.SyntaxList [x] -> Concat [Space; t env x]
799 | Syntax.SyntaxList _ ->
800 WithRule
801 ( Rule.Parental,
802 Nest
803 [handle_possible_list env ~before_each:space_split elements]
805 | _ -> Concat [Space; t env elements]);
806 t env semi;
807 Newline;
809 | Syntax.RequireClause
811 require_keyword = kw;
812 require_kind = kind;
813 require_name = name;
814 require_semicolon = semi;
815 } ->
816 let name = t env name in
817 Concat
819 t env kw;
820 Space;
821 t env kind;
822 Space;
823 (if has_split name then
824 SplitWith Cost.High
825 else
826 Nothing);
827 Nest [name; t env semi];
828 Newline;
830 | Syntax.ConstDeclaration
832 const_modifiers = modifiers;
833 const_keyword = kw;
834 const_type_specifier = const_type;
835 const_declarators = declarators;
836 const_semicolon = semi;
837 } ->
838 Concat
840 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
841 t env kw;
842 when_present const_type space;
843 t env const_type;
844 handle_declarator_list env declarators;
845 t env semi;
846 Newline;
848 | Syntax.TypeConstDeclaration
850 type_const_attribute_spec = attr;
851 type_const_modifiers = modifiers;
852 type_const_keyword = kw;
853 type_const_type_keyword = type_kw;
854 type_const_name = name;
855 type_const_type_parameters = type_params;
856 type_const_type_constraint = type_constraint;
857 type_const_equal = eq;
858 type_const_type_specifier = type_spec;
859 type_const_semicolon = semi;
860 } ->
861 Concat
863 t env attr;
864 when_present attr newline;
865 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
866 Space;
867 t env kw;
868 Space;
869 t env type_kw;
870 Space;
871 t env name;
872 t env type_params;
873 when_present type_constraint space;
874 t env type_constraint;
875 when_present eq space;
876 t env eq;
877 when_present type_spec (fun _ ->
878 Concat [Space; SplitWith Cost.Base; Nest [t env type_spec]]);
879 t env semi;
880 Newline;
882 | Syntax.ContextConstDeclaration
884 context_const_modifiers = modifiers;
885 context_const_const_keyword = kw;
886 context_const_ctx_keyword = ctx_kw;
887 context_const_name = name;
888 context_const_type_parameters = type_params;
889 context_const_constraint = constraint_list;
890 context_const_equal = eq;
891 context_const_ctx_list = ctx_list;
892 context_const_semicolon = semi;
893 } ->
894 Concat
896 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
897 Space;
898 t env kw;
899 Space;
900 t env ctx_kw;
901 Space;
902 t env name;
903 t env type_params;
904 when_present constraint_list space;
905 handle_possible_list
907 ~after_each:(fun is_last ->
908 if is_last then
909 Nothing
910 else
911 Space)
912 constraint_list;
913 when_present eq space;
914 t env eq;
915 when_present ctx_list (fun _ ->
916 Concat [Space; SplitWith Cost.Base; Nest [t env ctx_list]]);
917 t env semi;
918 Newline;
920 | Syntax.ParameterDeclaration
922 parameter_attribute = attr;
923 parameter_visibility = visibility;
924 parameter_call_convention = callconv;
925 parameter_readonly = readonly;
926 parameter_type = param_type;
927 parameter_name = name;
928 parameter_default_value = default;
929 } ->
930 Concat
932 handle_attribute_spec env attr ~always_split:false;
933 when_present attr (fun _ -> Concat [Space; SplitWith Cost.Base]);
934 t env visibility;
935 when_present visibility space;
936 t env callconv;
937 when_present callconv space;
938 t env readonly;
939 when_present readonly space;
940 t env param_type;
942 Syntax.is_missing visibility
943 && Syntax.is_missing callconv
944 && Syntax.is_missing param_type
945 then
946 t env name
947 else
948 Concat [Space; SplitWith Cost.Moderate; Nest [t env name]]);
949 t env default;
951 | Syntax.VariadicParameter
953 variadic_parameter_call_convention = callconv;
954 variadic_parameter_type = type_var;
955 variadic_parameter_ellipsis = ellipsis;
956 } ->
957 Concat
959 t env callconv;
960 when_present callconv space;
961 t env type_var;
962 t env ellipsis;
964 | Syntax.FileAttributeSpecification
966 file_attribute_specification_left_double_angle = left_da;
967 file_attribute_specification_keyword = keyword;
968 file_attribute_specification_colon = colon;
969 file_attribute_specification_attributes = attrs;
970 file_attribute_specification_right_double_angle = right_da;
971 } ->
972 Concat
974 t env left_da;
975 t env keyword;
976 t env colon;
977 when_present colon space;
978 transform_possible_comma_list env ~allow_trailing:false attrs right_da;
979 Newline;
981 | Syntax.OldAttributeSpecification _
982 | Syntax.AttributeSpecification _ ->
983 handle_attribute_spec env node ~always_split:true
984 | Syntax.Attribute { attribute_at = at; attribute_attribute_name = attr } ->
985 Concat [t env at; t env attr]
986 | Syntax.AttributizedSpecifier
988 attributized_specifier_attribute_spec = attr_spec;
989 attributized_specifier_type = attr_type;
990 } ->
991 Concat
993 handle_attribute_spec env attr_spec ~always_split:false;
994 Space;
995 t env attr_type;
997 | Syntax.InclusionExpression
998 { inclusion_require = kw; inclusion_filename = expr } ->
999 Concat
1001 t env kw;
1002 (match Syntax.syntax expr with
1003 | Syntax.ParenthesizedExpression _ -> Nothing
1004 | _ -> Space);
1005 SplitWith Cost.Base;
1006 t env expr;
1008 | Syntax.InclusionDirective
1009 { inclusion_expression = expr; inclusion_semicolon = semi } ->
1010 Concat [t env expr; t env semi; Newline]
1011 | Syntax.CompoundStatement
1012 { compound_left_brace; compound_statements; compound_right_brace } ->
1013 Concat
1015 handle_compound_statement
1017 compound_left_brace
1018 compound_statements
1019 compound_right_brace;
1020 Newline;
1022 | Syntax.UnsetStatement
1024 unset_keyword = kw;
1025 unset_left_paren = left_p;
1026 unset_variables = args;
1027 unset_right_paren = right_p;
1028 unset_semicolon = semi;
1029 } ->
1030 Concat
1032 t env kw;
1033 transform_argish env ~allow_trailing:false left_p args right_p;
1034 t env semi;
1035 Newline;
1037 | Syntax.WhileStatement x ->
1038 Concat
1040 t env x.while_keyword;
1041 Space;
1042 t env x.while_left_paren;
1043 Split;
1044 WithRule
1045 ( Rule.Parental,
1046 Concat
1048 Nest [t env x.while_condition];
1049 Split;
1050 t env x.while_right_paren;
1051 ] );
1052 handle_possible_compound_statement env x.while_body;
1053 Newline;
1055 | Syntax.UsingStatementBlockScoped x ->
1056 Concat
1058 t env x.using_block_await_keyword;
1059 when_present x.using_block_await_keyword space;
1060 t env x.using_block_using_keyword;
1061 Space;
1062 t env x.using_block_left_paren;
1063 Split;
1064 WithRule
1065 ( Rule.Parental,
1066 Concat
1068 Nest
1070 handle_possible_list
1072 ~after_each:separate_with_space_split
1073 x.using_block_expressions;
1075 Split;
1076 t env x.using_block_right_paren;
1077 ] );
1078 handle_possible_compound_statement env x.using_block_body;
1079 Newline;
1081 | Syntax.UsingStatementFunctionScoped x ->
1082 Concat
1084 t env x.using_function_await_keyword;
1085 when_present x.using_function_await_keyword space;
1086 t env x.using_function_using_keyword;
1087 Space;
1088 t env x.using_function_expression;
1089 t env x.using_function_semicolon;
1090 Newline;
1092 | Syntax.IfStatement
1094 if_keyword = kw;
1095 if_left_paren = left_p;
1096 if_condition = condition;
1097 if_right_paren = right_p;
1098 if_statement = if_body;
1099 if_elseif_clauses = elseif_clauses;
1100 if_else_clause = else_clause;
1101 } ->
1102 Concat
1104 t env kw;
1105 Space;
1106 transform_condition env left_p condition right_p;
1107 transform_consequence t env if_body right_p;
1108 handle_possible_list env elseif_clauses;
1109 t env else_clause;
1110 Newline;
1112 | Syntax.ElseifClause
1114 elseif_keyword = kw;
1115 elseif_left_paren = left_p;
1116 elseif_condition = condition;
1117 elseif_right_paren = right_p;
1118 elseif_statement = body;
1119 } ->
1120 Concat
1122 t env kw;
1123 Space;
1124 transform_condition env left_p condition right_p;
1125 transform_consequence t env body right_p;
1127 | Syntax.ElseClause x ->
1128 Concat
1130 t env x.else_keyword;
1131 (match Syntax.syntax x.else_statement with
1132 | Syntax.IfStatement _ ->
1133 Concat [Space; t env x.else_statement; Space]
1134 | _ -> transform_consequence t env x.else_statement x.else_keyword);
1136 | Syntax.TryStatement
1138 try_keyword = kw;
1139 try_compound_statement = body;
1140 try_catch_clauses = catch_clauses;
1141 try_finally_clause = finally_clause;
1142 } ->
1143 (* TODO: revisit *)
1144 Concat
1146 t env kw;
1147 handle_possible_compound_statement env body;
1148 handle_possible_list env catch_clauses;
1149 t env finally_clause;
1150 Newline;
1152 | Syntax.CatchClause
1154 catch_keyword = kw;
1155 catch_left_paren = left_p;
1156 catch_type = ex_type;
1157 catch_variable = var;
1158 catch_right_paren = right_p;
1159 catch_body = body;
1160 } ->
1161 Concat
1163 t env kw;
1164 Space;
1165 delimited_nest
1167 left_p
1168 right_p
1169 [t env ex_type; Space; SplitWith Cost.Base; Nest [t env var]];
1170 handle_possible_compound_statement env body;
1172 | Syntax.FinallyClause { finally_keyword = kw; finally_body = body } ->
1173 Concat [t env kw; Space; handle_possible_compound_statement env body]
1174 | Syntax.DoStatement
1176 do_keyword = do_kw;
1177 do_body = body;
1178 do_while_keyword = while_kw;
1179 do_left_paren = left_p;
1180 do_condition = cond;
1181 do_right_paren = right_p;
1182 do_semicolon = semi;
1183 } ->
1184 Concat
1186 t env do_kw;
1187 Space;
1188 handle_possible_compound_statement env body;
1189 t env while_kw;
1190 Space;
1191 transform_condition env left_p cond right_p;
1192 t env semi;
1193 Newline;
1195 | Syntax.ForStatement
1197 for_keyword = kw;
1198 for_left_paren = left_p;
1199 for_initializer = init;
1200 for_first_semicolon = semi1;
1201 for_control = control;
1202 for_second_semicolon = semi2;
1203 for_end_of_loop = after_iter;
1204 for_right_paren = right_p;
1205 for_body = body;
1206 } ->
1207 Concat
1209 t env kw;
1210 Space;
1211 t env left_p;
1212 WithRule
1213 ( Rule.Parental,
1214 Concat
1216 Split;
1217 Nest
1219 handle_possible_list
1221 ~after_each:separate_with_space_split
1222 init;
1223 t env semi1;
1224 Space;
1225 Split;
1226 handle_possible_list
1228 ~after_each:separate_with_space_split
1229 control;
1230 t env semi2;
1231 Space;
1232 Split;
1233 handle_possible_list
1235 ~after_each:separate_with_space_split
1236 after_iter;
1238 Split;
1239 t env right_p;
1240 ] );
1241 handle_possible_compound_statement env body;
1242 Newline;
1244 | Syntax.ForeachStatement
1246 foreach_keyword = kw;
1247 foreach_left_paren = left_p;
1248 foreach_collection = collection;
1249 foreach_await_keyword = await_kw;
1250 foreach_as = as_kw;
1251 foreach_key = key;
1252 foreach_arrow = arrow;
1253 foreach_value = value;
1254 foreach_right_paren = right_p;
1255 foreach_body = body;
1256 } ->
1257 Concat
1259 t env kw;
1260 Space;
1261 delimited_nest
1263 left_p
1264 right_p
1266 t env collection;
1267 Space;
1268 t env await_kw;
1269 Space;
1270 t env as_kw;
1271 Space;
1272 SplitWith Cost.Base;
1273 Nest
1275 Span
1277 t env key;
1278 Space;
1279 t env arrow;
1280 Space;
1281 SplitWith Cost.Base;
1282 Nest [t env value];
1286 handle_possible_compound_statement env body;
1287 Newline;
1289 | Syntax.SwitchStatement
1291 switch_keyword = kw;
1292 switch_left_paren = left_p;
1293 switch_expression = expr;
1294 switch_right_paren = right_p;
1295 switch_left_brace = left_b;
1296 switch_sections = sections;
1297 switch_right_brace = right_b;
1298 } ->
1299 let sections = Syntax.syntax_node_to_list sections in
1300 Concat
1302 t env kw;
1303 Space;
1304 delimited_nest env left_p right_p [t env expr];
1305 Space;
1306 braced_block_nest env left_b right_b (List.map sections ~f:(t env));
1307 Newline;
1309 | Syntax.SwitchSection
1311 switch_section_labels = labels;
1312 switch_section_statements = statements;
1313 switch_section_fallthrough = fallthrough;
1314 } ->
1315 (* If there is FallThrough trivia leading the first case label, handle it
1316 * in a BlockNest so that it is indented to the same level as the previous
1317 * SwitchSection's statements. *)
1318 let (labels_leading, labels) = remove_leading_trivia labels in
1319 let (after_fallthrough, upto_fallthrough) =
1320 List.split_while (List.rev labels_leading) ~f:(fun t ->
1321 not (is_trivia_kind_fallthrough (Trivia.kind t)))
1323 let upto_fallthrough = List.rev upto_fallthrough in
1324 let after_fallthrough = List.rev after_fallthrough in
1325 let labels = Syntax.syntax_node_to_list labels in
1326 let statements = Syntax.syntax_node_to_list statements in
1327 (* When the statements in the SwitchSection are wrapped in a single
1328 * CompoundStatement, special-case the opening curly brace to appear on
1329 * the same line as the case label. *)
1330 let is_scoped_section =
1331 match statements with
1332 | [Syntax.{ syntax = CompoundStatement _; _ }] -> true
1333 | _ -> false
1335 Concat
1337 (if List.is_empty upto_fallthrough then
1338 transform_leading_trivia after_fallthrough
1339 else
1340 Concat
1342 BlockNest [transform_leading_trivia upto_fallthrough; Newline];
1343 transform_trailing_trivia after_fallthrough;
1345 handle_list env labels ~after_each:(fun is_last_label ->
1346 if is_last_label && is_scoped_section then
1347 Nothing
1348 else
1349 Newline);
1350 (if is_scoped_section then
1351 handle_list env statements
1352 else
1353 BlockNest [handle_list env statements]);
1354 t env fallthrough;
1356 | Syntax.CaseLabel
1357 { case_keyword = kw; case_expression = expr; case_colon = colon } ->
1358 Concat [t env kw; Space; t env expr; t env colon]
1359 | Syntax.DefaultLabel { default_keyword = kw; default_colon = colon } ->
1360 Concat [t env kw; t env colon]
1361 | Syntax.SwitchFallthrough
1362 { fallthrough_keyword = kw; fallthrough_semicolon = semi } ->
1363 Concat [t env kw; t env semi]
1364 | Syntax.ReturnStatement
1366 return_keyword = kw;
1367 return_expression = expr;
1368 return_semicolon = semi;
1369 } ->
1370 transform_keyword_expression_statement env kw expr semi
1371 | Syntax.YieldBreakStatement
1373 yield_break_keyword = kw;
1374 yield_break_break = y;
1375 yield_break_semicolon = semi;
1376 } ->
1377 Concat [t env kw; Space; t env y; t env semi]
1378 | Syntax.ThrowStatement
1379 { throw_keyword = kw; throw_expression = expr; throw_semicolon = semi }
1381 transform_keyword_expression_statement env kw expr semi
1382 | Syntax.BreakStatement { break_keyword = kw; break_semicolon = semi }
1383 | Syntax.ContinueStatement
1384 { continue_keyword = kw; continue_semicolon = semi } ->
1385 Concat [t env kw; t env semi; Newline]
1386 | Syntax.EchoStatement
1388 echo_keyword = kw;
1389 echo_expressions = expr_list;
1390 echo_semicolon = semi;
1391 } ->
1392 (match Syntax.syntax expr_list with
1393 | Syntax.SyntaxList
1394 [Syntax.{ syntax = ListItem { list_item = expr; _ }; _ }]
1395 when is_syntax_kind_parenthesized_exprression (Syntax.kind expr) ->
1396 Concat [t env kw; t env expr; t env semi; Newline]
1397 | _ -> transform_keyword_expr_list_statement env kw expr_list semi)
1398 | Syntax.ConcurrentStatement
1399 { concurrent_keyword = kw; concurrent_statement = statement } ->
1400 Concat
1402 t env kw;
1403 Space;
1404 handle_possible_compound_statement env statement;
1405 Newline;
1407 | Syntax.SimpleInitializer
1408 { simple_initializer_equal = eq_kw; simple_initializer_value = value }
1410 Concat
1411 [Space; t env eq_kw; Space; SplitWith Cost.Base; Nest [t env value]]
1412 | Syntax.AnonymousFunction
1414 anonymous_attribute_spec = attr;
1415 anonymous_async_keyword = async_kw;
1416 anonymous_function_keyword = fun_kw;
1417 anonymous_left_paren = lp;
1418 anonymous_parameters = params;
1419 anonymous_right_paren = rp;
1420 anonymous_ctx_list = ctx_list;
1421 anonymous_colon = colon;
1422 anonymous_readonly_return = readonly_ret;
1423 anonymous_type = ret_type;
1424 anonymous_use = use;
1425 anonymous_body = body;
1426 } ->
1427 Concat
1429 handle_attribute_spec env attr ~always_split:false;
1430 when_present attr space;
1431 t env async_kw;
1432 when_present async_kw space;
1433 t env fun_kw;
1434 transform_argish_with_return_type
1437 params
1439 ctx_list
1440 colon
1441 readonly_ret
1442 ret_type;
1443 t env use;
1444 handle_possible_compound_statement
1446 ~space:false
1447 ~allow_collapse:true
1448 body;
1450 | Syntax.AnonymousFunctionUseClause
1452 anonymous_use_keyword = kw;
1453 anonymous_use_left_paren = left_p;
1454 anonymous_use_variables = vars;
1455 anonymous_use_right_paren = right_p;
1456 } ->
1457 (* TODO: Revisit *)
1458 Concat [Space; t env kw; Space; transform_argish env left_p vars right_p]
1459 | Syntax.LambdaExpression
1461 lambda_attribute_spec = attr;
1462 lambda_async = async;
1463 lambda_signature = signature;
1464 lambda_arrow = arrow;
1465 lambda_body = body;
1466 } ->
1467 Concat
1469 handle_attribute_spec env attr ~always_split:false;
1470 when_present attr space;
1471 t env async;
1472 when_present async space;
1473 t env signature;
1474 Space;
1475 t env arrow;
1476 handle_lambda_body env body;
1478 | Syntax.LambdaSignature
1480 lambda_left_paren = lp;
1481 lambda_parameters = params;
1482 lambda_right_paren = rp;
1483 lambda_contexts = ctxs;
1484 lambda_colon = colon;
1485 lambda_readonly_return = readonly;
1486 lambda_type = ret_type;
1487 } ->
1488 Concat
1490 t env lp;
1491 when_present params split;
1492 transform_fn_decl_args env params rp;
1493 t env ctxs;
1494 t env colon;
1495 when_present colon space;
1496 t env readonly;
1497 when_present readonly space;
1498 t env ret_type;
1500 | Syntax.CastExpression _ ->
1501 Span (List.map (Syntax.children node) ~f:(t env))
1502 | Syntax.MemberSelectionExpression _
1503 | Syntax.SafeMemberSelectionExpression _ ->
1504 handle_possible_chaining env node
1505 | Syntax.YieldExpression { yield_keyword = kw; yield_operand = operand } ->
1506 Concat [t env kw; Space; SplitWith Cost.Base; Nest [t env operand]]
1507 | Syntax.PrefixUnaryExpression
1508 { prefix_unary_operator = operator; prefix_unary_operand = operand } ->
1509 Concat
1511 t env operator;
1512 (match Syntax.syntax operator with
1513 | Syntax.Token x ->
1514 let is_parenthesized =
1515 match Syntax.syntax operand with
1516 | Syntax.ParenthesizedExpression _ -> true
1517 | _ -> false
1519 TokenKind.(
1520 (match Token.kind x with
1521 | Await
1522 | Readonly
1523 | Clone ->
1524 Space
1525 | Print ->
1526 if is_parenthesized then
1527 Nothing
1528 else
1529 Space
1530 | _ -> Nothing))
1531 | _ -> Nothing);
1532 t env operand;
1534 | Syntax.BinaryExpression
1535 { binary_left_operand; binary_operator; binary_right_operand } ->
1536 transform_binary_expression
1538 ~is_nested:false
1539 (binary_left_operand, binary_operator, binary_right_operand)
1540 | Syntax.IsExpression
1541 { is_left_operand = left; is_operator = kw; is_right_operand = right }
1542 | Syntax.AsExpression
1543 { as_left_operand = left; as_operator = kw; as_right_operand = right }
1544 | Syntax.NullableAsExpression
1546 nullable_as_left_operand = left;
1547 nullable_as_operator = kw;
1548 nullable_as_right_operand = right;
1550 | Syntax.UpcastExpression
1552 upcast_left_operand = left;
1553 upcast_operator = kw;
1554 upcast_right_operand = right;
1555 } ->
1556 Concat
1558 t env left;
1559 Space;
1560 SplitWith Cost.Base;
1561 Nest [t env kw; Space; t env right];
1563 | Syntax.ConditionalExpression
1565 conditional_test = test_expr;
1566 conditional_question = q_kw;
1567 conditional_consequence = true_expr;
1568 conditional_colon = c_kw;
1569 conditional_alternative = false_expr;
1570 } ->
1571 WithLazyRule
1572 ( Rule.Parental,
1573 t env test_expr,
1574 Nest
1576 Space;
1577 Split;
1578 t env q_kw;
1579 when_present true_expr (fun () ->
1580 Concat
1582 Space;
1583 (if env.Env.indent_width = 2 then
1584 Nest [t env true_expr]
1585 else
1586 t env true_expr);
1587 Space;
1588 Split;
1590 t env c_kw;
1591 Space;
1593 (not (Syntax.is_missing true_expr)) && env.Env.indent_width = 2
1594 then
1595 Nest [t env false_expr]
1596 else
1597 t env false_expr);
1599 | Syntax.FunctionCallExpression _ -> handle_possible_chaining env node
1600 | Syntax.FunctionPointerExpression _ -> transform_simple env node
1601 | Syntax.EvalExpression
1603 eval_keyword = kw;
1604 eval_left_paren = left_p;
1605 eval_argument = arg;
1606 eval_right_paren = right_p;
1607 } ->
1608 Concat [t env kw; transform_braced_item env left_p arg right_p]
1609 | Syntax.IssetExpression
1611 isset_keyword = kw;
1612 isset_left_paren = left_p;
1613 isset_argument_list = args;
1614 isset_right_paren = right_p;
1615 } ->
1616 Concat
1618 t env kw;
1619 transform_argish env ~allow_trailing:false left_p args right_p;
1621 | Syntax.ParenthesizedExpression
1623 parenthesized_expression_left_paren = left_p;
1624 parenthesized_expression_expression = expr;
1625 parenthesized_expression_right_paren = right_p;
1626 } ->
1627 Concat
1629 t env left_p;
1630 Split;
1631 WithRule
1632 (Rule.Parental, Concat [Nest [t env expr]; Split; t env right_p]);
1634 | Syntax.ETSpliceExpression
1636 et_splice_expression_dollar = dollar;
1637 et_splice_expression_left_brace = left_p;
1638 et_splice_expression_expression = expr;
1639 et_splice_expression_right_brace = right_p;
1640 } ->
1641 Concat
1643 t env dollar;
1644 t env left_p;
1645 Split;
1646 WithRule
1647 (Rule.Parental, Concat [Nest [t env expr]; Split; t env right_p]);
1649 | Syntax.BracedExpression
1651 braced_expression_left_brace = left_b;
1652 braced_expression_expression = expr;
1653 braced_expression_right_brace = right_b;
1654 } ->
1655 (* TODO: revisit this *)
1656 Concat
1658 t env left_b;
1659 Split;
1660 (let rule =
1662 List.is_empty (Syntax.trailing_trivia left_b)
1663 && List.is_empty (Syntax.trailing_trivia expr)
1664 then
1665 Rule.Simple Cost.Base
1666 else
1667 Rule.Parental
1669 WithRule (rule, Concat [Nest [t env expr]; Split; t env right_b]));
1671 | Syntax.EmbeddedBracedExpression
1673 embedded_braced_expression_left_brace = left_b;
1674 embedded_braced_expression_expression = expr;
1675 embedded_braced_expression_right_brace = right_b;
1676 } ->
1677 (* TODO: Consider finding a way to avoid treating these expressions as
1678 opportunities for line breaks in long strings:
1680 $sql = "DELETE FROM `foo` WHERE `left` BETWEEN {$res->left} AND {$res
1681 ->right} ORDER BY `level` DESC";
1683 Concat [t env left_b; Nest [t env expr]; t env right_b]
1684 | Syntax.ListExpression
1686 list_keyword = kw;
1687 list_left_paren = lp;
1688 list_members = members;
1689 list_right_paren = rp;
1690 } ->
1691 Concat [t env kw; transform_argish env lp members rp]
1692 | Syntax.CollectionLiteralExpression
1694 collection_literal_name = name;
1695 collection_literal_left_brace = left_b;
1696 collection_literal_initializers = initializers;
1697 collection_literal_right_brace = right_b;
1698 } ->
1699 transform_container_literal
1701 ~space:true
1702 name
1703 left_b
1704 initializers
1705 right_b
1706 | Syntax.ObjectCreationExpression
1707 { object_creation_new_keyword = newkw; object_creation_object = what }
1709 Concat [t env newkw; Space; t env what]
1710 | Syntax.ConstructorCall
1712 constructor_call_type = obj_type;
1713 constructor_call_left_paren = left_p;
1714 constructor_call_argument_list = arg_list;
1715 constructor_call_right_paren = right_p;
1716 } ->
1717 Concat [t env obj_type; transform_argish env left_p arg_list right_p]
1718 | Syntax.RecordCreationExpression
1720 record_creation_type = rec_type;
1721 record_creation_left_bracket = left_b;
1722 record_creation_members = members;
1723 record_creation_right_bracket = right_b;
1724 } ->
1725 transform_container_literal env rec_type left_b members right_b
1726 | Syntax.AnonymousClass
1728 anonymous_class_class_keyword = classkw;
1729 anonymous_class_left_paren = left_p;
1730 anonymous_class_argument_list = arg_list;
1731 anonymous_class_right_paren = right_p;
1732 anonymous_class_extends_keyword = extends_kw;
1733 anonymous_class_extends_list = extends;
1734 anonymous_class_implements_keyword = impl_kw;
1735 anonymous_class_implements_list = impls;
1736 anonymous_class_body = body;
1737 } ->
1738 let after_each_ancestor is_last =
1739 if is_last then
1740 Nothing
1741 else
1742 space_split ()
1744 Concat
1746 t env classkw;
1747 transform_argish env left_p arg_list right_p;
1748 when_present extends_kw (fun () ->
1749 Concat
1751 Space;
1752 Split;
1753 WithRule
1754 ( Rule.Parental,
1755 Nest
1757 Span
1759 t env extends_kw;
1760 Space;
1761 Split;
1762 WithRule
1763 ( Rule.Parental,
1764 Nest
1766 handle_possible_list
1768 ~after_each:after_each_ancestor
1769 extends;
1770 ] );
1772 ] );
1774 when_present impl_kw (fun () ->
1775 Concat
1777 Space;
1778 Split;
1779 WithRule
1780 ( Rule.Parental,
1781 Nest
1783 Span
1785 t env impl_kw;
1786 Space;
1787 Split;
1788 WithRule
1789 ( Rule.Parental,
1790 Nest
1792 handle_possible_list
1794 ~after_each:after_each_ancestor
1795 impls;
1796 ] );
1798 ] );
1800 t env body;
1802 | Syntax.DarrayIntrinsicExpression
1804 darray_intrinsic_keyword = kw;
1805 darray_intrinsic_explicit_type = explicit_type;
1806 darray_intrinsic_left_bracket = left_p;
1807 darray_intrinsic_members = members;
1808 darray_intrinsic_right_bracket = right_p;
1810 | Syntax.DictionaryIntrinsicExpression
1812 dictionary_intrinsic_keyword = kw;
1813 dictionary_intrinsic_explicit_type = explicit_type;
1814 dictionary_intrinsic_left_bracket = left_p;
1815 dictionary_intrinsic_members = members;
1816 dictionary_intrinsic_right_bracket = right_p;
1818 | Syntax.KeysetIntrinsicExpression
1820 keyset_intrinsic_keyword = kw;
1821 keyset_intrinsic_explicit_type = explicit_type;
1822 keyset_intrinsic_left_bracket = left_p;
1823 keyset_intrinsic_members = members;
1824 keyset_intrinsic_right_bracket = right_p;
1826 | Syntax.VarrayIntrinsicExpression
1828 varray_intrinsic_keyword = kw;
1829 varray_intrinsic_explicit_type = explicit_type;
1830 varray_intrinsic_left_bracket = left_p;
1831 varray_intrinsic_members = members;
1832 varray_intrinsic_right_bracket = right_p;
1834 | Syntax.VectorIntrinsicExpression
1836 vector_intrinsic_keyword = kw;
1837 vector_intrinsic_explicit_type = explicit_type;
1838 vector_intrinsic_left_bracket = left_p;
1839 vector_intrinsic_members = members;
1840 vector_intrinsic_right_bracket = right_p;
1841 } ->
1842 transform_container_literal env kw ~explicit_type left_p members right_p
1843 | Syntax.ElementInitializer
1844 { element_key = key; element_arrow = arrow; element_value = value } ->
1845 transform_mapish_entry env key arrow value
1846 | Syntax.SubscriptExpression
1848 subscript_receiver = receiver;
1849 subscript_left_bracket = lb;
1850 subscript_index = expr;
1851 subscript_right_bracket = rb;
1852 } ->
1853 Concat [t env receiver; transform_braced_item env lb expr rb]
1854 | Syntax.AwaitableCreationExpression
1856 awaitable_attribute_spec = attr;
1857 awaitable_async = async_kw;
1858 awaitable_compound_statement = body;
1859 } ->
1860 Concat
1862 handle_attribute_spec env attr ~always_split:false;
1863 when_present attr space;
1864 t env async_kw;
1865 when_present async_kw space;
1866 (* TODO: rethink possible one line bodies *)
1867 (* TODO: correctly handle spacing after the closing brace *)
1868 handle_possible_compound_statement env ~space:false body;
1870 | Syntax.XHPChildrenDeclaration
1872 xhp_children_keyword = kw;
1873 xhp_children_expression = expr;
1874 xhp_children_semicolon = semi;
1875 } ->
1876 Concat [t env kw; Space; t env expr; t env semi; Newline]
1877 | Syntax.XHPChildrenParenthesizedList
1879 xhp_children_list_left_paren = left_p;
1880 xhp_children_list_xhp_children = expressions;
1881 xhp_children_list_right_paren = right_p;
1882 } ->
1883 Concat
1884 [transform_argish env ~allow_trailing:false left_p expressions right_p]
1885 | Syntax.XHPCategoryDeclaration
1887 xhp_category_keyword = kw;
1888 xhp_category_categories = categories;
1889 xhp_category_semicolon = semi;
1890 } ->
1891 Concat
1893 t env kw;
1894 (* TODO: Eliminate code duplication *)
1895 WithRule
1896 ( Rule.Parental,
1897 Nest
1898 [handle_possible_list env ~before_each:space_split categories]
1900 t env semi;
1901 Newline;
1903 | Syntax.XHPEnumType
1905 xhp_enum_keyword = kw;
1906 xhp_enum_left_brace = left_b;
1907 xhp_enum_values = values;
1908 xhp_enum_right_brace = right_b;
1909 } ->
1910 Concat [t env kw; Space; transform_argish env left_b values right_b]
1911 | Syntax.XHPClassAttributeDeclaration
1913 xhp_attribute_keyword = kw;
1914 xhp_attribute_attributes = xhp_attributes;
1915 xhp_attribute_semicolon = semi;
1916 } ->
1917 Concat
1919 t env kw;
1920 (match Syntax.syntax xhp_attributes with
1921 | Syntax.Missing -> Nothing
1922 | Syntax.SyntaxList [attr] ->
1923 WithRule (Rule.Parental, Nest [Space; Split; t env attr])
1924 | Syntax.SyntaxList attrs ->
1925 Nest [handle_list env ~before_each:newline attrs]
1926 | _ -> failwith "Expected SyntaxList");
1927 t env semi;
1928 Newline;
1930 | Syntax.XHPClassAttribute
1932 xhp_attribute_decl_type = attr_type;
1933 xhp_attribute_decl_name = name;
1934 xhp_attribute_decl_initializer = init;
1935 xhp_attribute_decl_required = req;
1936 } ->
1937 (* TODO: figure out nesting here *)
1938 Concat
1940 t env attr_type;
1941 Space;
1942 t env name;
1943 when_present init space;
1944 t env init;
1945 when_present req space;
1946 t env req;
1948 | Syntax.XHPSimpleAttribute
1950 xhp_simple_attribute_name = name;
1951 xhp_simple_attribute_equal = eq;
1952 xhp_simple_attribute_expression = expr;
1953 } ->
1954 Span [t env name; t env eq; SplitWith Cost.Base; Nest [t env expr]]
1955 | Syntax.XHPSpreadAttribute
1957 xhp_spread_attribute_left_brace = l_brace;
1958 xhp_spread_attribute_spread_operator = spread;
1959 xhp_spread_attribute_expression = expr;
1960 xhp_spread_attribute_right_brace = r_brace;
1961 } ->
1962 Span
1964 t env l_brace;
1965 t env spread;
1966 SplitWith Cost.Base;
1967 Nest [t env expr];
1968 t env r_brace;
1970 | Syntax.XHPOpen
1972 xhp_open_left_angle = left_a;
1973 xhp_open_name = name;
1974 xhp_open_attributes = attrs;
1975 xhp_open_right_angle = right_a;
1976 } ->
1977 Concat
1979 t env left_a;
1980 t env name;
1981 (match Syntax.syntax attrs with
1982 | Syntax.Missing ->
1983 handle_xhp_open_right_angle_token env attrs right_a
1984 | _ ->
1985 Concat
1987 Space;
1988 Split;
1989 WithRule
1990 ( Rule.Parental,
1991 Concat
1993 Nest
1995 handle_possible_list
1997 ~after_each:(fun is_last ->
1998 if not is_last then
1999 space_split ()
2000 else
2001 Nothing)
2002 attrs;
2004 handle_xhp_open_right_angle_token env attrs right_a;
2005 ] );
2008 | Syntax.XHPExpression { xhp_open; xhp_body = body; xhp_close = close } ->
2009 let handle_xhp_body body =
2010 match Syntax.syntax body with
2011 | Syntax.Missing -> when_present close split
2012 | Syntax.SyntaxList xs ->
2013 (* Trivia is lexed differently within an XHP body because whitespace is
2014 semantically significant in an XHP body when it is adjacent to an
2015 XHPBody token. Any number of whitespaces or newlines adjacent to an
2016 XHPBody token will be rendered as a single space. In order to make it
2017 easier to determine whether a space character should be rendered next
2018 to an XHPBody token, all trailing trivia in an XHP body is lexed as
2019 leading trivia for the next token (except on XHPBody tokens, where
2020 trailing trivia is lexed normally). This ensures that any time
2021 semantically-significant whitespace is present, at least some of it
2022 occurs in the leading or trailing trivia list of an adjacent XHPBody
2023 token.
2025 To deal with this, we keep track of whether the last token we
2026 transformed was one that trailing trivia is scanned for. If it
2027 wasn't, we handle the next token's leading trivia list using
2028 transform_xhp_leading_trivia, which treats all trivia up to the first
2029 newline as trailing trivia. *)
2030 let prev_token_was_xhpbody = ref false in
2031 let transformed_body =
2032 Concat
2033 (List.map xs ~f:(fun node ->
2034 let node_is_xhpbody =
2035 match Syntax.syntax node with
2036 | Syntax.Token t -> is_token_kind_xhp_body (Token.kind t)
2037 | _ -> false
2040 (* Here, we preserve newlines after XHPBody tokens and don't otherwise
2041 add splits between them. This means that we don't reflow paragraphs
2042 in XHP to fit in the desired line length. It would be nice to do
2043 so, but this is not possible with the current set of Rule types.
2045 If we were to add a split between each XHPBody token instead of
2046 splitting only where newlines were already present, we'd need a new
2047 Rule type to govern word-wrap style splitting, since using
2048 independent splits (e.g. SplitWith Cost.Base) between every token
2049 would make solving too expensive. *)
2050 let preserve_xhpbody_whitespace trivia =
2051 if node_is_xhpbody then
2052 if has_newline trivia then
2053 Newline
2054 else if has_whitespace trivia then
2055 Space
2056 else
2057 Nothing
2058 else
2059 Nothing
2061 let (leading, node) = remove_leading_trivia node in
2062 let trailing = Syntax.trailing_trivia node in
2063 let leading_whitespace =
2064 Concat
2066 (* Whitespace in an XHP body is *only* significant when adjacent to
2067 an XHPBody token, so we are free to add splits between other
2068 nodes (like XHPExpressions and BracedExpressions). *)
2070 (not !prev_token_was_xhpbody) && not node_is_xhpbody
2071 then
2072 Split
2073 else
2074 Nothing);
2075 (* If the previous token was an XHPBody token, the lexer will have
2076 scanned trailing trivia for it, so we can handle the leading
2077 trivia for this node normally. Otherwise, handle the trivia up to
2078 the first newline as trailing trivia. *)
2079 (if !prev_token_was_xhpbody then
2080 transform_leading_trivia leading
2081 else
2082 transform_xhp_leading_trivia leading);
2085 prev_token_was_xhpbody := node_is_xhpbody;
2086 Concat
2088 leading_whitespace;
2089 preserve_xhpbody_whitespace leading;
2090 t env node;
2091 preserve_xhpbody_whitespace trailing;
2094 Concat
2096 transformed_body;
2097 (if !prev_token_was_xhpbody then
2098 Nothing
2099 else if
2100 (* Don't collapse XHPExpressions onto a single line if they were
2101 intentionally split across multiple lines in the original source.
2102 If there is a newline in the body's leading trivia, we consider
2103 that a signal that this expression was intended to be split
2104 across multiple lines. *)
2105 has_newline (Syntax.leading_trivia body)
2106 then
2107 Newline
2108 else
2109 Split);
2111 | _ -> failwith "Expected SyntaxList"
2113 WithOverridingParentalRule
2114 (Concat
2116 t env xhp_open;
2117 Nest [handle_xhp_body body];
2118 when_present close (fun () ->
2119 let (leading, close) = remove_leading_trivia close in
2120 Concat
2122 (* Ignore extra newlines by treating this as trailing trivia *)
2123 ignore_trailing_invisibles leading;
2124 t env close;
2127 | Syntax.VarrayTypeSpecifier
2129 varray_keyword = kw;
2130 varray_left_angle = left_a;
2131 varray_type;
2132 varray_trailing_comma = trailing_comma;
2133 varray_right_angle = right_a;
2134 } ->
2135 Concat
2137 t env kw;
2138 transform_braced_item_with_trailer
2140 left_a
2141 varray_type
2142 trailing_comma
2143 right_a;
2145 | Syntax.VectorTypeSpecifier
2147 vector_type_keyword = kw;
2148 vector_type_left_angle = left_a;
2149 vector_type_type = vec_type;
2150 vector_type_trailing_comma = trailing_comma;
2151 vector_type_right_angle = right_a;
2152 } ->
2153 Concat
2155 t env kw;
2156 transform_braced_item_with_trailer
2158 left_a
2159 vec_type
2160 trailing_comma
2161 right_a;
2163 | Syntax.KeysetTypeSpecifier
2165 keyset_type_keyword = kw;
2166 keyset_type_left_angle = left_a;
2167 keyset_type_type = ks_type;
2168 keyset_type_trailing_comma = trailing_comma;
2169 keyset_type_right_angle = right_a;
2170 } ->
2171 Concat
2173 t env kw;
2174 transform_braced_item_with_trailer
2176 left_a
2177 ks_type
2178 trailing_comma
2179 right_a;
2181 | Syntax.TypeParameter
2183 type_attribute_spec = attr;
2184 type_reified = reified;
2185 type_variance = variance;
2186 type_name = name;
2187 type_param_params = params;
2188 type_constraints = constraints;
2189 } ->
2190 Concat
2192 handle_attribute_spec env attr ~always_split:false;
2193 when_present attr space;
2194 t env reified;
2195 when_present reified space;
2196 t env variance;
2197 t env name;
2198 t env params;
2199 when_present constraints space;
2200 handle_possible_list env constraints ~after_each:(fun is_last ->
2201 if is_last then
2202 Nothing
2203 else
2204 Space);
2206 | Syntax.TypeConstraint { constraint_keyword = kw; constraint_type } ->
2207 Concat [t env kw; Space; t env constraint_type]
2208 | Syntax.ContextConstraint
2209 { ctx_constraint_keyword = kw; ctx_constraint_ctx_list = ctx_list } ->
2210 Concat [t env kw; Space; t env ctx_list]
2211 | Syntax.DarrayTypeSpecifier
2213 darray_keyword = kw;
2214 darray_left_angle = left_a;
2215 darray_key = key;
2216 darray_comma = comma_kw;
2217 darray_value = value;
2218 darray_trailing_comma = trailing_comma;
2219 darray_right_angle = right_a;
2220 } ->
2221 let key_list_item = Syntax.make_list_item key comma_kw in
2222 let val_list_item = Syntax.make_list_item value trailing_comma in
2223 let args = make_list [key_list_item; val_list_item] in
2224 Concat
2226 t env kw; transform_argish env ~allow_trailing:true left_a args right_a;
2228 | Syntax.DictionaryTypeSpecifier
2230 dictionary_type_keyword = kw;
2231 dictionary_type_left_angle = left_a;
2232 dictionary_type_members = members;
2233 dictionary_type_right_angle = right_a;
2234 } ->
2235 Concat [t env kw; transform_argish env left_a members right_a]
2236 | Syntax.ClosureTypeSpecifier
2238 closure_outer_left_paren = outer_left_p;
2239 closure_readonly_keyword = ro;
2240 closure_function_keyword = kw;
2241 closure_inner_left_paren = inner_left_p;
2242 closure_parameter_list = param_list;
2243 closure_inner_right_paren = inner_right_p;
2244 closure_contexts = ctxs;
2245 closure_colon = colon;
2246 closure_readonly_return = readonly;
2247 closure_return_type = ret_type;
2248 closure_outer_right_paren = outer_right_p;
2249 } ->
2250 Concat
2252 t env outer_left_p;
2253 t env ro;
2254 when_present ro space;
2255 t env kw;
2256 t env inner_left_p;
2257 when_present param_list split;
2258 transform_fn_decl_args env param_list inner_right_p;
2259 t env ctxs;
2260 t env colon;
2261 when_present colon space;
2262 t env readonly;
2263 when_present readonly space;
2264 t env ret_type;
2265 t env outer_right_p;
2267 | Syntax.ClosureParameterTypeSpecifier
2269 closure_parameter_call_convention = callconv;
2270 closure_parameter_readonly = readonly;
2271 closure_parameter_type = cp_type;
2272 } ->
2273 Concat
2275 t env callconv;
2276 when_present callconv space;
2277 t env readonly;
2278 when_present readonly space;
2279 t env cp_type;
2281 | Syntax.ClassnameTypeSpecifier
2283 classname_keyword = kw;
2284 classname_left_angle = left_a;
2285 classname_type = class_type;
2286 classname_trailing_comma = trailing_comma;
2287 classname_right_angle = right_a;
2288 } ->
2289 Concat
2291 t env kw;
2292 transform_braced_item_with_trailer
2294 left_a
2295 class_type
2296 trailing_comma
2297 right_a;
2299 | Syntax.FieldSpecifier
2301 field_question = question;
2302 field_name = name;
2303 field_arrow = arrow_kw;
2304 field_type;
2305 } ->
2306 Concat
2307 [t env question; transform_mapish_entry env name arrow_kw field_type]
2308 | Syntax.FieldInitializer
2310 field_initializer_name = name;
2311 field_initializer_arrow = arrow_kw;
2312 field_initializer_value = value;
2313 } ->
2314 transform_mapish_entry env name arrow_kw value
2315 | Syntax.ShapeTypeSpecifier
2317 shape_type_keyword = shape_kw;
2318 shape_type_left_paren = left_p;
2319 shape_type_fields = type_fields;
2320 shape_type_ellipsis = ellipsis;
2321 shape_type_right_paren = right_p;
2322 } ->
2323 let fields =
2324 if Syntax.is_missing ellipsis then
2325 type_fields
2326 else
2327 let missing_separator = make_missing () in
2328 let ellipsis_list =
2329 [Syntax.make_list_item ellipsis missing_separator]
2331 make_list (Syntax.children type_fields @ ellipsis_list)
2333 transform_container_literal
2335 shape_kw
2336 left_p
2337 fields
2338 right_p
2339 ~allow_trailing:(Syntax.is_missing ellipsis)
2340 | Syntax.ShapeExpression
2342 shape_expression_keyword = shape_kw;
2343 shape_expression_left_paren = left_p;
2344 shape_expression_fields = fields;
2345 shape_expression_right_paren = right_p;
2346 } ->
2347 transform_container_literal env shape_kw left_p fields right_p
2348 | Syntax.TupleExpression
2350 tuple_expression_keyword = kw;
2351 tuple_expression_left_paren = left_p;
2352 tuple_expression_items = items;
2353 tuple_expression_right_paren = right_p;
2354 } ->
2355 Concat [t env kw; transform_argish env left_p items right_p]
2356 | Syntax.TypeArguments
2358 type_arguments_left_angle = left_a;
2359 type_arguments_types = type_list;
2360 type_arguments_right_angle = right_a;
2361 } ->
2362 transform_argish env left_a type_list right_a
2363 | Syntax.TypeParameters
2365 type_parameters_left_angle = left_a;
2366 type_parameters_parameters = param_list;
2367 type_parameters_right_angle = right_a;
2368 } ->
2369 transform_argish env left_a param_list right_a
2370 | Syntax.TupleTypeSpecifier
2372 tuple_left_paren = left_p;
2373 tuple_types = types;
2374 tuple_right_paren = right_p;
2375 } ->
2376 transform_argish env left_p types right_p
2377 | Syntax.UnionTypeSpecifier
2379 union_left_paren = left_p;
2380 union_types = types;
2381 union_right_paren = right_p;
2382 } ->
2383 delimited_nest
2385 left_p
2386 right_p
2388 handle_possible_list
2390 types
2391 ~after_each:(fun is_last ->
2392 if is_last then
2393 Split
2394 else
2395 space_split ())
2396 ~handle_element:(fun node ->
2397 match Syntax.syntax node with
2398 | Syntax.ListItem { list_item; list_separator } ->
2399 Concat
2401 t env list_item;
2402 when_present list_separator space;
2403 t env list_separator;
2405 | _ -> t env node);
2407 | Syntax.IntersectionTypeSpecifier
2409 intersection_left_paren = left_p;
2410 intersection_types = types;
2411 intersection_right_paren = right_p;
2412 } ->
2413 delimited_nest
2415 left_p
2416 right_p
2418 handle_possible_list
2420 types
2421 ~after_each:(fun is_last ->
2422 if is_last then
2423 Split
2424 else
2425 space_split ())
2426 ~handle_element:(fun node ->
2427 match Syntax.syntax node with
2428 | Syntax.ListItem { list_item; list_separator } ->
2429 Concat
2431 t env list_item;
2432 when_present list_separator space;
2433 t env list_separator;
2435 | _ -> t env node);
2437 | Syntax.TupleTypeExplicitSpecifier
2439 tuple_type_keyword = kw;
2440 tuple_type_left_angle = left_a;
2441 tuple_type_types = types;
2442 tuple_type_right_angle = right_a;
2443 } ->
2444 Concat [t env kw; transform_argish env left_a types right_a]
2445 | Syntax.PrefixedCodeExpression
2447 prefixed_code_prefix = prefix;
2448 prefixed_code_left_backtick = left_bt;
2449 prefixed_code_expression = expression;
2450 prefixed_code_right_backtick = right_bt;
2451 } ->
2452 Concat
2453 [t env prefix; transform_braced_item env left_bt expression right_bt]
2454 | Syntax.DecoratedExpression
2456 decorated_expression_decorator = op;
2457 decorated_expression_expression = expr;
2458 } ->
2459 Concat
2461 t env op;
2462 begin
2463 match Syntax.syntax op with
2464 | Syntax.Token t when is_token_kind_in_out (Token.kind t) -> Space
2465 | _ -> Nothing
2466 end;
2467 t env expr;
2469 | Syntax.ErrorSyntax _ -> raise Hackfmt_error.InvalidSyntax
2470 | Syntax.EnumClassDeclaration
2472 enum_class_attribute_spec = attr_spec;
2473 enum_class_modifiers = modifiers;
2474 enum_class_enum_keyword = enum_kw;
2475 enum_class_class_keyword = class_kw;
2476 enum_class_name = name;
2477 enum_class_colon = colon;
2478 enum_class_base = base;
2479 enum_class_extends = extends_kw;
2480 enum_class_extends_list = extends_list;
2481 enum_class_left_brace = left_brace;
2482 enum_class_elements = elements;
2483 enum_class_right_brace = right_brace;
2484 } ->
2485 let after_each_ancestor is_last =
2486 if is_last then
2487 Nothing
2488 else
2489 space_split ()
2491 Concat
2493 t env attr_spec;
2494 when_present attr_spec newline;
2495 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
2496 t env enum_kw;
2497 Space;
2498 t env class_kw;
2499 Space;
2500 t env name;
2501 t env colon;
2502 Space;
2503 SplitWith Cost.Base;
2504 Nest [Space; t env base; Space];
2505 when_present extends_kw (fun () ->
2506 Nest
2508 Space;
2509 Split;
2510 t env extends_kw;
2511 WithRule
2512 ( Rule.Parental,
2513 Nest
2515 Span
2517 Space;
2518 (if list_length extends_list = 1 then
2519 SplitWith Cost.Base
2520 else
2521 Split);
2522 Nest
2524 handle_possible_list
2526 ~after_each:after_each_ancestor
2527 extends_list;
2530 ] );
2532 Space;
2533 braced_block_nest
2535 left_brace
2536 right_brace
2537 [handle_possible_list env elements];
2538 Newline;
2540 | Syntax.EnumClassEnumerator
2542 enum_class_enumerator_modifiers = modifiers;
2543 enum_class_enumerator_type = type_;
2544 enum_class_enumerator_name = name;
2545 enum_class_enumerator_initializer = init;
2546 enum_class_enumerator_semicolon = semicolon;
2547 } ->
2548 Concat
2550 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
2551 t env type_;
2552 when_present type_ space;
2553 t env name;
2554 t env init;
2555 t env semicolon;
2556 Newline;
2558 | Syntax.EnumClassLabelExpression _ -> transform_simple env node)
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_enum_class_label = _enum_class_label;
2807 function_call_left_paren = lp;
2808 function_call_argument_list = args;
2809 function_call_right_paren = rp;
2810 } ->
2811 handle_fun_call acc node receiver targs lp args rp
2812 | Syntax.MemberSelectionExpression
2813 { member_object = obj; member_operator = arrow; member_name = member }
2814 | Syntax.SafeMemberSelectionExpression
2816 safe_member_object = obj;
2817 safe_member_operator = arrow;
2818 safe_member_name = member;
2819 } ->
2820 handle_member_selection acc (obj, arrow, member, None) None
2821 | _ -> (node, [])
2823 (* It's easy to end up with an infinite loop by passing an unexpected node
2824 kind here, so confirm that we have an expected kind in hand. *)
2825 let () =
2826 match Syntax.kind node with
2827 | SyntaxKind.FunctionCallExpression
2828 | SyntaxKind.MemberSelectionExpression
2829 | SyntaxKind.SafeMemberSelectionExpression ->
2831 | kind ->
2832 failwith
2833 ("Unexpected SyntaxKind in handle_possible_chaining: "
2834 ^ SyntaxKind.show kind)
2836 (* Flatten nested member selection expressions into the first receiver and a
2837 list of member selections.
2838 E.g., transform $x->a->b->c into ($x, [->a; ->b; ->c]) *)
2839 let (first_receiver, chain_list) = handle_chaining [] node in
2840 let chain_list = List.rev chain_list in
2841 let transform_chain (arrow, member, targs, argish) =
2842 Concat
2844 t env arrow;
2845 t env member;
2846 Option.value_map targs ~default:Nothing ~f:(t env);
2847 Option.value_map argish ~default:Nothing ~f:(fun (lp, args, rp) ->
2848 transform_argish env lp args rp);
2851 (* The actual transform for function call expressions (the default transform
2852 just calls into [handle_possible_chaining]). *)
2853 let transform_first_receiver node =
2854 match Syntax.syntax node with
2855 | Syntax.FunctionCallExpression
2857 function_call_receiver = receiver;
2858 function_call_type_args = targs;
2859 function_call_enum_class_label = _enum_class_label;
2860 function_call_left_paren = lp;
2861 function_call_argument_list = args;
2862 function_call_right_paren = rp;
2863 } ->
2864 Concat [t env receiver; t env targs; transform_argish env lp args rp]
2865 | Syntax.MemberSelectionExpression _
2866 | Syntax.SafeMemberSelectionExpression _ ->
2867 failwith
2868 "Should not be possible for a member selection expression to be considered first_receiver"
2869 | _ -> t env node
2871 let first_receiver_has_trailing_newline =
2872 node_has_trailing_newline first_receiver
2874 match chain_list with
2875 | [] -> transform_first_receiver first_receiver
2876 | [hd] ->
2877 Concat
2879 Span [transform_first_receiver first_receiver];
2880 (if first_receiver_has_trailing_newline then
2881 Newline
2882 else
2883 SplitWith Cost.High);
2884 Nest [transform_chain hd];
2886 | hd :: tl ->
2887 let transformed_hd = transform_chain hd in
2888 let tl = List.map tl ~f:transform_chain in
2889 let rule_type =
2890 match hd with
2891 | (_, trailing, None, None)
2892 | (_, _, Some trailing, None)
2893 | (_, _, _, Some (_, _, trailing)) ->
2894 if node_has_trailing_newline trailing then
2895 Rule.Always
2896 else if first_receiver_has_trailing_newline then
2897 Rule.Parental
2898 else
2899 (* If we have a chain where only the final item contains internal
2900 splits, use a Simple rule instead of a Parental one.
2901 This allows us to preserve this style:
2903 return $this->fooGenerator->generateFoo(
2904 $argument_one,
2905 $argument_two,
2906 $argument_three,
2909 let rev_tl_except_last = List.rev tl |> List.tl_exn in
2910 let items_except_last = transformed_hd :: rev_tl_except_last in
2911 if List.exists items_except_last ~f:has_split then
2912 Rule.Parental
2913 else
2914 Rule.Simple Cost.NoCost
2916 Span
2918 WithLazyRule
2919 ( rule_type,
2920 Concat
2922 transform_first_receiver first_receiver;
2923 (if first_receiver_has_trailing_newline then
2924 Newline
2925 else
2926 SplitWith Cost.Base);
2928 Concat
2930 (* This needs to be nested separately due to the above SplitWith *)
2931 Nest [transformed_hd];
2932 Nest (List.map tl ~f:(fun x -> Concat [Split; x]));
2933 ] );
2936 and transform_fn_decl_name env modifiers kw name type_params leftp =
2937 let mods = handle_possible_list env ~after_each:(fun _ -> Space) modifiers in
2938 [mods; t env kw; Space; t env name; t env type_params; t env leftp; Split]
2940 and transform_fn_decl_args env params rightp =
2941 (* It is a syntax error to follow a variadic parameter with a trailing
2942 * comma, so suppress trailing commas in that case. *)
2943 let allow_trailing =
2944 match Syntax.syntax params with
2945 | Syntax.SyntaxList params ->
2946 let last_param =
2947 match Syntax.syntax (List.last_exn params) with
2948 | Syntax.ListItem { list_item; _ } -> list_item
2949 | _ -> failwith "Expected ListItem"
2951 begin
2952 match Syntax.syntax last_param with
2953 | Syntax.VariadicParameter _
2954 | Syntax.(
2955 ParameterDeclaration
2957 parameter_name =
2959 syntax =
2960 DecoratedExpression
2962 decorated_expression_decorator =
2964 syntax =
2965 Token { Token.kind = TokenKind.DotDotDot; _ };
2973 }) ->
2974 false
2975 | _ -> true
2977 | _ -> true
2979 WithRule
2980 ( Rule.Parental,
2981 Concat [transform_possible_comma_list env ~allow_trailing params rightp]
2984 and transform_argish_with_return_type
2985 env left_p params right_p ctx_list colon readonly_ret ret_type =
2986 Concat
2988 t env left_p;
2989 when_present params split;
2990 transform_fn_decl_args env params right_p;
2991 t env ctx_list;
2992 t env colon;
2993 when_present colon space;
2994 t env readonly_ret;
2995 when_present readonly_ret space;
2996 t env ret_type;
2999 and transform_argish
3001 ?(allow_trailing = true)
3002 ?(force_newlines = false)
3003 ?(spaces = false)
3004 left_p
3005 arg_list
3006 right_p =
3007 (* It is a syntax error to follow a splat argument with a trailing comma, so
3008 suppress trailing commas in that case. *)
3009 let allow_trailing =
3010 match Syntax.syntax arg_list with
3011 | Syntax.SyntaxList args ->
3012 let last_arg =
3013 match Syntax.syntax (List.last_exn args) with
3014 | Syntax.ListItem { list_item; _ } -> list_item
3015 | _ -> failwith "Expected ListItem"
3017 begin
3018 match Syntax.syntax last_arg with
3019 | Syntax.(
3020 DecoratedExpression
3022 decorated_expression_decorator =
3023 { syntax = Token { Token.kind = TokenKind.DotDotDot; _ }; _ };
3025 }) ->
3026 false
3027 | _ -> allow_trailing
3029 | _ -> allow_trailing
3032 (* When the last argument breaks across multiple lines, we want to allow the
3033 arg list rule to stay unbroken even though the last argument contains
3034 splits that may be broken on.
3036 For example:
3038 // We do not want to break f's rule even though its child splits:
3039 f(vec[
3040 $foo, // single-line comment forces the vec's rule to split
3041 $bar,
3044 // We do not want to break map's rule even though the lambda has splits:
3045 map($vec, $element ==> {
3046 // ...
3049 let split_when_children_split =
3050 if spaces then
3051 true
3052 else
3053 match Syntax.syntax arg_list with
3054 | Syntax.SyntaxList [] -> true
3055 | Syntax.SyntaxList [x] ->
3056 let has_surrounding_whitespace =
3058 (List.is_empty (Syntax.trailing_trivia left_p)
3059 && List.is_empty (Syntax.trailing_trivia arg_list))
3061 if has_surrounding_whitespace then
3062 true
3063 else
3064 looks_bad_in_non_parental_braces x
3065 | Syntax.SyntaxList items ->
3066 let last = List.last_exn items in
3067 let has_surrounding_whitespace =
3069 (List.is_empty (Syntax.leading_trivia last)
3070 && List.is_empty (Syntax.trailing_trivia last))
3072 if has_surrounding_whitespace then
3073 true
3074 else (
3075 (* When there are multiple arguments, opt into this behavior only when we
3076 have no splits in any of the arguments except the last. *)
3077 match List.rev items with
3078 | [] -> assert false
3079 | last :: rest ->
3080 let prev_args_may_split =
3081 rest |> List.map ~f:(t env) |> List.exists ~f:has_split
3083 if prev_args_may_split then
3084 true
3085 else
3086 looks_bad_in_non_parental_braces last
3088 | _ -> true
3090 delimited_nest
3092 ~split_when_children_split
3093 ~force_newlines
3094 left_p
3095 right_p
3096 [transform_arg_list env ~allow_trailing arg_list]
3098 (** Sometimes, we want to use a non-Parental rule for function call argument
3099 lists and other similar constructs when not breaking around the argument
3100 list looks reasonable. For example:
3102 f($x ==> {
3103 return do_something_with($x);
3106 Some constructs don't look so great when we do this:
3108 f($x ==>
3109 do_something_with($x));
3111 f($x
3112 ? $y
3113 : $z);
3115 This function blacklists those constructs. *)
3116 and looks_bad_in_non_parental_braces item =
3117 let item =
3118 match Syntax.syntax item with
3119 | Syntax.ListItem { list_item; _ } -> list_item
3120 | _ -> item
3122 match Syntax.syntax item with
3123 | Syntax.(
3124 LambdaExpression { lambda_body = { syntax = CompoundStatement _; _ }; _ })
3126 false
3127 | Syntax.FunctionCallExpression { function_call_receiver; _ } ->
3128 Syntax.is_member_selection_expression function_call_receiver
3129 | Syntax.ConditionalExpression _
3130 | Syntax.BinaryExpression _
3131 | Syntax.MemberSelectionExpression _
3132 | Syntax.FieldSpecifier _
3133 | Syntax.FieldInitializer _
3134 | Syntax.ElementInitializer _
3135 | Syntax.LambdaExpression _
3136 | Syntax.XHPExpression _
3137 | Syntax.IsExpression _
3138 | Syntax.AsExpression _
3139 | Syntax.NullableAsExpression _ ->
3140 true
3141 | _ -> false
3143 and transform_braced_item env left_p item right_p =
3144 let has_no_surrounding_trivia =
3145 List.is_empty (Syntax.trailing_trivia left_p)
3146 && List.is_empty (Syntax.leading_trivia item)
3147 && List.is_empty (Syntax.trailing_trivia item)
3148 && List.is_empty (Syntax.leading_trivia right_p)
3150 if has_no_surrounding_trivia && not (looks_bad_in_non_parental_braces item)
3151 then
3152 Concat (List.map [left_p; item; right_p] ~f:(t env))
3153 else
3154 delimited_nest env left_p right_p [t env item]
3156 and transform_argish_item env x =
3157 match Syntax.syntax x with
3158 | Syntax.ListItem { list_item; list_separator } ->
3159 Concat [transform_argish_item env list_item; t env list_separator]
3160 | Syntax.BinaryExpression
3162 binary_left_operand = left;
3163 binary_operator = op;
3164 binary_right_operand = right;
3166 when not (is_concat op) ->
3167 transform_binary_expression env ~is_nested:true (left, op, right)
3168 | _ -> t env x
3170 and transform_trailing_comma env ~allow_trailing item comma =
3171 (* PHP does not permit trailing commas in function calls. Rather than try to
3172 * account for where PHP's parser permits trailing commas, we just never add
3173 * them in PHP files. *)
3174 let allow_trailing = allow_trailing && env.Env.add_trailing_commas in
3175 match Syntax.syntax comma with
3176 | Syntax.Token tok ->
3177 Concat
3179 transform_argish_item env item;
3180 transform_leading_trivia (Token.leading tok);
3181 (if allow_trailing then
3182 TrailingComma true
3183 else
3184 Nothing);
3185 Ignore (Token.text tok, Token.width tok);
3186 transform_trailing_trivia (Token.trailing tok);
3188 | Syntax.Missing ->
3189 let (item, item_trailing) = remove_trailing_trivia item in
3190 Concat
3192 transform_argish_item env item;
3193 (if allow_trailing then
3194 TrailingComma false
3195 else
3196 Nothing);
3197 transform_trailing_trivia item_trailing;
3199 | _ -> failwith "Expected Token"
3201 and transform_braced_item_with_trailer env left_p item comma right_p =
3202 let has_no_surrounding_trivia =
3203 List.is_empty (Syntax.trailing_trivia left_p)
3204 && List.is_empty (Syntax.leading_trivia item)
3205 && List.is_empty (Syntax.trailing_trivia item)
3206 && List.is_empty (Syntax.leading_trivia comma)
3207 && List.is_empty (Syntax.trailing_trivia comma)
3208 && List.is_empty (Syntax.leading_trivia right_p)
3210 (* TODO: turn allow_trailing:true when HHVM versions that don't support
3211 trailing commas in all these places reach end-of-life. *)
3212 let item_and_comma =
3213 transform_trailing_comma env ~allow_trailing:false item comma
3215 if has_no_surrounding_trivia && not (looks_bad_in_non_parental_braces item)
3216 then
3217 Concat [t env left_p; item_and_comma; t env right_p]
3218 else
3219 delimited_nest env left_p right_p [item_and_comma]
3221 and transform_arg_list env ?(allow_trailing = true) items =
3222 handle_possible_list
3224 items
3225 ~after_each:after_each_argument
3226 ~handle_last:(transform_last_arg env ~allow_trailing)
3227 ~handle_element:(transform_argish_item env)
3229 and transform_possible_comma_list env ?(allow_trailing = true) items right_p =
3230 nest env right_p [transform_arg_list env ~allow_trailing items]
3232 and transform_container_literal
3234 ?(space = false)
3235 ?allow_trailing
3236 ?explicit_type
3238 left_p
3239 members
3240 right_p =
3241 let force_newlines = node_has_trailing_newline left_p in
3242 let ty =
3243 match explicit_type with
3244 | Some ex_ty -> t env ex_ty
3245 | None -> Nothing
3247 Concat
3249 t env kw;
3251 (if space then
3252 Space
3253 else
3254 Nothing);
3255 transform_argish
3257 ~force_newlines
3258 ?allow_trailing
3259 left_p
3260 members
3261 right_p;
3264 and replace_leading_trivia node new_leading_trivia =
3265 match Syntax.leading_token node with
3266 | None -> node
3267 | Some leading_token ->
3268 let rewritten_node =
3269 Rewriter.rewrite_pre
3270 (fun node_to_rewrite ->
3271 match Syntax.syntax node_to_rewrite with
3272 | Syntax.Token t when phys_equal t leading_token ->
3273 Rewriter.Replace
3274 (Syntax.make_token { t with Token.leading = new_leading_trivia })
3275 | _ -> Rewriter.Keep)
3276 node
3278 rewritten_node
3280 and remove_leading_trivia node =
3281 match Syntax.leading_token node with
3282 | None -> ([], node)
3283 | Some leading_token ->
3284 let rewritten_node =
3285 Rewriter.rewrite_pre
3286 (fun rewrite_node ->
3287 match Syntax.syntax rewrite_node with
3288 | Syntax.Token t when phys_equal t leading_token ->
3289 Rewriter.Replace (Syntax.make_token { t with Token.leading = [] })
3290 | _ -> Rewriter.Keep)
3291 node
3293 (Token.leading leading_token, rewritten_node)
3295 and remove_trailing_trivia node =
3296 match Syntax.trailing_token node with
3297 | None -> (node, [])
3298 | Some trailing_token ->
3299 let rewritten_node =
3300 Rewriter.rewrite_pre
3301 (fun rewrite_node ->
3302 match Syntax.syntax rewrite_node with
3303 | Syntax.Token t when phys_equal t trailing_token ->
3304 Rewriter.Replace (Syntax.make_token { t with Token.trailing = [] })
3305 | _ -> Rewriter.Keep)
3306 node
3308 (rewritten_node, Token.trailing trailing_token)
3310 and transform_last_arg env ~allow_trailing node =
3311 match Syntax.syntax node with
3312 | Syntax.ListItem { list_item = item; list_separator = separator } ->
3313 transform_trailing_comma env ~allow_trailing item separator
3314 | _ -> failwith "Expected ListItem"
3316 and transform_mapish_entry env key arrow value =
3317 Concat
3319 t env key;
3320 Space;
3321 t env arrow;
3322 Space;
3323 SplitWith Cost.Base;
3324 Nest [t env value];
3327 and transform_keyword_expression_statement env kw expr semi =
3328 Concat
3330 t env kw;
3331 when_present expr (fun () ->
3332 Concat [Space; SplitWith Cost.Moderate; Nest [t env expr]]);
3333 t env semi;
3334 Newline;
3337 and transform_keyword_expr_list_statement env kw expr_list semi =
3338 Concat [t env kw; handle_declarator_list env expr_list; t env semi; Newline]
3340 and transform_condition env left_p condition right_p =
3341 Concat
3343 t env left_p;
3344 Split;
3345 WithRule
3346 (Rule.Parental, Concat [Nest [t env condition]; Split; t env right_p]);
3349 and get_operator_type op =
3350 match Syntax.syntax op with
3351 | Syntax.Token t -> Full_fidelity_operator.trailing_from_token (Token.kind t)
3352 | _ -> failwith "Operator should always be a token"
3354 and is_concat op =
3355 match get_operator_type op with
3356 | Full_fidelity_operator.ConcatenationOperator -> true
3357 | _ -> false
3359 and transform_binary_expression env ~is_nested (left, operator, right) =
3360 let operator_has_surrounding_spaces op = not (is_concat op) in
3361 let operator_is_leading op =
3362 match get_operator_type op with
3363 | Full_fidelity_operator.PipeOperator -> true
3364 | _ -> false
3366 let operator_preserves_newlines op =
3367 match get_operator_type op with
3368 | Full_fidelity_operator.PipeOperator -> true
3369 | _ -> false
3371 let operator_t = get_operator_type operator in
3372 if Full_fidelity_operator.is_comparison operator_t then
3373 WithLazyRule
3374 ( Rule.Parental,
3375 Concat [t env left; Space; t env operator],
3376 Concat [Space; Split; Nest [t env right]] )
3377 else if Full_fidelity_operator.is_assignment operator_t then
3378 Concat
3380 t env left;
3381 Space;
3382 t env operator;
3383 Space;
3384 SplitWith Cost.Moderate;
3385 Nest [t env right];
3387 else
3388 Concat
3390 (let penv = Full_fidelity_parser_env.default in
3391 let precedence = Full_fidelity_operator.precedence penv operator_t in
3392 let rec flatten_expression expr =
3393 match Syntax.syntax expr with
3394 | Syntax.BinaryExpression
3396 binary_left_operand = left;
3397 binary_operator = operator;
3398 binary_right_operand = right;
3399 } ->
3400 let operator_t = get_operator_type operator in
3401 let op_precedence =
3402 Full_fidelity_operator.precedence penv operator_t
3404 if op_precedence = precedence then
3405 flatten_expression left @ operator :: flatten_expression right
3406 else
3407 [expr]
3408 | _ -> [expr]
3410 let transform_operand operand =
3411 match Syntax.syntax operand with
3412 | Syntax.BinaryExpression
3413 { binary_left_operand; binary_operator; binary_right_operand } ->
3414 transform_binary_expression
3416 ~is_nested:true
3417 (binary_left_operand, binary_operator, binary_right_operand)
3418 | _ -> t env operand
3420 let binary_expression_syntax_list =
3421 flatten_expression
3422 (Syntax.make_binary_expression left operator right)
3424 match binary_expression_syntax_list with
3425 | hd :: tl ->
3426 WithLazyRule
3427 ( Rule.Parental,
3428 transform_operand hd,
3429 let expression =
3430 let last_operand = ref hd in
3431 let last_op = ref (List.hd_exn tl) in
3432 List.mapi tl ~f:(fun i x ->
3433 if i mod 2 = 0 then (
3434 let op = x in
3435 last_op := op;
3436 let op_has_spaces = operator_has_surrounding_spaces op in
3437 let op_is_leading = operator_is_leading op in
3438 let newline_before_op =
3439 operator_preserves_newlines op
3440 && node_has_trailing_newline !last_operand
3442 Concat
3444 (if newline_before_op then
3445 Newline
3446 else if op_is_leading then
3447 if op_has_spaces then
3448 space_split ()
3449 else
3450 Split
3451 else if op_has_spaces then
3452 Space
3453 else
3454 Nothing);
3455 (if is_concat op then
3456 ConcatOperator (t env op)
3457 else
3458 t env op);
3460 ) else
3461 let operand = x in
3462 last_operand := x;
3463 let op_has_spaces =
3464 operator_has_surrounding_spaces !last_op
3466 let op_is_leading = operator_is_leading !last_op in
3467 Concat
3469 (if op_is_leading then
3470 if op_has_spaces then
3471 Space
3472 else
3473 Nothing
3474 else if op_has_spaces then
3475 space_split ()
3476 else
3477 Split);
3478 transform_operand operand;
3481 if is_nested then
3482 Nest expression
3483 else
3484 ConditionalNest expression )
3485 | _ -> failwith "Expected non empty list of binary expression pieces");
3488 and make_string text width =
3489 let split_text = Str.split_delim (Str.regexp "\n") text in
3490 match split_text with
3491 | [_] -> Text (text, width)
3492 | _ -> MultilineString (split_text, width)
3494 (* Check the leading trivia of the node's leading token.
3495 Treat the node's text as a multiline string if the leading trivia contains
3496 an ignore comment. *)
3497 and transform_node_if_ignored node =
3498 let (leading_before, leading_including_and_after) =
3499 leading_ignore_comment (Syntax.leading_trivia node)
3501 if List.length leading_including_and_after = 0 then
3502 None
3503 else
3504 let node = replace_leading_trivia node leading_including_and_after in
3505 let (node, trailing_trivia) = remove_trailing_trivia node in
3506 let is_fixme =
3507 match Trivia.kind (List.hd_exn leading_including_and_after) with
3508 | TriviaKind.(FixMe | IgnoreError) -> true
3509 | _ -> false
3511 Some
3512 (Concat
3514 transform_leading_trivia leading_before;
3515 (* If we have a non-error-suppression comment here, then we want to
3516 ensure that we don't join it up onto the preceding line. Since we
3517 only scan leading trivia for hackfmt-ignore comments, and joining
3518 the comment onto the preceding line would make it trailing trivia,
3519 we would make the ignore comment useless if we joined it with the
3520 preceding line (breaking idempotence of hackfmt). Adding [Newline]
3521 here ensures a line break.
3523 Error-suppression comments are different--they are specially
3524 handled by the lexer to ensure that they always appear in leading
3525 trivia. *)
3526 (if is_fixme then
3527 Nothing
3528 else
3529 Newline);
3530 make_string (Syntax.text node) (Syntax.width node);
3531 transform_trailing_trivia trailing_trivia;
3532 (if has_newline trailing_trivia then
3533 Newline
3534 else
3535 Nothing);
3538 and ignore_re = Str.regexp_string "hackfmt-ignore"
3540 and is_ignore_comment trivia =
3541 match Trivia.kind trivia with
3542 (* We don't format the node after a comment containing "hackfmt-ignore". *)
3543 | TriviaKind.(DelimitedComment | SingleLineComment) ->
3544 begin
3545 try Str.search_forward ignore_re (Trivia.text trivia) 0 >= 0 with
3546 | Caml.Not_found -> false
3548 | _ -> false
3550 and leading_ignore_comment trivia_list =
3551 let before = List.take_while trivia_list ~f:(Fn.non is_ignore_comment) in
3552 let (_, including_and_after) =
3553 List.split_n trivia_list (List.length before)
3555 (before, including_and_after)
3557 (* True if the trivia list contains WhiteSpace trivia.
3558 * Note that WhiteSpace includes spaces and tabs, but not newlines. *)
3559 and has_whitespace trivia_list =
3560 List.exists trivia_list ~f:(fun trivia ->
3561 is_trivia_kind_white_space (Trivia.kind trivia))
3563 (* True if the trivia list contains EndOfLine trivia. *)
3564 and has_newline trivia_list =
3565 List.exists trivia_list ~f:(fun trivia ->
3566 is_trivia_kind_end_of_line (Trivia.kind trivia))
3568 and is_invisible trivia =
3569 match Trivia.kind trivia with
3570 | TriviaKind.WhiteSpace
3571 | TriviaKind.EndOfLine ->
3572 true
3573 | _ -> false
3575 and transform_leading_trivia t = transform_trivia ~is_leading:true t
3577 and transform_trailing_trivia t = transform_trivia ~is_leading:false t
3579 and transform_trivia ~is_leading trivia =
3580 let new_line_regex = Str.regexp "\n" in
3581 let indent = ref 0 in
3582 let currently_leading = ref is_leading in
3583 let leading_invisibles = ref [] in
3584 let last_comment = ref None in
3585 let last_comment_was_delimited = ref false in
3586 let newline_followed_last_comment = ref false in
3587 let whitespace_followed_last_comment = ref false in
3588 let trailing_invisibles = ref [] in
3589 let comments = ref [] in
3590 let make_comment _ =
3591 if Option.is_some !last_comment then (
3592 newline_followed_last_comment := has_newline !trailing_invisibles;
3593 whitespace_followed_last_comment := has_whitespace !trailing_invisibles
3595 comments :=
3596 Concat
3598 transform_leading_invisibles (List.rev !leading_invisibles);
3599 Option.value !last_comment ~default:Nothing;
3600 ignore_trailing_invisibles (List.rev !trailing_invisibles);
3601 (if !last_comment_was_delimited && !whitespace_followed_last_comment
3602 then
3603 Space
3604 else if !newline_followed_last_comment then
3605 Newline
3606 else
3607 Nothing);
3609 :: !comments;
3610 last_comment := None;
3611 leading_invisibles := [];
3612 trailing_invisibles := []
3614 List.iter trivia ~f:(fun triv ->
3615 match Trivia.kind triv with
3616 | TriviaKind.ExtraTokenError
3617 | TriviaKind.FixMe
3618 | TriviaKind.IgnoreError
3619 | TriviaKind.DelimitedComment ->
3620 let preceded_by_whitespace =
3621 if !currently_leading then
3622 has_whitespace !leading_invisibles
3623 else
3624 has_whitespace !trailing_invisibles
3626 make_comment ();
3627 let delimited_lines = Str.split new_line_regex (Trivia.text triv) in
3628 let map_tail str =
3629 let prefix_space_count str =
3630 let len = String.length str in
3631 let rec aux i =
3632 if i = len || Char.(str.[i] <> ' ' && str.[i] <> '\t') then
3634 else
3635 1 + aux (i + 1)
3637 aux 0
3639 (* If we're dealing with trailing trivia, then we don't have a good
3640 signal for the indent level, so we just cut all leading spaces.
3641 Otherwise, we cut a number of spaces equal to the indent before
3642 the delimited comment opener. *)
3643 let start_index =
3644 if is_leading then
3645 min !indent (prefix_space_count str)
3646 else
3647 prefix_space_count str
3649 let len = String.length str - start_index in
3650 let dc =
3651 Trivia.create_delimited_comment
3652 @@ String.sub str ~pos:start_index ~len
3654 Concat
3656 Ignore ("\n", 1);
3657 Newline;
3658 Ignore (String.make start_index ' ', start_index);
3659 Comment (Trivia.text dc, Trivia.width dc);
3662 let hd = List.hd_exn delimited_lines in
3663 let tl = List.tl_exn delimited_lines in
3664 let hd = Comment (hd, String.length hd) in
3665 let should_break =
3666 match Trivia.kind triv with
3667 | TriviaKind.FixMe
3668 | TriviaKind.IgnoreError ->
3669 false
3670 | _ -> !currently_leading
3672 last_comment :=
3673 Some
3674 (Concat
3676 (if should_break then
3677 Newline
3678 else if preceded_by_whitespace then
3679 Space
3680 else
3681 Nothing);
3682 Concat (hd :: List.map tl ~f:map_tail);
3684 last_comment_was_delimited := true;
3685 currently_leading := false
3686 | TriviaKind.FallThrough
3687 | TriviaKind.SingleLineComment ->
3688 make_comment ();
3689 last_comment :=
3690 Some
3691 (Concat
3693 (if !currently_leading then
3694 Newline
3695 else
3696 Space);
3697 SingleLineComment (Trivia.text triv, Trivia.width triv);
3699 last_comment_was_delimited := false;
3700 currently_leading := false
3701 | TriviaKind.EndOfLine ->
3702 indent := 0;
3703 if !currently_leading then
3704 leading_invisibles := triv :: !leading_invisibles
3705 else (
3706 trailing_invisibles := triv :: !trailing_invisibles;
3707 make_comment ()
3709 currently_leading := true
3710 | TriviaKind.WhiteSpace ->
3711 if !currently_leading then (
3712 indent := Trivia.width triv;
3713 leading_invisibles := triv :: !leading_invisibles
3714 ) else
3715 trailing_invisibles := triv :: !trailing_invisibles);
3716 if List.is_empty !comments then
3717 if is_leading then
3718 transform_leading_invisibles trivia
3719 else
3720 ignore_trailing_invisibles trivia
3721 else (
3722 make_comment ();
3723 Concat (List.rev !comments)
3726 and _MAX_CONSECUTIVE_BLANK_LINES = 2
3728 and transform_leading_invisibles triv =
3729 let newlines = ref 0 in
3730 Concat
3731 (List.map triv ~f:(fun t ->
3732 let ignored = Ignore (Trivia.text t, Trivia.width t) in
3733 match Trivia.kind t with
3734 | TriviaKind.EndOfLine ->
3735 newlines := !newlines + 1;
3736 Concat
3738 ignored;
3739 (if !newlines <= _MAX_CONSECUTIVE_BLANK_LINES then
3740 BlankLine
3741 else
3742 Nothing);
3744 | _ -> ignored))
3746 and ignore_trailing_invisibles triv =
3747 Concat (List.map triv ~f:(fun t -> Ignore (Trivia.text t, Trivia.width t)))
3749 and transform_xhp_leading_trivia triv =
3750 let (up_to_first_newline, after_newline, _) =
3751 List.fold triv ~init:([], [], false) ~f:(fun (upto, after, seen) t ->
3752 if seen then
3753 (upto, t :: after, true)
3754 else
3755 (t :: upto, after, is_trivia_kind_end_of_line (Trivia.kind t)))
3757 Concat
3759 ignore_trailing_invisibles up_to_first_newline;
3760 transform_leading_invisibles after_newline;
3763 and node_has_trailing_newline node =
3764 let trivia = Syntax.trailing_trivia node in
3765 List.exists trivia ~f:(fun x -> is_trivia_kind_end_of_line (Trivia.kind x))
3767 and transform_consequence
3768 t (env : Env.t) (node_body : Syntax.t) (node_newline : Syntax.t) =
3769 match Syntax.syntax node_body with
3770 | Syntax.CompoundStatement _ ->
3771 handle_possible_compound_statement env node_body
3772 | _ ->
3773 Concat
3775 Space;
3776 (if has_newline (Syntax.trailing_trivia node_newline) then
3777 Concat [Newline; Nest [t env node_body]]
3778 else
3779 WithRule (Rule.Parental, Nest [Span [Space; Split; t env node_body]]));
3782 let transform (env : Env.t) (node : Syntax.t) : Doc.t = t env node