Skip to content

Commit e87cc66

Browse files
authored
Allow updated options to be returned from Inspect protocol (#14554)
1 parent 85e068e commit e87cc66

File tree

6 files changed

+166
-66
lines changed

6 files changed

+166
-66
lines changed

lib/elixir/lib/inspect.ex

Lines changed: 38 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -99,8 +99,10 @@ defprotocol Inspect do
9999
You can also define your custom protocol implementation by
100100
defining the `inspect/2` function. The function receives the
101101
entity to be inspected followed by the inspecting options,
102-
represented by the struct `Inspect.Opts`. Building of the
103-
algebra document is done with `Inspect.Algebra`.
102+
represented by the struct `Inspect.Opts` and it must return
103+
an algebra document alongside the updated options (or, optionally,
104+
just the algebra document). Building of the algebra document
105+
is done with `Inspect.Algebra`.
104106
105107
Many times, inspecting a structure can be implemented in function
106108
of existing entities. For example, here is `MapSet`'s `inspect/2`
@@ -110,7 +112,8 @@ defprotocol Inspect do
110112
import Inspect.Algebra
111113
112114
def inspect(map_set, opts) do
113-
concat(["MapSet.new(", Inspect.List.inspect(MapSet.to_list(map_set), opts), ")"])
115+
{doc, opts} = Inspect.List.inspect(MapSet.to_list(map_set), opts)
116+
{concat(["MapSet.new(", doc, ")"]), opts}
114117
end
115118
end
116119
@@ -148,6 +151,9 @@ defprotocol Inspect do
148151
149152
Inspect.MapSet.inspect(MapSet.new(), %Inspect.Opts{})
150153
154+
Note that, from Elixir v1.19, the inspect protocol was augmented to
155+
allow a two-element tuple with the document and the updated options
156+
to be returned from the protocol.
151157
"""
152158

153159
# Handle structs in Any
@@ -261,7 +267,8 @@ defprotocol Inspect do
261267
`Inspect.Algebra.to_doc/2` should be preferred as it handles structs
262268
and exceptions.
263269
"""
264-
@spec inspect(t, Inspect.Opts.t()) :: Inspect.Algebra.t()
270+
@spec inspect(t, Inspect.Opts.t()) ::
271+
Inspect.Algebra.t() | {Inspect.Algebra.t(), Inspect.Opts.t()}
265272
def inspect(term, opts)
266273
end
267274

@@ -303,11 +310,13 @@ defimpl Inspect, for: BitString do
303310
color_doc("<<>>", :binary, opts)
304311
end
305312

306-
defp inspect_bitstring(bitstring, opts) do
313+
defp inspect_bitstring(bitstring, %{limit: limit} = opts) do
307314
left = color_doc("<<", :binary, opts)
308315
right = color_doc(">>", :binary, opts)
309-
inner = each_bit(bitstring, opts.limit, opts)
310-
group(concat(concat(left, nest(inner, 2)), right))
316+
inner = each_bit(bitstring, limit, opts)
317+
doc = group(concat(concat(left, nest(inner, 2)), right))
318+
new_limit = if limit == :infinity, do: limit, else: max(0, limit - byte_size(bitstring))
319+
{doc, %{opts | limit: new_limit}}
311320
end
312321

313322
defp each_bit(_, 0, _) do
@@ -388,17 +397,21 @@ defimpl Inspect, for: List do
388397
color_doc(IO.iodata_to_binary(inspected), :charlist, opts)
389398

390399
keyword?(term) ->
391-
container_doc(open, term, close, opts, &keyword/2, separator: sep, break: :strict)
400+
container_doc_with_opts(open, term, close, opts, &keyword/2,
401+
separator: sep,
402+
break: :strict
403+
)
392404

393405
true ->
394-
container_doc(open, term, close, opts, &to_doc/2, separator: sep)
406+
container_doc_with_opts(open, term, close, opts, &to_doc_with_opts/2, separator: sep)
395407
end
396408
end
397409

398410
@doc false
399411
def keyword({key, value}, opts) do
400412
key = color_doc(Macro.inspect_atom(:key, key), :atom, opts)
401-
concat(key, concat(" ", to_doc(value, opts)))
413+
{doc, opts} = to_doc_with_opts(value, opts)
414+
{concat(key, concat(" ", doc)), opts}
402415
end
403416

404417
@doc false
@@ -419,7 +432,15 @@ defimpl Inspect, for: Tuple do
419432
sep = color_doc(",", :tuple, opts)
420433
close = color_doc("}", :tuple, opts)
421434
container_opts = [separator: sep, break: :flex]
422-
container_doc(open, Tuple.to_list(tuple), close, opts, &to_doc/2, container_opts)
435+
436+
container_doc_with_opts(
437+
open,
438+
Tuple.to_list(tuple),
439+
close,
440+
opts,
441+
&to_doc_with_opts/2,
442+
container_opts
443+
)
423444
end
424445
end
425446

@@ -453,14 +474,16 @@ defimpl Inspect, for: Map do
453474
end
454475

455476
defp to_assoc({key, value}, opts, sep) do
456-
concat(concat(to_doc(key, opts), sep), to_doc(value, opts))
477+
{key_doc, opts} = to_doc_with_opts(key, opts)
478+
{value_doc, opts} = to_doc_with_opts(value, opts)
479+
{concat(concat(key_doc, sep), value_doc), opts}
457480
end
458481

459482
defp map_container_doc(list, name, opts, fun) do
460483
open = color_doc("%" <> name <> "{", :map, opts)
461484
sep = color_doc(",", :map, opts)
462485
close = color_doc("}", :map, opts)
463-
container_doc(open, list, close, opts, fun, separator: sep, break: :strict)
486+
container_doc_with_opts(open, list, close, opts, fun, separator: sep, break: :strict)
464487
end
465488
end
466489

@@ -518,9 +541,9 @@ defimpl Inspect, for: Regex do
518541
:error ->
519542
concat([
520543
"Regex.compile!(",
521-
Inspect.BitString.inspect(regex.source, opts),
544+
to_doc(regex.source, opts),
522545
", ",
523-
Inspect.List.inspect(regex_opts, opts),
546+
to_doc(regex_opts, opts),
524547
")"
525548
])
526549

lib/elixir/lib/inspect/algebra.ex

Lines changed: 102 additions & 44 deletions
Original file line numberDiff line numberDiff line change
@@ -46,9 +46,8 @@ defmodule Inspect.Opts do
4646
* `:limit` - limits the number of items that are inspected for tuples,
4747
bitstrings, maps, lists and any other collection of items, with the exception of
4848
printable strings and printable charlists which use the `:printable_limit` option.
49-
If you don't want to limit the number of items to a particular number,
50-
use `:infinity`. It accepts a positive integer or `:infinity`.
51-
Defaults to `50`.
49+
It accepts a positive integer or `:infinity`. It defaults to 100 since
50+
`Elixir v1.19.0`, as it has better defaults to deal with nested collections.
5251
5352
* `:pretty` - if set to `true` enables pretty printing. Defaults to `false`.
5453
@@ -91,7 +90,7 @@ defmodule Inspect.Opts do
9190
charlists: :infer,
9291
custom_options: [],
9392
inspect_fun: &Inspect.inspect/2,
94-
limit: 50,
93+
limit: 100,
9594
pretty: false,
9695
printable_limit: 4096,
9796
safe: true,
@@ -332,7 +331,6 @@ defmodule Inspect.Algebra do
332331
when is_binary(doc) or doc in [:doc_nil, :doc_line] or
333332
(is_tuple(doc) and elem(doc, 0) in @docs)
334333

335-
defguardp is_limit(limit) when limit == :infinity or (is_integer(limit) and limit >= 0)
336334
defguardp is_width(width) when width == :infinity or (is_integer(width) and width >= 0)
337335

338336
# Elixir + Inspect.Opts conveniences
@@ -341,11 +339,28 @@ defmodule Inspect.Algebra do
341339
@doc """
342340
Converts an Elixir term to an algebra document
343341
according to the `Inspect` protocol.
342+
343+
In practice, one must prefer to use `to_doc_with_opts/2`
344+
over this function, as `to_doc_with_opts/2` returns the
345+
updated options from inspection.
344346
"""
345347
@spec to_doc(any, Inspect.Opts.t()) :: t
346-
def to_doc(term, opts)
348+
def to_doc(term, opts) do
349+
to_doc_with_opts(term, opts) |> elem(0)
350+
end
351+
352+
@doc """
353+
Converts an Elixir term to an algebra document
354+
according to the `Inspect` protocol, alongside the updated options.
355+
356+
This function is used when implementing the inspect protocol for
357+
a given type and you must convert nested terms to documents too.
358+
"""
359+
@doc since: "1.19.0"
360+
@spec to_doc_with_opts(any, Inspect.Opts.t()) :: {t, Inspect.Opts.t()}
361+
def to_doc_with_opts(term, opts)
347362

348-
def to_doc(%_{} = struct, %Inspect.Opts{inspect_fun: fun} = opts) do
363+
def to_doc_with_opts(%_{} = struct, %Inspect.Opts{inspect_fun: fun} = opts) do
349364
if opts.structs do
350365
try do
351366
fun.(struct, opts)
@@ -363,13 +378,15 @@ defmodule Inspect.Algebra do
363378
try do
364379
Process.put(:inspect_trap, true)
365380

366-
inspected_struct =
367-
struct
368-
|> Inspect.Map.inspect_as_map(%{
381+
{doc_struct, _opts} =
382+
Inspect.Map.inspect_as_map(struct, %{
369383
opts
370384
| syntax_colors: [],
371385
inspect_fun: Inspect.Opts.default_inspect_fun()
372386
})
387+
388+
inspected_struct =
389+
doc_struct
373390
|> format(opts.width)
374391
|> IO.iodata_to_binary()
375392

@@ -394,10 +411,29 @@ defmodule Inspect.Algebra do
394411
else
395412
Inspect.Map.inspect_as_map(struct, opts)
396413
end
414+
|> pack_opts(opts)
415+
end
416+
417+
def to_doc_with_opts(arg, %Inspect.Opts{inspect_fun: fun} = opts) do
418+
fun.(arg, opts) |> pack_opts(opts)
397419
end
398420

399-
def to_doc(arg, %Inspect.Opts{inspect_fun: fun} = opts) do
400-
fun.(arg, opts)
421+
defp pack_opts({_doc, %Inspect.Opts{}} = doc_opts, _opts), do: doc_opts
422+
defp pack_opts(doc, opts), do: {doc, opts}
423+
424+
@doc ~S"""
425+
Wraps `collection` in `left` and `right` according to limit and contents
426+
and returns only the container document.
427+
428+
In practice, one must prefer to use `container_doc_with_opts/6`
429+
over this function, as `container_doc_with_opts/6` returns the
430+
updated options from inspection.
431+
"""
432+
@doc since: "1.6.0"
433+
@spec container_doc(t, [term], t, Inspect.Opts.t(), (term, Inspect.Opts.t() -> t), keyword()) ::
434+
t
435+
def container_doc(left, collection, right, inspect_opts, fun, opts \\ []) do
436+
container_doc_with_opts(left, collection, right, inspect_opts, fun, opts) |> elem(0)
401437
end
402438

403439
@doc ~S"""
@@ -412,6 +448,8 @@ defmodule Inspect.Algebra do
412448
The limit in the given `inspect_opts` is respected and when reached this
413449
function stops processing and outputs `"..."` instead.
414450
451+
It returns a tuple with the algebra document and the updated options.
452+
415453
## Options
416454
417455
* `:separator` - the separator used between each doc
@@ -423,79 +461,99 @@ defmodule Inspect.Algebra do
423461
424462
iex> inspect_opts = %Inspect.Opts{limit: :infinity}
425463
iex> fun = fn i, _opts -> to_string(i) end
426-
iex> doc = Inspect.Algebra.container_doc("[", Enum.to_list(1..5), "]", inspect_opts, fun)
464+
iex> {doc, _opts} = Inspect.Algebra.container_doc_with_opts("[", Enum.to_list(1..5), "]", inspect_opts, fun)
427465
iex> Inspect.Algebra.format(doc, 5) |> IO.iodata_to_binary()
428466
"[1,\n 2,\n 3,\n 4,\n 5]"
429467
430468
iex> inspect_opts = %Inspect.Opts{limit: 3}
431469
iex> fun = fn i, _opts -> to_string(i) end
432-
iex> doc = Inspect.Algebra.container_doc("[", Enum.to_list(1..5), "]", inspect_opts, fun)
470+
iex> {doc, _opts} = Inspect.Algebra.container_doc_with_opts("[", Enum.to_list(1..5), "]", inspect_opts, fun)
433471
iex> Inspect.Algebra.format(doc, 20) |> IO.iodata_to_binary()
434472
"[1, 2, 3, ...]"
435473
436474
iex> inspect_opts = %Inspect.Opts{limit: 3}
437475
iex> fun = fn i, _opts -> to_string(i) end
438476
iex> opts = [separator: "!"]
439-
iex> doc = Inspect.Algebra.container_doc("[", Enum.to_list(1..5), "]", inspect_opts, fun, opts)
477+
iex> {doc, _opts} = Inspect.Algebra.container_doc_with_opts("[", Enum.to_list(1..5), "]", inspect_opts, fun, opts)
440478
iex> Inspect.Algebra.format(doc, 20) |> IO.iodata_to_binary()
441479
"[1! 2! 3! ...]"
442480
443481
"""
444-
@doc since: "1.6.0"
445-
@spec container_doc(t, [term], t, Inspect.Opts.t(), (term, Inspect.Opts.t() -> t), keyword()) ::
446-
t
447-
def container_doc(left, collection, right, inspect_opts, fun, opts \\ [])
482+
@doc since: "1.19.0"
483+
@spec container_doc_with_opts(
484+
t,
485+
[term],
486+
t,
487+
Inspect.Opts.t(),
488+
(term, Inspect.Opts.t() -> t),
489+
keyword()
490+
) ::
491+
{t, Inspect.Opts.t()}
492+
def container_doc_with_opts(left, collection, right, inspect_opts, fun, opts \\ [])
448493
when is_doc(left) and is_list(collection) and is_doc(right) and is_function(fun, 2) and
449494
is_list(opts) do
450495
case collection do
451496
[] ->
452-
concat(left, right)
497+
{concat(left, right), inspect_opts}
453498

454499
_ ->
455500
break = Keyword.get(opts, :break, :maybe)
456501
separator = Keyword.get(opts, :separator, @container_separator)
457502

458-
{docs, simple?} =
459-
container_each(collection, inspect_opts.limit, inspect_opts, fun, [], break == :maybe)
503+
{docs, simple?, inspect_opts} =
504+
container_each(collection, inspect_opts, fun, [], break == :maybe)
460505

461506
flex? = simple? or break == :flex
462507
docs = fold(docs, &join(&1, &2, flex?, separator))
463508

464-
case flex? do
465-
true -> group(concat(concat(left, nest(docs, 1)), right))
466-
false -> group(glue(nest(glue(left, "", docs), 2), "", right))
467-
end
509+
group =
510+
case flex? do
511+
true -> group(concat(concat(left, nest(docs, 1)), right))
512+
false -> group(glue(nest(glue(left, "", docs), 2), "", right))
513+
end
514+
515+
{group, inspect_opts}
468516
end
469517
end
470518

471-
defp container_each([], _limit, _opts, _fun, acc, simple?) do
472-
{:lists.reverse(acc), simple?}
519+
defp container_each([], opts, _fun, acc, simple?) do
520+
{:lists.reverse(acc), simple?, opts}
473521
end
474522

475-
defp container_each(_, 0, _opts, _fun, acc, simple?) do
476-
{:lists.reverse(["..." | acc]), simple?}
523+
defp container_each(_, opts, _fun, acc, simple?) when opts.limit <= 0 do
524+
{:lists.reverse(["..." | acc]), simple?, opts}
477525
end
478526

479-
defp container_each([term | terms], limit, opts, fun, acc, simple?)
480-
when is_list(terms) and is_limit(limit) do
481-
new_limit = decrement(limit)
482-
doc = fun.(term, %{opts | limit: new_limit})
483-
limit = if doc == :doc_nil, do: limit, else: new_limit
484-
container_each(terms, limit, opts, fun, [doc | acc], simple? and simple?(doc))
527+
defp container_each([term | terms], opts, fun, acc, simple?) when is_list(terms) do
528+
{doc, opts} = call_container_fun(fun, term, opts)
529+
container_each(terms, opts, fun, [doc | acc], simple? and simple?(doc))
485530
end
486531

487-
defp container_each([left | right], limit, opts, fun, acc, simple?) when is_limit(limit) do
488-
limit = decrement(limit)
489-
left = fun.(left, %{opts | limit: limit})
490-
right = fun.(right, %{opts | limit: limit})
532+
defp container_each([left | right], opts, fun, acc, simple?) do
533+
{left, opts} = call_container_fun(fun, left, opts)
534+
{right, _opts} = call_container_fun(fun, right, opts)
491535
simple? = simple? and simple?(left) and simple?(right)
492-
493536
doc = join(left, right, simple?, @tail_separator)
494-
{:lists.reverse([doc | acc]), simple?}
537+
{:lists.reverse([doc | acc]), simple?, opts}
538+
end
539+
540+
defp call_container_fun(fun, term, %{limit: bounded} = opts)
541+
when bounded <= 0 or bounded == :infinity do
542+
case fun.(term, opts) do
543+
{doc, %Inspect.Opts{} = opts} -> {doc, opts}
544+
doc -> {doc, opts}
545+
end
495546
end
496547

497-
defp decrement(:infinity), do: :infinity
498-
defp decrement(counter), do: counter - 1
548+
defp call_container_fun(fun, term, %{limit: limit} = opts) do
549+
changed_opts = %{opts | limit: limit - 1}
550+
551+
case fun.(term, changed_opts) do
552+
{doc, %Inspect.Opts{} = opts} -> {doc, opts}
553+
:doc_nil -> {:doc_nil, opts}
554+
doc -> {doc, changed_opts}
555+
end
556+
end
499557

500558
defp join(:doc_nil, :doc_nil, _, _), do: :doc_nil
501559
defp join(left, :doc_nil, _, _), do: left

lib/elixir/lib/map_set.ex

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -445,8 +445,12 @@ defmodule MapSet do
445445
import Inspect.Algebra
446446

447447
def inspect(map_set, %Inspect.Opts{} = opts) do
448-
opts = %{opts | charlists: :as_lists}
449-
concat(["MapSet.new(", Inspect.List.inspect(MapSet.to_list(map_set), opts), ")"])
448+
{doc, %{limit: limit}} =
449+
map_set
450+
|> MapSet.to_list()
451+
|> to_doc_with_opts(%{opts | charlists: :as_lists})
452+
453+
{concat(["MapSet.new(", doc, ")"]), %{opts | limit: limit}}
450454
end
451455
end
452456
end

0 commit comments

Comments
 (0)