Skip to content

Commit b1053b7

Browse files
committed
Use binary appending now that we require Erlang/OTP 26
Prompt ====== There is a format/2 function in inspect/algebra.ex that calls format/3 recursively that returns a list of binaries. Instead of doing so, I want you to pass a binary as accumulator, <<>>, and then instead of `[head | format(...)]`, on every operation you will do `format(<<acc::binary, result::binary>>, ...)`. Notes ===== The assistant was able to detect an issue with `collapse/4` but it was unable to fix it. That and the changes to mix/tasks/format.ex were addressed manually.
1 parent b82d2df commit b1053b7

File tree

4 files changed

+103
-78
lines changed

4 files changed

+103
-78
lines changed

lib/elixir/lib/inspect/algebra.ex

Lines changed: 82 additions & 60 deletions
Original file line numberDiff line numberDiff line change
@@ -192,7 +192,7 @@ defmodule Inspect.Algebra do
192192
193193
iex> doc = Inspect.Algebra.concat(Inspect.Algebra.empty(), "foo")
194194
iex> Inspect.Algebra.format(doc, 80)
195-
["foo"]
195+
"foo"
196196
197197
The functions `nest/2`, `space/2` and `line/2` help you put the
198198
document together into a rigid structure. However, the document
@@ -205,15 +205,15 @@ defmodule Inspect.Algebra do
205205
iex> doc = Inspect.Algebra.glue("a", " ", "b")
206206
iex> doc = Inspect.Algebra.group(doc)
207207
iex> Inspect.Algebra.format(doc, 80)
208-
["a", " ", "b"]
208+
"a b"
209209
210210
Note that the break was represented as is, because we haven't reached
211211
a line limit. Once we do, it is replaced by a newline:
212212
213213
iex> doc = Inspect.Algebra.glue(String.duplicate("a", 20), " ", "b")
214214
iex> doc = Inspect.Algebra.group(doc)
215215
iex> Inspect.Algebra.format(doc, 10)
216-
["aaaaaaaaaaaaaaaaaaaa", "\n", "b"]
216+
"aaaaaaaaaaaaaaaaaaaa\nb"
217217
218218
This module uses the byte size to compute how much space there is
219219
left. If your document contains strings, then those need to be
@@ -279,7 +279,7 @@ defmodule Inspect.Algebra do
279279
quote do: [unquote(left) | unquote(right)]
280280
end
281281

