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