Bash-style switch syntax support
[hiphop-php.git] / hphp / hack / src / hackfmt / hack_format.ml
blob17648b8bb4be02518496305479938c77781311ca
1 (**
2 * Copyright (c) 2018, Facebook, Inc.
3 * All rights reserved.
5 * This source code is licensed under the BSD-style license found in the
6 * LICENSE file in the "hack" directory of this source tree. An additional grant
7 * of patent rights can be found in the PATENTS file in the same directory.
9 *)
11 module 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)
21 open Hh_core
22 open Doc
24 let make_list = Syntax.make_list SourceText.empty 0
25 let make_missing () = Syntax.make_missing SourceText.empty 0
27 (* Main transform function, which takes a full-fidelity CST node and produces a
28 * Doc.t node (the IR which is fed to Chunk_builder.build).
30 * Exported via the `transform` alias below. *)
31 let rec t (env: Env.t) (node: Syntax.t) : Doc.t =
32 match Syntax.syntax node with
33 | Syntax.Missing ->
34 Nothing
35 | Syntax.Token x ->
36 let token_kind = Token.kind x in
37 Concat [
38 begin
39 match token_kind with
40 | TokenKind.EndOfFile ->
41 let leading_trivia = Token.leading x in
42 let trivia_without_trailing_invisibles =
43 let reversed = List.rev leading_trivia in
44 List.rev (List.drop_while reversed ~f:is_invisible)
46 transform_leading_trivia trivia_without_trailing_invisibles
47 | _ -> transform_leading_trivia (Token.leading x)
48 end;
49 begin
50 match token_kind with
51 | TokenKind.SingleQuotedStringLiteral
52 | TokenKind.DoubleQuotedStringLiteral
53 | TokenKind.DoubleQuotedStringLiteralHead
54 | TokenKind.StringLiteralBody
55 | TokenKind.DoubleQuotedStringLiteralTail
56 | TokenKind.HeredocStringLiteral
57 | TokenKind.HeredocStringLiteralHead
58 | TokenKind.HeredocStringLiteralTail
59 | TokenKind.NowdocStringLiteral ->
60 let split_text = (Str.split_delim (Str.regexp "\n") (Token.text x)) in
61 begin match split_text with
62 | [_] -> Text (Token.text x, Token.width x)
63 | _ -> MultilineString (split_text, Token.width x)
64 end
65 | _ -> Text (Token.text x, Token.width x)
66 end;
67 transform_trailing_trivia (Token.trailing x);
69 | Syntax.SyntaxList _ ->
70 failwith (Printf.sprintf
71 "Error: SyntaxList should never be handled directly;
72 offending text is '%s'." (Syntax.text node));
73 | Syntax.EndOfFile x ->
74 t env x.end_of_file_token
75 | Syntax.Script x ->
76 begin match Syntax.syntax x.script_declarations with
77 | Syntax.SyntaxList (header::declarations)
78 when Syntax.is_markup_section header ->
79 Concat [
80 t env header;
81 Newline;
82 handle_list env declarations;
84 | _ ->
85 Concat [
86 handle_possible_list env x.script_declarations;
88 end
89 | Syntax.LiteralExpression { literal_expression } ->
90 (* Double quoted string literals can create a list *)
91 let wrap_with_literal_type token transformed =
92 match Token.kind token with
93 | TokenKind.HeredocStringLiteral
94 | TokenKind.HeredocStringLiteralHead
95 | TokenKind.HeredocStringLiteralTail
96 | TokenKind.NowdocStringLiteral -> DocLiteral transformed
97 | TokenKind.DecimalLiteral
98 | TokenKind.OctalLiteral
99 | TokenKind.HexadecimalLiteral
100 | TokenKind.BinaryLiteral
101 | TokenKind.FloatingLiteral -> NumericLiteral transformed
102 | _ -> transformed
104 begin match Syntax.syntax literal_expression with
105 | Syntax.Token tok ->
106 wrap_with_literal_type tok (t env literal_expression)
107 | Syntax.SyntaxList l ->
108 let last = Syntax.trailing_token literal_expression in
109 begin match last with
110 | Some tok -> wrap_with_literal_type tok (Concat (List.map l (t env)))
111 | _ -> failwith "Expected Token"
113 | _ -> failwith "Expected Token or SyntaxList"
115 | Syntax.MarkupSection {
116 markup_prefix = prefix;
117 markup_text = text;
118 markup_suffix = suffix;
119 _ } ->
120 if Syntax.is_missing prefix
121 then
122 (* leading markup section
123 for hh files - strip leading whitespaces\newlines - they are not
124 emitted and having them in Hack file is illegal anyways *)
125 let is_hh_script = match Syntax.syntax suffix with
126 | Syntax.MarkupSuffix { markup_suffix_name = Syntax.{
127 syntax = Token t; _
128 }; _ } ->
129 (Token.text t) = "hh"
130 | _ -> false
132 let rec all_whitespaces s i =
133 i >= String.length s
134 || (match String.get s i with
135 | ' ' | '\t' | '\r' | '\n' -> all_whitespaces s (i + 1)
136 | _ -> false)
138 let text_contains_only_whitespaces = match Syntax.syntax text with
139 | Syntax.Token t -> all_whitespaces (Token.text t) 0
140 | _ -> false
142 if is_hh_script && text_contains_only_whitespaces
143 then t env suffix
144 else transform_simple env node
145 else transform_simple env node
146 | Syntax.MarkupSuffix _
147 | Syntax.SimpleTypeSpecifier _
148 | Syntax.VariableExpression _
149 | Syntax.PipeVariableExpression _
150 | Syntax.PropertyDeclarator _
151 | Syntax.ConstantDeclarator _
152 | Syntax.StaticDeclarator _
153 | Syntax.ScopeResolutionExpression _
154 | Syntax.EmbeddedMemberSelectionExpression _
155 | Syntax.EmbeddedSubscriptExpression _
156 | Syntax.PostfixUnaryExpression _
157 | Syntax.XHPRequired _
158 | Syntax.XHPSimpleClassAttribute _
159 | Syntax.XHPClose _
160 | Syntax.TypeConstant _
161 | Syntax.GenericTypeSpecifier _
162 | Syntax.NullableTypeSpecifier _
163 | Syntax.SoftTypeSpecifier _
164 | Syntax.ListItem _ ->
165 transform_simple env node
166 | Syntax.QualifiedName { qualified_name_parts; } ->
167 handle_possible_list env qualified_name_parts
168 | Syntax.ExpressionStatement _ ->
169 transform_simple_statement env node
170 | Syntax.EnumDeclaration {
171 enum_attribute_spec = attr;
172 enum_keyword = kw;
173 enum_name = name;
174 enum_colon = colon_kw;
175 enum_base = base;
176 enum_type = enum_type;
177 enum_left_brace = left_b;
178 enum_enumerators = enumerators;
179 enum_right_brace = right_b } ->
180 Concat [
181 t env attr;
182 when_present attr newline;
183 t env kw;
184 Space;
185 t env name;
186 t env colon_kw;
187 Space;
188 SplitWith Cost.Base;
189 Nest [
190 Space;
191 t env base;
192 Space;
193 t env enum_type;
194 Space;
196 braced_block_nest env left_b right_b [
197 handle_possible_list env enumerators
199 Newline;
201 | Syntax.Enumerator {
202 enumerator_name = name;
203 enumerator_equal = eq_kw;
204 enumerator_value = value;
205 enumerator_semicolon = semi } ->
206 Concat [
207 t env name;
208 Space;
209 t env eq_kw;
210 Space;
211 SplitWith Cost.Base;
212 Nest [t env value];
213 t env semi;
214 Newline;
216 | Syntax.AliasDeclaration {
217 alias_attribute_spec = attr;
218 alias_keyword = kw;
219 alias_name = name;
220 alias_generic_parameter = generic;
221 alias_constraint = type_constraint;
222 alias_equal = eq_kw;
223 alias_type = alias_type;
224 alias_semicolon = semi } ->
225 (* TODO: revisit this for long names *)
226 Concat [
227 t env attr;
228 when_present attr newline;
229 t env kw;
230 Space;
231 t env name;
232 t env generic;
233 Space;
234 t env type_constraint;
235 Space;
236 t env eq_kw;
237 Space;
238 SplitWith Cost.Base;
239 Nest [t env alias_type];
240 t env semi;
241 Newline;
243 | Syntax.PropertyDeclaration {
244 property_modifiers = modifiers;
245 property_type = prop_type;
246 property_declarators = declarators;
247 property_semicolon = semi } ->
248 Concat [
249 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
250 t env prop_type;
251 handle_declarator_list env declarators;
252 t env semi;
253 Newline;
255 | Syntax.NamespaceDeclaration {
256 namespace_keyword = kw;
257 namespace_name = name;
258 namespace_body = body } ->
259 Concat [
260 t env kw;
261 Space;
262 t env name;
263 t env body;
264 Newline;
266 | Syntax.NamespaceBody {
267 namespace_left_brace = left_b;
268 namespace_declarations = decls;
269 namespace_right_brace = right_b } ->
270 Concat [
271 Space;
272 braced_block_nest env left_b right_b [handle_possible_list env decls];
274 | Syntax.NamespaceEmptyBody {
275 namespace_semicolon = semi } ->
276 Concat [
277 t env semi;
279 | Syntax.NamespaceUseDeclaration {
280 namespace_use_keyword = kw;
281 namespace_use_kind = use_kind;
282 namespace_use_clauses = clauses;
283 namespace_use_semicolon = semi } ->
284 Concat [
285 t env kw;
286 Space;
287 t env use_kind;
288 when_present use_kind space;
289 WithRule (Rule.Parental, Nest [
290 handle_possible_list env clauses ~after_each:after_each_argument;
292 t env semi;
293 Newline;
295 | Syntax.NamespaceGroupUseDeclaration {
296 namespace_group_use_keyword = kw;
297 namespace_group_use_kind = use_kind;
298 namespace_group_use_prefix = prefix;
299 namespace_group_use_left_brace = left_b;
300 namespace_group_use_clauses = clauses;
301 namespace_group_use_right_brace = right_b;
302 namespace_group_use_semicolon = semi } ->
303 Concat [
304 t env kw;
305 Space;
306 t env use_kind;
307 when_present use_kind space;
308 t env prefix;
309 transform_argish env left_b clauses right_b;
310 t env semi;
311 Newline;
313 | Syntax.NamespaceUseClause {
314 namespace_use_clause_kind = use_kind;
315 namespace_use_name = name;
316 namespace_use_as = as_kw;
317 namespace_use_alias = alias } ->
318 Concat [
319 t env use_kind;
320 when_present use_kind space;
321 t env name;
322 when_present as_kw space;
323 t env as_kw;
324 when_present alias space;
325 t env alias;
327 | Syntax.FunctionDeclaration {
328 function_attribute_spec = attr;
329 function_declaration_header = header;
330 function_body = body } ->
331 Concat [
332 t env attr;
333 when_present attr newline;
334 t env header;
335 handle_possible_compound_statement env ~allow_collapse:true body;
336 Newline;
338 | Syntax.FunctionDeclarationHeader {
339 function_modifiers = modifiers;
340 function_keyword = kw;
341 function_ampersand = amp;
342 function_name = name;
343 function_type_parameter_list = type_params;
344 function_left_paren = leftp;
345 function_parameter_list = params;
346 function_right_paren = rightp;
347 function_colon = colon;
348 function_type = ret_type;
349 function_where_clause = where } ->
350 Concat [
351 Span (
352 transform_fn_decl_name env modifiers kw amp name type_params leftp);
353 transform_fn_decl_args env params rightp colon ret_type where;
355 | Syntax.WhereClause {
356 where_clause_keyword = where;
357 where_clause_constraints = constraints } ->
358 Concat [
359 t env where;
360 Space;
361 handle_possible_list env constraints ~after_each:(fun _ -> Space);
363 | Syntax.WhereConstraint {
364 where_constraint_left_type = left;
365 where_constraint_operator = op;
366 where_constraint_right_type = right } ->
367 Concat [
368 t env left;
369 Space;
370 t env op;
371 Space;
372 t env right;
374 | Syntax.MethodishDeclaration {
375 methodish_attribute = attr;
376 methodish_function_decl_header = func_decl;
377 methodish_function_body = body;
378 methodish_semicolon = semi } ->
379 Concat [
380 t env attr;
381 when_present attr newline;
383 let fn_name, args_and_where = match Syntax.syntax func_decl with
384 | Syntax.FunctionDeclarationHeader {
385 function_modifiers = modifiers;
386 function_keyword = kw;
387 function_ampersand = amp;
388 function_name = name;
389 function_type_parameter_list = type_params;
390 function_left_paren = leftp;
391 function_parameter_list = params;
392 function_right_paren = rightp;
393 function_colon = colon;
394 function_type = ret_type;
395 function_where_clause = where } ->
396 Concat (
397 transform_fn_decl_name env
398 modifiers
401 name
402 type_params
403 leftp
405 transform_fn_decl_args env params rightp colon ret_type where
406 | _ -> failwith "Expected FunctionDeclarationHeader"
408 Concat [
409 Span [fn_name];
410 args_and_where;
413 when_present body (fun () ->
414 handle_possible_compound_statement env ~allow_collapse:true body
416 t env semi;
417 Newline;
419 | Syntax.ClassishDeclaration {
420 classish_attribute = attr;
421 classish_modifiers = modifiers;
422 classish_keyword = kw;
423 classish_name = name;
424 classish_type_parameters = type_params;
425 classish_extends_keyword = extends_kw;
426 classish_extends_list = extends;
427 classish_implements_keyword = impl_kw;
428 classish_implements_list = impls;
429 classish_body = body } ->
430 let after_each_ancestor is_last =
431 if is_last then Nothing else space_split () in
432 Concat [
433 t env attr;
434 when_present attr newline;
435 Span [
436 handle_possible_list env ~after_each:(fun _ -> Space) modifiers;
437 t env kw;
438 Space;
439 Split;
440 Nest [
441 t env name;
442 t env type_params;
446 when_present extends_kw (fun () -> Concat [
447 Space;
448 Split;
449 WithRule (Rule.Parental, Nest [ Span [
450 t env extends_kw;
451 Space;
452 Split;
453 WithRule (Rule.Parental, Nest [
454 handle_possible_list env ~after_each:after_each_ancestor extends
459 when_present impl_kw (fun () -> Concat [
460 Space;
461 Split;
462 WithRule (Rule.Parental, Nest [ Span [
463 t env impl_kw;
464 Space;
465 Split;
466 WithRule (Rule.Parental, Nest [
467 handle_possible_list env ~after_each:after_each_ancestor impls
471 t env body;
473 | Syntax.ClassishBody {
474 classish_body_left_brace = left_b;
475 classish_body_elements = body;
476 classish_body_right_brace = right_b } ->
477 Concat [
478 Space;
479 braced_block_nest env left_b right_b [
480 handle_possible_list env body
482 Newline;
484 | Syntax.TraitUsePrecedenceItem {
485 trait_use_precedence_item_name = name;
486 trait_use_precedence_item_keyword = kw;
487 trait_use_precedence_item_removed_names = removed_names } ->
488 Concat [
489 t env name;
490 Space;
491 t env kw;
492 Space;
493 t env removed_names;
494 Newline;
496 | Syntax.TraitUseAliasItem {
497 trait_use_alias_item_aliasing_name = aliasing_name;
498 trait_use_alias_item_keyword = kw;
499 trait_use_alias_item_modifiers = visibility;
500 trait_use_alias_item_aliased_name = aliased_name } ->
501 Concat [
502 t env aliasing_name;
503 Space;
504 t env kw;
505 Space;
506 t env visibility;
507 Space;
508 t env aliased_name;
509 Newline;
511 | Syntax.TraitUseConflictResolution {
512 trait_use_conflict_resolution_keyword = kw;
513 trait_use_conflict_resolution_names = elements;
514 trait_use_conflict_resolution_left_brace = lb;
515 trait_use_conflict_resolution_clauses = clauses;
516 trait_use_conflict_resolution_right_brace = rb } ->
517 Concat [
518 t env kw;
519 WithRule (Rule.Parental, Nest [
520 handle_possible_list env ~before_each:space_split elements;
522 t env lb;
523 Newline;
524 WithRule (Rule.Parental, Nest [
525 handle_possible_list env ~before_each:space_split clauses;
527 Newline;
528 t env rb;
530 | Syntax.TraitUse {
531 trait_use_keyword = kw;
532 trait_use_names = elements;
533 trait_use_semicolon = semi } ->
534 Concat [
535 t env kw;
536 WithRule (Rule.Parental, Nest [
537 handle_possible_list env ~before_each:space_split elements;
539 t env semi;
540 Newline;
542 | Syntax.RequireClause {
543 require_keyword = kw;
544 require_kind = kind;
545 require_name = name;
546 require_semicolon = semi } ->
547 Concat [
548 t env kw;
549 Space;
550 t env kind;
551 Space;
552 Split;
553 t env name;
554 t env semi;
555 Newline;
557 | Syntax.ConstDeclaration {
558 const_abstract = abstr;
559 const_keyword = kw;
560 const_type_specifier = const_type;
561 const_declarators = declarators;
562 const_semicolon = semi } ->
563 Concat [
564 t env abstr;
565 when_present abstr space;
566 t env kw;
567 when_present const_type space;
568 t env const_type;
569 WithRule (Rule.Parental, Nest [
570 handle_possible_list env ~before_each:space_split declarators;
572 t env semi;
573 Newline;
575 | Syntax.TypeConstDeclaration {
576 type_const_abstract = abs;
577 type_const_keyword = kw;
578 type_const_type_keyword = type_kw ;
579 type_const_name = name;
580 type_const_type_parameters = type_params;
581 type_const_type_constraint = type_constraint;
582 type_const_equal = eq;
583 type_const_type_specifier = type_spec;
584 type_const_semicolon = semi } ->
585 Concat [
586 t env abs;
587 Space;
588 t env kw;
589 Space;
590 t env type_kw;
591 Space;
592 t env name;
593 t env type_params;
594 when_present type_constraint space;
595 t env type_constraint;
596 when_present eq space;
597 t env eq;
598 when_present type_spec (fun _ -> Concat [
599 Space;
600 SplitWith Cost.Base;
601 Nest [t env type_spec];
603 t env semi;
604 Newline;
606 | Syntax.ParameterDeclaration {
607 parameter_attribute = attr;
608 parameter_visibility = visibility;
609 parameter_call_convention = callconv;
610 parameter_type = param_type;
611 parameter_name = name;
612 parameter_default_value = default } ->
613 Concat [
614 t env attr;
615 t env visibility;
616 when_present visibility space;
617 t env callconv;
618 when_present callconv space;
619 t env param_type;
620 if Syntax.is_missing visibility
621 && Syntax.is_missing callconv
622 && Syntax.is_missing param_type
623 then t env name
624 else Concat [
625 Space;
626 SplitWith Cost.Base;
627 Nest [t env name];
629 t env default;
631 | Syntax.VariadicParameter {
632 variadic_parameter_call_convention = callconv;
633 variadic_parameter_type = type_var;
634 variadic_parameter_ellipsis = ellipsis } ->
635 Concat [
636 t env callconv;
637 when_present callconv space;
638 t env type_var;
639 t env ellipsis;
641 | Syntax.AttributeSpecification {
642 attribute_specification_left_double_angle = left_da;
643 attribute_specification_attributes = attrs;
644 attribute_specification_right_double_angle = right_da; } ->
645 transform_argish env ~allow_trailing:false left_da attrs right_da
646 | Syntax.Attribute {
647 attribute_name = name;
648 attribute_left_paren = left_p;
649 attribute_values = values;
650 attribute_right_paren = right_p; } ->
651 Concat [
652 t env name;
653 transform_argish env left_p values right_p;
655 | Syntax.InclusionExpression {
656 inclusion_require = kw;
657 inclusion_filename = expr; } ->
658 Concat [
659 t env kw;
660 (match Syntax.syntax expr with
661 | Syntax.ParenthesizedExpression _ -> Nothing
662 | _ -> Space
664 SplitWith Cost.Base;
665 t env expr;
667 | Syntax.InclusionDirective {
668 inclusion_expression = expr;
669 inclusion_semicolon = semi; } ->
670 Concat [
671 t env expr;
672 t env semi;
673 Newline;
675 | Syntax.CompoundStatement {
676 compound_left_brace;
677 compound_statements;
678 compound_right_brace; } ->
679 Concat [
680 handle_compound_statement env
681 compound_left_brace
682 compound_statements
683 compound_right_brace;
684 Newline;
686 | Syntax.AlternateLoopStatement {
687 alternate_loop_opening_colon;
688 alternate_loop_statements;
689 alternate_loop_closing_keyword;
690 alternate_loop_closing_semicolon; } ->
691 Concat [
692 handle_alternate_loop_statement env
693 alternate_loop_opening_colon
694 alternate_loop_statements
695 alternate_loop_closing_keyword
696 alternate_loop_closing_semicolon;
697 Newline;
699 | Syntax.UnsetStatement {
700 unset_keyword = kw;
701 unset_left_paren = left_p;
702 unset_variables = args;
703 unset_right_paren = right_p;
704 unset_semicolon = semi; } ->
705 Concat [
706 t env kw;
707 transform_argish env ~allow_trailing:false left_p args right_p;
708 t env semi;
709 Newline;
711 | Syntax.WhileStatement x ->
712 Concat [
713 t env x.while_keyword;
714 Space;
715 t env x.while_left_paren;
716 Split;
717 WithRule (Rule.Parental, Concat [
718 Nest [t env x.while_condition];
719 Split;
720 t env x.while_right_paren;
722 handle_possible_compound_statement env x.while_body;
723 Newline;
725 | Syntax.DeclareDirectiveStatement x ->
726 Concat [
727 t env x.declare_directive_keyword;
728 Space;
729 t env x.declare_directive_left_paren;
730 Split;
731 WithRule (Rule.Parental, Concat [
732 Nest [t env x.declare_directive_expression];
733 Split;
734 t env x.declare_directive_right_paren;
736 t env x.declare_directive_semicolon;
737 Newline;
739 | Syntax.DeclareBlockStatement x ->
740 Concat [
741 t env x.declare_block_keyword;
742 Space;
743 t env x.declare_block_left_paren;
744 Split;
745 WithRule (Rule.Parental, Concat [
746 Nest [t env x.declare_block_expression];
747 Split;
748 t env x.declare_block_right_paren;
750 handle_possible_compound_statement env x.declare_block_body;
751 Newline;
753 | Syntax.UsingStatementBlockScoped x ->
754 Concat [
755 t env x.using_block_await_keyword;
756 when_present x.using_block_await_keyword space;
757 t env x.using_block_using_keyword;
758 Space;
759 t env x.using_block_left_paren;
760 Split;
761 WithRule (Rule.Parental, Concat [
762 Nest [handle_possible_list env x.using_block_expressions];
763 Split;
764 t env x.using_block_right_paren;
766 handle_possible_compound_statement env x.using_block_body;
767 Newline;
769 | Syntax.UsingStatementFunctionScoped x ->
770 Concat [
771 t env x.using_function_await_keyword;
772 when_present x.using_function_await_keyword space;
773 t env x.using_function_using_keyword;
774 Space;
775 t env x.using_function_expression;
776 t env x.using_function_semicolon;
777 Newline;
779 | Syntax.IfStatement {
780 if_keyword = kw;
781 if_left_paren = left_p;
782 if_condition = condition;
783 if_right_paren = right_p;
784 if_statement = if_body;
785 if_elseif_clauses = elseif_clauses;
786 if_else_clause = else_clause; } ->
787 Concat [
788 t env kw;
789 Space;
790 transform_condition env left_p condition right_p;
791 handle_possible_compound_statement env if_body;
792 handle_possible_list env elseif_clauses;
793 t env else_clause;
794 Newline;
796 | Syntax.ElseifClause {
797 elseif_keyword = kw;
798 elseif_left_paren = left_p;
799 elseif_condition = condition;
800 elseif_right_paren = right_p;
801 elseif_statement = body; } ->
802 Concat [
803 t env kw;
804 Space;
805 transform_condition env left_p condition right_p;
806 handle_possible_compound_statement env body;
808 | Syntax.ElseClause x ->
809 Concat [
810 t env x.else_keyword;
811 match Syntax.syntax x.else_statement with
812 | Syntax.IfStatement _ -> Concat [
813 Space;
814 t env x.else_statement;
815 Space;
817 | _ -> handle_possible_compound_statement env x.else_statement
819 | Syntax.IfEndIfStatement {
820 if_endif_keyword = kw;
821 if_endif_left_paren = left_p;
822 if_endif_condition = condition;
823 if_endif_right_paren = right_p;
824 if_endif_colon = colon;
825 if_endif_statement = if_body;
826 if_endif_elseif_colon_clauses = elseif_clauses;
827 if_endif_else_colon_clause = else_clause;
828 if_endif_endif_keyword = endif_kw;
829 if_endif_semicolon = semicolon; } ->
830 Concat [
831 t env kw;
832 Space;
833 transform_condition env left_p condition right_p;
834 t env colon;
835 handle_possible_compound_statement env if_body;
836 handle_possible_list env elseif_clauses;
837 t env else_clause;
838 t env endif_kw;
839 t env semicolon;
840 Newline;
842 | Syntax.ElseifColonClause {
843 elseif_colon_keyword = kw;
844 elseif_colon_left_paren = left_p;
845 elseif_colon_condition = condition;
846 elseif_colon_right_paren = right_p;
847 elseif_colon_colon = colon;
848 elseif_colon_statement = body; } ->
849 Concat [
850 t env kw;
851 Space;
852 transform_condition env left_p condition right_p;
853 t env colon;
854 handle_possible_compound_statement env body;
856 | Syntax.ElseColonClause x ->
857 Concat [
858 t env x.else_colon_keyword;
859 match Syntax.syntax x.else_colon_statement with
860 | Syntax.IfStatement _ -> Concat [
861 Space;
862 t env x.else_colon_statement;
863 Space;
865 | _ -> handle_possible_compound_statement env x.else_colon_statement
867 | Syntax.TryStatement {
868 try_keyword = kw;
869 try_compound_statement = body;
870 try_catch_clauses = catch_clauses;
871 try_finally_clause = finally_clause; } ->
872 (* TODO: revisit *)
873 Concat [
874 t env kw;
875 handle_possible_compound_statement env body;
876 handle_possible_list env catch_clauses;
877 t env finally_clause;
878 Newline;
880 | Syntax.CatchClause {
881 catch_keyword = kw;
882 catch_left_paren = left_p;
883 catch_type = ex_type;
884 catch_variable = var;
885 catch_right_paren = right_p;
886 catch_body = body; } ->
887 Concat [
888 t env kw;
889 Space;
890 delimited_nest env left_p right_p [
891 t env ex_type;
892 Space;
893 SplitWith Cost.Base;
894 Nest [
895 t env var;
898 handle_possible_compound_statement env body;
900 | Syntax.FinallyClause {
901 finally_keyword = kw;
902 finally_body = body; } ->
903 Concat [
904 t env kw;
905 Space;
906 handle_possible_compound_statement env body;
908 | Syntax.DoStatement {
909 do_keyword = do_kw;
910 do_body = body;
911 do_while_keyword = while_kw;
912 do_left_paren = left_p;
913 do_condition = cond;
914 do_right_paren = right_p;
915 do_semicolon = semi; } ->
916 Concat [
917 t env do_kw;
918 Space;
919 handle_possible_compound_statement env body;
920 t env while_kw;
921 Space;
922 transform_condition env left_p cond right_p;
923 t env semi;
924 Newline;
926 | Syntax.ForStatement {
927 for_keyword = kw;
928 for_left_paren = left_p;
929 for_initializer = init;
930 for_first_semicolon = semi1;
931 for_control = control;
932 for_second_semicolon = semi2;
933 for_end_of_loop = after_iter;
934 for_right_paren = right_p;
935 for_body = body; } ->
936 Concat [
937 t env kw;
938 Space;
939 t env left_p;
940 WithRule (Rule.Parental, Concat [
941 Split;
942 Nest [
943 handle_possible_list env init;
944 t env semi1;
945 Space;
946 Split;
947 handle_possible_list env control;
948 t env semi2;
949 Space;
950 Split;
951 handle_possible_list env after_iter;
953 Split;
954 t env right_p;
956 handle_possible_compound_statement env body;
957 Newline;
959 | Syntax.ForeachStatement {
960 foreach_keyword = kw;
961 foreach_left_paren = left_p;
962 foreach_collection = collection;
963 foreach_await_keyword = await_kw;
964 foreach_as = as_kw;
965 foreach_key = key;
966 foreach_arrow = arrow;
967 foreach_value = value;
968 foreach_right_paren = right_p;
969 foreach_body = body; } ->
970 Concat [
971 t env kw;
972 Space;
973 delimited_nest env left_p right_p [
974 t env collection;
975 Space;
976 t env await_kw;
977 Space;
978 t env as_kw;
979 Space;
980 SplitWith Cost.Base;
981 Nest [
982 Span [
983 t env key;
984 Space;
985 t env arrow;
986 Space;
987 SplitWith Cost.Base;
988 Nest [
989 t env value;
994 handle_possible_compound_statement env body;
995 Newline;
997 | Syntax.SwitchStatement {
998 switch_keyword = kw;
999 switch_left_paren = left_p;
1000 switch_expression = expr;
1001 switch_right_paren = right_p;
1002 switch_left_brace = left_b;
1003 switch_sections = sections;
1004 switch_right_brace = right_b; } ->
1005 let sections = Syntax.syntax_node_to_list sections in
1006 Concat [
1007 t env kw;
1008 Space;
1009 delimited_nest env left_p right_p [t env expr];
1010 Space;
1011 braced_block_nest env left_b right_b (List.map sections (t env));
1012 Newline;
1014 | Syntax.AlternateSwitchStatement {
1015 alternate_switch_keyword = kw;
1016 alternate_switch_left_paren = left_p;
1017 alternate_switch_expression = expr;
1018 alternate_switch_right_paren = right_p;
1019 alternate_switch_opening_colon = colon;
1020 alternate_switch_sections = sections;
1021 alternate_switch_closing_endswitch = endswitch;
1022 alternate_switch_closing_semicolon = semicolon; } ->
1023 let sections = Syntax.syntax_node_to_list sections in
1024 Concat [
1025 t env kw;
1026 Space;
1027 delimited_nest env left_p right_p [t env expr];
1028 Space;
1029 coloned_block_nest env colon endswitch semicolon (List.map sections (t env));
1030 Newline;
1032 | Syntax.SwitchSection {
1033 switch_section_labels = labels;
1034 switch_section_statements = statements;
1035 switch_section_fallthrough = fallthrough; } ->
1036 (* If there is FallThrough trivia leading the first case label, handle it
1037 * in a BlockNest so that it is indented to the same level as the previous
1038 * SwitchSection's statements. *)
1039 let (labels_leading, labels) = remove_leading_trivia labels in
1040 let (after_fallthrough, upto_fallthrough) =
1041 List.split_while (List.rev labels_leading)
1042 ~f:(fun t -> Trivia.kind t <> TriviaKind.FallThrough)
1044 let upto_fallthrough = List.rev upto_fallthrough in
1045 let after_fallthrough = List.rev after_fallthrough in
1046 let labels = Syntax.syntax_node_to_list labels in
1047 let statements = Syntax.syntax_node_to_list statements in
1048 (* When the statements in the SwitchSection are wrapped in a single
1049 * CompoundStatement, special-case the opening curly brace to appear on
1050 * the same line as the case label. *)
1051 let is_scoped_section =
1052 match statements with
1053 | [Syntax.{ syntax = CompoundStatement _; _ }] -> true
1054 | _ -> false
1056 Concat [
1057 if List.is_empty upto_fallthrough
1058 then transform_leading_trivia after_fallthrough
1059 else Concat [
1060 BlockNest [transform_leading_trivia upto_fallthrough; Newline];
1061 transform_trailing_trivia after_fallthrough;
1063 handle_list env labels ~after_each:begin fun is_last_label ->
1064 if is_last_label && is_scoped_section
1065 then Nothing
1066 else Newline
1067 end;
1068 if is_scoped_section
1069 then handle_list env statements
1070 else BlockNest [handle_list env statements];
1071 t env fallthrough;
1073 | Syntax.CaseLabel {
1074 case_keyword = kw;
1075 case_expression = expr;
1076 case_colon = colon; } ->
1077 Concat [
1078 t env kw;
1079 Space;
1080 SplitWith Cost.Base;
1081 t env expr;
1082 t env colon;
1084 | Syntax.DefaultLabel {
1085 default_keyword = kw;
1086 default_colon = colon; } ->
1087 Concat [
1088 t env kw;
1089 t env colon;
1091 | Syntax.SwitchFallthrough {
1092 fallthrough_keyword = kw;
1093 fallthrough_semicolon = semi; } ->
1094 Concat [
1095 t env kw;
1096 t env semi;
1098 | Syntax.ReturnStatement {
1099 return_keyword = kw;
1100 return_expression = expr;
1101 return_semicolon = semi; } ->
1102 transform_keyword_expression_statement env kw expr semi
1103 | Syntax.GotoLabel { goto_label_name; goto_label_colon } ->
1104 Concat [
1105 t env goto_label_name;
1106 t env goto_label_colon;
1107 Newline;
1109 | Syntax.GotoStatement {
1110 goto_statement_keyword;
1111 goto_statement_label_name;
1112 goto_statement_semicolon; } ->
1113 Concat [
1114 t env goto_statement_keyword;
1115 Space;
1116 t env goto_statement_label_name;
1117 t env goto_statement_semicolon;
1118 Newline;
1120 | Syntax.ThrowStatement {
1121 throw_keyword = kw;
1122 throw_expression = expr;
1123 throw_semicolon = semi; } ->
1124 transform_keyword_expression_statement env kw expr semi
1125 | Syntax.BreakStatement {
1126 break_keyword = kw;
1127 break_level = expr;
1128 break_semicolon = semi; } ->
1129 transform_keyword_expression_statement env kw expr semi
1130 | Syntax.ContinueStatement {
1131 continue_keyword = kw;
1132 continue_level = level;
1133 continue_semicolon = semi; } ->
1134 transform_keyword_expression_statement env kw level semi
1135 | Syntax.FunctionStaticStatement {
1136 static_static_keyword = static_kw;
1137 static_declarations = declarators;
1138 static_semicolon = semi; } ->
1139 transform_keyword_expr_list_statement env static_kw declarators semi
1140 | Syntax.EchoStatement {
1141 echo_keyword = kw;
1142 echo_expressions = expr_list;
1143 echo_semicolon = semi; } ->
1144 (match Syntax.syntax expr_list with
1145 | Syntax.SyntaxList [
1146 Syntax.{ syntax = ListItem { list_item = expr; _ }; _ }]
1147 when Syntax.kind expr = SyntaxKind.ParenthesizedExpression ->
1148 Concat [
1149 t env kw;
1150 t env expr;
1151 t env semi;
1152 Newline;
1154 | _ ->
1155 transform_keyword_expr_list_statement env kw expr_list semi
1157 | Syntax.GlobalStatement {
1158 global_keyword = kw;
1159 global_variables = var_list;
1160 global_semicolon = semi; } ->
1161 transform_keyword_expr_list_statement env kw var_list semi
1162 | Syntax.SimpleInitializer {
1163 simple_initializer_equal = eq_kw;
1164 simple_initializer_value = value; } ->
1165 Concat [
1166 Space;
1167 t env eq_kw;
1168 Space;
1169 SplitWith Cost.Base;
1170 Nest [t env value];
1172 | Syntax.AnonymousFunction {
1173 anonymous_static_keyword = static_kw;
1174 anonymous_async_keyword = async_kw;
1175 anonymous_coroutine_keyword = coroutine_kw;
1176 anonymous_function_keyword = fun_kw;
1177 anonymous_left_paren = lp;
1178 anonymous_parameters = params;
1179 anonymous_right_paren = rp;
1180 anonymous_colon = colon;
1181 anonymous_type = ret_type;
1182 anonymous_use = use;
1183 anonymous_body = body; } ->
1184 Concat [
1185 t env static_kw;
1186 when_present static_kw space;
1187 t env async_kw;
1188 when_present async_kw space;
1189 t env coroutine_kw;
1190 when_present coroutine_kw space;
1191 t env fun_kw;
1192 transform_argish_with_return_type env lp params rp colon ret_type;
1193 t env use;
1194 handle_possible_compound_statement env
1195 ~space:false
1196 ~allow_collapse:true
1197 body;
1199 | Syntax.Php7AnonymousFunction {
1200 php7_anonymous_static_keyword = static_kw;
1201 php7_anonymous_async_keyword = async_kw;
1202 php7_anonymous_coroutine_keyword = coroutine_kw;
1203 php7_anonymous_function_keyword = fun_kw;
1204 php7_anonymous_left_paren = lp;
1205 php7_anonymous_parameters = params;
1206 php7_anonymous_right_paren = rp;
1207 php7_anonymous_use = use;
1208 php7_anonymous_colon = colon;
1209 php7_anonymous_type = ret_type;
1210 php7_anonymous_body = body; } ->
1211 Concat [
1212 t env static_kw;
1213 when_present static_kw space;
1214 t env async_kw;
1215 when_present async_kw space;
1216 t env coroutine_kw;
1217 when_present coroutine_kw space;
1218 t env fun_kw;
1219 transform_argish env lp params rp;
1220 t env use;
1221 t env colon;
1222 when_present colon space;
1223 t env ret_type;
1224 handle_possible_compound_statement env
1225 ~space:false
1226 ~allow_collapse:true
1227 body;
1229 | Syntax.AnonymousFunctionUseClause {
1230 anonymous_use_keyword = kw;
1231 anonymous_use_left_paren = left_p;
1232 anonymous_use_variables = vars;
1233 anonymous_use_right_paren = right_p; } ->
1234 (* TODO: Revisit *)
1235 Concat [
1236 Space;
1237 t env kw;
1238 Space;
1239 transform_argish env left_p vars right_p;
1241 | Syntax.LambdaExpression {
1242 lambda_async = async;
1243 lambda_coroutine = coroutine;
1244 lambda_signature = signature;
1245 lambda_arrow = arrow;
1246 lambda_body = body; } ->
1247 Concat [
1248 t env async;
1249 when_present async space;
1250 t env coroutine;
1251 when_present coroutine space;
1252 t env signature;
1253 Space;
1254 t env arrow;
1255 handle_lambda_body env body;
1257 | Syntax.LambdaSignature {
1258 lambda_left_paren = lp;
1259 lambda_parameters = params;
1260 lambda_right_paren = rp;
1261 lambda_colon = colon;
1262 lambda_type = ret_type; } ->
1263 transform_argish_with_return_type env lp params rp colon ret_type
1264 | Syntax.CastExpression _ ->
1265 Span (List.map (Syntax.children node) (t env))
1266 | Syntax.MemberSelectionExpression {
1267 member_object;
1268 member_operator;
1269 member_name; } ->
1270 handle_possible_chaining env
1272 member_object,
1273 member_operator,
1274 member_name
1276 None
1277 | Syntax.SafeMemberSelectionExpression {
1278 safe_member_object;
1279 safe_member_operator;
1280 safe_member_name; } ->
1281 handle_possible_chaining env
1283 safe_member_object,
1284 safe_member_operator,
1285 safe_member_name
1287 None
1288 | Syntax.YieldExpression {
1289 yield_keyword = kw;
1290 yield_operand = operand; } ->
1291 Concat [
1292 t env kw;
1293 Space;
1294 SplitWith Cost.Base;
1295 Nest [t env operand];
1297 | Syntax.YieldFromExpression {
1298 yield_from_yield_keyword = yield_kw;
1299 yield_from_from_keyword = from_kw;
1300 yield_from_operand = operand; } ->
1301 Concat [
1302 t env yield_kw;
1303 Space;
1304 t env from_kw;
1305 Space;
1306 SplitWith Cost.Base;
1307 Nest [t env operand];
1309 | Syntax.PrefixUnaryExpression {
1310 prefix_unary_operator = operator;
1311 prefix_unary_operand = operand; } ->
1312 Concat [
1313 t env operator;
1314 (match Syntax.syntax operator with
1315 | Syntax.Token x ->
1316 let is_parenthesized =
1317 match Syntax.syntax operand with
1318 | Syntax.ParenthesizedExpression _ -> true
1319 | _ -> false
1321 let open TokenKind in
1322 (match Token.kind x with
1323 | Await | Clone | Suspend -> Space
1324 | Print -> if is_parenthesized then Nothing else Space
1325 | _ -> Nothing
1327 | _ -> Nothing
1329 t env operand;
1331 | Syntax.BinaryExpression {
1332 binary_left_operand;
1333 binary_operator;
1334 binary_right_operand; } ->
1335 transform_binary_expression env ~is_nested:false
1336 (binary_left_operand, binary_operator, binary_right_operand)
1337 | Syntax.InstanceofExpression {
1338 instanceof_left_operand = left;
1339 instanceof_operator = kw;
1340 instanceof_right_operand = right; } ->
1341 Concat [
1342 t env left;
1343 Space;
1344 t env kw;
1345 Space;
1346 SplitWith Cost.Base;
1347 Nest [t env right];
1349 | Syntax.IsExpression {
1350 is_left_operand = left;
1351 is_operator = kw;
1352 is_right_operand = right; } ->
1353 Concat [
1354 t env left;
1355 Space;
1356 t env kw;
1357 Space;
1358 SplitWith Cost.Base;
1359 Nest [t env right];
1361 | Syntax.ConditionalExpression {
1362 conditional_test = test_expr;
1363 conditional_question = q_kw;
1364 conditional_consequence = true_expr;
1365 conditional_colon = c_kw;
1366 conditional_alternative = false_expr; } ->
1367 WithLazyRule (Rule.Parental,
1368 t env test_expr,
1369 Nest [
1370 Space;
1371 Split;
1372 t env q_kw;
1373 when_present true_expr (fun () -> Concat [
1374 Space;
1375 if env.Env.indent_width = 2
1376 then Nest [t env true_expr]
1377 else t env true_expr;
1378 Space;
1379 Split;
1381 t env c_kw;
1382 Space;
1383 if not (Syntax.is_missing true_expr) && env.Env.indent_width = 2
1384 then Nest [t env false_expr]
1385 else t env false_expr;
1387 | Syntax.FunctionCallExpression {
1388 function_call_receiver;
1389 function_call_left_paren;
1390 function_call_argument_list;
1391 function_call_right_paren; } ->
1392 handle_function_call_expression env
1393 function_call_receiver
1394 function_call_left_paren
1395 function_call_argument_list
1396 function_call_right_paren
1397 | Syntax.FunctionCallWithTypeArgumentsExpression {
1398 function_call_with_type_arguments_receiver;
1399 function_call_with_type_arguments_type_args;
1400 function_call_with_type_arguments_left_paren;
1401 function_call_with_type_arguments_argument_list;
1402 function_call_with_type_arguments_right_paren; } ->
1403 handle_function_call_with_type_arguments_expression env
1404 function_call_with_type_arguments_receiver
1405 function_call_with_type_arguments_type_args
1406 function_call_with_type_arguments_left_paren
1407 function_call_with_type_arguments_argument_list
1408 function_call_with_type_arguments_right_paren
1409 | Syntax.EvalExpression {
1410 eval_keyword = kw;
1411 eval_left_paren = left_p;
1412 eval_argument = arg;
1413 eval_right_paren = right_p; } ->
1414 Concat [
1415 t env kw;
1416 transform_braced_item env left_p arg right_p;
1418 | Syntax.EmptyExpression {
1419 empty_keyword = kw;
1420 empty_left_paren = left_p;
1421 empty_argument = arg;
1422 empty_right_paren = right_p; } ->
1423 Concat [
1424 t env kw;
1425 transform_braced_item env left_p arg right_p;
1427 | Syntax.IssetExpression {
1428 isset_keyword = kw;
1429 isset_left_paren = left_p;
1430 isset_argument_list = args;
1431 isset_right_paren = right_p; } ->
1432 Concat [
1433 t env kw;
1434 transform_argish env ~allow_trailing:false left_p args right_p;
1436 | Syntax.DefineExpression {
1437 define_keyword = kw;
1438 define_left_paren = left_p;
1439 define_argument_list = args;
1440 define_right_paren = right_p; } ->
1441 Concat [
1442 t env kw;
1443 transform_argish env left_p args right_p;
1445 | Syntax.HaltCompilerExpression {
1446 halt_compiler_keyword = kw;
1447 halt_compiler_left_paren = left_p;
1448 halt_compiler_argument_list = args;
1449 halt_compiler_right_paren = right_p; } ->
1450 Concat [
1451 t env kw;
1452 transform_argish env left_p args right_p;
1454 | Syntax.ParenthesizedExpression {
1455 parenthesized_expression_left_paren = left_p;
1456 parenthesized_expression_expression = expr;
1457 parenthesized_expression_right_paren = right_p; } ->
1458 Concat [
1459 t env left_p;
1460 Split;
1461 WithRule (Rule.Parental, Concat [
1462 Nest [ t env expr; ];
1463 Split;
1464 t env right_p
1467 | Syntax.BracedExpression {
1468 braced_expression_left_brace = left_b;
1469 braced_expression_expression = expr;
1470 braced_expression_right_brace = right_b; } ->
1471 (* TODO: revisit this *)
1472 Concat [
1473 t env left_b;
1474 Split;
1475 let rule =
1476 if List.is_empty (Syntax.trailing_trivia left_b)
1477 && List.is_empty (Syntax.trailing_trivia expr)
1478 then Rule.Simple Cost.Base
1479 else Rule.Parental
1481 WithRule (rule, Concat [
1482 Nest [t env expr];
1483 Split;
1484 t env right_b
1487 | Syntax.EmbeddedBracedExpression {
1488 embedded_braced_expression_left_brace = left_b;
1489 embedded_braced_expression_expression = expr;
1490 embedded_braced_expression_right_brace = right_b; } ->
1491 (* TODO: Consider finding a way to avoid treating these expressions as
1492 opportunities for line breaks in long strings:
1494 $sql = "DELETE FROM `foo` WHERE `left` BETWEEN {$res->left} AND {$res
1495 ->right} ORDER BY `level` DESC";
1497 Concat [
1498 t env left_b;
1499 Nest [t env expr];
1500 t env right_b;
1502 | Syntax.ListExpression {
1503 list_keyword = kw;
1504 list_left_paren = lp;
1505 list_members = members;
1506 list_right_paren = rp; } ->
1507 Concat [
1508 t env kw;
1509 transform_argish env lp members rp;
1511 | Syntax.CollectionLiteralExpression {
1512 collection_literal_name = name;
1513 collection_literal_left_brace = left_b;
1514 collection_literal_initializers = initializers;
1515 collection_literal_right_brace = right_b; } ->
1516 transform_container_literal
1517 env ~spaces:true name left_b initializers right_b
1518 | Syntax.ObjectCreationExpression {
1519 object_creation_new_keyword = newkw;
1520 object_creation_object = what; } ->
1521 Concat [
1522 t env newkw;
1523 Space;
1524 t env what;
1526 | Syntax.ConstructorCall {
1527 constructor_call_type = obj_type;
1528 constructor_call_left_paren = left_p;
1529 constructor_call_argument_list = arg_list;
1530 constructor_call_right_paren = right_p; } ->
1531 Concat [
1532 t env obj_type;
1533 transform_argish env left_p arg_list right_p;
1535 | Syntax.AnonymousClass {
1536 anonymous_class_class_keyword = classkw;
1537 anonymous_class_left_paren = left_p;
1538 anonymous_class_argument_list = arg_list;
1539 anonymous_class_right_paren = right_p;
1540 anonymous_class_extends_keyword = extends_kw;
1541 anonymous_class_extends_list = extends;
1542 anonymous_class_implements_keyword = impl_kw;
1543 anonymous_class_implements_list = impls;
1544 anonymous_class_body = body; } ->
1545 let after_each_ancestor is_last =
1546 if is_last then Nothing else space_split () in
1547 Concat [
1548 t env classkw;
1549 transform_argish env left_p arg_list right_p;
1550 when_present extends_kw (fun () -> Concat [
1551 Space;
1552 Split;
1553 WithRule (Rule.Parental, Nest [ Span [
1554 t env extends_kw;
1555 Space;
1556 Split;
1557 WithRule (Rule.Parental, Nest [
1558 handle_possible_list env ~after_each:after_each_ancestor extends
1563 when_present impl_kw (fun () -> Concat [
1564 Space;
1565 Split;
1566 WithRule (Rule.Parental, Nest [ Span [
1567 t env impl_kw;
1568 Space;
1569 Split;
1570 WithRule (Rule.Parental, Nest [
1571 handle_possible_list env ~after_each:after_each_ancestor impls
1575 t env body;
1577 | Syntax.ArrayCreationExpression {
1578 array_creation_left_bracket = left_b;
1579 array_creation_members = members;
1580 array_creation_right_bracket = right_b; } ->
1581 transform_argish env left_b members right_b
1582 | Syntax.ArrayIntrinsicExpression {
1583 array_intrinsic_keyword = kw;
1584 array_intrinsic_left_paren = left_p;
1585 array_intrinsic_members = members;
1586 array_intrinsic_right_paren = right_p; } ->
1587 transform_container_literal env kw left_p members right_p
1588 | Syntax.DarrayIntrinsicExpression {
1589 darray_intrinsic_keyword = kw;
1590 darray_intrinsic_left_bracket = left_p;
1591 darray_intrinsic_members = members;
1592 darray_intrinsic_right_bracket = right_p; } ->
1593 transform_container_literal env kw left_p members right_p
1594 | Syntax.DictionaryIntrinsicExpression {
1595 dictionary_intrinsic_keyword = kw;
1596 dictionary_intrinsic_left_bracket = left_p;
1597 dictionary_intrinsic_members = members;
1598 dictionary_intrinsic_right_bracket = right_p; } ->
1599 transform_container_literal env kw left_p members right_p
1600 | Syntax.KeysetIntrinsicExpression {
1601 keyset_intrinsic_keyword = kw;
1602 keyset_intrinsic_left_bracket = left_p;
1603 keyset_intrinsic_members = members;
1604 keyset_intrinsic_right_bracket = right_p; } ->
1605 transform_container_literal env kw left_p members right_p
1606 | Syntax.VarrayIntrinsicExpression {
1607 varray_intrinsic_keyword = kw;
1608 varray_intrinsic_left_bracket = left_p;
1609 varray_intrinsic_members = members;
1610 varray_intrinsic_right_bracket = right_p; } ->
1611 transform_container_literal env kw left_p members right_p
1612 | Syntax.VectorIntrinsicExpression {
1613 vector_intrinsic_keyword = kw;
1614 vector_intrinsic_left_bracket = left_p;
1615 vector_intrinsic_members = members;
1616 vector_intrinsic_right_bracket = right_p; } ->
1617 transform_container_literal env kw left_p members right_p
1618 | Syntax.ElementInitializer {
1619 element_key = key;
1620 element_arrow = arrow;
1621 element_value = value; } ->
1622 transform_mapish_entry env key arrow value
1623 | Syntax.SubscriptExpression {
1624 subscript_receiver = receiver;
1625 subscript_left_bracket = lb;
1626 subscript_index = expr;
1627 subscript_right_bracket = rb; } ->
1628 Concat [
1629 t env receiver;
1630 transform_braced_item env lb expr rb;
1632 | Syntax.AwaitableCreationExpression {
1633 awaitable_async = async_kw;
1634 awaitable_coroutine = coroutine_kw;
1635 awaitable_compound_statement = body; } ->
1636 Concat [
1637 t env async_kw;
1638 when_present async_kw space;
1639 t env coroutine_kw;
1640 when_present coroutine_kw space;
1641 (* TODO: rethink possible one line bodies *)
1642 (* TODO: correctly handle spacing after the closing brace *)
1643 handle_possible_compound_statement env ~space:false body;
1645 | Syntax.XHPChildrenDeclaration {
1646 xhp_children_keyword = kw;
1647 xhp_children_expression = expr;
1648 xhp_children_semicolon = semi; } ->
1649 Concat [
1650 t env kw;
1651 Space;
1652 t env expr;
1653 t env semi;
1654 Newline;
1656 | Syntax.XHPChildrenParenthesizedList {
1657 xhp_children_list_left_paren = left_p;
1658 xhp_children_list_xhp_children = expressions;
1659 xhp_children_list_right_paren = right_p; } ->
1660 Concat [
1661 transform_argish env ~allow_trailing:false left_p expressions right_p;
1663 | Syntax.XHPCategoryDeclaration {
1664 xhp_category_keyword = kw;
1665 xhp_category_categories = categories;
1666 xhp_category_semicolon = semi; } ->
1667 Concat [
1668 t env kw;
1669 (* TODO: Eliminate code duplication *)
1670 WithRule (Rule.Parental, Nest [
1671 handle_possible_list env ~before_each:space_split categories;
1673 t env semi;
1674 Newline;
1676 | Syntax.XHPEnumType {
1677 xhp_enum_optional = opt;
1678 xhp_enum_keyword = kw;
1679 xhp_enum_left_brace = left_b;
1680 xhp_enum_values = values;
1681 xhp_enum_right_brace = right_b; } ->
1682 Concat [
1683 t env opt;
1684 t env kw;
1685 Space;
1686 transform_argish env left_b values right_b;
1688 | Syntax.XHPClassAttributeDeclaration {
1689 xhp_attribute_keyword = kw;
1690 xhp_attribute_attributes = xhp_attributes;
1691 xhp_attribute_semicolon = semi; } ->
1692 Concat [
1693 t env kw;
1694 (match Syntax.syntax xhp_attributes with
1695 | Syntax.Missing -> Nothing
1696 | Syntax.SyntaxList [attr] ->
1697 WithRule (Rule.Parental, Nest [Space; Split; t env attr])
1698 | Syntax.SyntaxList attrs ->
1699 Nest [handle_list env ~before_each:newline attrs]
1700 | _ -> failwith "Expected SyntaxList"
1702 t env semi;
1703 Newline;
1705 | Syntax.XHPClassAttribute {
1706 xhp_attribute_decl_type = attr_type;
1707 xhp_attribute_decl_name = name;
1708 xhp_attribute_decl_initializer = init;
1709 xhp_attribute_decl_required = req; } ->
1710 (* TODO: figure out nesting here *)
1711 Concat [
1712 t env attr_type;
1713 Space;
1714 t env name;
1715 when_present init space;
1716 t env init;
1717 when_present req space;
1718 t env req;
1720 | Syntax.XHPSimpleAttribute {
1721 xhp_simple_attribute_name = name;
1722 xhp_simple_attribute_equal = eq;
1723 xhp_simple_attribute_expression = expr; } ->
1724 Span [
1725 t env name;
1726 t env eq;
1727 SplitWith Cost.Base;
1728 Nest [t env expr];
1730 | Syntax.XHPSpreadAttribute {
1731 xhp_spread_attribute_left_brace =l_brace;
1732 xhp_spread_attribute_spread_operator =spread;
1733 xhp_spread_attribute_expression =expr;
1734 xhp_spread_attribute_right_brace = r_brace; } ->
1735 Span [
1736 t env l_brace;
1737 t env spread;
1738 SplitWith Cost.Base;
1739 Nest [t env expr];
1740 t env r_brace;
1742 | Syntax.XHPOpen {
1743 xhp_open_left_angle = left_a;
1744 xhp_open_name = name;
1745 xhp_open_attributes = attrs;
1746 xhp_open_right_angle = right_a; } ->
1747 Concat [
1748 t env left_a;
1749 t env name;
1750 match Syntax.syntax attrs with
1751 | Syntax.Missing -> handle_xhp_open_right_angle_token env attrs right_a
1752 | _ ->
1753 Concat [
1754 Space;
1755 Split;
1756 WithRule (Rule.Parental, Concat [
1757 Nest [
1758 handle_possible_list env ~after_each:(fun is_last ->
1759 if not is_last then space_split () else Nothing
1760 ) attrs;
1762 handle_xhp_open_right_angle_token env attrs right_a;
1766 | Syntax.XHPExpression {
1767 xhp_open = xhp_open;
1768 xhp_body = body;
1769 xhp_close = close; } ->
1770 let handle_xhp_body body =
1771 match Syntax.syntax body with
1772 | Syntax.Missing -> Nothing, true
1773 | Syntax.SyntaxList xs ->
1774 (* XHP breaks the normal rules of trivia. All trailing trivia (except
1775 * on XHPBody tokens) is lexed as leading trivia for the next token.
1777 * To deal with this, we keep track of whether the last token we added
1778 * was one that trailing trivia is scanned for. If it wasn't, we
1779 * handle the next token's leading trivia with
1780 * transform_xhp_leading_trivia, which treats all trivia up to the
1781 * first newline as trailing trivia. *)
1782 let prev_token_was_xhpbody = ref false in
1783 let transformed_body = Concat (List.map xs ~f:begin fun node ->
1784 let leading, node = remove_leading_trivia node in
1785 let transformed_node = Concat [
1786 (* Whitespace in an XHPBody is only significant when adjacent to
1787 * an XHPBody token, so we are free to add splits between other
1788 * nodes (like XHPExpressions and BracedExpressions). We can also
1789 * safely add splits before XHPBody tokens, but only if they
1790 * already have whitespace in their leading trivia.
1792 * Splits *after* XHPBody tokens are handled below by
1793 * trailing_whitespace, so if the previous token was an XHPBody
1794 * token, we don't need to do anything. *)
1795 if !prev_token_was_xhpbody
1796 then transform_leading_trivia leading
1797 else begin
1798 let v =
1799 match Syntax.syntax node with
1800 | Syntax.Token _ ->
1801 if has_invisibles leading then Split else Nothing
1802 | _ -> Split in
1803 Concat [v; transform_xhp_leading_trivia leading]
1804 end;
1805 t env node;
1806 ] in
1807 prev_token_was_xhpbody := begin
1808 match Syntax.syntax node with
1809 | Syntax.Token t -> Token.kind t = TokenKind.XHPBody
1810 | _ -> false
1811 end;
1812 (* Here, we preserve newlines after XHPBody tokens and don't add
1813 * splits between them. This means that we don't reflow paragraphs
1814 * in XHP to fit in the column limit.
1816 * If we were to split between XHPBody tokens, we'd need a new Rule
1817 * type to govern word-wrap style splitting, since using independent
1818 * splits (e.g. SplitWith Cost.Base) between every token would make
1819 * solving too expensive. *)
1820 let trailing = Syntax.trailing_trivia node in
1821 let trailing_whitespace =
1822 match Syntax.syntax node with
1823 | Syntax.Token _ when has_newline trailing -> Newline
1824 | _ when has_whitespace trailing -> Space
1825 | _ -> Nothing
1827 Concat [transformed_node; trailing_whitespace]
1828 end) in
1829 let leading_token =
1830 match Syntax.leading_token (List.hd_exn xs) with
1831 | None -> failwith "Expected token"
1832 | Some token -> token
1834 let can_split_before_first_token =
1835 Token.kind leading_token <> TokenKind.XHPBody ||
1836 has_invisibles (Token.leading leading_token)
1838 let transformed_body = Concat [
1839 if can_split_before_first_token then Split else Nothing;
1840 transformed_body;
1841 ] in
1842 let can_split_before_close = not !prev_token_was_xhpbody in
1843 transformed_body, can_split_before_close
1844 | _ -> failwith "Expected SyntaxList"
1846 WithPossibleLazyRule (Rule.Parental, t env xhp_open,
1847 let transformed_body, can_split_before_close = handle_xhp_body body in
1848 Concat [
1849 Nest [transformed_body];
1850 when_present close begin fun () ->
1851 let leading, close = remove_leading_trivia close in Concat [
1852 (* Ignore extra newlines by treating this as trailing trivia *)
1853 ignore_trailing_invisibles leading;
1854 if can_split_before_close then Split else Nothing;
1855 t env close;
1857 end;
1859 | Syntax.VarrayTypeSpecifier {
1860 varray_keyword = kw;
1861 varray_left_angle = left_a;
1862 varray_type = varray_type;
1863 varray_trailing_comma = trailing_comma;
1864 varray_right_angle = right_a; } ->
1865 Concat [
1866 t env kw;
1867 transform_braced_item_with_trailer env
1868 left_a varray_type trailing_comma right_a;
1870 | Syntax.VectorArrayTypeSpecifier {
1871 vector_array_keyword = kw;
1872 vector_array_left_angle = left_a;
1873 vector_array_type = vec_type;
1874 vector_array_right_angle = right_a; } ->
1875 Concat [
1876 t env kw;
1877 transform_braced_item env left_a vec_type right_a;
1879 | Syntax.VectorTypeSpecifier {
1880 vector_type_keyword = kw;
1881 vector_type_left_angle = left_a;
1882 vector_type_type = vec_type;
1883 vector_type_trailing_comma = trailing_comma;
1884 vector_type_right_angle = right_a; } ->
1885 Concat [
1886 t env kw;
1887 transform_braced_item_with_trailer env
1888 left_a vec_type trailing_comma right_a;
1890 | Syntax.KeysetTypeSpecifier {
1891 keyset_type_keyword = kw;
1892 keyset_type_left_angle = left_a;
1893 keyset_type_type = ks_type;
1894 keyset_type_trailing_comma = trailing_comma;
1895 keyset_type_right_angle = right_a; } ->
1896 Concat [
1897 t env kw;
1898 transform_braced_item_with_trailer env
1899 left_a ks_type trailing_comma right_a;
1901 | Syntax.TypeParameter {
1902 type_variance = variance;
1903 type_name = name;
1904 type_constraints = constraints; } ->
1905 Concat [
1906 t env variance;
1907 t env name;
1908 when_present constraints space;
1909 handle_possible_list env constraints
1910 ~after_each:(fun is_last -> if is_last then Nothing else Space);
1912 | Syntax.TypeConstraint {
1913 constraint_keyword = kw;
1914 constraint_type = constraint_type; } ->
1915 Concat [
1916 t env kw;
1917 Space;
1918 t env constraint_type;
1920 | Syntax.DarrayTypeSpecifier {
1921 darray_keyword = kw;
1922 darray_left_angle = left_a;
1923 darray_key = key;
1924 darray_comma = comma_kw;
1925 darray_value = value;
1926 darray_trailing_comma = trailing_comma;
1927 darray_right_angle = right_a; } ->
1928 let key_list_item = Syntax.make_list_item key comma_kw in
1929 let val_list_item = Syntax.make_list_item value trailing_comma in
1930 let args = make_list [key_list_item; val_list_item] in
1931 Concat [
1932 t env kw;
1933 transform_argish env ~allow_trailing:true left_a args right_a;
1935 | Syntax.MapArrayTypeSpecifier {
1936 map_array_keyword = kw;
1937 map_array_left_angle = left_a;
1938 map_array_key = key;
1939 map_array_comma = comma_kw;
1940 map_array_value = value;
1941 map_array_right_angle = right_a; } ->
1942 Concat [
1943 t env kw;
1944 let key_list_item = Syntax.make_list_item key comma_kw in
1945 let val_list_item = Syntax.make_list_item value (make_missing ()) in
1946 let args = make_list [key_list_item; val_list_item] in
1947 transform_argish env ~allow_trailing:false left_a args right_a;
1949 | Syntax.DictionaryTypeSpecifier {
1950 dictionary_type_keyword = kw;
1951 dictionary_type_left_angle = left_a;
1952 dictionary_type_members = members;
1953 dictionary_type_right_angle = right_a; } ->
1954 Concat [
1955 t env kw;
1956 transform_argish env left_a members right_a;
1958 | Syntax.ClosureTypeSpecifier {
1959 closure_outer_left_paren = outer_left_p;
1960 closure_coroutine = coroutine;
1961 closure_function_keyword = kw;
1962 closure_inner_left_paren = inner_left_p;
1963 closure_parameter_list = param_list;
1964 closure_inner_right_paren = inner_right_p;
1965 closure_colon = colon;
1966 closure_return_type = ret_type;
1967 closure_outer_right_paren = outer_right_p; } ->
1968 Concat [
1969 t env outer_left_p;
1970 t env coroutine;
1971 when_present coroutine space;
1972 t env kw;
1973 transform_argish_with_return_type env
1974 inner_left_p param_list inner_right_p colon ret_type;
1975 t env outer_right_p;
1977 | Syntax.ClosureParameterTypeSpecifier {
1978 closure_parameter_call_convention = callconv;
1979 closure_parameter_type = cp_type; } ->
1980 Concat [
1981 t env callconv;
1982 when_present callconv space;
1983 t env cp_type;
1985 | Syntax.ClassnameTypeSpecifier {
1986 classname_keyword = kw;
1987 classname_left_angle = left_a;
1988 classname_type = class_type;
1989 classname_trailing_comma = trailing_comma;
1990 classname_right_angle = right_a; } ->
1991 Concat [
1992 t env kw;
1993 transform_braced_item_with_trailer env
1994 left_a class_type trailing_comma right_a;
1996 | Syntax.FieldSpecifier {
1997 field_question = question;
1998 field_name = name;
1999 field_arrow = arrow_kw;
2000 field_type = field_type; } ->
2001 Concat [
2002 t env question;
2003 transform_mapish_entry env name arrow_kw field_type;
2005 | Syntax.FieldInitializer {
2006 field_initializer_name = name;
2007 field_initializer_arrow = arrow_kw;
2008 field_initializer_value = value; } ->
2009 transform_mapish_entry env name arrow_kw value
2010 | Syntax.ShapeTypeSpecifier {
2011 shape_type_keyword = shape_kw;
2012 shape_type_left_paren = left_p;
2013 shape_type_fields = type_fields;
2014 shape_type_ellipsis = ellipsis;
2015 shape_type_right_paren = right_p; } ->
2016 let fields = if Syntax.is_missing ellipsis
2017 then type_fields
2018 else
2019 let missing_separator = make_missing () in
2020 let ellipsis_list =
2021 [Syntax.make_list_item ellipsis missing_separator] in
2022 make_list (Syntax.children type_fields @ ellipsis_list) in
2023 transform_container_literal env shape_kw left_p fields right_p
2024 ~allow_trailing:(Syntax.is_missing ellipsis)
2025 | Syntax.ShapeExpression {
2026 shape_expression_keyword = shape_kw;
2027 shape_expression_left_paren = left_p;
2028 shape_expression_fields = fields;
2029 shape_expression_right_paren = right_p; } ->
2030 transform_container_literal env shape_kw left_p fields right_p
2031 | Syntax.TupleExpression {
2032 tuple_expression_keyword = kw;
2033 tuple_expression_left_paren = left_p;
2034 tuple_expression_items = items;
2035 tuple_expression_right_paren = right_p; } ->
2036 Concat [
2037 t env kw;
2038 transform_argish env left_p items right_p;
2040 | Syntax.TypeArguments {
2041 type_arguments_left_angle = left_a;
2042 type_arguments_types = type_list;
2043 type_arguments_right_angle = right_a; } ->
2044 transform_argish env left_a type_list right_a
2045 | Syntax.TypeParameters {
2046 type_parameters_left_angle = left_a;
2047 type_parameters_parameters = param_list;
2048 type_parameters_right_angle = right_a; } ->
2049 transform_argish env left_a param_list right_a
2050 | Syntax.TupleTypeSpecifier {
2051 tuple_left_paren = left_p;
2052 tuple_types = types;
2053 tuple_right_paren = right_p; } ->
2054 transform_argish env left_p types right_p
2055 | Syntax.TupleTypeExplicitSpecifier {
2056 tuple_type_keyword = kw;
2057 tuple_type_left_angle = left_a;
2058 tuple_type_types = types;
2059 tuple_type_right_angle = right_a; } ->
2060 Concat [
2061 t env kw;
2062 transform_argish env left_a types right_a
2064 | Syntax.DecoratedExpression {
2065 decorated_expression_decorator = op;
2066 decorated_expression_expression = expr; } ->
2067 Concat [
2068 t env op;
2069 begin
2070 match Syntax.syntax op with
2071 | Syntax.Token t when Token.kind t = TokenKind.Inout -> Space
2072 | _ -> Nothing
2073 end;
2074 t env expr;
2076 | Syntax.ErrorSyntax _ ->
2077 raise Hackfmt_error.InvalidSyntax
2079 and when_present node f =
2080 match Syntax.syntax node with
2081 | Syntax.Missing -> Nothing
2082 | _ -> f ()
2084 and transform_simple env node =
2085 Concat (List.map (Syntax.children node) (t env))
2087 and transform_simple_statement env node =
2088 Concat ((List.map (Syntax.children node) (t env)) @ [Newline])
2090 and braced_block_nest env ?(allow_collapse=true) open_b close_b nodes =
2091 let nodes = Concat nodes in
2092 match allow_collapse, has_printable_content nodes, Syntax.syntax open_b with
2093 | true, false, Syntax.Token ob
2094 when List.for_all (Token.trailing ob)
2095 (fun t -> Trivia.kind t <> TriviaKind.EndOfLine) ->
2096 Concat [
2097 t env open_b;
2098 t env close_b;
2100 | _ ->
2101 (* Remove the closing brace's leading trivia and handle it inside the
2102 * BlockNest, so that comments will be indented correctly. *)
2103 let leading, close_b = remove_leading_trivia close_b in
2104 Concat [
2105 t env open_b;
2106 Newline;
2107 BlockNest [
2108 nodes;
2109 transform_leading_trivia leading;
2110 Newline;
2112 t env close_b;
2115 and coloned_block_nest env open_colon close_token close_semi nodes =
2116 let leading, close_token = remove_leading_trivia close_token in
2117 let close_token, trailing = remove_trailing_trivia close_token in
2118 Concat [
2119 t env open_colon;
2120 Newline;
2121 BlockNest [
2122 Concat nodes;
2123 transform_leading_trivia leading;
2124 Newline;
2126 t env close_token;
2127 t env close_semi;
2128 transform_trailing_trivia trailing;
2131 and delimited_nest env
2132 ?(spaces=false)
2133 ?(split_when_children_split=true)
2134 ?(force_newlines=false)
2135 left_delim
2136 right_delim
2137 nodes
2139 let rule =
2140 match () with
2141 | _ when force_newlines -> Rule.Always
2142 | _ when split_when_children_split -> Rule.Parental
2143 | _ -> Rule.Simple Cost.Base
2145 Span [
2146 t env left_delim;
2147 WithRule (rule,
2148 nest env ~spaces right_delim nodes
2152 and nest env ?(spaces=false) right_delim nodes =
2153 (* Remove the right delimiter's leading trivia and handle it inside the
2154 * Nest, so that comments will be indented correctly. *)
2155 let leading, right_delim = remove_leading_trivia right_delim in
2156 let nested_contents =
2157 Nest [Concat nodes; transform_leading_trivia leading]
2159 let content_present = has_printable_content nested_contents in
2160 let maybe_split =
2161 match content_present, spaces with
2162 | false, _ -> Nothing
2163 | true, false -> Split
2164 | true, true -> space_split ()
2166 Concat [
2167 maybe_split;
2168 nested_contents;
2169 maybe_split;
2170 t env right_delim;
2173 and after_each_argument is_last =
2174 if is_last
2175 then Split
2176 else space_split ()
2178 and handle_lambda_body env node =
2179 match Syntax.syntax node with
2180 | Syntax.CompoundStatement {
2181 compound_left_brace;
2182 compound_statements;
2183 compound_right_brace; } ->
2184 handle_compound_statement env ~allow_collapse:true
2185 compound_left_brace compound_statements compound_right_brace;
2186 | Syntax.XHPExpression _ ->
2187 WithRule (Rule.Parental, Concat [
2188 Space;
2189 Split;
2190 Nest [t env node];
2192 | _ ->
2193 Concat [
2194 Space;
2195 SplitWith Cost.Base;
2196 Nest [t env node];
2199 and handle_possible_compound_statement env
2200 ?(space=true)
2201 ?(allow_collapse=false)
2202 node
2204 match Syntax.syntax node with
2205 | Syntax.CompoundStatement {
2206 compound_left_brace;
2207 compound_statements;
2208 compound_right_brace; } ->
2209 Concat [
2210 handle_compound_statement env
2211 ~allow_collapse
2212 compound_left_brace
2213 compound_statements
2214 compound_right_brace;
2215 if space then Space else Nothing;
2217 | Syntax.AlternateLoopStatement {
2218 alternate_loop_opening_colon;
2219 alternate_loop_statements;
2220 alternate_loop_closing_keyword;
2221 alternate_loop_closing_semicolon; } ->
2222 Concat [
2223 handle_alternate_loop_statement env
2224 alternate_loop_opening_colon
2225 alternate_loop_statements
2226 alternate_loop_closing_keyword
2227 alternate_loop_closing_semicolon;
2228 if space then Space else Nothing;
2230 | _ ->
2231 Concat [
2232 Newline;
2233 BlockNest [
2234 t env node
2238 and handle_compound_statement env
2239 ?(allow_collapse=false)
2240 left_b
2241 statements
2242 right_b
2244 Concat [
2245 Space;
2246 braced_block_nest env ~allow_collapse left_b right_b [
2247 handle_possible_list env statements
2251 and handle_alternate_loop_statement env
2252 open_colon
2253 statements
2254 close_keyword
2255 close_semi
2257 Concat [
2258 coloned_block_nest env open_colon close_keyword close_semi [
2259 handle_possible_list env statements
2264 * Special-case handling for lists of declarators, where we want the splits
2265 * between declarators to break if their children break, but we want a single
2266 * declarator to stay joined with the line preceding it if it fits, even when
2267 * its children break.
2269 and handle_declarator_list env declarators =
2270 match Syntax.syntax declarators with
2271 | Syntax.Missing -> Nothing
2272 | Syntax.SyntaxList [declarator] ->
2273 Nest [
2274 Space;
2275 (* Use an independent split, so we don't break just because a line break
2276 * occurs in the declarator. *)
2277 SplitWith Cost.Base;
2278 t env declarator;
2280 | Syntax.SyntaxList xs ->
2281 (* Use Rule.Parental to break each declarator onto its own line if any
2282 * line break occurs in a declarator, or if they can't all fit onto one
2283 * line. *)
2284 WithRule (Rule.Parental, Nest (List.map xs (fun declarator -> Concat [
2285 Space;
2286 Split;
2287 t env declarator;
2288 ])));
2289 | _ -> failwith "SyntaxList expected"
2291 and handle_list env
2292 ?(before_each=(fun () -> Nothing))
2293 ?(after_each=(fun _is_last -> Nothing))
2294 ?(handle_last=t env)
2295 list =
2296 let rec aux l = (
2297 match l with
2298 | hd :: [] ->
2299 Concat [
2300 before_each ();
2301 handle_last hd;
2302 after_each true;
2304 | hd :: tl ->
2305 Concat [
2306 before_each ();
2307 t env hd;
2308 after_each false;
2309 aux tl
2311 | [] -> Nothing
2312 ) in
2313 aux list
2315 and handle_possible_list env
2316 ?(before_each=(fun () -> Nothing))
2317 ?(after_each=(fun _is_last -> Nothing))
2318 ?(handle_last=t env)
2319 node =
2320 match Syntax.syntax node with
2321 | Syntax.Missing -> Nothing
2322 | Syntax.SyntaxList x ->
2323 handle_list env x ~before_each ~after_each ~handle_last
2324 | _ -> handle_list env [node] ~before_each ~after_each ~handle_last
2326 and handle_xhp_open_right_angle_token env attrs node =
2327 match Syntax.syntax node with
2328 | Syntax.Token token ->
2329 Concat [
2330 if Token.text token = "/>"
2331 then Concat [Space; when_present attrs split]
2332 else Nothing;
2333 t env node
2335 | _ -> failwith "expected xhp_open right_angle token"
2337 and handle_function_call_expression env
2338 receiver
2340 args
2343 match Syntax.syntax receiver with
2344 | Syntax.MemberSelectionExpression {
2345 member_object;
2346 member_operator;
2347 member_name; } ->
2348 handle_possible_chaining env
2349 (member_object, member_operator, member_name)
2350 (Some (lp, args, rp))
2351 | Syntax.SafeMemberSelectionExpression {
2352 safe_member_object;
2353 safe_member_operator;
2354 safe_member_name; } ->
2355 handle_possible_chaining env
2356 (safe_member_object, safe_member_operator, safe_member_name)
2357 (Some (lp, args, rp))
2358 | _ ->
2359 Concat [
2360 t env receiver;
2361 transform_argish env lp args rp
2364 and handle_function_call_with_type_arguments_expression env
2365 receiever
2366 tyargs
2368 args
2371 match Syntax.syntax receiever with
2372 | Syntax.MemberSelectionExpression {
2373 member_object;
2374 member_operator;
2375 member_name; } ->
2376 handle_possible_chaining env
2377 (member_object, member_operator, member_name)
2378 (Some (lp, args, rp))
2379 | Syntax.SafeMemberSelectionExpression {
2380 safe_member_object;
2381 safe_member_operator;
2382 safe_member_name; } ->
2383 handle_possible_chaining env
2384 (safe_member_object, safe_member_operator, safe_member_name)
2385 (Some (lp, args, rp))
2386 | _ ->
2387 Concat [
2388 t env receiever;
2389 t env tyargs;
2390 transform_argish env lp args rp
2393 and handle_possible_chaining env (obj, arrow1, member1) argish =
2394 let rec handle_chaining obj =
2395 let handle_mse_or_smse (obj, arrow, member) fun_paren_args =
2396 let (obj, l) = handle_chaining obj in
2397 obj, l @ [(arrow, member, fun_paren_args)]
2399 match Syntax.syntax obj with
2400 | Syntax.FunctionCallExpression {
2401 function_call_receiver = receiver;
2402 function_call_left_paren = lp;
2403 function_call_argument_list = args;
2404 function_call_right_paren = rp; } ->
2405 (match Syntax.syntax receiver with
2406 | Syntax.MemberSelectionExpression {
2407 member_object;
2408 member_operator;
2409 member_name; } ->
2410 handle_mse_or_smse
2411 (member_object, member_operator, member_name)
2412 (Some (lp, args, rp))
2413 | Syntax.SafeMemberSelectionExpression {
2414 safe_member_object;
2415 safe_member_operator;
2416 safe_member_name; } ->
2417 handle_mse_or_smse
2418 (safe_member_object, safe_member_operator, safe_member_name)
2419 (Some (lp, args, rp))
2420 | _ -> obj, []
2422 | Syntax.MemberSelectionExpression {
2423 member_object;
2424 member_operator;
2425 member_name; } ->
2426 handle_mse_or_smse
2427 (member_object, member_operator, member_name)
2428 None
2429 | Syntax.SafeMemberSelectionExpression {
2430 safe_member_object;
2431 safe_member_operator;
2432 safe_member_name; } ->
2433 handle_mse_or_smse
2434 (safe_member_object, safe_member_operator, safe_member_name)
2435 None
2436 | _ -> obj, []
2439 let (obj, chain_list) = handle_chaining obj in
2440 let chain_list = chain_list @ [(arrow1, member1, argish)] in
2442 let transform_chain (arrow, member, argish) =
2443 Concat [
2444 t env arrow;
2445 t env member;
2446 Option.value_map argish ~default:Nothing
2447 ~f:(fun (lp, args, rp) -> transform_argish env lp args rp);
2450 match chain_list with
2451 | hd :: [] ->
2452 Concat [
2453 Span [t env obj];
2454 if node_has_trailing_newline obj
2455 then Newline
2456 else SplitWith Cost.SimpleMemberSelection;
2457 Nest [transform_chain hd];
2459 | hd :: tl ->
2460 let rule_type = match hd with
2461 | (_, trailing, None)
2462 | (_, _, Some (_, _, trailing)) ->
2463 if node_has_trailing_newline trailing
2464 then Rule.Always
2465 else Rule.Parental
2467 Span [
2468 WithLazyRule (rule_type,
2469 Concat [
2470 t env obj;
2471 if node_has_trailing_newline obj
2472 then Newline
2473 else SplitWith Cost.Base;
2475 Concat [
2476 (* This needs to be nested separately due to the above SplitWith *)
2477 Nest [transform_chain hd];
2478 Nest (List.map tl ~f:(fun x -> Concat [Split; transform_chain x]))
2481 | _ -> failwith "Expected a chain of at least length 1"
2483 and transform_fn_decl_name env modifiers kw amp name type_params leftp =
2484 let mods = handle_possible_list env ~after_each:(fun _ -> Space) modifiers in
2486 mods;
2487 t env kw;
2488 Space;
2489 t env amp;
2490 t env name;
2491 t env type_params;
2492 t env leftp;
2493 Split;
2496 and transform_fn_decl_args env params rightp colon ret_type where =
2497 (* It is a syntax error to follow a variadic parameter with a trailing
2498 * comma, so suppress trailing commas in that case. *)
2499 let allow_trailing =
2500 match Syntax.syntax params with
2501 | Syntax.SyntaxList params ->
2502 let last_param =
2503 match Syntax.syntax (List.last_exn params) with
2504 | Syntax.ListItem { list_item; _ } -> list_item
2505 | _ -> failwith "Expected ListItem"
2507 begin
2508 match Syntax.syntax last_param with
2509 | Syntax.VariadicParameter _
2510 | Syntax.(ParameterDeclaration {
2511 parameter_name = { syntax = DecoratedExpression {
2512 decorated_expression_decorator = {
2513 syntax = Token { Token.kind = TokenKind.DotDotDot; _ }; _
2514 }; _
2515 }; _ }; _
2516 }) ->
2517 false
2518 | _ -> true
2520 | _ -> true
2522 WithRule (Rule.Parental, Concat [
2523 transform_possible_comma_list env ~allow_trailing params rightp;
2524 t env colon;
2525 when_present colon space;
2526 t env ret_type;
2527 when_present where space;
2528 t env where;
2531 and transform_argish_with_return_type env left_p params right_p colon ret_type =
2532 Concat [
2533 t env left_p;
2534 when_present params split;
2535 WithRule (Rule.Parental, Span [
2536 Span [ transform_possible_comma_list env params right_p ];
2537 t env colon;
2538 when_present colon space;
2539 t env ret_type;
2543 and transform_argish env
2544 ?(allow_trailing=true) ?(force_newlines=false) ?(spaces=false)
2545 left_p arg_list right_p =
2546 (* When there is only one argument, with no surrounding whitespace in the
2547 * original source, allow that style to be preserved even when there are
2548 * line breaks within the argument (normally these would force the splits
2549 * around the argument to break). *)
2550 let split_when_children_split =
2551 match spaces, Syntax.syntax arg_list with
2552 | false, Syntax.SyntaxList [x] ->
2553 let has_surrounding_whitespace =
2554 not (
2555 List.is_empty (Syntax.trailing_trivia left_p) &&
2556 List.is_empty (Syntax.trailing_trivia x)
2559 let item =
2560 match Syntax.syntax x with
2561 | Syntax.ListItem { list_item; _ } -> list_item
2562 | _ -> failwith "Expected ListItem"
2564 (* Blacklist constructs which look ugly when we try to preserve the
2565 * lack-of-whitespace style. *)
2566 (match Syntax.syntax item with
2567 | Syntax.(LambdaExpression
2568 { lambda_body = { syntax = CompoundStatement _; _ }; _ }) ->
2569 has_surrounding_whitespace
2570 | Syntax.FunctionCallExpression { function_call_receiver; _ } ->
2571 Syntax.is_member_selection_expression function_call_receiver ||
2572 has_surrounding_whitespace
2573 | Syntax.ConditionalExpression _
2574 | Syntax.BinaryExpression _
2575 | Syntax.MemberSelectionExpression _
2576 | Syntax.FieldSpecifier _
2577 | Syntax.FieldInitializer _
2578 | Syntax.ElementInitializer _
2579 | Syntax.LambdaExpression _
2580 -> true
2581 | _ -> has_surrounding_whitespace
2583 | _ -> true
2585 delimited_nest env
2586 ~spaces
2587 ~split_when_children_split
2588 ~force_newlines
2589 left_p
2590 right_p
2591 [transform_arg_list env ~allow_trailing arg_list]
2593 and transform_braced_item env left_p item right_p =
2594 delimited_nest env left_p right_p [t env item]
2596 and transform_trailing_comma env ~allow_trailing item comma =
2597 (* PHP does not permit trailing commas in function calls. Rather than try to
2598 * account for where PHP's parser permits trailing commas, we just never add
2599 * them in PHP files. *)
2600 let allow_trailing = allow_trailing && env.Env.add_trailing_commas in
2601 match Syntax.syntax comma with
2602 | Syntax.Token tok ->
2603 Concat [
2604 t env item;
2605 transform_leading_trivia (Token.leading tok);
2606 if allow_trailing then TrailingComma true else Nothing;
2607 Ignore (Token.text tok, Token.width tok);
2608 transform_trailing_trivia (Token.trailing tok);
2610 | Syntax.Missing ->
2611 let item, item_trailing = remove_trailing_trivia item in
2612 Concat [
2613 t env item;
2614 if allow_trailing then TrailingComma false else Nothing;
2615 transform_trailing_trivia item_trailing;
2617 | _ -> failwith "Expected Token"
2619 and transform_braced_item_with_trailer env left_p item comma right_p =
2620 delimited_nest env left_p right_p
2621 (* TODO: turn allow_trailing:true when HHVM versions that don't support
2622 trailing commas in all these places reach end-of-life. *)
2623 [transform_trailing_comma env ~allow_trailing:false item comma]
2625 and transform_arg_list env ?(allow_trailing=true) items =
2626 handle_possible_list env items
2627 ~after_each:after_each_argument
2628 ~handle_last:(transform_last_arg env ~allow_trailing)
2630 and transform_possible_comma_list env ?(allow_trailing=true) ?(spaces=false)
2631 items right_p =
2632 nest env ~spaces right_p [
2633 transform_arg_list env ~allow_trailing items
2636 and transform_container_literal env
2637 ?(spaces=false) ?allow_trailing kw left_p members right_p =
2638 let force_newlines = node_has_trailing_newline left_p in
2639 Concat [
2640 t env kw;
2641 if spaces then Space else Nothing;
2642 transform_argish env
2643 ~spaces ~force_newlines ?allow_trailing left_p members right_p;
2646 and remove_leading_trivia node =
2647 match Syntax.leading_token node with
2648 | None -> [], node
2649 | Some leading_token ->
2650 let rewritten_node = Rewriter.rewrite_pre (fun rewrite_node ->
2651 match Syntax.syntax rewrite_node with
2652 | Syntax.Token t when t == leading_token ->
2653 Rewriter.Replace
2654 (Syntax.make_token {t with Token.leading = []})
2655 | _ -> Rewriter.Keep
2656 ) node in
2657 Token.leading leading_token, rewritten_node
2659 and remove_trailing_trivia node =
2660 match Syntax.trailing_token node with
2661 | None -> node, []
2662 | Some trailing_token ->
2663 let rewritten_node = Rewriter.rewrite_pre (fun rewrite_node ->
2664 match Syntax.syntax rewrite_node with
2665 | Syntax.Token t when t == trailing_token ->
2666 Rewriter.Replace
2667 (Syntax.make_token {t with Token.trailing = []})
2668 | _ -> Rewriter.Keep
2669 ) node in
2670 rewritten_node, Token.trailing trailing_token
2672 and transform_last_arg env ~allow_trailing node =
2673 match Syntax.syntax node with
2674 | Syntax.ListItem {
2675 list_item = item;
2676 list_separator = separator; } ->
2677 transform_trailing_comma env ~allow_trailing item separator
2678 | _ -> failwith "Expected ListItem"
2681 and transform_mapish_entry env key arrow value =
2682 Concat [
2683 t env key;
2684 Space;
2685 t env arrow;
2686 Space;
2687 SplitWith Cost.Base;
2688 Nest [t env value];
2691 and transform_keyword_expression_statement env kw expr semi =
2692 Concat [
2693 t env kw;
2694 when_present expr (fun () -> Concat [
2695 Space;
2696 SplitWith Cost.Base;
2697 Nest [t env expr];
2699 t env semi;
2700 Newline;
2703 and transform_keyword_expr_list_statement env kw expr_list semi =
2704 Concat [
2705 t env kw;
2706 handle_declarator_list env expr_list;
2707 t env semi;
2708 Newline;
2711 and transform_condition env left_p condition right_p =
2712 Concat [
2713 t env left_p;
2714 Split;
2715 WithRule (Rule.Parental, Concat [
2716 Nest [t env condition];
2717 Split;
2718 t env right_p;
2722 and transform_binary_expression env ~is_nested (left, operator, right) =
2723 let get_operator_type op =
2724 match Syntax.syntax op with
2725 | Syntax.Token t -> Full_fidelity_operator.trailing_from_token
2726 (Token.kind t)
2727 | _ -> failwith "Operator should always be a token"
2729 let is_concat op =
2730 get_operator_type op = Full_fidelity_operator.ConcatenationOperator in
2731 let operator_has_surrounding_spaces op = not (is_concat op) in
2732 let operator_is_leading op =
2733 get_operator_type op = Full_fidelity_operator.PipeOperator in
2734 let operator_preserves_newlines op =
2735 get_operator_type op = Full_fidelity_operator.PipeOperator in
2737 let operator_t = get_operator_type operator in
2739 if Full_fidelity_operator.is_comparison operator_t then
2740 WithLazyRule (Rule.Parental,
2741 Concat [
2742 t env left;
2743 Space;
2744 t env operator;
2746 Concat [
2747 Space;
2748 Split;
2749 Nest [t env right];
2751 else if Full_fidelity_operator.is_assignment operator_t then
2752 Concat [
2753 t env left;
2754 Space;
2755 t env operator;
2756 Space;
2757 SplitWith Cost.NoCost;
2758 Nest [t env right];
2760 else
2761 Concat [
2762 let precedence = Full_fidelity_operator.precedence operator_t in
2764 let rec flatten_expression expr =
2765 match Syntax.syntax expr with
2766 | Syntax.BinaryExpression {
2767 binary_left_operand = left;
2768 binary_operator = operator;
2769 binary_right_operand = right; } ->
2770 let operator_t = get_operator_type operator in
2771 let op_precedence = Full_fidelity_operator.precedence operator_t in
2772 if (op_precedence = precedence) then
2773 (flatten_expression left) @ (operator :: flatten_expression right)
2774 else [expr]
2775 | _ -> [expr]
2778 let transform_operand operand =
2779 match Syntax.syntax operand with
2780 | Syntax.BinaryExpression {
2781 binary_left_operand;
2782 binary_operator;
2783 binary_right_operand; } ->
2784 transform_binary_expression env ~is_nested:true
2785 (binary_left_operand, binary_operator, binary_right_operand)
2786 | _ -> t env operand
2789 let binary_expression_syntax_list =
2790 flatten_expression (Syntax.make_binary_expression left operator right)
2792 match binary_expression_syntax_list with
2793 | hd :: tl ->
2794 WithLazyRule (Rule.Parental,
2795 transform_operand hd,
2796 let expression =
2797 let last_operand = ref hd in
2798 let last_op = ref (List.hd_exn tl) in
2799 List.mapi tl ~f:(fun i x ->
2800 if i mod 2 = 0 then begin
2801 let op = x in
2802 last_op := op;
2803 let op_has_spaces = operator_has_surrounding_spaces op in
2804 let op_is_leading = operator_is_leading op in
2805 let newline_before_op =
2806 operator_preserves_newlines op &&
2807 node_has_trailing_newline !last_operand
2809 Concat [
2810 if newline_before_op then Newline
2811 else
2812 if op_is_leading
2813 then (if op_has_spaces then space_split () else Split)
2814 else (if op_has_spaces then Space else Nothing);
2815 if is_concat op
2816 then ConcatOperator (t env op)
2817 else t env op;
2820 else begin
2821 let operand = x in
2822 last_operand := x;
2823 let op_has_spaces =
2824 operator_has_surrounding_spaces !last_op
2826 let op_is_leading = operator_is_leading !last_op in
2827 Concat [
2828 if op_is_leading
2829 then (if op_has_spaces then Space else Nothing)
2830 else (if op_has_spaces then space_split () else Split);
2831 transform_operand operand;
2836 if is_nested
2837 then Nest expression
2838 else ConditionalNest expression)
2839 | _ ->
2840 failwith "Expected non empty list of binary expression pieces"
2843 (* True if the trivia list contains WhiteSpace trivia.
2844 * Note that WhiteSpace includes spaces and tabs, but not newlines. *)
2845 and has_whitespace trivia_list =
2846 List.exists trivia_list
2847 ~f:(fun trivia -> Trivia.kind trivia = TriviaKind.WhiteSpace)
2849 (* True if the trivia list contains EndOfLine trivia. *)
2850 and has_newline trivia_list =
2851 List.exists trivia_list
2852 ~f:(fun trivia -> Trivia.kind trivia = TriviaKind.EndOfLine)
2854 and is_invisible trivia =
2855 match Trivia.kind trivia with
2856 | TriviaKind.WhiteSpace | TriviaKind.EndOfLine -> true
2857 | _ -> false
2859 (* True if the trivia list contains any "invisible" trivia, meaning spaces,
2860 * tabs, or newlines. *)
2861 and has_invisibles trivia_list =
2862 List.exists trivia_list ~f:is_invisible
2864 and transform_leading_trivia t = transform_trivia ~is_leading:true t
2865 and transform_trailing_trivia t = transform_trivia ~is_leading:false t
2867 and transform_trivia ~is_leading trivia =
2868 let new_line_regex = Str.regexp "\n" in
2869 let indent = ref 0 in
2870 let currently_leading = ref is_leading in
2871 let leading_invisibles = ref [] in
2872 let last_comment = ref None in
2873 let last_comment_was_delimited = ref false in
2874 let newline_followed_last_comment = ref false in
2875 let whitespace_followed_last_comment = ref false in
2876 let trailing_invisibles = ref [] in
2877 let comments = ref [] in
2878 let make_comment _ =
2879 if Option.is_some !last_comment then begin
2880 newline_followed_last_comment := has_newline !trailing_invisibles;
2881 whitespace_followed_last_comment := has_whitespace !trailing_invisibles;
2882 end;
2883 comments :=
2884 (Concat [
2885 transform_leading_invisibles (List.rev !leading_invisibles);
2886 Option.value !last_comment ~default:Nothing;
2887 ignore_trailing_invisibles (List.rev !trailing_invisibles);
2888 if !last_comment_was_delimited && !whitespace_followed_last_comment
2889 then Space
2890 else if !newline_followed_last_comment
2891 then Newline
2892 else Nothing
2894 :: !comments;
2895 last_comment := None;
2896 leading_invisibles := [];
2897 trailing_invisibles := [];
2899 List.iter trivia ~f:(fun triv ->
2900 match Trivia.kind triv with
2901 | TriviaKind.AfterHaltCompiler ->
2902 (* ignore content that appears after __halt_compiler *)
2904 | TriviaKind.ExtraTokenError
2905 | TriviaKind.UnsafeExpression
2906 | TriviaKind.FixMe
2907 | TriviaKind.IgnoreError
2908 | TriviaKind.DelimitedComment ->
2909 let preceded_by_whitespace =
2910 if !currently_leading
2911 then has_whitespace !leading_invisibles
2912 else has_whitespace !trailing_invisibles
2914 make_comment ();
2915 let delimited_lines = Str.split new_line_regex (Trivia.text triv) in
2916 let map_tail str =
2917 let prefix_space_count str =
2918 let len = String.length str in
2919 let rec aux i =
2920 if i = len || str.[i] <> ' '
2921 then 0
2922 else 1 + (aux (i + 1))
2924 aux 0
2926 (* If we're dealing with trailing trivia, then we don't have a good
2927 signal for the indent level, so we just cut all leading spaces.
2928 Otherwise, we cut a number of spaces equal to the indent before
2929 the delimited comment opener. *)
2930 let start_index = if is_leading
2931 then min !indent (prefix_space_count str)
2932 else prefix_space_count str
2934 let len = String.length str - start_index in
2935 let dc =
2936 Trivia.create_delimited_comment @@ String.sub str start_index len
2938 Concat [
2939 Ignore ("\n", 1);
2940 Newline;
2941 Ignore ((String.make start_index ' '), start_index);
2942 Comment ((Trivia.text dc), (Trivia.width dc));
2946 let hd = List.hd_exn delimited_lines in
2947 let tl = List.tl_exn delimited_lines in
2948 let hd = Comment (hd, (String.length hd)) in
2950 let should_break =
2951 match Trivia.kind triv with
2952 | TriviaKind.UnsafeExpression
2953 | TriviaKind.FixMe
2954 | TriviaKind.IgnoreError
2955 -> false
2956 | _ -> !currently_leading
2959 last_comment := Some (Concat [
2960 if should_break then Newline
2961 else if preceded_by_whitespace then Space
2962 else Nothing;
2963 Concat (hd :: List.map tl ~f:map_tail);
2965 last_comment_was_delimited := true;
2966 currently_leading := false;
2967 | TriviaKind.Unsafe
2968 | TriviaKind.FallThrough
2969 | TriviaKind.SingleLineComment ->
2970 make_comment ();
2971 last_comment := Some (Concat [
2972 if !currently_leading then Newline else Space;
2973 SingleLineComment ((Trivia.text triv), (Trivia.width triv));
2975 last_comment_was_delimited := false;
2976 currently_leading := false;
2977 | TriviaKind.EndOfLine ->
2978 indent := 0;
2979 if !currently_leading then
2980 leading_invisibles := triv :: !leading_invisibles
2981 else begin
2982 trailing_invisibles := triv :: !trailing_invisibles;
2983 make_comment ();
2984 end;
2985 currently_leading := true;
2986 | TriviaKind.WhiteSpace ->
2987 if !currently_leading then begin
2988 indent := Trivia.width triv;
2989 leading_invisibles := triv :: !leading_invisibles
2991 else
2992 trailing_invisibles := triv :: !trailing_invisibles;
2994 if List.is_empty !comments then begin
2995 if is_leading
2996 then transform_leading_invisibles trivia
2997 else ignore_trailing_invisibles trivia
2999 else begin
3000 make_comment ();
3001 Concat (List.rev !comments)
3004 and _MAX_CONSECUTIVE_BLANK_LINES = 2
3006 and transform_leading_invisibles triv =
3007 let newlines = ref 0 in
3008 Concat (List.map triv ~f:(fun t ->
3009 let ignored = Ignore ((Trivia.text t), (Trivia.width t)) in
3010 match Trivia.kind t with
3011 | TriviaKind.EndOfLine ->
3012 newlines := !newlines + 1;
3013 Concat [
3014 ignored;
3015 if !newlines <= _MAX_CONSECUTIVE_BLANK_LINES
3016 then BlankLine
3017 else Nothing
3019 | _ -> ignored;
3022 and ignore_trailing_invisibles triv =
3023 Concat
3024 (List.map triv ~f:(fun t -> Ignore ((Trivia.text t), (Trivia.width t))))
3026 and transform_xhp_leading_trivia triv =
3027 let (up_to_first_newline, after_newline, _) =
3028 List.fold triv
3029 ~init:([], [], false)
3030 ~f:begin fun (upto, after, seen) t ->
3031 if seen then upto, t :: after, true
3032 else t :: upto, after, Trivia.kind t = TriviaKind.EndOfLine
3035 Concat [
3036 ignore_trailing_invisibles up_to_first_newline;
3037 transform_leading_invisibles after_newline;
3040 and node_has_trailing_newline node =
3041 let trivia = Syntax.trailing_trivia node in
3042 List.exists trivia ~f:(fun x -> Trivia.kind x = TriviaKind.EndOfLine)
3044 let transform (env: Env.t) (node: Syntax.t) : Doc.t =
3045 t env node