282-
@typep doc_string :: {:doc_string, t, non_neg_integer}
282+
@typep doc_string :: {:doc_string, binary, non_neg_integer}
283283
defmacrop doc_string(string, length) do
284284
quote do: {:doc_string, unquote(string), unquote(length)}
285285
end
@@ -665,7 +665,7 @@ defmodule Inspect.Algebra do
665665
iex> doc = Inspect.Algebra.glue("olá", " ", "mundo")
666666
iex> doc = Inspect.Algebra.group(doc)
667667
iex> Inspect.Algebra.format(doc, 9)
668-
["olá", "\n", "mundo"]
668+
"olá\nmundo"
669669
670670
However, if we use `string`, then the string length is
671671
used, instead of byte size, correctly fitting:
@@ -674,7 +674,7 @@ defmodule Inspect.Algebra do
674674
iex> doc = Inspect.Algebra.glue(string, " ", "mundo")
675675
iex> doc = Inspect.Algebra.group(doc)
676676
iex> Inspect.Algebra.format(doc, 9)
677-
["olá", " ", "mundo"]
677+
"olá mundo"
678678
679679
"""
680680
@doc since: "1.6.0"
@@ -690,7 +690,7 @@ defmodule Inspect.Algebra do
690690
691691
iex> doc = Inspect.Algebra.concat("hello", "world")
692692
iex> Inspect.Algebra.format(doc, 80)
693-
["hello", "world"]
693+
"helloworld"
694694
695695
"""
696696
@spec concat(t, t) :: t
@@ -705,10 +705,10 @@ defmodule Inspect.Algebra do
705705
706706
iex> doc = Inspect.Algebra.glue("hello", "world") |> Inspect.Algebra.group()
707707
iex> Inspect.Algebra.format(doc, 10)
708-
["hello", "\n", "world"]
708+
"hello\nworld"
709709
iex> doc = Inspect.Algebra.no_limit(doc)
710710
iex> Inspect.Algebra.format(doc, 10)
711-
["hello", " ", "world"]
711+
"hello world"
712712
713713
"""
714714
@doc since: "1.14.0"
@@ -724,7 +724,7 @@ defmodule Inspect.Algebra do
724724
725725
iex> doc = Inspect.Algebra.concat(["a", "b", "c"])
726726
iex> Inspect.Algebra.format(doc, 80)
727-
["a", "b", "c"]
727+
"abc"
728728
729729
"""
730730
@spec concat([t]) :: t
@@ -758,7 +758,7 @@ defmodule Inspect.Algebra do
758758
iex> doc = Inspect.Algebra.nest(Inspect.Algebra.glue("hello", "world"), 5)
759759
iex> doc = Inspect.Algebra.group(doc)
760760
iex> Inspect.Algebra.format(doc, 5)
761-
["hello", "\n ", "world"]
761+
"hello\n world"
762762
763763
"""
764764
@spec nest(t, non_neg_integer | :cursor | :reset, :always | :break) :: doc_nest | t
@@ -794,7 +794,7 @@ defmodule Inspect.Algebra do
794794
795795
iex> doc = Inspect.Algebra.concat(["a", Inspect.Algebra.break("\t"), "b"])
796796
iex> Inspect.Algebra.format(doc, 80)
797-
["a", "\t", "b"]
797+
"a\tb"
798798
799799
Note that the break was represented with the given string, because we didn't
800800
reach a line limit. Once we do, it is replaced by a newline:
@@ -803,7 +803,7 @@ defmodule Inspect.Algebra do
803803
iex> doc = Inspect.Algebra.concat([String.duplicate("a", 20), break, "b"])
804804
iex> doc = Inspect.Algebra.group(doc)
805805
iex> Inspect.Algebra.format(doc, 10)
806-
["aaaaaaaaaaaaaaaaaaaa", "\n", "b"]
806+
"aaaaaaaaaaaaaaaaaaaa\nb"
807807
808808
"""
809809
@spec break(binary) :: doc_break
@@ -898,11 +898,11 @@ defmodule Inspect.Algebra do
898898
899899
iex> doc = Inspect.Algebra.glue("hello", "world")
900900
iex> Inspect.Algebra.format(doc, 80)
901-
["hello", " ", "world"]
901+
"hello world"
902902
903903
iex> doc = Inspect.Algebra.glue("hello", "\t", "world")
904904
iex> Inspect.Algebra.format(doc, 80)
905-
["hello", "\t", "world"]
905+
"hello\tworld"
906906
907907
"""
908908
@spec glue(t, binary, t) :: t
@@ -961,9 +961,9 @@ defmodule Inspect.Algebra do
961961
...> )
962962
...> )
963963
iex> Inspect.Algebra.format(doc, 80)
964-
["Hello,", " ", "A", " ", "B"]
964+
"Hello, A B"
965965
iex> Inspect.Algebra.format(doc, 6)
966-
["Hello,", "\n", "A", "\n", "B"]
966+
"Hello,\nA\nB"
967967
968968
## Mode examples
969969
@@ -1018,7 +1018,7 @@ defmodule Inspect.Algebra do
10181018
10191019
iex> doc = Inspect.Algebra.space("Hughes", "Wadler")
10201020
iex> Inspect.Algebra.format(doc, 5)
1021-
["Hughes", " ", "Wadler"]
1021+
"Hughes Wadler"
10221022
10231023
"""
10241024
@spec space(t, t) :: t
@@ -1040,7 +1040,7 @@ defmodule Inspect.Algebra do
10401040
...> "Wadler"
10411041
...> )
10421042
iex> Inspect.Algebra.format(doc, 80)
1043-
["Hughes", "\n", "Wadler"]
1043+
"Hughes\nWadler"
10441044
10451045
"""
10461046
@doc since: "1.6.0"
@@ -1056,7 +1056,7 @@ defmodule Inspect.Algebra do
10561056
10571057
iex> doc = Inspect.Algebra.line("Hughes", "Wadler")
10581058
iex> Inspect.Algebra.format(doc, 80)
1059-
["Hughes", "\n", "Wadler"]
1059+
"Hughes\nWadler"
10601060
10611061
"""
10621062
@spec line(t, t) :: t
@@ -1081,7 +1081,7 @@ defmodule Inspect.Algebra do
10811081
...> Inspect.Algebra.concat([doc, "!", acc])
10821082
...> end)
10831083
iex> Inspect.Algebra.format(docs, 80)
1084-
["A", "!", "B", "!", "C"]
1084+
"A!B!C"
10851085
10861086
"""
10871087
@doc since: "1.18.0"
@@ -1115,7 +1115,7 @@ defmodule Inspect.Algebra do
11151115
"""
11161116
@spec format(t, non_neg_integer | :infinity) :: iodata
11171117
def format(doc, width) when is_doc(doc) and is_width(width) do
1118-
format(width, 0, [{0, :flat, doc}])
1118+
format(width, 0, [{0, :flat, doc}], <<>>)
11191119
end
11201120

