Skip to content

Commit 4f5a221

Browse files
authored
Fix Erlang Scanning & Warnings (#1818)
* Move autolink function parsing to language specific part This makes it so that we do not have to deal with parsing Erlang using the Elixir parser, things that are keywords in Elixir are not in Erlang and vice versa. The most recent example I came across was `c:do/1` which is valid in Erlang but not in Elixir. * Parse Erlang module names using erl_scan to make things consistent * Add correct line numbers to Erlang link warnings * Warning on undefined types and callbacks in Erlang * Fix warnings for un-implemented see links
1 parent f1cebca commit 4f5a221

File tree

5 files changed

+246
-64
lines changed

5 files changed

+246
-64
lines changed

Diff for: lib/ex_doc/autolink.ex

+18-26
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,9 @@ defmodule ExDoc.Autolink do
77
# * `:current_module` - the module that the docs are being generated for. Used to link local
88
# calls and see if remote calls are in the same app.
99
#
10+
# * `:current_kfa` - the kind, function, arity that the docs are being generated for. Is nil
11+
# if there is no such thing. Used to generate more accurate warnings.
12+
#
1013
# * `:module_id` - id of the module being documented (e.g.: `"String"`)
1114
#
1215
# * `:file` - source file location
@@ -48,6 +51,7 @@ defmodule ExDoc.Autolink do
4851
extras: [],
4952
deps: [],
5053
ext: ".html",
54+
current_kfa: nil,
5155
siblings: [],
5256
skip_undefined_reference_warnings_on: [],
5357
skip_code_autolink_to: [],
@@ -371,29 +375,6 @@ defmodule ExDoc.Autolink do
371375
end
372376
end
373377

374-
# There are special forms that are forbidden by the tokenizer
375-
def parse_function("__aliases__"), do: {:function, :__aliases__}
376-
def parse_function("__block__"), do: {:function, :__block__}
377-
def parse_function("%"), do: {:function, :%}
378-
379-
def parse_function(string) do
380-
case Code.string_to_quoted("& #{string}/0", warnings: false) do
381-
{:ok, {:&, _, [{:/, _, [{:__aliases__, _, [function]}, 0]}]}} when is_atom(function) ->
382-
## When function starts with capital letter
383-
{:function, function}
384-
385-
## When function is 'nil'
386-
{:ok, {:&, _, [{:/, _, [nil, 0]}]}} ->
387-
{:function, nil}
388-
389-
{:ok, {:&, _, [{:/, _, [{function, _, _}, 0]}]}} when is_atom(function) ->
390-
{:function, function}
391-
392-
_ ->
393-
:error
394-
end
395-
end
396-
397378
def kind("c:" <> rest), do: {:callback, rest}
398379
def kind("t:" <> rest), do: {:type, rest}
399380
## \\ does not work for :custom_url as Earmark strips the \...
@@ -432,7 +413,7 @@ defmodule ExDoc.Autolink do
432413
{:type, _visibility} ->
433414
case config.language.try_builtin_type(name, arity, mode, config, original_text) do
434415
nil ->
435-
if mode == :custom_link do
416+
if mode == :custom_link or config.language == ExDoc.Language.Erlang do
436417
maybe_warn(config, ref, visibility, %{original_text: original_text})
437418
end
438419

@@ -501,7 +482,9 @@ defmodule ExDoc.Autolink do
501482

502483
nil
503484

504-
{:regular_link, _module_visibility, :undefined} when not same_module? ->
485+
{:regular_link, _module_visibility, :undefined}
486+
when not same_module? and
487+
(config.language != ExDoc.Language.Erlang or kind == :function) ->
505488
nil
506489

507490
{_mode, _module_visibility, visibility} ->
@@ -518,7 +501,16 @@ defmodule ExDoc.Autolink do
518501
# TODO: Remove on Elixir v1.14
519502
stacktrace_info =
520503
if unquote(Version.match?(System.version(), ">= 1.14.0")) do
521-
[file: config.file, line: config.line]
504+
f =
505+
case config.current_kfa do
506+
{:function, f, a} ->
507+
[function: {f, a}]
508+
509+
_ ->
510+
[]
511+
end
512+
513+
[file: config.file, line: config.line, module: config.current_module] ++ f
522514
else
523515
[]
524516
end

Diff for: lib/ex_doc/formatter/html.ex

+17-2
Original file line numberDiff line numberDiff line change
@@ -92,7 +92,15 @@ defmodule ExDoc.Formatter.HTML do
9292
docs =
9393
for child_node <- node.docs do
9494
id = id(node, child_node)
95-
autolink_opts = autolink_opts ++ [id: id, line: child_node.doc_line]
95+
96+
autolink_opts =
97+
autolink_opts ++
98+
[
99+
id: id,
100+
line: child_node.doc_line,
101+
current_kfa: {:function, child_node.name, child_node.arity}
102+
]
103+
96104
specs = Enum.map(child_node.specs, &language.autolink_spec(&1, autolink_opts))
97105
child_node = %{child_node | specs: specs}
98106
render_doc(child_node, language, autolink_opts, opts)
@@ -101,7 +109,14 @@ defmodule ExDoc.Formatter.HTML do
101109
typespecs =
102110
for child_node <- node.typespecs do
103111
id = id(node, child_node)
104-
autolink_opts = autolink_opts ++ [id: id, line: child_node.doc_line]
112+
113+
autolink_opts =
114+
autolink_opts ++
115+
[
116+
id: id,
117+
line: child_node.doc_line,
118+
current_kfa: {child_node.type, child_node.name, child_node.arity}
119+
]
105120

106121
child_node = %{
107122
child_node

Diff for: lib/ex_doc/language/elixir.ex

+17-2
Original file line numberDiff line numberDiff line change
@@ -267,7 +267,7 @@ defmodule ExDoc.Language.Elixir do
267267
def parse_module_function(string) do
268268
case string |> String.split(".") |> Enum.reverse() do
269269
[string] ->
270-
with {:function, function} <- Autolink.parse_function(string) do
270+
with {:function, function} <- parse_function(string) do
271271
{:local, function}
272272
end
273273

@@ -298,12 +298,27 @@ defmodule ExDoc.Language.Elixir do
298298
module_string = rest |> Enum.reverse() |> Enum.join(".")
299299

300300
with {:module, module} <- parse_module(module_string, :custom_link),
301-
{:function, function} <- Autolink.parse_function(function_string) do
301+
{:function, function} <- parse_function(function_string) do
302302
{:remote, module, function}
303303
end
304304
end
305305
end
306306

307+
# There are special forms that are forbidden by the tokenizer
308+
defp parse_function("__aliases__"), do: {:function, :__aliases__}
309+
defp parse_function("__block__"), do: {:function, :__block__}
310+
defp parse_function("%"), do: {:function, :%}
311+
312+
defp parse_function(string) do
313+
case Code.string_to_quoted("& #{string}/0", warnings: false) do
314+
{:ok, {:&, _, [{:/, _, [{function, _, _}, 0]}]}} when is_atom(function) ->
315+
{:function, function}
316+
317+
_ ->
318+
:error
319+
end
320+
end
321+
307322
@impl true
308323
def parse_module(<<first>> <> _ = string, _mode) when first in ?A..?Z do
309324
if string =~ ~r/^[A-Za-z0-9_.]+$/ do

Diff for: lib/ex_doc/language/erlang.ex

+34-17
Original file line numberDiff line numberDiff line change
@@ -262,6 +262,8 @@ defmodule ExDoc.Language.Erlang do
262262
end
263263

264264
defp walk_doc({:code, attrs, [code], meta} = ast, config) when is_binary(code) do
265+
config = %{config | line: meta[:line]}
266+
265267
case Autolink.url(code, :regular_link, config) do
266268
url when is_binary(url) ->
267269
code = remove_prefix(code)
@@ -279,11 +281,11 @@ defmodule ExDoc.Language.Erlang do
279281

280282
case String.split(url, ":") do
281283
[module] ->
282-
walk_doc({:a, [href: "`m:#{module}#{fragment}`"], inner, meta}, config)
284+
walk_doc({:a, [href: "`m:#{maybe_quote(module)}#{fragment}`"], inner, meta}, config)
283285

284286
[app, module] ->
285287
inner = strip_app(inner, app)
286-
walk_doc({:a, [href: "`m:#{module}#{fragment}`"], inner, meta}, config)
288+
walk_doc({:a, [href: "`m:#{maybe_quote(module)}#{fragment}`"], inner, meta}, config)
287289

288290
_ ->
289291
warn_ref(attrs[:href], config)
@@ -333,7 +335,7 @@ defmodule ExDoc.Language.Erlang do
333335
walk_doc({:a, [href: "`t:#{fixup(type)}`"], inner, meta}, config)
334336

335337
"https://erlang.org/doc/link/" <> see ->
336-
warn_ref(attrs[:href] <> " (#{see})", config)
338+
warn_ref(attrs[:href] <> " (#{see})", %{config | id: nil})
337339
inner
338340

339341
_ ->
@@ -372,13 +374,21 @@ defmodule ExDoc.Language.Erlang do
372374
end
373375

374376
defp fixup(mfa) do
375-
case String.split(mfa, "#") do
376-
["", mfa] ->
377-
mfa
377+
{m, fa} =
378+
case String.split(mfa, "#") do
379+
["", mfa] ->
380+
{"", mfa}
378381

379-
[m, fa] ->
380-
m <> ":" <> fa
381-
end
382+
[m, fa] ->
383+
{"#{maybe_quote(m)}:", fa}
384+
end
385+
386+
[f, a] = String.split(fa, "/")
387+
m <> maybe_quote(f) <> "/" <> a
388+
end
389+
390+
defp maybe_quote(m) do
391+
to_string(:io_lib.write_atom(String.to_atom(m)))
382392
end
383393

384394
defp strip_app([{:code, attrs, [code], meta}], app) do
@@ -413,12 +423,12 @@ defmodule ExDoc.Language.Erlang do
413423
case String.split(string, ":") do
414424
[module_string, function_string] ->
415425
with {:module, module} <- parse_module_string(module_string, :custom_link),
416-
{:function, function} <- Autolink.parse_function(function_string) do
426+
{:function, function} <- parse_function(function_string) do
417427
{:remote, module, function}
418428
end
419429

420430
[function_string] ->
421-
with {:function, function} <- Autolink.parse_function(function_string) do
431+
with {:function, function} <- parse_function(function_string) do
422432
{:local, function}
423433
end
424434

@@ -427,6 +437,16 @@ defmodule ExDoc.Language.Erlang do
427437
end
428438
end
429439

440+
defp parse_function(string) do
441+
with {:ok, toks, _} <- :erl_scan.string(String.to_charlist("fun #{string}/0.")),
442+
{:ok, [{:fun, _, {:function, name, _arity}}]} <- :erl_parse.parse_exprs(toks) do
443+
{:function, name}
444+
else
445+
_ ->
446+
:error
447+
end
448+
end
449+
430450
@impl true
431451
def try_autoimported_function(name, arity, mode, config, original_text) do
432452
if :erl_internal.bif(name, arity) do
@@ -464,12 +484,9 @@ defmodule ExDoc.Language.Erlang do
464484
end
465485
end
466486

467-
def parse_module_string(string, _mode) do
468-
case Code.string_to_quoted(":'#{string}'",
469-
warn_on_unnecessary_quotes: false,
470-
emit_warnings: false
471-
) do
472-
{:ok, module} when is_atom(module) ->
487+
defp parse_module_string(string, _mode) do
488+
case :erl_scan.string(String.to_charlist(string)) do
489+
{:ok, [{:atom, _, module}], _} when is_atom(module) ->
473490
{:module, module}
474491

475492
_ ->

0 commit comments

Comments
 (0)