1defmodule Code.Formatter do
2  @moduledoc false
3  import Inspect.Algebra, except: [format: 2, surround: 3, surround: 4]
4
5  @double_quote "\""
6  @double_heredoc "\"\"\""
7  @single_quote "'"
8  @single_heredoc "'''"
9  @newlines 2
10  @min_line 0
11  @max_line 9_999_999
12  @empty empty()
13  @ampersand_prec Code.Identifier.unary_op(:&) |> elem(1)
14
15  # Operators that are composed of multiple binary operators
16  @multi_binary_operators [:"..//"]
17
18  # Operators that do not have space between operands
19  @no_space_binary_operators [:.., :"//"]
20
21  # Operators that do not have newline between operands (as well as => and keywords)
22  @no_newline_binary_operators [:\\, :in]
23
24  # Left associative operators that start on the next line in case of breaks (always pipes)
25  @pipeline_operators [:|>, :~>>, :<<~, :~>, :<~, :<~>, :<|>]
26
27  # Right associative operators that start on the next line in case of breaks
28  @right_new_line_before_binary_operators [:|, :when]
29
30  # Operators that are logical cannot be mixed without parens
31  @required_parens_logical_binary_operands [:||, :|||, :or, :&&, :&&&, :and]
32
33  # Operators with next break fits. = and :: do not consider new lines though
34  @next_break_fits_operators [:<-, :==, :!=, :=~, :===, :!==, :<, :>, :<=, :>=, :=, :"::"]
35
36  # Operators that always require parens on operands when they are the parent
37  @required_parens_on_binary_operands [
38    :|>,
39    :<<<,
40    :>>>,
41    :<~,
42    :~>,
43    :<<~,
44    :~>>,
45    :<~>,
46    :<|>,
47    :^^^,
48    :+++,
49    :---,
50    :in,
51    :++,
52    :--,
53    :..,
54    :<>
55  ]
56
57  @locals_without_parens [
58    # Special forms
59    alias: 1,
60    alias: 2,
61    case: 2,
62    cond: 1,
63    for: :*,
64    import: 1,
65    import: 2,
66    quote: 1,
67    quote: 2,
68    receive: 1,
69    require: 1,
70    require: 2,
71    try: 1,
72    with: :*,
73
74    # Kernel
75    def: 1,
76    def: 2,
77    defp: 1,
78    defp: 2,
79    defguard: 1,
80    defguardp: 1,
81    defmacro: 1,
82    defmacro: 2,
83    defmacrop: 1,
84    defmacrop: 2,
85    defmodule: 2,
86    defdelegate: 2,
87    defexception: 1,
88    defoverridable: 1,
89    defstruct: 1,
90    destructure: 2,
91    raise: 1,
92    raise: 2,
93    reraise: 2,
94    reraise: 3,
95    if: 2,
96    unless: 2,
97    use: 1,
98    use: 2,
99
100    # Stdlib,
101    defrecord: 2,
102    defrecord: 3,
103    defrecordp: 2,
104    defrecordp: 3,
105
106    # Testing
107    assert: 1,
108    assert: 2,
109    assert_in_delta: 3,
110    assert_in_delta: 4,
111    assert_raise: 2,
112    assert_raise: 3,
113    assert_receive: 1,
114    assert_receive: 2,
115    assert_receive: 3,
116    assert_received: 1,
117    assert_received: 2,
118    doctest: 1,
119    doctest: 2,
120    refute: 1,
121    refute: 2,
122    refute_in_delta: 3,
123    refute_in_delta: 4,
124    refute_receive: 1,
125    refute_receive: 2,
126    refute_receive: 3,
127    refute_received: 1,
128    refute_received: 2,
129    setup: 1,
130    setup: 2,
131    setup_all: 1,
132    setup_all: 2,
133    test: 1,
134    test: 2,
135
136    # Mix config
137    config: 2,
138    config: 3,
139    import_config: 1
140  ]
141
142  @do_end_keywords [:rescue, :catch, :else, :after]
143
144  @doc """
145  Converts the quoted expression into an algebra document.
146  """
147  def to_algebra(quoted, opts \\ []) do
148    comments = Keyword.get(opts, :comments, [])
149
150    state =
151      comments
152      |> Enum.map(&format_comment/1)
153      |> gather_comments()
154      |> state(opts)
155
156    {doc, _} = block_to_algebra(quoted, @min_line, @max_line, state)
157    doc
158  end
159
160  @doc """
161  Lists all default locals without parens.
162  """
163  def locals_without_parens do
164    @locals_without_parens
165  end
166
167  @doc """
168  Checks if a function is a local without parens.
169  """
170  def local_without_parens?(fun, arity, locals_without_parens) do
171    arity > 0 and
172      Enum.any?(locals_without_parens, fn {key, val} ->
173        key == fun and (val == :* or val == arity)
174      end)
175  end
176
177  defp state(comments, opts) do
178    force_do_end_blocks = Keyword.get(opts, :force_do_end_blocks, false)
179    locals_without_parens = Keyword.get(opts, :locals_without_parens, [])
180    sigils = Keyword.get(opts, :sigils, [])
181
182    sigils =
183      Map.new(sigils, fn {key, value} ->
184        with true <- is_atom(key) and is_function(value, 2),
185             [char] <- Atom.to_charlist(key),
186             true <- char in ?A..?Z do
187          {char, value}
188        else
189          _ ->
190            raise ArgumentError,
191                  ":sigils must be a keyword list with a single uppercased letter as key and an " <>
192                    "anonymous function expecting two arguments as value, got: #{inspect(sigils)}"
193        end
194      end)
195
196    %{
197      force_do_end_blocks: force_do_end_blocks,
198      locals_without_parens: locals_without_parens ++ locals_without_parens(),
199      operand_nesting: 2,
200      skip_eol: false,
201      comments: comments,
202      sigils: sigils
203    }
204  end
205
206  defp format_comment(%{text: text} = comment) do
207    %{comment | text: format_comment_text(text)}
208  end
209
210  defp format_comment_text("#"), do: "#"
211  defp format_comment_text("#!" <> rest), do: "#!" <> rest
212  defp format_comment_text("##" <> rest), do: "#" <> format_comment_text("#" <> rest)
213  defp format_comment_text("# " <> rest), do: "# " <> rest
214  defp format_comment_text("#" <> rest), do: "# " <> rest
215
216  # If there is a no new line before, we can't gather all followup comments.
217  defp gather_comments([%{previous_eol_count: 0} = comment | comments]) do
218    comment = %{comment | previous_eol_count: @newlines}
219    [comment | gather_comments(comments)]
220  end
221
222  defp gather_comments([comment | comments]) do
223    %{line: line, next_eol_count: next_eol_count, text: doc} = comment
224
225    {next_eol_count, comments, doc} =
226      gather_followup_comments(line + 1, next_eol_count, comments, doc)
227
228    comment = %{comment | next_eol_count: next_eol_count, text: doc}
229    [comment | gather_comments(comments)]
230  end
231
232  defp gather_comments([]) do
233    []
234  end
235
236  defp gather_followup_comments(line, _, [%{line: line} = comment | comments], doc)
237       when comment.previous_eol_count != 0 do
238    %{next_eol_count: next_eol_count, text: text} = comment
239    gather_followup_comments(line + 1, next_eol_count, comments, line(doc, text))
240  end
241
242  defp gather_followup_comments(_line, next_eol_count, comments, doc) do
243    {next_eol_count, comments, doc}
244  end
245
246  # Special AST nodes from compiler feedback
247
248  defp quoted_to_algebra({{:special, :clause_args}, _meta, [args]}, _context, state) do
249    {doc, state} = clause_args_to_algebra(args, state)
250    {group(doc), state}
251  end
252
253  defp quoted_to_algebra({{:special, :bitstring_segment}, _meta, [arg, last]}, _context, state) do
254    bitstring_segment_to_algebra({arg, -1}, state, last)
255  end
256
257  defp quoted_to_algebra({var, _meta, var_context}, _context, state) when is_atom(var_context) do
258    {var |> Atom.to_string() |> string(), state}
259  end
260
261  defp quoted_to_algebra({:<<>>, meta, entries}, _context, state) do
262    cond do
263      entries == [] ->
264        {"<<>>", state}
265
266      not interpolated?(entries) ->
267        bitstring_to_algebra(meta, entries, state)
268
269      meta[:delimiter] == ~s["""] ->
270        {doc, state} =
271          entries
272          |> prepend_heredoc_line()
273          |> interpolation_to_algebra(~s["""], state, @double_heredoc, @double_heredoc)
274
275        {force_unfit(doc), state}
276
277      true ->
278        interpolation_to_algebra(entries, @double_quote, state, @double_quote, @double_quote)
279    end
280  end
281
282  defp quoted_to_algebra(
283         {{:., _, [List, :to_charlist]}, meta, [entries]} = quoted,
284         context,
285         state
286       ) do
287    cond do
288      not list_interpolated?(entries) ->
289        remote_to_algebra(quoted, context, state)
290
291      meta[:delimiter] == ~s['''] ->
292        {doc, state} =
293          entries
294          |> prepend_heredoc_line()
295          |> list_interpolation_to_algebra(~s['''], state, @single_heredoc, @single_heredoc)
296
297        {force_unfit(doc), state}
298
299      true ->
300        list_interpolation_to_algebra(entries, @single_quote, state, @single_quote, @single_quote)
301    end
302  end
303
304  defp quoted_to_algebra(
305         {{:., _, [:erlang, :binary_to_atom]}, _, [{:<<>>, _, entries}, :utf8]} = quoted,
306         context,
307         state
308       ) do
309    if interpolated?(entries) do
310      interpolation_to_algebra(entries, @double_quote, state, ":\"", @double_quote)
311    else
312      remote_to_algebra(quoted, context, state)
313    end
314  end
315
316  # foo[bar]
317  defp quoted_to_algebra({{:., _, [Access, :get]}, meta, [target, arg]}, _context, state) do
318    {target_doc, state} = remote_target_to_algebra(target, state)
319
320    {access_doc, state} =
321      if keyword?(arg) do
322        list_to_algebra(meta, arg, state)
323      else
324        list_to_algebra(meta, [arg], state)
325      end
326
327    {concat(target_doc, access_doc), state}
328  end
329
330  # %Foo{}
331  # %name{foo: 1}
332  # %name{bar | foo: 1}
333  defp quoted_to_algebra({:%, _, [name, {:%{}, meta, args}]}, _context, state) do
334    {name_doc, state} = quoted_to_algebra(name, :parens_arg, state)
335    map_to_algebra(meta, name_doc, args, state)
336  end
337
338  # %{foo: 1}
339  # %{foo => bar}
340  # %{name | foo => bar}
341  defp quoted_to_algebra({:%{}, meta, args}, _context, state) do
342    map_to_algebra(meta, @empty, args, state)
343  end
344
345  # {}
346  # {1, 2}
347  defp quoted_to_algebra({:{}, meta, args}, _context, state) do
348    tuple_to_algebra(meta, args, :flex_break, state)
349  end
350
351  defp quoted_to_algebra({:__block__, meta, [{left, right}]}, _context, state) do
352    tuple_to_algebra(meta, [left, right], :flex_break, state)
353  end
354
355  defp quoted_to_algebra({:__block__, meta, [list]}, _context, state) when is_list(list) do
356    case meta[:delimiter] do
357      ~s['''] ->
358        string = list |> List.to_string() |> escape_heredoc(~s['''])
359        {@single_heredoc |> concat(string) |> concat(@single_heredoc) |> force_unfit(), state}
360
361      ~s['] ->
362        string = list |> List.to_string() |> escape_string(@single_quote)
363        {@single_quote |> concat(string) |> concat(@single_quote), state}
364
365      _other ->
366        list_to_algebra(meta, list, state)
367    end
368  end
369
370  defp quoted_to_algebra({:__block__, meta, [string]}, _context, state) when is_binary(string) do
371    if meta[:delimiter] == ~s["""] do
372      string = escape_heredoc(string, ~s["""])
373      {@double_heredoc |> concat(string) |> concat(@double_heredoc) |> force_unfit(), state}
374    else
375      string = escape_string(string, @double_quote)
376      {@double_quote |> concat(string) |> concat(@double_quote), state}
377    end
378  end
379
380  defp quoted_to_algebra({:__block__, _, [atom]}, _context, state) when is_atom(atom) do
381    {atom_to_algebra(atom), state}
382  end
383
384  defp quoted_to_algebra({:__block__, meta, [integer]}, _context, state)
385       when is_integer(integer) do
386    {integer_to_algebra(Keyword.fetch!(meta, :token)), state}
387  end
388
389  defp quoted_to_algebra({:__block__, meta, [float]}, _context, state) when is_float(float) do
390    {float_to_algebra(Keyword.fetch!(meta, :token)), state}
391  end
392
393  defp quoted_to_algebra(
394         {:__block__, _meta, [{:unquote_splicing, meta, [_] = args}]},
395         context,
396         state
397       ) do
398    {doc, state} = local_to_algebra(:unquote_splicing, meta, args, context, state)
399    {wrap_in_parens(doc), state}
400  end
401
402  defp quoted_to_algebra({:__block__, _meta, [arg]}, context, state) do
403    quoted_to_algebra(arg, context, state)
404  end
405
406  defp quoted_to_algebra({:__block__, _meta, []}, _context, state) do
407    {"nil", state}
408  end
409
410  defp quoted_to_algebra({:__block__, meta, _} = block, _context, state) do
411    {block, state} = block_to_algebra(block, line(meta), closing_line(meta), state)
412    {surround("(", block, ")"), state}
413  end
414
415  defp quoted_to_algebra({:__aliases__, _meta, [head | tail]}, context, state) do
416    {doc, state} =
417      if is_atom(head) do
418        {Atom.to_string(head), state}
419      else
420        quoted_to_algebra_with_parens_if_operator(head, context, state)
421      end
422
423    {Enum.reduce(tail, doc, &concat(&2, "." <> Atom.to_string(&1))), state}
424  end
425
426  # &1
427  # &local(&1)
428  # &local/1
429  # &Mod.remote/1
430  # & &1
431  # & &1 + &2
432  defp quoted_to_algebra({:&, _, [arg]}, context, state) do
433    capture_to_algebra(arg, context, state)
434  end
435
436  defp quoted_to_algebra({:@, meta, [arg]}, context, state) do
437    module_attribute_to_algebra(meta, arg, context, state)
438  end
439
440  # not(left in right)
441  # left not in right
442  defp quoted_to_algebra({:not, meta, [{:in, _, [left, right]}]}, context, state) do
443    binary_op_to_algebra(:in, "not in", meta, left, right, context, state)
444  end
445
446  # 1..2//3
447  defp quoted_to_algebra({:"..//", meta, [left, middle, right]}, context, state) do
448    quoted_to_algebra({:"//", meta, [{:.., meta, [left, middle]}, right]}, context, state)
449  end
450
451  defp quoted_to_algebra({:fn, meta, [_ | _] = clauses}, _context, state) do
452    anon_fun_to_algebra(clauses, line(meta), closing_line(meta), state, eol?(meta, state))
453  end
454
455  defp quoted_to_algebra({fun, meta, args}, context, state) when is_atom(fun) and is_list(args) do
456    with :error <- maybe_sigil_to_algebra(fun, meta, args, state),
457         :error <- maybe_unary_op_to_algebra(fun, meta, args, context, state),
458         :error <- maybe_binary_op_to_algebra(fun, meta, args, context, state),
459         do: local_to_algebra(fun, meta, args, context, state)
460  end
461
462  defp quoted_to_algebra({_, _, args} = quoted, context, state) when is_list(args) do
463    remote_to_algebra(quoted, context, state)
464  end
465
466  # (left -> right)
467  defp quoted_to_algebra([{:->, _, _} | _] = clauses, _context, state) do
468    type_fun_to_algebra(clauses, @max_line, @min_line, state)
469  end
470
471  # [keyword: :list] (inner part)
472  # %{:foo => :bar} (inner part)
473  defp quoted_to_algebra(list, context, state) when is_list(list) do
474    many_args_to_algebra(list, state, &quoted_to_algebra(&1, context, &2))
475  end
476
477  # keyword: :list
478  # key => value
479  defp quoted_to_algebra({left_arg, right_arg}, context, state) do
480    {left, op, right, state} =
481      if keyword_key?(left_arg) do
482        {left, state} =
483          case left_arg do
484            # TODO: Remove this clause in v1.16 when we no longer quote operator :..//
485            {:__block__, _, [:"..//"]} ->
486              {string(~S{"..//":}), state}
487
488            {:__block__, _, [atom]} when is_atom(atom) ->
489              key =
490                case Code.Identifier.classify(atom) do
491                  type when type in [:callable_local, :callable_operator, :not_callable] ->
492                    IO.iodata_to_binary([Atom.to_string(atom), ?:])
493
494                  _ ->
495                    IO.iodata_to_binary([?", Atom.to_string(atom), ?", ?:])
496                end
497
498              {string(key), state}
499
500            {{:., _, [:erlang, :binary_to_atom]}, _, [{:<<>>, _, entries}, :utf8]} ->
501              interpolation_to_algebra(entries, @double_quote, state, "\"", "\":")
502          end
503
504        {right, state} = quoted_to_algebra(right_arg, context, state)
505        {left, "", right, state}
506      else
507        {left, state} = quoted_to_algebra(left_arg, context, state)
508        {right, state} = quoted_to_algebra(right_arg, context, state)
509        left = wrap_in_parens_if_binary_operator(left, left_arg)
510        {left, " =>", right, state}
511      end
512
513    doc =
514      with_next_break_fits(next_break_fits?(right_arg, state), right, fn right ->
515        concat(group(left), group(nest(glue(op, group(right)), 2, :break)))
516      end)
517
518    {doc, state}
519  end
520
521  # #PID's and #Ref's may appear on regular AST
522  defp quoted_to_algebra(unknown, _context, state) do
523    {inspect(unknown), state}
524  end
525
526  ## Blocks
527
528  defp block_to_algebra([{:->, _, _} | _] = type_fun, min_line, max_line, state) do
529    type_fun_to_algebra(type_fun, min_line, max_line, state)
530  end
531
532  defp block_to_algebra({:__block__, _, []}, min_line, max_line, state) do
533    block_args_to_algebra([], min_line, max_line, state)
534  end
535
536  defp block_to_algebra({:__block__, _, [_, _ | _] = args}, min_line, max_line, state) do
537    block_args_to_algebra(args, min_line, max_line, state)
538  end
539
540  defp block_to_algebra(block, min_line, max_line, state) do
541    block_args_to_algebra([block], min_line, max_line, state)
542  end
543
544  defp block_args_to_algebra(args, min_line, max_line, state) do
545    quoted_to_algebra = fn {kind, meta, _} = arg, _args, state ->
546      newlines = meta[:end_of_expression][:newlines] || 1
547      {doc, state} = quoted_to_algebra(arg, :block, state)
548      {{doc, block_next_line(kind), newlines}, state}
549    end
550
551    {args_docs, _comments?, state} =
552      quoted_to_algebra_with_comments(args, [], min_line, max_line, state, quoted_to_algebra)
553
554    case args_docs do
555      [] -> {@empty, state}
556      [line] -> {line, state}
557      lines -> {lines |> Enum.reduce(&line(&2, &1)) |> force_unfit(), state}
558    end
559  end
560
561  defp block_next_line(:@), do: @empty
562  defp block_next_line(_), do: break("")
563
564  ## Operators
565
566  defp maybe_unary_op_to_algebra(fun, meta, args, context, state) do
567    with [arg] <- args,
568         {_, _} <- Code.Identifier.unary_op(fun) do
569      unary_op_to_algebra(fun, meta, arg, context, state)
570    else
571      _ -> :error
572    end
573  end
574
575  defp unary_op_to_algebra(op, _meta, arg, context, state) do
576    {doc, state} = quoted_to_algebra(arg, force_many_args_or_operand(context, :operand), state)
577
578    # not and ! are nestable, all others are not.
579    doc =
580      case arg do
581        {^op, _, [_]} when op in [:!, :not] -> doc
582        _ -> wrap_in_parens_if_operator(doc, arg)
583      end
584
585    # not requires a space unless the doc was wrapped in parens.
586    op_string =
587      if op == :not do
588        "not "
589      else
590        Atom.to_string(op)
591      end
592
593    {concat(op_string, doc), state}
594  end
595
596  defp maybe_binary_op_to_algebra(fun, meta, args, context, state) do
597    with [left, right] <- args,
598         {_, _} <- Code.Identifier.binary_op(fun) do
599      binary_op_to_algebra(fun, Atom.to_string(fun), meta, left, right, context, state)
600    else
601      _ -> :error
602    end
603  end
604
605  # There are five kinds of operators.
606  #
607  #   1. no space binary operators, for example,  1..2
608  #   2. no newline binary operators, for example, left in right
609  #   3. strict newlines before a left precedent operator, for example, foo |> bar |> baz
610  #   4. strict newlines before a right precedent operator, for example, foo when bar when baz
611  #   5. flex newlines after the operator, for example, foo ++ bar ++ baz
612  #
613  # Cases 1, 2 and 5 are handled fairly easily by relying on the
614  # operator precedence and making sure nesting is applied only once.
615  #
616  # Cases 3 and 4 are the complex ones, as it requires passing the
617  # strict or flex mode around.
618  defp binary_op_to_algebra(op, op_string, meta, left_arg, right_arg, context, state) do
619    %{operand_nesting: nesting} = state
620    binary_op_to_algebra(op, op_string, meta, left_arg, right_arg, context, state, nesting)
621  end
622
623  defp binary_op_to_algebra(op, op_string, meta, left_arg, right_arg, context, state, _nesting)
624       when op in @right_new_line_before_binary_operators do
625    op_info = Code.Identifier.binary_op(op)
626    op_string = op_string <> " "
627    left_context = left_op_context(context)
628    right_context = right_op_context(context)
629
630    min_line =
631      case left_arg do
632        {_, left_meta, _} -> line(left_meta)
633        _ -> line(meta)
634      end
635
636    {operands, max_line} =
637      unwrap_right(right_arg, op, meta, right_context, [{{:root, left_context}, left_arg}])
638
639    fun = fn
640      {{:root, context}, arg}, _args, state ->
641        {doc, state} = binary_operand_to_algebra(arg, context, state, op, op_info, :left, 2)
642        {{doc, @empty, 1}, state}
643
644      {{kind, context}, arg}, _args, state ->
645        {doc, state} = binary_operand_to_algebra(arg, context, state, op, op_info, kind, 0)
646        doc = doc |> nest_by_length(op_string) |> force_keyword(arg)
647        {{concat(op_string, doc), @empty, 1}, state}
648    end
649
650    {doc, state} =
651      operand_to_algebra_with_comments(operands, meta, min_line, max_line, context, state, fun)
652
653    if keyword?(right_arg) and context in [:parens_arg, :no_parens_arg] do
654      {wrap_in_parens(doc), state}
655    else
656      {doc, state}
657    end
658  end
659
660  defp binary_op_to_algebra(op, _, meta, left_arg, right_arg, context, state, _nesting)
661       when op in @pipeline_operators do
662    op_info = Code.Identifier.binary_op(op)
663    left_context = left_op_context(context)
664    right_context = right_op_context(context)
665    max_line = line(meta)
666
667    {pipes, min_line} =
668      unwrap_pipes(left_arg, meta, left_context, [{{op, right_context}, right_arg}])
669
670    fun = fn
671      {{:root, context}, arg}, _args, state ->
672        {doc, state} = binary_operand_to_algebra(arg, context, state, op, op_info, :left, 2)
673        {{doc, @empty, 1}, state}
674
675      {{op, context}, arg}, _args, state ->
676        op_info = Code.Identifier.binary_op(op)
677        op_string = Atom.to_string(op) <> " "
678        {doc, state} = binary_operand_to_algebra(arg, context, state, op, op_info, :right, 0)
679        {{concat(op_string, doc), @empty, 1}, state}
680    end
681
682    operand_to_algebra_with_comments(pipes, meta, min_line, max_line, context, state, fun)
683  end
684
685  defp binary_op_to_algebra(op, op_string, meta, left_arg, right_arg, context, state, nesting) do
686    op_info = Code.Identifier.binary_op(op)
687    left_context = left_op_context(context)
688    right_context = right_op_context(context)
689
690    {left, state} =
691      binary_operand_to_algebra(left_arg, left_context, state, op, op_info, :left, 2)
692
693    {right, state} =
694      binary_operand_to_algebra(right_arg, right_context, state, op, op_info, :right, 0)
695
696    doc =
697      cond do
698        op in @no_space_binary_operators ->
699          concat(concat(group(left), op_string), group(right))
700
701        op in @no_newline_binary_operators ->
702          op_string = " " <> op_string <> " "
703          concat(concat(group(left), op_string), group(right))
704
705        true ->
706          eol? = eol?(meta, state)
707
708          next_break_fits? =
709            op in @next_break_fits_operators and next_break_fits?(right_arg, state) and not eol?
710
711          with_next_break_fits(next_break_fits?, right, fn right ->
712            op_string = " " <> op_string
713            right = nest(glue(op_string, group(right)), nesting, :break)
714            right = if eol?, do: force_unfit(right), else: right
715            concat(group(left), group(right))
716          end)
717      end
718
719    {doc, state}
720  end
721
722  # TODO: We can remove this workaround once we remove
723  # ?rearrange_uop from the parser on v2.0.
724  # (! left) in right
725  # (not left) in right
726  defp binary_operand_to_algebra(
727         {:__block__, _, [{op, meta, [arg]}]},
728         context,
729         state,
730         :in,
731         _parent_info,
732         :left,
733         _nesting
734       )
735       when op in [:not, :!] do
736    {doc, state} = unary_op_to_algebra(op, meta, arg, context, state)
737    {wrap_in_parens(doc), state}
738  end
739
740  defp binary_operand_to_algebra(operand, context, state, parent_op, parent_info, side, nesting) do
741    {parent_assoc, parent_prec} = parent_info
742
743    with {op, meta, [left, right]} <- operand,
744         op_info = Code.Identifier.binary_op(op),
745         {_assoc, prec} <- op_info do
746      op_string = Atom.to_string(op)
747
748      cond do
749        # If the operator has the same precedence as the parent and is on
750        # the correct side, we respect the nesting rule to avoid multiple
751        # nestings. This only applies for left associativity or same operator.
752        parent_prec == prec and parent_assoc == side and (side == :left or op == parent_op) ->
753          binary_op_to_algebra(op, op_string, meta, left, right, context, state, nesting)
754
755        # If the parent requires parens or the precedence is inverted or
756        # it is in the wrong side, then we *need* parenthesis.
757        (parent_op in @required_parens_on_binary_operands and op not in @no_space_binary_operators) or
758          (op in @required_parens_logical_binary_operands and
759             parent_op in @required_parens_logical_binary_operands) or parent_prec > prec or
760            (parent_prec == prec and parent_assoc != side) ->
761          {operand, state} =
762            binary_op_to_algebra(op, op_string, meta, left, right, context, state, 2)
763
764          {wrap_in_parens(operand), state}
765
766        # Otherwise, we rely on precedence but also nest.
767        true ->
768          binary_op_to_algebra(op, op_string, meta, left, right, context, state, 2)
769      end
770    else
771      {:&, _, [arg]}
772      when not is_integer(arg) and side == :left
773      when not is_integer(arg) and parent_assoc == :left and parent_prec > @ampersand_prec ->
774        {doc, state} = quoted_to_algebra(operand, context, state)
775        {wrap_in_parens(doc), state}
776
777      _ ->
778        quoted_to_algebra(operand, context, state)
779    end
780  end
781
782  defp unwrap_pipes({op, meta, [left, right]}, _meta, context, acc)
783       when op in @pipeline_operators do
784    left_context = left_op_context(context)
785    right_context = right_op_context(context)
786    unwrap_pipes(left, meta, left_context, [{{op, right_context}, right} | acc])
787  end
788
789  defp unwrap_pipes(left, meta, context, acc) do
790    min_line =
791      case left do
792        {_, meta, _} -> line(meta)
793        _ -> line(meta)
794      end
795
796    {[{{:root, context}, left} | acc], min_line}
797  end
798
799  defp unwrap_right({op, meta, [left, right]}, op, _meta, context, acc) do
800    left_context = left_op_context(context)
801    right_context = right_op_context(context)
802    unwrap_right(right, op, meta, right_context, [{{:left, left_context}, left} | acc])
803  end
804
805  defp unwrap_right(right, _op, meta, context, acc) do
806    acc = [{{:right, context}, right} | acc]
807    {Enum.reverse(acc), line(meta)}
808  end
809
810  defp operand_to_algebra_with_comments(operands, meta, min_line, max_line, context, state, fun) do
811    # If we are in a no_parens_one_arg expression, we actually cannot
812    # extract comments from the first operand, because it would rewrite:
813    #
814    #     @spec function(x) ::
815    #             # Comment
816    #             any
817    #           when x: any
818    #
819    # to:
820    #
821    #     @spec # Comment
822    #           function(x) ::
823    #             any
824    #           when x: any
825    #
826    # Instead we get:
827    #
828    #     @spec function(x) ::
829    #             any
830    #           # Comment
831    #           when x: any
832    #
833    # Which may look counter-intuitive but it actually makes sense,
834    # as the closest possible location for the comment is the when
835    # operator.
836    {operands, acc, state} =
837      if context == :no_parens_one_arg do
838        [operand | operands] = operands
839        {doc_triplet, state} = fun.(operand, :unused, state)
840        {operands, [doc_triplet], state}
841      else
842        {operands, [], state}
843      end
844
845    {docs, comments?, state} =
846      quoted_to_algebra_with_comments(operands, acc, min_line, max_line, state, fun)
847
848    if comments? or eol?(meta, state) do
849      {docs |> Enum.reduce(&line(&2, &1)) |> force_unfit(), state}
850    else
851      {docs |> Enum.reduce(&glue(&2, &1)), state}
852    end
853  end
854
855  ## Module attributes
856
857  # @Foo
858  # @Foo.Bar
859  defp module_attribute_to_algebra(_meta, {:__aliases__, _, [_, _ | _]} = quoted, _context, state) do
860    {doc, state} = quoted_to_algebra(quoted, :parens_arg, state)
861    {concat(concat("@(", doc), ")"), state}
862  end
863
864  # @foo bar
865  # @foo(bar)
866  defp module_attribute_to_algebra(meta, {name, call_meta, [_] = args} = expr, context, state)
867       when is_atom(name) and name not in [:__block__, :__aliases__] do
868    if Code.Identifier.classify(name) == :callable_local do
869      {{call_doc, state}, wrap_in_parens?} =
870        call_args_to_algebra(args, call_meta, context, :skip_unless_many_args, false, state)
871
872      doc =
873        "@#{name}"
874        |> string()
875        |> concat(call_doc)
876
877      doc = if wrap_in_parens?, do: wrap_in_parens(doc), else: doc
878      {doc, state}
879    else
880      unary_op_to_algebra(:@, meta, expr, context, state)
881    end
882  end
883
884  # @foo
885  # @(foo.bar())
886  defp module_attribute_to_algebra(meta, quoted, context, state) do
887    unary_op_to_algebra(:@, meta, quoted, context, state)
888  end
889
890  ## Capture operator
891
892  defp capture_to_algebra(integer, _context, state) when is_integer(integer) do
893    {"&" <> Integer.to_string(integer), state}
894  end
895
896  defp capture_to_algebra(arg, context, state) do
897    {doc, state} = capture_target_to_algebra(arg, context, state)
898
899    if doc |> format_to_string() |> String.starts_with?("&") do
900      {concat("& ", doc), state}
901    else
902      {concat("&", doc), state}
903    end
904  end
905
906  defp capture_target_to_algebra(
907         {:/, _, [{{:., _, [target, fun]}, _, []}, {:__block__, _, [arity]}]},
908         _context,
909         state
910       )
911       when is_atom(fun) and is_integer(arity) do
912    {target_doc, state} = remote_target_to_algebra(target, state)
913    fun = Code.Identifier.inspect_as_function(fun)
914    {target_doc |> nest(1) |> concat(string(".#{fun}/#{arity}")), state}
915  end
916
917  defp capture_target_to_algebra(
918         {:/, _, [{name, _, var_context}, {:__block__, _, [arity]}]},
919         _context,
920         state
921       )
922       when is_atom(name) and is_atom(var_context) and is_integer(arity) do
923    {string("#{name}/#{arity}"), state}
924  end
925
926  defp capture_target_to_algebra(arg, context, state) do
927    {doc, state} = quoted_to_algebra(arg, context, state)
928    {wrap_in_parens_if_operator(doc, arg), state}
929  end
930
931  ## Calls (local, remote and anonymous)
932
933  # expression.{arguments}
934  defp remote_to_algebra({{:., _, [target, :{}]}, meta, args}, _context, state) do
935    {target_doc, state} = remote_target_to_algebra(target, state)
936    {call_doc, state} = tuple_to_algebra(meta, args, :break, state)
937    {concat(concat(target_doc, "."), call_doc), state}
938  end
939
940  # expression.(arguments)
941  defp remote_to_algebra({{:., _, [target]}, meta, args}, context, state) do
942    {target_doc, state} = remote_target_to_algebra(target, state)
943
944    {{call_doc, state}, wrap_in_parens?} =
945      call_args_to_algebra(args, meta, context, :skip_if_do_end, true, state)
946
947    doc = concat(concat(target_doc, "."), call_doc)
948    doc = if wrap_in_parens?, do: wrap_in_parens(doc), else: doc
949    {doc, state}
950  end
951
952  # Mod.function()
953  # var.function
954  # expression.function(arguments)
955  defp remote_to_algebra({{:., _, [target, fun]}, meta, args}, context, state)
956       when is_atom(fun) do
957    {target_doc, state} = remote_target_to_algebra(target, state)
958    fun = Code.Identifier.inspect_as_function(fun)
959    remote_doc = target_doc |> concat(".") |> concat(string(fun))
960
961    if args == [] and not remote_target_is_a_module?(target) and not meta?(meta, :closing) do
962      {remote_doc, state}
963    else
964      {{call_doc, state}, wrap_in_parens?} =
965        call_args_to_algebra(args, meta, context, :skip_if_do_end, true, state)
966
967      doc = concat(remote_doc, call_doc)
968      doc = if wrap_in_parens?, do: wrap_in_parens(doc), else: doc
969      {doc, state}
970    end
971  end
972
973  # call(call)(arguments)
974  defp remote_to_algebra({target, meta, args}, context, state) do
975    {target_doc, state} = quoted_to_algebra(target, :no_parens_arg, state)
976
977    {{call_doc, state}, wrap_in_parens?} =
978      call_args_to_algebra(args, meta, context, :required, true, state)
979
980    doc = concat(target_doc, call_doc)
981    doc = if wrap_in_parens?, do: wrap_in_parens(doc), else: doc
982    {doc, state}
983  end
984
985  defp remote_target_is_a_module?(target) do
986    case target do
987      {:__MODULE__, _, context} when is_atom(context) -> true
988      {:__block__, _, [atom]} when is_atom(atom) -> true
989      {:__aliases__, _, _} -> true
990      _ -> false
991    end
992  end
993
994  defp remote_target_to_algebra({:fn, _, [_ | _]} = quoted, state) do
995    # This change is not semantically required but for beautification.
996    {doc, state} = quoted_to_algebra(quoted, :no_parens_arg, state)
997    {wrap_in_parens(doc), state}
998  end
999
1000  defp remote_target_to_algebra(quoted, state) do
1001    quoted_to_algebra_with_parens_if_operator(quoted, :no_parens_arg, state)
1002  end
1003
1004  # function(arguments)
1005  defp local_to_algebra(fun, meta, args, context, state) when is_atom(fun) do
1006    skip_parens =
1007      cond do
1008        meta?(meta, :closing) ->
1009          :skip_if_only_do_end
1010
1011        local_without_parens?(fun, length(args), state.locals_without_parens) ->
1012          :skip_unless_many_args
1013
1014        true ->
1015          :skip_if_do_end
1016      end
1017
1018    {{call_doc, state}, wrap_in_parens?} =
1019      call_args_to_algebra(args, meta, context, skip_parens, true, state)
1020
1021    doc =
1022      fun
1023      |> Atom.to_string()
1024      |> string()
1025      |> concat(call_doc)
1026
1027    doc = if wrap_in_parens?, do: wrap_in_parens(doc), else: doc
1028    {doc, state}
1029  end
1030
1031  # parens may be one of:
1032  #
1033  #   * :skip_unless_many_args - skips parens unless we are the argument context
1034  #   * :skip_if_only_do_end - skip parens if we are do-end and the only arg
1035  #   * :skip_if_do_end - skip parens if we are do-end
1036  #   * :required - never skip parens
1037  #
1038  defp call_args_to_algebra([], meta, _context, _parens, _list_to_keyword?, state) do
1039    {args_doc, _join, state} =
1040      args_to_algebra_with_comments([], meta, false, :none, :break, state, &{&1, &2})
1041
1042    {{surround("(", args_doc, ")"), state}, false}
1043  end
1044
1045  defp call_args_to_algebra(args, meta, context, parens, list_to_keyword?, state) do
1046    {rest, last} = split_last(args)
1047
1048    if blocks = do_end_blocks(meta, last, state) do
1049      {call_doc, state} =
1050        case rest do
1051          [] when parens == :required ->
1052            {"() do", state}
1053
1054          [] ->
1055            {" do", state}
1056
1057          _ ->
1058            no_parens? = parens not in [:required, :skip_if_only_do_end]
1059            call_args_to_algebra_no_blocks(meta, rest, no_parens?, list_to_keyword?, " do", state)
1060        end
1061
1062      {blocks_doc, state} = do_end_blocks_to_algebra(blocks, state)
1063      call_doc = call_doc |> concat(blocks_doc) |> line("end") |> force_unfit()
1064      {{call_doc, state}, context in [:no_parens_arg, :no_parens_one_arg]}
1065    else
1066      no_parens? =
1067        parens == :skip_unless_many_args and
1068          context in [:block, :operand, :no_parens_one_arg, :parens_one_arg]
1069
1070      res =
1071        call_args_to_algebra_no_blocks(meta, args, no_parens?, list_to_keyword?, @empty, state)
1072
1073      {res, false}
1074    end
1075  end
1076
1077  defp call_args_to_algebra_no_blocks(meta, args, skip_parens?, list_to_keyword?, extra, state) do
1078    {left, right} = split_last(args)
1079    {keyword?, right} = last_arg_to_keyword(right, list_to_keyword?, skip_parens?, state.comments)
1080
1081    context =
1082      if left == [] and not keyword? do
1083        if skip_parens?, do: :no_parens_one_arg, else: :parens_one_arg
1084      else
1085        if skip_parens?, do: :no_parens_arg, else: :parens_arg
1086      end
1087
1088    args = if keyword?, do: left ++ right, else: left ++ [right]
1089    many_eol? = match?([_, _ | _], args) and eol?(meta, state)
1090    no_generators? = no_generators?(args)
1091    to_algebra_fun = &quoted_to_algebra(&1, context, &2)
1092
1093    {args_doc, next_break_fits?, state} =
1094      if left != [] and keyword? and no_generators? do
1095        join = if force_args?(left) or many_eol?, do: :line, else: :break
1096
1097        {left_doc, _join, state} =
1098          args_to_algebra_with_comments(
1099            left,
1100            Keyword.delete(meta, :closing),
1101            skip_parens?,
1102            :force_comma,
1103            join,
1104            state,
1105            to_algebra_fun
1106          )
1107
1108        join = if force_args?(right) or force_args?(args) or many_eol?, do: :line, else: :break
1109
1110        {right_doc, _join, state} =
1111          args_to_algebra_with_comments(right, meta, false, :none, join, state, to_algebra_fun)
1112
1113        right_doc = apply(Inspect.Algebra, join, []) |> concat(right_doc)
1114
1115        args_doc =
1116          if skip_parens? do
1117            left_doc
1118            |> concat(next_break_fits(group(right_doc, :inherit), :enabled))
1119            |> nest(:cursor, :break)
1120          else
1121            right_doc =
1122              right_doc
1123              |> nest(2, :break)
1124              |> concat(break(""))
1125              |> group(:inherit)
1126              |> next_break_fits(:enabled)
1127
1128            concat(nest(left_doc, 2, :break), right_doc)
1129          end
1130
1131        {args_doc, true, state}
1132      else
1133        join = if force_args?(args) or many_eol?, do: :line, else: :break
1134        next_break_fits? = join == :break and next_break_fits?(right, state)
1135        last_arg_mode = if next_break_fits?, do: :next_break_fits, else: :none
1136
1137        {args_doc, _join, state} =
1138          args_to_algebra_with_comments(
1139            args,
1140            meta,
1141            skip_parens?,
1142            last_arg_mode,
1143            join,
1144            state,
1145            to_algebra_fun
1146          )
1147
1148        # If we have a single argument, then we won't have an option to break
1149        # before the "extra" part, so we ungroup it and build it later.
1150        args_doc = ungroup_if_group(args_doc)
1151
1152        args_doc =
1153          if skip_parens? do
1154            nest(args_doc, :cursor, :break)
1155          else
1156            nest(args_doc, 2, :break) |> concat(break(""))
1157          end
1158
1159        {args_doc, next_break_fits?, state}
1160      end
1161
1162    doc =
1163      cond do
1164        left != [] and keyword? and skip_parens? and no_generators? ->
1165          " "
1166          |> concat(args_doc)
1167          |> nest(2)
1168          |> concat(extra)
1169          |> group()
1170
1171        skip_parens? ->
1172          " "
1173          |> concat(args_doc)
1174          |> concat(extra)
1175          |> group()
1176
1177        true ->
1178          "("
1179          |> concat(break(""))
1180          |> nest(2, :break)
1181          |> concat(args_doc)
1182          |> concat(")")
1183          |> concat(extra)
1184          |> group()
1185      end
1186
1187    if next_break_fits? do
1188      {next_break_fits(doc, :disabled), state}
1189    else
1190      {doc, state}
1191    end
1192  end
1193
1194  defp no_generators?(args) do
1195    not Enum.any?(args, &match?({:<-, _, [_, _]}, &1))
1196  end
1197
1198  defp do_end_blocks(meta, [{{:__block__, _, [:do]}, _} | rest] = blocks, state) do
1199    if meta?(meta, :do) or can_force_do_end_blocks?(rest, state) do
1200      blocks
1201      |> Enum.map(fn {{:__block__, meta, [key]}, value} -> {key, line(meta), value} end)
1202      |> do_end_blocks_with_range(end_line(meta))
1203    end
1204  end
1205
1206  defp do_end_blocks(_, _, _), do: nil
1207
1208  defp can_force_do_end_blocks?(rest, state) do
1209    state.force_do_end_blocks and
1210      Enum.all?(rest, fn {{:__block__, _, [key]}, _} -> key in @do_end_keywords end)
1211  end
1212
1213  defp do_end_blocks_with_range([{key1, line1, value1}, {_, line2, _} = h | t], end_line) do
1214    [{key1, line1, line2, value1} | do_end_blocks_with_range([h | t], end_line)]
1215  end
1216
1217  defp do_end_blocks_with_range([{key, line, value}], end_line) do
1218    [{key, line, end_line, value}]
1219  end
1220
1221  defp do_end_blocks_to_algebra([{:do, line, end_line, value} | blocks], state) do
1222    {acc, state} = do_end_block_to_algebra(@empty, line, end_line, value, state)
1223
1224    Enum.reduce(blocks, {acc, state}, fn {key, line, end_line, value}, {acc, state} ->
1225      {doc, state} = do_end_block_to_algebra(Atom.to_string(key), line, end_line, value, state)
1226      {line(acc, doc), state}
1227    end)
1228  end
1229
1230  defp do_end_block_to_algebra(key_doc, line, end_line, value, state) do
1231    case clauses_to_algebra(value, line, end_line, state) do
1232      {@empty, state} -> {key_doc, state}
1233      {value_doc, state} -> {key_doc |> line(value_doc) |> nest(2), state}
1234    end
1235  end
1236
1237  ## Interpolation
1238
1239  defp list_interpolated?(entries) do
1240    Enum.all?(entries, fn
1241      {{:., _, [Kernel, :to_string]}, _, [_]} -> true
1242      entry when is_binary(entry) -> true
1243      _ -> false
1244    end)
1245  end
1246
1247  defp interpolated?(entries) do
1248    Enum.all?(entries, fn
1249      {:"::", _, [{{:., _, [Kernel, :to_string]}, _, [_]}, {:binary, _, _}]} -> true
1250      entry when is_binary(entry) -> true
1251      _ -> false
1252    end)
1253  end
1254
1255  defp prepend_heredoc_line([entry | entries]) when is_binary(entry) do
1256    ["\n" <> entry | entries]
1257  end
1258
1259  defp prepend_heredoc_line(entries) do
1260    ["\n" | entries]
1261  end
1262
1263  defp list_interpolation_to_algebra([entry | entries], escape, state, acc, last)
1264       when is_binary(entry) do
1265    acc = concat(acc, escape_string(entry, escape))
1266    list_interpolation_to_algebra(entries, escape, state, acc, last)
1267  end
1268
1269  defp list_interpolation_to_algebra([entry | entries], escape, state, acc, last) do
1270    {{:., _, [Kernel, :to_string]}, _meta, [quoted]} = entry
1271    {doc, state} = interpolation_to_string(quoted, state)
1272    list_interpolation_to_algebra(entries, escape, state, concat(acc, doc), last)
1273  end
1274
1275  defp list_interpolation_to_algebra([], _escape, state, acc, last) do
1276    {concat(acc, last), state}
1277  end
1278
1279  defp interpolation_to_algebra([entry | entries], escape, state, acc, last)
1280       when is_binary(entry) do
1281    acc = concat(acc, escape_string(entry, escape))
1282    interpolation_to_algebra(entries, escape, state, acc, last)
1283  end
1284
1285  defp interpolation_to_algebra([entry | entries], escape, state, acc, last) do
1286    {:"::", _, [{{:., _, [Kernel, :to_string]}, _meta, [quoted]}, {:binary, _, _}]} = entry
1287    {doc, state} = interpolation_to_string(quoted, state)
1288    interpolation_to_algebra(entries, escape, state, concat(acc, doc), last)
1289  end
1290
1291  defp interpolation_to_algebra([], _escape, state, acc, last) do
1292    {concat(acc, last), state}
1293  end
1294
1295  defp interpolation_to_string(quoted, %{skip_eol: skip_eol} = state) do
1296    {doc, state} = block_to_algebra(quoted, @max_line, @min_line, %{state | skip_eol: true})
1297    doc = interpolation_to_string(surround("\#{", doc, "}"))
1298    {doc, %{state | skip_eol: skip_eol}}
1299  end
1300
1301  defp interpolation_to_string(doc) do
1302    [head | tail] =
1303      doc
1304      |> format_to_string()
1305      |> String.split("\n")
1306
1307    Enum.reduce(tail, string(head), fn line, acc ->
1308      concat([acc, line(), string(line)])
1309    end)
1310  end
1311
1312  ## Sigils
1313
1314  defp maybe_sigil_to_algebra(fun, meta, args, state) do
1315    with <<"sigil_", name>> <- Atom.to_string(fun),
1316         [{:<<>>, _, entries}, modifiers] when is_list(modifiers) <- args,
1317         opening_delimiter when not is_nil(opening_delimiter) <- meta[:delimiter] do
1318      doc = <<?~, name, opening_delimiter::binary>>
1319
1320      entries =
1321        case state.sigils do
1322          %{^name => callback} ->
1323            case callback.(hd(entries), sigil: List.to_atom([name]), modifiers: modifiers) do
1324              binary when is_binary(binary) ->
1325                [binary]
1326
1327              other ->
1328                raise ArgumentError,
1329                      "expected sigil callback to return a binary, got: #{inspect(other)}"
1330            end
1331
1332          %{} ->
1333            entries
1334        end
1335
1336      if opening_delimiter in [@double_heredoc, @single_heredoc] do
1337        closing_delimiter = concat(opening_delimiter, List.to_string(modifiers))
1338
1339        {doc, state} =
1340          entries
1341          |> prepend_heredoc_line()
1342          |> interpolation_to_algebra(opening_delimiter, state, doc, closing_delimiter)
1343
1344        {force_unfit(doc), state}
1345      else
1346        escape = closing_sigil_delimiter(opening_delimiter)
1347        closing_delimiter = concat(escape, List.to_string(modifiers))
1348        interpolation_to_algebra(entries, escape, state, doc, closing_delimiter)
1349      end
1350    else
1351      _ ->
1352        :error
1353    end
1354  end
1355
1356  defp closing_sigil_delimiter("("), do: ")"
1357  defp closing_sigil_delimiter("["), do: "]"
1358  defp closing_sigil_delimiter("{"), do: "}"
1359  defp closing_sigil_delimiter("<"), do: ">"
1360  defp closing_sigil_delimiter(other) when other in ["\"", "'", "|", "/"], do: other
1361
1362  ## Bitstrings
1363
1364  defp bitstring_to_algebra(meta, args, state) do
1365    last = length(args) - 1
1366    join = if eol?(meta, state), do: :line, else: :flex_break
1367    to_algebra_fun = &bitstring_segment_to_algebra(&1, &2, last)
1368
1369    {args_doc, join, state} =
1370      args
1371      |> Enum.with_index()
1372      |> args_to_algebra_with_comments(meta, false, :none, join, state, to_algebra_fun)
1373
1374    if join == :flex_break do
1375      {"<<" |> concat(args_doc) |> nest(2) |> concat(">>") |> group(), state}
1376    else
1377      {surround("<<", args_doc, ">>"), state}
1378    end
1379  end
1380
1381  defp bitstring_segment_to_algebra({{:<-, meta, [left, right]}, i}, state, last) do
1382    left = {{:special, :bitstring_segment}, meta, [left, last]}
1383    {doc, state} = quoted_to_algebra({:<-, meta, [left, right]}, :parens_arg, state)
1384    {bitstring_wrap_parens(doc, i, last), state}
1385  end
1386
1387  defp bitstring_segment_to_algebra({{:"::", _, [segment, spec]}, i}, state, last) do
1388    {doc, state} = quoted_to_algebra(segment, :parens_arg, state)
1389    {spec, state} = bitstring_spec_to_algebra(spec, state)
1390
1391    spec = wrap_in_parens_if_inspected_atom(spec)
1392    spec = if i == last, do: bitstring_wrap_parens(spec, i, last), else: spec
1393
1394    doc =
1395      doc
1396      |> bitstring_wrap_parens(i, -1)
1397      |> concat("::")
1398      |> concat(spec)
1399
1400    {doc, state}
1401  end
1402
1403  defp bitstring_segment_to_algebra({segment, i}, state, last) do
1404    {doc, state} = quoted_to_algebra(segment, :parens_arg, state)
1405    {bitstring_wrap_parens(doc, i, last), state}
1406  end
1407
1408  defp bitstring_spec_to_algebra({op, _, [left, right]}, state) when op in [:-, :*] do
1409    {left, state} = bitstring_spec_to_algebra(left, state)
1410    {right, state} = quoted_to_algebra_with_parens_if_operator(right, :parens_arg, state)
1411    {concat(concat(left, Atom.to_string(op)), right), state}
1412  end
1413
1414  defp bitstring_spec_to_algebra(spec, state) do
1415    quoted_to_algebra_with_parens_if_operator(spec, :parens_arg, state)
1416  end
1417
1418  defp bitstring_wrap_parens(doc, i, last) when i == 0 or i == last do
1419    string = format_to_string(doc)
1420
1421    if (i == 0 and String.starts_with?(string, ["~", "<<"])) or
1422         (i == last and String.ends_with?(string, [">>"])) do
1423      wrap_in_parens(doc)
1424    else
1425      doc
1426    end
1427  end
1428
1429  defp bitstring_wrap_parens(doc, _, _), do: doc
1430
1431  ## Literals
1432
1433  defp list_to_algebra(meta, args, state) do
1434    join = if eol?(meta, state), do: :line, else: :break
1435    fun = &quoted_to_algebra(&1, :parens_arg, &2)
1436
1437    {args_doc, _join, state} =
1438      args_to_algebra_with_comments(args, meta, false, :none, join, state, fun)
1439
1440    {surround("[", args_doc, "]"), state}
1441  end
1442
1443  defp map_to_algebra(meta, name_doc, [{:|, _, [left, right]}], state) do
1444    join = if eol?(meta, state), do: :line, else: :break
1445    fun = &quoted_to_algebra(&1, :parens_arg, &2)
1446    {left_doc, state} = fun.(left, state)
1447
1448    {right_doc, _join, state} =
1449      args_to_algebra_with_comments(right, meta, false, :none, join, state, fun)
1450
1451    args_doc =
1452      left_doc
1453      |> wrap_in_parens_if_binary_operator(left)
1454      |> glue(concat("| ", nest(right_doc, 2)))
1455
1456    name_doc = "%" |> concat(name_doc) |> concat("{")
1457    {surround(name_doc, args_doc, "}"), state}
1458  end
1459
1460  defp map_to_algebra(meta, name_doc, args, state) do
1461    join = if eol?(meta, state), do: :line, else: :break
1462    fun = &quoted_to_algebra(&1, :parens_arg, &2)
1463
1464    {args_doc, _join, state} =
1465      args_to_algebra_with_comments(args, meta, false, :none, join, state, fun)
1466
1467    name_doc = "%" |> concat(name_doc) |> concat("{")
1468    {surround(name_doc, args_doc, "}"), state}
1469  end
1470
1471  defp tuple_to_algebra(meta, args, join, state) do
1472    join = if eol?(meta, state), do: :line, else: join
1473    fun = &quoted_to_algebra(&1, :parens_arg, &2)
1474
1475    {args_doc, join, state} =
1476      args_to_algebra_with_comments(args, meta, false, :none, join, state, fun)
1477
1478    if join == :flex_break do
1479      {"{" |> concat(args_doc) |> nest(1) |> concat("}") |> group(), state}
1480    else
1481      {surround("{", args_doc, "}"), state}
1482    end
1483  end
1484
1485  defp atom_to_algebra(atom) when atom in [nil, true, false] do
1486    Atom.to_string(atom)
1487  end
1488
1489  # TODO: Remove this clause in v1.16 when we no longer quote operator :..//
1490  defp atom_to_algebra(:"..//") do
1491    string(":\"..//\"")
1492  end
1493
1494  defp atom_to_algebra(atom) do
1495    string = Atom.to_string(atom)
1496
1497    iodata =
1498      case Code.Identifier.classify(atom) do
1499        type when type in [:callable_local, :callable_operator, :not_callable] ->
1500          [?:, string]
1501
1502        _ ->
1503          [?:, ?", String.replace(string, "\"", "\\\""), ?"]
1504      end
1505
1506    iodata |> IO.iodata_to_binary() |> string()
1507  end
1508
1509  defp integer_to_algebra(text) do
1510    case text do
1511      <<?0, ?x, rest::binary>> ->
1512        "0x" <> String.upcase(rest)
1513
1514      <<?0, base, _::binary>> = digits when base in [?b, ?o] ->
1515        digits
1516
1517      <<??, _::binary>> = char ->
1518        char
1519
1520      decimal ->
1521        insert_underscores(decimal)
1522    end
1523  end
1524
1525  defp float_to_algebra(text) do
1526    [int_part, decimal_part] = :binary.split(text, ".")
1527    decimal_part = String.downcase(decimal_part)
1528    insert_underscores(int_part) <> "." <> decimal_part
1529  end
1530
1531  defp insert_underscores(digits) do
1532    cond do
1533      digits =~ "_" ->
1534        digits
1535
1536      byte_size(digits) >= 6 ->
1537        digits
1538        |> String.to_charlist()
1539        |> Enum.reverse()
1540        |> Enum.chunk_every(3)
1541        |> Enum.intersperse('_')
1542        |> List.flatten()
1543        |> Enum.reverse()
1544        |> List.to_string()
1545
1546      true ->
1547        digits
1548    end
1549  end
1550
1551  defp escape_heredoc(string, escape) do
1552    string = String.replace(string, escape, "\\" <> escape)
1553    heredoc_to_algebra(["" | String.split(string, "\n")])
1554  end
1555
1556  defp escape_string(string, <<_, _, _>> = escape) do
1557    string = String.replace(string, escape, "\\" <> escape)
1558    heredoc_to_algebra(String.split(string, "\n"))
1559  end
1560
1561  defp escape_string(string, escape) when is_binary(escape) do
1562    string
1563    |> String.replace(escape, "\\" <> escape)
1564    |> String.split("\n")
1565    |> Enum.reverse()
1566    |> Enum.map(&string/1)
1567    |> Enum.reduce(&concat(&1, concat(nest(line(), :reset), &2)))
1568  end
1569
1570  defp heredoc_to_algebra([string]) do
1571    string(string)
1572  end
1573
1574  defp heredoc_to_algebra(["" | rest]) do
1575    rest
1576    |> heredoc_line()
1577    |> concat(heredoc_to_algebra(rest))
1578  end
1579
1580  defp heredoc_to_algebra([string | rest]) do
1581    string
1582    |> string()
1583    |> concat(heredoc_line(rest))
1584    |> concat(heredoc_to_algebra(rest))
1585  end
1586
1587  defp heredoc_line(["", _ | _]), do: nest(line(), :reset)
1588  defp heredoc_line(_), do: line()
1589
1590  defp args_to_algebra_with_comments(args, meta, skip_parens?, last_arg_mode, join, state, fun) do
1591    min_line = line(meta)
1592    max_line = closing_line(meta)
1593
1594    arg_to_algebra = fn arg, args, state ->
1595      {doc, state} = fun.(arg, state)
1596
1597      doc =
1598        case args do
1599          [_ | _] -> concat_to_last_group(doc, ",")
1600          [] when last_arg_mode == :force_comma -> concat_to_last_group(doc, ",")
1601          [] when last_arg_mode == :next_break_fits -> next_break_fits(doc, :enabled)
1602          [] when last_arg_mode == :none -> doc
1603        end
1604
1605      {{doc, @empty, 1}, state}
1606    end
1607
1608    # If skipping parens, we cannot extract the comments of the first
1609    # argument as there is no place to move them to, so we handle it now.
1610    {args, acc, state} =
1611      case args do
1612        [head | tail] when skip_parens? ->
1613          {doc_triplet, state} = arg_to_algebra.(head, tail, state)
1614          {tail, [doc_triplet], state}
1615
1616        _ ->
1617          {args, [], state}
1618      end
1619
1620    {args_docs, comments?, state} =
1621      quoted_to_algebra_with_comments(args, acc, min_line, max_line, state, arg_to_algebra)
1622
1623    cond do
1624      args_docs == [] ->
1625        {@empty, :empty, state}
1626
1627      join == :line or comments? ->
1628        {args_docs |> Enum.reduce(&line(&2, &1)) |> force_unfit(), :line, state}
1629
1630      join == :break ->
1631        {args_docs |> Enum.reduce(&glue(&2, &1)), :break, state}
1632
1633      join == :flex_break ->
1634        {args_docs |> Enum.reduce(&flex_glue(&2, &1)), :flex_break, state}
1635    end
1636  end
1637
1638  ## Anonymous functions
1639
1640  # fn -> block end
1641  defp anon_fun_to_algebra(
1642         [{:->, meta, [[], body]}] = clauses,
1643         _min_line,
1644         max_line,
1645         state,
1646         _multi_clauses_style
1647       ) do
1648    min_line = line(meta)
1649    {body_doc, state} = block_to_algebra(body, min_line, max_line, state)
1650
1651    doc =
1652      "fn ->"
1653      |> glue(body_doc)
1654      |> nest(2)
1655      |> glue("end")
1656      |> maybe_force_clauses(clauses, state)
1657      |> group()
1658
1659    {doc, state}
1660  end
1661
1662  # fn x -> y end
1663  # fn x ->
1664  #   y
1665  # end
1666  defp anon_fun_to_algebra(
1667         [{:->, meta, [args, body]}] = clauses,
1668         _min_line,
1669         max_line,
1670         state,
1671         false = _multi_clauses_style
1672       ) do
1673    min_line = line(meta)
1674    {args_doc, state} = clause_args_to_algebra(args, min_line, state)
1675    {body_doc, state} = block_to_algebra(body, min_line, max_line, state)
1676
1677    head =
1678      args_doc
1679      |> ungroup_if_group()
1680      |> concat(" ->")
1681      |> nest(:cursor)
1682      |> group()
1683
1684    doc =
1685      "fn "
1686      |> concat(head)
1687      |> glue(body_doc)
1688      |> nest(2)
1689      |> glue("end")
1690      |> maybe_force_clauses(clauses, state)
1691      |> group()
1692
1693    {doc, state}
1694  end
1695
1696  # fn
1697  #   args1 ->
1698  #     block1
1699  #   args2 ->
1700  #     block2
1701  # end
1702  defp anon_fun_to_algebra(clauses, min_line, max_line, state, _multi_clauses_style) do
1703    {clauses_doc, state} = clauses_to_algebra(clauses, min_line, max_line, state)
1704    {"fn" |> line(clauses_doc) |> nest(2) |> line("end") |> force_unfit(), state}
1705  end
1706
1707  ## Type functions
1708
1709  # (() -> block)
1710  defp type_fun_to_algebra([{:->, meta, [[], body]}] = clauses, _min_line, max_line, state) do
1711    min_line = line(meta)
1712    {body_doc, state} = block_to_algebra(body, min_line, max_line, state)
1713
1714    doc =
1715      "(() -> "
1716      |> concat(nest(body_doc, :cursor))
1717      |> concat(")")
1718      |> maybe_force_clauses(clauses, state)
1719      |> group()
1720
1721    {doc, state}
1722  end
1723
1724  # (x -> y)
1725  # (x ->
1726  #    y)
1727  defp type_fun_to_algebra([{:->, meta, [args, body]}] = clauses, _min_line, max_line, state) do
1728    min_line = line(meta)
1729    {args_doc, state} = clause_args_to_algebra(args, min_line, state)
1730    {body_doc, state} = block_to_algebra(body, min_line, max_line, state)
1731
1732    doc =
1733      args_doc
1734      |> ungroup_if_group()
1735      |> concat(" ->")
1736      |> group()
1737      |> concat(break() |> concat(body_doc) |> nest(2))
1738      |> wrap_in_parens()
1739      |> maybe_force_clauses(clauses, state)
1740      |> group()
1741
1742    {doc, state}
1743  end
1744
1745  # (
1746  #   args1 ->
1747  #     block1
1748  #   args2 ->
1749  #     block2
1750  # )
1751  defp type_fun_to_algebra(clauses, min_line, max_line, state) do
1752    {clauses_doc, state} = clauses_to_algebra(clauses, min_line, max_line, state)
1753    {"(" |> line(clauses_doc) |> nest(2) |> line(")") |> force_unfit(), state}
1754  end
1755
1756  ## Clauses
1757
1758  defp maybe_force_clauses(doc, clauses, state) do
1759    if Enum.any?(clauses, fn {:->, meta, _} -> eol?(meta, state) end) do
1760      force_unfit(doc)
1761    else
1762      doc
1763    end
1764  end
1765
1766  defp clauses_to_algebra([{:->, _, _} | _] = clauses, min_line, max_line, state) do
1767    [clause | clauses] = add_max_line_to_last_clause(clauses, max_line)
1768    {clause_doc, state} = clause_to_algebra(clause, min_line, state)
1769
1770    {clauses_doc, state} =
1771      Enum.reduce(clauses, {clause_doc, state}, fn clause, {doc_acc, state_acc} ->
1772        {clause_doc, state_acc} = clause_to_algebra(clause, min_line, state_acc)
1773
1774        doc_acc =
1775          doc_acc
1776          |> concat(maybe_empty_line())
1777          |> line(clause_doc)
1778
1779        {doc_acc, state_acc}
1780      end)
1781
1782    {clauses_doc |> maybe_force_clauses([clause | clauses], state) |> group(), state}
1783  end
1784
1785  defp clauses_to_algebra(other, min_line, max_line, state) do
1786    case block_to_algebra(other, min_line, max_line, state) do
1787      {@empty, state} -> {@empty, state}
1788      {doc, state} -> {group(doc), state}
1789    end
1790  end
1791
1792  defp clause_to_algebra({:->, meta, [[], body]}, _min_line, state) do
1793    {body_doc, state} = block_to_algebra(body, line(meta), closing_line(meta), state)
1794    {"() ->" |> glue(body_doc) |> nest(2), state}
1795  end
1796
1797  defp clause_to_algebra({:->, meta, [args, body]}, min_line, state) do
1798    %{operand_nesting: nesting} = state
1799
1800    state = %{state | operand_nesting: nesting + 2}
1801    {args_doc, state} = clause_args_to_algebra(args, min_line, state)
1802
1803    state = %{state | operand_nesting: nesting}
1804    {body_doc, state} = block_to_algebra(body, min_line, closing_line(meta), state)
1805
1806    doc =
1807      args_doc
1808      |> ungroup_if_group()
1809      |> concat(" ->")
1810      |> group()
1811      |> concat(break() |> concat(body_doc) |> nest(2))
1812
1813    {doc, state}
1814  end
1815
1816  defp add_max_line_to_last_clause([{op, meta, args}], max_line) do
1817    [{op, [closing: [line: max_line]] ++ meta, args}]
1818  end
1819
1820  defp add_max_line_to_last_clause([clause | clauses], max_line) do
1821    [clause | add_max_line_to_last_clause(clauses, max_line)]
1822  end
1823
1824  defp clause_args_to_algebra(args, min_line, state) do
1825    arg_to_algebra = fn arg, _args, state ->
1826      {doc, state} = clause_args_to_algebra(arg, state)
1827      {{doc, @empty, 1}, state}
1828    end
1829
1830    {args_docs, comments?, state} =
1831      quoted_to_algebra_with_comments([args], [], min_line, @min_line, state, arg_to_algebra)
1832
1833    if comments? do
1834      {Enum.reduce(args_docs, &line(&2, &1)), state}
1835    else
1836      {Enum.reduce(args_docs, &glue(&2, &1)), state}
1837    end
1838  end
1839
1840  # fn a, b, c when d -> e end
1841  defp clause_args_to_algebra([{:when, meta, args}], state) do
1842    {args, right} = split_last(args)
1843    left = {{:special, :clause_args}, meta, [args]}
1844    binary_op_to_algebra(:when, "when", meta, left, right, :no_parens_arg, state)
1845  end
1846
1847  # fn () -> e end
1848  defp clause_args_to_algebra([], state) do
1849    {"()", state}
1850  end
1851
1852  # fn a, b, c -> e end
1853  defp clause_args_to_algebra(args, state) do
1854    many_args_to_algebra(args, state, &quoted_to_algebra(&1, :no_parens_arg, &2))
1855  end
1856
1857  ## Quoted helpers for comments
1858
1859  defp quoted_to_algebra_with_comments(args, acc, min_line, max_line, state, fun) do
1860    {pre_comments, state} =
1861      get_and_update_in(state.comments, fn comments ->
1862        Enum.split_while(comments, fn %{line: line} -> line <= min_line end)
1863      end)
1864
1865    {docs, comments?, state} =
1866      each_quoted_to_algebra_with_comments(args, acc, max_line, state, false, fun)
1867
1868    {docs, comments?, update_in(state.comments, &(pre_comments ++ &1))}
1869  end
1870
1871  defp each_quoted_to_algebra_with_comments([], acc, max_line, state, comments?, _fun) do
1872    {acc, comments, comments?} = extract_comments_before(max_line, acc, state.comments, comments?)
1873    args_docs = merge_algebra_with_comments(Enum.reverse(acc), @empty)
1874    {args_docs, comments?, %{state | comments: comments}}
1875  end
1876
1877  defp each_quoted_to_algebra_with_comments([arg | args], acc, max_line, state, comments?, fun) do
1878    case traverse_line(arg, {@max_line, @min_line}) do
1879      {@max_line, @min_line} ->
1880        {doc_triplet, state} = fun.(arg, args, state)
1881        acc = [doc_triplet | acc]
1882        each_quoted_to_algebra_with_comments(args, acc, max_line, state, comments?, fun)
1883
1884      {doc_start, doc_end} ->
1885        {acc, comments, comments?} =
1886          extract_comments_before(doc_start, acc, state.comments, comments?)
1887
1888        {doc_triplet, state} = fun.(arg, args, %{state | comments: comments})
1889
1890        {acc, comments, comments?} =
1891          extract_comments_trailing(doc_start, doc_end, acc, state.comments, comments?)
1892
1893        acc = [adjust_trailing_newlines(doc_triplet, doc_end, comments) | acc]
1894        state = %{state | comments: comments}
1895        each_quoted_to_algebra_with_comments(args, acc, max_line, state, comments?, fun)
1896    end
1897  end
1898
1899  defp extract_comments_before(max, acc, [%{line: line} = comment | rest], _) when line < max do
1900    %{previous_eol_count: previous, next_eol_count: next, text: doc} = comment
1901    acc = [{doc, @empty, next} | add_previous_to_acc(acc, previous)]
1902    extract_comments_before(max, acc, rest, true)
1903  end
1904
1905  defp extract_comments_before(_max, acc, rest, comments?) do
1906    {acc, rest, comments?}
1907  end
1908
1909  defp add_previous_to_acc([{doc, next_line, newlines} | acc], previous) when newlines < previous,
1910    do: [{doc, next_line, previous} | acc]
1911
1912  defp add_previous_to_acc(acc, _previous),
1913    do: acc
1914
1915  defp extract_comments_trailing(min, max, acc, [%{line: line, text: doc_comment} | rest], _)
1916       when line >= min and line <= max do
1917    acc = [{doc_comment, @empty, 1} | acc]
1918    extract_comments_trailing(min, max, acc, rest, true)
1919  end
1920
1921  defp extract_comments_trailing(_min, _max, acc, rest, comments?) do
1922    {acc, rest, comments?}
1923  end
1924
1925  # If the document is immediately followed by comment which is followed by newlines,
1926  # its newlines wouldn't have considered the comment, so we need to adjust it.
1927  defp adjust_trailing_newlines({doc, next_line, newlines}, doc_end, [%{line: line} | _])
1928       when newlines > 1 and line == doc_end + 1 do
1929    {doc, next_line, 1}
1930  end
1931
1932  defp adjust_trailing_newlines(doc_triplet, _, _), do: doc_triplet
1933
1934  defp traverse_line({expr, meta, args}, {min, max}) do
1935    acc =
1936      case Keyword.fetch(meta, :line) do
1937        {:ok, line} -> {min(line, min), max(line, max)}
1938        :error -> {min, max}
1939      end
1940
1941    traverse_line(args, traverse_line(expr, acc))
1942  end
1943
1944  defp traverse_line({left, right}, acc) do
1945    traverse_line(right, traverse_line(left, acc))
1946  end
1947
1948  defp traverse_line(args, acc) when is_list(args) do
1949    Enum.reduce(args, acc, &traverse_line/2)
1950  end
1951
1952  defp traverse_line(_, acc) do
1953    acc
1954  end
1955
1956  # Below are the rules for line rendering in the formatter:
1957  #
1958  #   1. respect the user's choice
1959  #   2. and add empty lines around expressions that take multiple lines
1960  #      (except for module attributes)
1961  #   3. empty lines are collapsed as to not exceed more than one
1962  #
1963  defp merge_algebra_with_comments([{doc, next_line, newlines} | docs], left) do
1964    right = if newlines >= @newlines, do: line(), else: next_line
1965
1966    doc =
1967      if left != @empty do
1968        concat(left, doc)
1969      else
1970        doc
1971      end
1972
1973    doc =
1974      if docs != [] and right != @empty do
1975        concat(doc, concat(collapse_lines(2), right))
1976      else
1977        doc
1978      end
1979
1980    [group(doc) | merge_algebra_with_comments(docs, right)]
1981  end
1982
1983  defp merge_algebra_with_comments([], _) do
1984    []
1985  end
1986
1987  ## Quoted helpers
1988
1989  defp left_op_context(context), do: force_many_args_or_operand(context, :parens_arg)
1990  defp right_op_context(context), do: force_many_args_or_operand(context, :operand)
1991
1992  defp force_many_args_or_operand(:no_parens_one_arg, _choice), do: :no_parens_arg
1993  defp force_many_args_or_operand(:parens_one_arg, _choice), do: :parens_arg
1994  defp force_many_args_or_operand(:no_parens_arg, _choice), do: :no_parens_arg
1995  defp force_many_args_or_operand(:parens_arg, _choice), do: :parens_arg
1996  defp force_many_args_or_operand(:operand, choice), do: choice
1997  defp force_many_args_or_operand(:block, choice), do: choice
1998
1999  defp quoted_to_algebra_with_parens_if_operator(ast, context, state) do
2000    {doc, state} = quoted_to_algebra(ast, context, state)
2001    {wrap_in_parens_if_operator(doc, ast), state}
2002  end
2003
2004  defp wrap_in_parens_if_operator(doc, {:__block__, _, [expr]}) do
2005    wrap_in_parens_if_operator(doc, expr)
2006  end
2007
2008  defp wrap_in_parens_if_operator(doc, quoted) do
2009    if operator?(quoted) and not module_attribute_read?(quoted) and not integer_capture?(quoted) do
2010      wrap_in_parens(doc)
2011    else
2012      doc
2013    end
2014  end
2015
2016  defp wrap_in_parens_if_binary_operator(doc, quoted) do
2017    if binary_operator?(quoted) do
2018      wrap_in_parens(doc)
2019    else
2020      doc
2021    end
2022  end
2023
2024  defp wrap_in_parens_if_inspected_atom(":" <> _ = doc) do
2025    "(" <> doc <> ")"
2026  end
2027
2028  defp wrap_in_parens_if_inspected_atom(doc) do
2029    doc
2030  end
2031
2032  defp wrap_in_parens(doc) do
2033    concat(concat("(", nest(doc, :cursor)), ")")
2034  end
2035
2036  defp many_args_to_algebra([arg | args], state, fun) do
2037    Enum.reduce(args, fun.(arg, state), fn arg, {doc_acc, state_acc} ->
2038      {arg_doc, state_acc} = fun.(arg, state_acc)
2039      {glue(concat(doc_acc, ","), arg_doc), state_acc}
2040    end)
2041  end
2042
2043  defp module_attribute_read?({:@, _, [{var, _, var_context}]})
2044       when is_atom(var) and is_atom(var_context) do
2045    Code.Identifier.classify(var) == :callable_local
2046  end
2047
2048  defp module_attribute_read?(_), do: false
2049
2050  defp integer_capture?({:&, _, [integer]}) when is_integer(integer), do: true
2051  defp integer_capture?(_), do: false
2052
2053  defp operator?(quoted) do
2054    unary_operator?(quoted) or binary_operator?(quoted)
2055  end
2056
2057  defp binary_operator?(quoted) do
2058    case quoted do
2059      {op, _, [_, _, _]} when op in @multi_binary_operators -> true
2060      {op, _, [_, _]} when is_atom(op) -> Code.Identifier.binary_op(op) != :error
2061      _ -> false
2062    end
2063  end
2064
2065  defp unary_operator?(quoted) do
2066    case quoted do
2067      {op, _, [_]} when is_atom(op) -> Code.Identifier.unary_op(op) != :error
2068      _ -> false
2069    end
2070  end
2071
2072  defp with_next_break_fits(condition, doc, fun) do
2073    if condition do
2074      doc
2075      |> next_break_fits(:enabled)
2076      |> fun.()
2077      |> next_break_fits(:disabled)
2078    else
2079      fun.(doc)
2080    end
2081  end
2082
2083  defp next_break_fits?({:{}, meta, _args}, state) do
2084    eol_or_comments?(meta, state)
2085  end
2086
2087  defp next_break_fits?({:__block__, meta, [{_, _}]}, state) do
2088    eol_or_comments?(meta, state)
2089  end
2090
2091  defp next_break_fits?({:<<>>, meta, [_ | _] = entries}, state) do
2092    meta[:delimiter] == ~s["""] or
2093      (not interpolated?(entries) and eol_or_comments?(meta, state))
2094  end
2095
2096  defp next_break_fits?({{:., _, [List, :to_charlist]}, meta, [[_ | _]]}, _state) do
2097    meta[:delimiter] == ~s[''']
2098  end
2099
2100  defp next_break_fits?({{:., _, [_left, :{}]}, _, _}, _state) do
2101    true
2102  end
2103
2104  defp next_break_fits?({:__block__, meta, [string]}, _state) when is_binary(string) do
2105    meta[:delimiter] == ~s["""]
2106  end
2107
2108  defp next_break_fits?({:__block__, meta, [list]}, _state) when is_list(list) do
2109    meta[:delimiter] != ~s[']
2110  end
2111
2112  defp next_break_fits?({form, _, [_ | _]}, _state) when form in [:fn, :%{}, :%] do
2113    true
2114  end
2115
2116  defp next_break_fits?({fun, meta, args}, _state) when is_atom(fun) and is_list(args) do
2117    meta[:delimiter] in [@double_heredoc, @single_heredoc] and
2118      fun |> Atom.to_string() |> String.starts_with?("sigil_")
2119  end
2120
2121  defp next_break_fits?({{:__block__, _, [atom]}, expr}, state) when is_atom(atom) do
2122    next_break_fits?(expr, state)
2123  end
2124
2125  defp next_break_fits?(_, _state) do
2126    false
2127  end
2128
2129  defp eol_or_comments?(meta, %{comments: comments} = state) do
2130    eol?(meta, state) or
2131      (
2132        min_line = line(meta)
2133        max_line = closing_line(meta)
2134        Enum.any?(comments, fn %{line: line} -> line > min_line and line < max_line end)
2135      )
2136  end
2137
2138  # A literal list is a keyword or (... -> ...)
2139  defp last_arg_to_keyword([_ | _] = arg, _list_to_keyword?, _skip_parens?, _comments) do
2140    {keyword?(arg), arg}
2141  end
2142
2143  # This is a list of tuples, it can be converted to keywords.
2144  defp last_arg_to_keyword(
2145         {:__block__, meta, [[_ | _] = arg]} = block,
2146         true,
2147         skip_parens?,
2148         comments
2149       ) do
2150    cond do
2151      not keyword?(arg) ->
2152        {false, block}
2153
2154      skip_parens? ->
2155        block_line = line(meta)
2156        {{_, arg_meta, _}, _} = hd(arg)
2157        first_line = line(arg_meta)
2158
2159        case Enum.drop_while(comments, fn %{line: line} -> line <= block_line end) do
2160          [%{line: line} | _] when line <= first_line ->
2161            {false, block}
2162
2163          _ ->
2164            {true, arg}
2165        end
2166
2167      true ->
2168        {true, arg}
2169    end
2170  end
2171
2172  # Otherwise we don't have a keyword.
2173  defp last_arg_to_keyword(arg, _list_to_keyword?, _skip_parens?, _comments) do
2174    {false, arg}
2175  end
2176
2177  defp force_args?(args) do
2178    match?([_ | _], args) and force_args?(args, %{})
2179  end
2180
2181  defp force_args?([[arg | _] | args], lines) do
2182    force_args?([arg | args], lines)
2183  end
2184
2185  defp force_args?([arg | args], lines) do
2186    line =
2187      case arg do
2188        {{_, meta, _}, _} -> meta[:line]
2189        {_, meta, _} -> meta[:line]
2190      end
2191
2192    cond do
2193      # Line may be missing from non-formatter AST
2194      is_nil(line) -> force_args?(args, lines)
2195      Map.has_key?(lines, line) -> false
2196      true -> force_args?(args, Map.put(lines, line, true))
2197    end
2198  end
2199
2200  defp force_args?([], lines), do: map_size(lines) >= 2
2201
2202  defp force_keyword(doc, arg) do
2203    if force_args?(arg), do: force_unfit(doc), else: doc
2204  end
2205
2206  defp keyword?([{_, _} | list]), do: keyword?(list)
2207  defp keyword?(rest), do: rest == []
2208
2209  defp keyword_key?({:__block__, meta, [atom]}) when is_atom(atom),
2210    do: meta[:format] == :keyword
2211
2212  defp keyword_key?({{:., _, [:erlang, :binary_to_atom]}, meta, [{:<<>>, _, _}, :utf8]}),
2213    do: meta[:format] == :keyword
2214
2215  defp keyword_key?(_),
2216    do: false
2217
2218  defp eol?(_meta, %{skip_eol: true}), do: false
2219  defp eol?(meta, _state), do: Keyword.get(meta, :newlines, 0) > 0
2220
2221  defp meta?(meta, key) do
2222    is_list(meta[key])
2223  end
2224
2225  defp line(meta) do
2226    meta[:line] || @max_line
2227  end
2228
2229  defp end_line(meta) do
2230    meta[:end][:line] || @min_line
2231  end
2232
2233  defp closing_line(meta) do
2234    meta[:closing][:line] || @min_line
2235  end
2236
2237  ## Algebra helpers
2238
2239  # Relying on the inner document is brittle and error prone.
2240  # It would be best if we had a mechanism to apply this.
2241  defp concat_to_last_group({:doc_cons, left, right}, concat) do
2242    {:doc_cons, left, concat_to_last_group(right, concat)}
2243  end
2244
2245  defp concat_to_last_group({:doc_group, group, mode}, concat) do
2246    {:doc_group, {:doc_cons, group, concat}, mode}
2247  end
2248
2249  defp concat_to_last_group(other, concat) do
2250    {:doc_cons, other, concat}
2251  end
2252
2253  defp ungroup_if_group({:doc_group, group, _mode}), do: group
2254  defp ungroup_if_group(other), do: other
2255
2256  defp format_to_string(doc) do
2257    doc |> Inspect.Algebra.format(:infinity) |> IO.iodata_to_binary()
2258  end
2259
2260  defp maybe_empty_line() do
2261    nest(break(""), :reset)
2262  end
2263
2264  defp surround(left, doc, right) do
2265    if doc == @empty do
2266      concat(left, right)
2267    else
2268      group(glue(nest(glue(left, "", doc), 2, :break), "", right))
2269    end
2270  end
2271
2272  defp nest_by_length(doc, string) do
2273    nest(doc, String.length(string))
2274  end
2275
2276  defp split_last(list) do
2277    {left, [right]} = Enum.split(list, -1)
2278    {left, right}
2279  end
2280end
2281