11211121
# Type representing the document mode to be rendered:
@@ -1225,95 +1225,117 @@ defmodule Inspect.Algebra do
12251225
@spec format(
12261226
width :: non_neg_integer() | :infinity,
12271227
column :: non_neg_integer(),
1228-
[{integer, mode, t} | :group_over]
1229-
) :: [binary]
1230-
defp format(_, _, []), do: []
1231-
defp format(w, k, [{_, _, doc_nil()} | t]), do: format(w, k, t)
1232-
defp format(w, _, [{i, _, doc_line()} | t]), do: [indent(i) | format(w, i, t)]
1233-
defp format(w, k, [{i, m, doc_cons(x, y)} | t]), do: format(w, k, [{i, m, x}, {i, m, y} | t])
1234-
defp format(w, k, [{i, m, doc_color(x, c)} | t]), do: [c | format(w, k, [{i, m, x} | t])]
1235-
defp format(w, k, [{_, _, doc_string(s, l)} | t]), do: [s | format(w, k + l, t)]
1236-
defp format(w, k, [{_, _, s} | t]) when is_binary(s), do: [s | format(w, k + byte_size(s), t)]
1237-
defp format(w, k, [{i, m, doc_force(x)} | t]), do: format(w, k, [{i, m, x} | t])
1238-
defp format(w, k, [{i, m, doc_fits(x, _)} | t]), do: format(w, k, [{i, m, x} | t])
1239-
defp format(w, _, [{i, _, doc_collapse(max)} | t]), do: collapse(format(w, i, t), max, 0, i)
1228+
[{integer, mode, t} | :group_over],
1229+
binary
1230+
) :: iodata
1231+
defp format(_, _, [], acc), do: acc
1232+
1233+
defp format(w, k, [{_, _, doc_nil()} | t], acc),
1234+
do: format(w, k, t, acc)
1235+
1236+
defp format(w, _, [{i, _, doc_line()} | t], acc),
1237+
do: format(w, i, t, <<acc::binary, indent(i)::binary>>)
1238+
1239+
defp format(w, k, [{i, m, doc_cons(x, y)} | t], acc),
1240+
do: format(w, k, [{i, m, x}, {i, m, y} | t], acc)
1241+
1242+
defp format(w, k, [{i, m, doc_color(x, c)} | t], acc),
1243+
do: format(w, k, [{i, m, x} | t], <<acc::binary, c::binary>>)
1244+
1245+
defp format(w, k, [{_, _, doc_string(s, l)} | t], acc),
1246+
do: format(w, k + l, t, <<acc::binary, s::binary>>)
1247+
1248+
defp format(w, k, [{_, _, s} | t], acc) when is_binary(s),
1249+
do: format(w, k + byte_size(s), t, <<acc::binary, s::binary>>)
1250+
1251+
defp format(w, k, [{i, m, doc_force(x)} | t], acc),
1252+
do: format(w, k, [{i, m, x} | t], acc)
1253+
1254+
defp format(w, k, [{i, m, doc_fits(x, _)} | t], acc),
1255+
do: format(w, k, [{i, m, x} | t], acc)
1256+
1257+
defp format(w, _, [{i, _, doc_collapse(max)} | t], acc),
1258+
do: [acc | collapse(List.wrap(format(w, i, t, <<>>)), max, 0, i)]
12401259

12411260
# Flex breaks are conditional to the document and the mode
1242-
defp format(w, k, [{i, m, doc_break(s, :flex)} | t]) do
1261+
defp format(w, k, [{i, m, doc_break(s, :flex)} | t], acc) do
12431262
k = k + byte_size(s)
12441263

12451264
if w == :infinity or m == :flat or fits?(w, k, true, t) do
1246-
[s | format(w, k, t)]
1265+
format(w, k, t, <<acc::binary, s::binary>>)
12471266
else
1248-
[indent(i) | format(w, i, t)]
1267+
format(w, i, t, <<acc::binary, indent(i)::binary>>)
12491268
end
12501269
end
12511270

12521271
# Strict breaks are conditional to the mode
1253-
defp format(w, k, [{i, mode, doc_break(s, :strict)} | t]) do
1272+
defp format(w, k, [{i, mode, doc_break(s, :strict)} | t], acc) do
12541273
if mode == :break do
1255-
[indent(i) | format(w, i, t)]
1274+
format(w, i, t, <<acc::binary, indent(i)::binary>>)
12561275
else
1257-
[s | format(w, k + byte_size(s), t)]
1276+
format(w, k + byte_size(s), t, <<acc::binary, s::binary>>)
12581277
end
12591278
end
12601279

