@@ -17,8 +17,8 @@ defmodule Code.Formatter do
1717 # Operators that do not have newline between operands (as well as => and keywords)
1818 @ no_newline_binary_operators [ :\\ , :in ]
1919
20- # Left associative operators that start on the next line in case of breaks
21- @ left_new_line_before_binary_operators [ :|> , :~>> , :<<~ , :~> , :<~ , :<~> , :<|> ]
20+ # Left associative operators that start on the next line in case of breaks (always pipes)
21+ @ pipeline_operators [ :|> , :~>> , :<<~ , :~> , :<~ , :<~> , :<|> ]
2222
2323 # Right associative operators that start on the next line in case of breaks
2424 @ right_new_line_before_binary_operators [ :| , :when ]
@@ -325,12 +325,12 @@ defmodule Code.Formatter do
325325
326326 # Special AST nodes from compiler feedback.
327327
328- defp quoted_to_algebra ( { :special , :clause_args , [ args ] } , _context , state ) do
328+ defp quoted_to_algebra ( { { :special , :clause_args } , _meta , [ args ] } , _context , state ) do
329329 { doc , state } = clause_args_to_algebra ( args , state )
330330 { group ( doc ) , state }
331331 end
332332
333- defp quoted_to_algebra ( { :special , :bitstring_segment , [ arg , last ] } , _context , state ) do
333+ defp quoted_to_algebra ( { { :special , :bitstring_segment } , _meta , [ arg , last ] } , _context , state ) do
334334 bitstring_segment_to_algebra ( { arg , - 1 } , state , last )
335335 end
336336
@@ -670,23 +670,75 @@ defmodule Code.Formatter do
670670 # strict or flex mode around.
671671 defp binary_op_to_algebra ( op , op_string , meta , left_arg , right_arg , context , state ) do
672672 % { operand_nesting: nesting } = state
673- binary_op_to_algebra ( op , op_string , meta , left_arg , right_arg , context , state , nil , nesting )
673+ binary_op_to_algebra ( op , op_string , meta , left_arg , right_arg , context , state , nesting )
674674 end
675675
676- defp binary_op_to_algebra (
677- op ,
678- op_string ,
679- meta ,
680- left_arg ,
681- right_arg ,
682- context ,
683- state ,
684- parent_info ,
685- nesting
686- ) do
676+ defp binary_op_to_algebra ( op , op_string , meta , left_arg , right_arg , context , state , _nesting )
677+ when op in @ right_new_line_before_binary_operators do
687678 op_info = Code.Identifier . binary_op ( op )
688- left_context = force_many_args_or_operand ( context , :parens_arg )
689- right_context = force_many_args_or_operand ( context , :operand )
679+ op_string = op_string <> " "
680+ left_context = left_op_context ( context )
681+ right_context = right_op_context ( context )
682+
683+ min_line =
684+ case left_arg do
685+ { _ , left_meta , _ } -> line ( left_meta )
686+ _ -> line ( meta )
687+ end
688+
689+ { operands , max_line } =
690+ unwrap_right ( right_arg , op , meta , right_context , [ { { :root , left_context } , left_arg } ] )
691+
692+ operand_to_algebra = fn
693+ { { :root , context } , arg } , _args , newlines , state ->
694+ { doc , state } = binary_operand_to_algebra ( arg , context , state , op , op_info , :left , 2 )
695+ { doc , @ empty , newlines , state }
696+
697+ { { kind , context } , arg } , _args , newlines , state ->
698+ { doc , state } = binary_operand_to_algebra ( arg , context , state , op , op_info , kind , 0 )
699+ doc = doc |> nest_by_length ( op_string ) |> force_keyword ( arg )
700+ { concat ( op_string , doc ) , @ empty , newlines , state }
701+ end
702+
703+ operand_to_algebra_with_comments (
704+ operands ,
705+ meta ,
706+ min_line ,
707+ max_line ,
708+ state ,
709+ operand_to_algebra
710+ )
711+ end
712+
713+ defp binary_op_to_algebra ( op , _ , meta , left_arg , right_arg , context , state , _nesting )
714+ when op in @ pipeline_operators do
715+ op_info = Code.Identifier . binary_op ( op )
716+ left_context = left_op_context ( context )
717+ right_context = right_op_context ( context )
718+ max_line = line ( meta )
719+
720+ { pipes , min_line } =
721+ unwrap_pipes ( left_arg , meta , left_context , [ { { op , right_context } , right_arg } ] )
722+
723+ operand_to_algebra = fn
724+ { { :root , context } , arg } , _args , newlines , state ->
725+ { doc , state } = binary_operand_to_algebra ( arg , context , state , op , op_info , :left , 2 )
726+ { doc , @ empty , newlines , state }
727+
728+ { { op , context } , arg } , _args , newlines , state ->
729+ op_info = Code.Identifier . binary_op ( op )
730+ op_string = Atom . to_string ( op ) <> " "
731+ { doc , state } = binary_operand_to_algebra ( arg , context , state , op , op_info , :right , 0 )
732+ { concat ( op_string , doc ) , @ empty , newlines , state }
733+ end
734+
735+ operand_to_algebra_with_comments ( pipes , meta , min_line , max_line , state , operand_to_algebra )
736+ end
737+
738+ defp binary_op_to_algebra ( op , op_string , meta , left_arg , right_arg , context , state , nesting ) do
739+ op_info = Code.Identifier . binary_op ( op )
740+ left_context = left_op_context ( context )
741+ right_context = right_op_context ( context )
690742
691743 { left , state } =
692744 binary_operand_to_algebra ( left_arg , left_context , state , op , op_info , :left , 2 )
@@ -703,39 +755,6 @@ defmodule Code.Formatter do
703755 op_string = " " <> op_string <> " "
704756 concat ( concat ( group ( left ) , op_string ) , group ( right ) )
705757
706- op in @ left_new_line_before_binary_operators ->
707- op_string = op_string <> " "
708-
709- # If the parent is of the same type (computed via same precedence),
710- # we cannot group the left side yet.
711- left = if op_info == parent_info , do: left , else: group ( left )
712-
713- doc = glue ( left , concat ( op_string , group ( right ) ) )
714- if Keyword . get ( meta , :eol , false ) , do: force_unfit ( doc ) , else: doc
715-
716- op in @ right_new_line_before_binary_operators ->
717- op_string = op_string <> " "
718-
719- # If the parent is of the same type (computed via same precedence),
720- # we need to nest the left side because of the associativity.
721- left =
722- if op_info == parent_info do
723- nest_by_length ( left , op_string )
724- else
725- group ( left )
726- end
727-
728- # If the right side is of the same type, we will keep recursing
729- # and do the nesting on the left side later on (as written above).
730- right =
731- case right_arg do
732- { ^ op , _ , [ _ , _ ] } -> right
733- _ -> right |> nest_by_length ( op_string ) |> force_keyword ( right_arg ) |> group ( )
734- end
735-
736- doc = glue ( left , concat ( op_string , right ) )
737- if Keyword . get ( meta , :eol , false ) , do: force_unfit ( doc ) , else: doc
738-
739758 true ->
740759 next_break_fits? =
741760 op in @ next_break_fits_operators and next_break_fits? ( right_arg , state ) and
@@ -780,17 +799,7 @@ defmodule Code.Formatter do
780799 # the correct side, we respect the nesting rule to avoid multiple
781800 # nestings. This only applies for left associativity or same operator.
782801 parent_prec == prec and parent_assoc == side and ( side == :left or op == parent_op ) ->
783- binary_op_to_algebra (
784- op ,
785- op_string ,
786- meta ,
787- left ,
788- right ,
789- context ,
790- state ,
791- parent_info ,
792- nesting
793- )
802+ binary_op_to_algebra ( op , op_string , meta , left , right , context , state , nesting )
794803
795804 # If the parent requires parens or the precedence is inverted or
796805 # it is in the wrong side, then we *need* parenthesis.
@@ -799,13 +808,13 @@ defmodule Code.Formatter do
799808 parent_op in @ required_parens_logical_binary_operands ) or parent_prec > prec or
800809 ( parent_prec == prec and parent_assoc != side ) ->
801810 { operand , state } =
802- binary_op_to_algebra ( op , op_string , meta , left , right , context , state , parent_info , 2 )
811+ binary_op_to_algebra ( op , op_string , meta , left , right , context , state , 2 )
803812
804813 { wrap_in_parens ( operand ) , state }
805814
806815 # Otherwise, we rely on precedence but also nest.
807816 true ->
808- binary_op_to_algebra ( op , op_string , meta , left , right , context , state , parent_info , 2 )
817+ binary_op_to_algebra ( op , op_string , meta , left , right , context , state , 2 )
809818 end
810819 else
811820 { :& , _ , [ arg ] } when not is_integer ( arg ) and side == :left ->
@@ -817,6 +826,45 @@ defmodule Code.Formatter do
817826 end
818827 end
819828
829+ defp unwrap_pipes ( { op , meta , [ left , right ] } , _meta , context , acc )
830+ when op in @ pipeline_operators do
831+ left_context = left_op_context ( context )
832+ right_context = right_op_context ( context )
833+ unwrap_pipes ( left , meta , left_context , [ { { op , right_context } , right } | acc ] )
834+ end
835+
836+ defp unwrap_pipes ( left , meta , context , acc ) do
837+ min_line =
838+ case left do
839+ { _ , meta , _ } -> line ( meta )
840+ _ -> line ( meta )
841+ end
842+
843+ { [ { { :root , context } , left } | acc ] , min_line }
844+ end
845+
846+ defp unwrap_right ( { op , meta , [ left , right ] } , op , _meta , context , acc ) do
847+ left_context = left_op_context ( context )
848+ right_context = right_op_context ( context )
849+ unwrap_right ( right , op , meta , right_context , [ { { :left , left_context } , left } | acc ] )
850+ end
851+
852+ defp unwrap_right ( right , _op , meta , context , acc ) do
853+ acc = [ { { :right , context } , right } | acc ]
854+ { Enum . reverse ( acc ) , line ( meta ) }
855+ end
856+
857+ defp operand_to_algebra_with_comments ( operands , meta , min_line , max_line , state , fun ) do
858+ { docs , comments? , state } =
859+ quoted_to_algebra_with_comments ( operands , [ ] , min_line , max_line , 1 , state , fun )
860+
861+ if comments? or Keyword . get ( meta , :eol , false ) do
862+ { docs |> Enum . reduce ( & line ( & 2 , & 1 ) ) |> force_unfit ( ) , state }
863+ else
864+ { docs |> Enum . reduce ( & glue ( & 2 , & 1 ) ) , state }
865+ end
866+ end
867+
820868 ## Module attributes
821869
822870 # @Foo
@@ -1278,7 +1326,7 @@ defmodule Code.Formatter do
12781326 end
12791327
12801328 defp bitstring_segment_to_algebra ( { { :<- , meta , [ left , right ] } , i } , state , last ) do
1281- left = { :special , :bitstring_segment , [ left , last ] }
1329+ left = { { :special , :bitstring_segment } , meta , [ left , last ] }
12821330 { doc , state } = quoted_to_algebra ( { :<- , meta , [ left , right ] } , :parens_arg , state )
12831331 { bitstring_wrap_parens ( doc , i , last ) , state }
12841332 end
@@ -1709,7 +1757,7 @@ defmodule Code.Formatter do
17091757 # fn a, b, c when d -> e end
17101758 defp clause_args_to_algebra ( [ { :when , meta , args } ] , state ) do
17111759 { args , right } = split_last ( args )
1712- left = { :special , :clause_args , [ args ] }
1760+ left = { { :special , :clause_args } , meta , [ args ] }
17131761 binary_op_to_algebra ( :when , "when" , meta , left , right , :no_parens_arg , state )
17141762 end
17151763
@@ -1839,6 +1887,9 @@ defmodule Code.Formatter do
18391887
18401888 ## Quoted helpers
18411889
1890+ defp left_op_context ( context ) , do: force_many_args_or_operand ( context , :parens_arg )
1891+ defp right_op_context ( context ) , do: force_many_args_or_operand ( context , :operand )
1892+
18421893 defp force_many_args_or_operand ( :no_parens_one_arg , _choice ) , do: :no_parens_arg
18431894 defp force_many_args_or_operand ( :parens_one_arg , _choice ) , do: :parens_arg
18441895 defp force_many_args_or_operand ( :no_parens_arg , _choice ) , do: :no_parens_arg
@@ -2000,20 +2051,23 @@ defmodule Code.Formatter do
20002051 )
20012052 end
20022053
2054+ # A literal list is a keyword or (... -> ...)
20032055 defp last_arg_to_keyword ( [ _ | _ ] = arg , _list_to_keyword? ) do
20042056 { keyword? ( arg ) , arg }
20052057 end
20062058
2059+ # This is a list of tuples, it can be converted to keywords.
20072060 defp last_arg_to_keyword ( { :__block__ , _ , [ [ _ | _ ] = arg ] } = block , true ) do
20082061 if keyword? ( arg ) , do: { true , arg } , else: { false , block }
20092062 end
20102063
2064+ # Otherwise we don't have a keyword.
20112065 defp last_arg_to_keyword ( arg , _list_to_keyword? ) do
20122066 { false , arg }
20132067 end
20142068
20152069 defp force_keyword? ( keyword ) do
2016- match? ( [ _ , _ | _ ] , keyword ) and force_keyword? ( keyword , MapSet . new ( ) )
2070+ match? ( [ { _ , _ } , _ | _ ] , keyword ) and force_keyword? ( keyword , MapSet . new ( ) )
20172071 end
20182072
20192073 defp force_keyword? ( [ { { _ , meta , _ } , _ } | keyword ] , lines ) do
0 commit comments