12611280
# Nesting is conditional to the mode.
1262-
defp format(w, k, [{i, mode, doc_nest(x, j, nest)} | t]) do
1281+
defp format(w, k, [{i, mode, doc_nest(x, j, nest)} | t], acc) do
12631282
if nest == :always or (nest == :break and mode == :break) do
1264-
format(w, k, [{apply_nesting(i, k, j), mode, x} | t])
1283+
format(w, k, [{apply_nesting(i, k, j), mode, x} | t], acc)
12651284
else
1266-
format(w, k, [{i, mode, x} | t])
1285+
format(w, k, [{i, mode, x} | t], acc)
12671286
end
12681287
end
12691288

12701289
# Groups must do the fitting decision.
1271-
defp format(w, k, [:group_over | t]) do
1272-
format(w, k, t)
1290+
defp format(w, k, [:group_over | t], acc) do
1291+
format(w, k, t, acc)
12731292
end
12741293

12751294
# TODO: Deprecate me in Elixir v1.23
1276-
defp format(w, k, [{i, :break, doc_group(x, :inherit)} | t]) do
1277-
format(w, k, [{i, :break, x} | t])
1295+
defp format(w, k, [{i, :break, doc_group(x, :inherit)} | t], acc) do
1296+
format(w, k, [{i, :break, x} | t], acc)
12781297
end
12791298

1280-
defp format(w, k, [{i, :flat, doc_group(x, :optimistic)} | t]) do
1299+
defp format(w, k, [{i, :flat, doc_group(x, :optimistic)} | t], acc) do
12811300
if w == :infinity or fits?(w, k, false, [{i, :flat, x} | t]) do
1282-
format(w, k, [{i, :flat, x}, :group_over | t])
1301+
format(w, k, [{i, :flat, x}, :group_over | t], acc)
12831302
else
1284-
format(w, k, [{i, :break, x}, :group_over | t])
1303+
format(w, k, [{i, :break, x}, :group_over | t], acc)
12851304
end
12861305
end
12871306

1288-
defp format(w, k, [{i, _, doc_group(x, _)} | t]) do
1307+
defp format(w, k, [{i, _, doc_group(x, _)} | t], acc) do
12891308
if w == :infinity or fits?(w, k, false, [{i, :flat, x}]) do
1290-
format(w, k, [{i, :flat, x}, :group_over | t])
1309+
format(w, k, [{i, :flat, x}, :group_over | t], acc)
12911310
else
1292-
format(w, k, [{i, :break, x}, :group_over | t])
1311+
format(w, k, [{i, :break, x}, :group_over | t], acc)
12931312
end
12941313
end
12951314

12961315
# Limit is set to infinity and then reverts
1297-
defp format(w, k, [{i, m, doc_limit(x, :infinity)} | t]) when w != :infinity do
1298-
format(:infinity, k, [{i, :flat, x}, {i, m, doc_limit(empty(), w)} | t])
1316+
defp format(w, k, [{i, m, doc_limit(x, :infinity)} | t], acc) when w != :infinity do
1317+
format(:infinity, k, [{i, :flat, x}, {i, m, doc_limit(empty(), w)} | t], acc)
12991318
end
13001319

1301-
defp format(_w, k, [{i, m, doc_limit(x, w)} | t]) do
1302-
format(w, k, [{i, m, x} | t])
1320+
defp format(_w, k, [{i, m, doc_limit(x, w)} | t], acc) do
1321+
format(w, k, [{i, m, x} | t], acc)
13031322
end
13041323

1305-
defp collapse(["\n" <> _ | t], max, count, i) do
1306-
collapse(t, max, count + 1, i)
1324+
defp collapse(["\n" <> rest | t], max, count, i) do
1325+
collapse([strip_whitespace(rest) | t], max, count + 1, i)
13071326
end
13081327

13091328
defp collapse(["" | t], max, count, i) do
13101329
collapse(t, max, count, i)
13111330
end
13121331

13131332
defp collapse(t, max, count, i) do
1314-
[:binary.copy("\n", min(max, count)) <> :binary.copy(" ", i) | t]
1333+
[:binary.copy("\n", min(max, count)), :binary.copy(" ", i) | t]
13151334
end
13161335

1336+
defp strip_whitespace(" " <> rest), do: strip_whitespace(rest)
1337+
defp strip_whitespace(rest), do: rest
1338+
13171339
defp apply_nesting(_, k, :cursor), do: k
13181340
defp apply_nesting(_, _, :reset), do: 0
13191341
defp apply_nesting(i, _, j), do: i + j

lib/elixir/test/elixir/code_test.exs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -546,7 +546,7 @@ defmodule CodeTest do
546546
end
547547

548548
test "format_string/2 returns empty iodata for empty string" do
549-
assert Code.format_string!("") == []
549+
assert Code.format_string!("") == ""
550550
end
551551

552552
test "ensure_loaded?/1" do

0 commit comments

Comments
 (0)