@@ -3,8 +3,9 @@ defmodule ExDoc.AutolinkTest do
3
3
doctest ExDoc.Autolink
4
4
import ExUnit.CaptureIO
5
5
6
- defp sigil_t ( text , [ ] ) do
7
- { :code , [ ] , [ text ] }
6
+ defp sigil_m ( text , [ ] ) do
7
+ [ { :p , _ , [ ast ] } ] = ExDoc.Markdown . to_ast ( text , [ ] )
8
+ ast
8
9
end
9
10
10
11
setup do
@@ -14,35 +15,38 @@ defmodule ExDoc.AutolinkTest do
14
15
15
16
describe "doc/3" do
16
17
test "elixir stdlib module" do
17
- assert autolinked ( ~t" String" ) == "https://hexdocs.pm/elixir/String.html"
18
- assert autolinked ( ~t" Elixir.String" ) == "https://hexdocs.pm/elixir/String.html"
18
+ assert autolink ( "String" ) == ~m" [`String`](https://hexdocs.pm/elixir/String.html)"
19
+
20
+ assert autolink ( "Elixir.String" ) ==
21
+ ~m" [`Elixir.String`](https://hexdocs.pm/elixir/String.html)"
19
22
end
20
23
21
24
test "other elixir core module" do
22
- assert autolinked ( ~t" IEx.Helpers" ) == "https://hexdocs.pm/iex/IEx.Helpers.html"
25
+ assert autolink ( "IEx.Helpers" ) ==
26
+ ~m" [`IEx.Helpers`](https://hexdocs.pm/iex/IEx.Helpers.html)"
23
27
end
24
28
25
29
test "private module" do
26
- assert_unchanged ( ~t " String.Unicode" )
30
+ assert_unchanged ( "String.Unicode" )
27
31
end
28
32
29
33
test "erlang module" do
30
- assert_unchanged ( ~t " :array" )
34
+ assert_unchanged ( ":array" )
31
35
end
32
36
33
37
test "unknown module" do
34
- assert_unchanged ( ~t " Unknown" )
35
- assert_unchanged ( ~t " :unknown" )
38
+ assert_unchanged ( "Unknown" )
39
+ assert_unchanged ( ":unknown" )
36
40
end
37
41
38
42
test "project-local module" do
39
43
ExDoc.Refs . insert ( [
40
44
{ { :module , Foo } , true }
41
45
] )
42
46
43
- assert autolinked ( ~t " Foo" ) == " Foo.html"
44
- assert autolinked ( ~t " String" , app: :elixir ) == " String.html"
45
- assert autolinked ( ~t " Foo" , current_module: Foo ) == " #content"
47
+ assert autolink ( "Foo" ) == ~m " [` Foo`](Foo .html) "
48
+ assert autolink ( "String" , app: :elixir ) == ~m " [` String`](String .html) "
49
+ assert autolink ( "Foo" , current_module: Foo ) == ~m " [`Foo`]( #content) "
46
50
end
47
51
48
52
test "remote function" do
@@ -51,23 +55,24 @@ defmodule ExDoc.AutolinkTest do
51
55
{ { :function , Foo , :foo , 1 } , true }
52
56
] )
53
57
54
- assert autolinked ( ~t " Foo.foo/1" ) == " Foo.html#foo/1"
58
+ assert autolink ( "Foo.foo/1" ) == ~m " [` Foo.foo/1`](Foo. html#foo/1) "
55
59
56
- assert_unchanged ( ~t " Bad.bar/1" )
60
+ assert_unchanged ( "Bad.bar/1" )
57
61
end
58
62
59
63
test "elixir stdlib function" do
60
- assert autolinked ( ~t " String.upcase/2" ) ==
61
- " https://hexdocs.pm/elixir/String.html#upcase/2"
64
+ assert autolink ( "String.upcase/2" ) ==
65
+ ~m " [`String.upcase/2`]( https://hexdocs.pm/elixir/String.html#upcase/2) "
62
66
end
63
67
64
68
test "elixir function with default argument" do
65
- assert autolinked ( ~t" Enum.join/1" ) == "https://hexdocs.pm/elixir/Enum.html#join/1"
69
+ assert autolink ( "Enum.join/1" ) ==
70
+ ~m" [`Enum.join/1`](https://hexdocs.pm/elixir/Enum.html#join/1)"
66
71
end
67
72
68
73
test "erlang stdlib function" do
69
- assert autolinked ( ~t " :lists.all/2" ) ==
70
- " http://www.erlang.org/doc/man/lists.html#all-2"
74
+ assert autolink ( ":lists.all/2" ) ==
75
+ ~m " [`:lists.all/2`]( http://www.erlang.org/doc/man/lists.html#all-2) "
71
76
end
72
77
73
78
test "local function" do
@@ -76,130 +81,131 @@ defmodule ExDoc.AutolinkTest do
76
81
{ { :function , Foo , :foo , 1 } , true }
77
82
] )
78
83
79
- assert autolinked ( ~t " foo/1" , current_module: Foo ) == " #foo/1"
80
- assert_unchanged ( ~t " bar/1" , current_module: Foo )
84
+ assert autolink ( "foo/1" , current_module: Foo ) == ~m " [`foo/1`]( #foo/1) "
85
+ assert_unchanged ( "bar/1" , current_module: Foo )
81
86
end
82
87
83
88
test "elixir callback" do
84
- assert autolinked ( ~t" c:GenServer.handle_call/3" ) ==
85
- "https://hexdocs.pm/elixir/GenServer.html#c:handle_call/3"
89
+ assert autolink ( "c:GenServer.handle_call/3" ) ==
90
+ ~m" [`c:GenServer.handle_call/3`](https://hexdocs.pm/elixir/GenServer.html#c:handle_call/3)"
91
+
92
+ # TODO: there should be no `c:` in the link _text_!
93
+ # assert autolink("c:GenServer.handle_call/3") ==
94
+ # ~m"[`GenServer.handle_call/3`](https://hexdocs.pm/elixir/GenServer.html#c:handle_call/3)"
86
95
end
87
96
88
- # TODO: enable when OTP 23.0-rc2 is out (it should have callbacks support)
89
- # test "erlang callback" do
90
- # assert autolinked(~t"c::gen_server.handle_call/3") ==
91
- # "http://www.erlang.org/doc/man/gen_server.html#Module:handle_call-3"
92
- # end
97
+ test "erlang callback" do
98
+ assert autolink ( "c::gen_server.handle_call/3" ) ==
99
+ ~m" [`c::gen_server.handle_call/3`](http://www.erlang.org/doc/man/gen_server.html#Module:handle_call-3)"
100
+ end
93
101
94
102
test "elixir type" do
95
- assert autolinked ( ~t " t:Calendar.date/0" ) ==
96
- " https://hexdocs.pm/elixir/Calendar.html#t:date/0"
103
+ assert autolink ( "t:Calendar.date/0" ) ==
104
+ ~m " [`t:Calendar.date/0`]( https://hexdocs.pm/elixir/Calendar.html#t:date/0) "
97
105
end
98
106
99
107
test "elixir basic & built-in types" do
100
- assert autolinked ( ~t " t:atom/0" ) ==
101
- " https://hexdocs.pm/elixir/typespecs.html#basic-types"
108
+ assert autolink ( "t:atom/0" ) ==
109
+ ~m " [`t:atom/0`]( https://hexdocs.pm/elixir/typespecs.html#basic-types) "
102
110
103
- assert autolinked ( ~t " t:keyword/0" ) ==
104
- " https://hexdocs.pm/elixir/typespecs.html#built-in-types"
111
+ assert autolink ( "t:keyword/0" ) ==
112
+ ~m " [`t:keyword/0`]( https://hexdocs.pm/elixir/typespecs.html#built-in-types) "
105
113
106
- assert autolinked ( ~t " t:keyword/0" , app: :elixir ) ==
107
- " typespecs.html#built-in-types"
114
+ assert autolink ( "t:keyword/0" , app: :elixir ) ==
115
+ ~m " [`t:keyword/0`]( typespecs.html#built-in-types) "
108
116
end
109
117
110
118
test "erlang type" do
111
- assert autolinked ( ~t " t::array.array/0" ) ==
112
- " http://www.erlang.org/doc/man/array.html#type-array"
119
+ assert autolink ( "t::array.array/0" ) ==
120
+ ~m " [`t::array.array/0`]( http://www.erlang.org/doc/man/array.html#type-array) "
113
121
end
114
122
115
123
test "special forms" do
116
- assert autolinked ( ~t " __block__/1" , current_module: Kernel.SpecialForms ) ==
117
- " #__block__/1"
124
+ assert autolink ( "__block__/1" , current_module: Kernel.SpecialForms ) ==
125
+ ~m " [`__block__/1`]( #__block__/1) "
118
126
119
- assert autolinked ( ~t " __aliases__/1" , current_module: Kernel.SpecialForms ) ==
120
- " #__aliases__/1"
127
+ assert autolink ( "__aliases__/1" , current_module: Kernel.SpecialForms ) ==
128
+ ~m " [`__aliases__/1`]( #__aliases__/1) "
121
129
end
122
130
123
131
test "escaping" do
124
- assert autolinked ( ~t " Kernel.SpecialForms.\" %{}\" /1" ) ==
125
- " https://hexdocs.pm/elixir/Kernel.SpecialForms.html#%25%7B%7D/1"
132
+ assert autolink ( "Kernel.SpecialForms.%{}/1" ) ==
133
+ ~m " [`Kernel.SpecialForms.%{}/1`]( https://hexdocs.pm/elixir/Kernel.SpecialForms.html#%25%7B%7D/1) "
126
134
127
- assert autolinked ( ~t " Kernel.SpecialForms.{}/1" ) ==
128
- " https://hexdocs.pm/elixir/Kernel.SpecialForms.html#%7B%7D/1"
135
+ assert autolink ( "Kernel.SpecialForms.{}/1" ) ==
136
+ ~m " [`Kernel.SpecialForms.{}/1`]( https://hexdocs.pm/elixir/Kernel.SpecialForms.html#%7B%7D/1) "
129
137
130
- assert autolinked ( ~t " Kernel.SpecialForms.\" <<>>\" /1" ) ==
131
- " https://hexdocs.pm/elixir/Kernel.SpecialForms.html#%3C%3C%3E%3E/1"
138
+ assert autolink ( "Kernel.SpecialForms.<<>>/1" ) ==
139
+ ~m " [`Kernel.SpecialForms.<<>>/1`]( https://hexdocs.pm/elixir/Kernel.SpecialForms.html#%3C%3C%3E%3E/1) "
132
140
end
133
141
134
142
test "custom link" do
135
- assert autolinked ( { :a , [ href: "`String`" ] , [ " custom" , " text" ] } ) ==
136
- " https://hexdocs.pm/elixir/String.html"
143
+ assert autolink ( ~m " [ custom text](`String`) " ) ==
144
+ ~m " [custom text]( https://hexdocs.pm/elixir/String.html) "
137
145
138
- assert autolinked ( { :a , [ href: " `:lists`" ] , [ "custom" , "text" ] } ) ==
139
- " http://www.erlang.org/doc/man/lists.html"
146
+ assert autolink ( ~m " [custom text]( `:lists`) " ) ==
147
+ ~m " [custom text]( http://www.erlang.org/doc/man/lists.html) "
140
148
141
- assert autolinked ( { :a , [ href: " `:lists.all/2`" ] , [ "custom" , "text" ] } ) ==
142
- " http://www.erlang.org/doc/man/lists.html#all-2"
149
+ assert autolink ( ~m " [custom text]( `:lists.all/2`) " ) ==
150
+ ~m " [custom text]( http://www.erlang.org/doc/man/lists.html#all-2) "
143
151
144
152
# TODO: with custom links and backticks there are no false positives (you
145
153
# always mean to link) so we should always warn on mismatches?
146
154
# Though backticks are markdown specific, is that ok?
147
155
# assert_warn(fn ->
148
- assert autolinked ( { :a , [ href: "`unknown`" ] , [ "custom" , "text" ] } ) ==
149
- "`unknown`"
156
+ assert_unchanged ( ~m" [custom text](`Unknown`)" )
150
157
end
151
158
152
159
test "mix task" do
153
- assert autolinked ( ~t " mix compile.elixir" ) ==
154
- " https://hexdocs.pm/mix/Mix.Tasks.Compile.Elixir.html"
160
+ assert autolink ( "mix compile.elixir" ) ==
161
+ ~m " [`mix compile.elixir`]( https://hexdocs.pm/mix/Mix.Tasks.Compile.Elixir.html) "
155
162
156
- assert autolinked ( ~t " mix help compile.elixir" ) ==
157
- " https://hexdocs.pm/mix/Mix.Tasks.Compile.Elixir.html"
163
+ assert autolink ( "mix help compile.elixir" ) ==
164
+ ~m " [`mix help compile.elixir`]( https://hexdocs.pm/mix/Mix.Tasks.Compile.Elixir.html) "
158
165
159
- assert autolinked ( ~t " mix help help" ) ==
160
- " https://hexdocs.pm/mix/Mix.Tasks.Help.html"
166
+ assert autolink ( "mix help help" ) ==
167
+ ~m " [`mix help help`]( https://hexdocs.pm/mix/Mix.Tasks.Help.html) "
161
168
162
- assert autolinked ( ~t " mix compile.elixir" , app: :mix ) ==
163
- " Mix.Tasks.Compile.Elixir.html"
169
+ assert autolink ( "mix compile.elixir" , app: :mix ) ==
170
+ ~m " [`mix compile.elixir`]( Mix.Tasks.Compile.Elixir.html) "
164
171
165
- assert_unchanged ( ~t " mix compile.elixir --verbose" )
172
+ assert_unchanged ( "mix compile.elixir --verbose" )
166
173
167
- assert_unchanged ( ~t " mix unknown.task" )
174
+ assert_unchanged ( "mix unknown.task" )
168
175
end
169
176
170
177
test "3rd party links" do
171
- assert autolinked ( ~t " Earmark.as_ast/2" ) ==
172
- " https://hexdocs.pm/earmark/Earmark.html#as_ast/2"
178
+ assert autolink ( "Earmark.as_ast/2" ) ==
179
+ ~m " [`Earmark.as_ast/2`]( https://hexdocs.pm/earmark/Earmark.html#as_ast/2) "
173
180
174
- assert_unchanged ( ~t " :test_module.foo/0" )
181
+ assert_unchanged ( ":test_module.foo/0" )
175
182
end
176
183
177
184
test "extras" do
178
185
opts = [ extras: [ "Foo Bar.md" ] ]
179
186
180
- assert autolinked ( { :a , [ href: " Foo Bar.md" ] , [ "Foo" ] } , opts ) == " foo-bar.html"
187
+ assert autolink ( ~m " [ Foo](Foo Bar.md) " , opts ) == ~m " [Foo]( foo-bar.html) "
181
188
182
- assert autolinked ( { :a , [ href: "Foo Bar.md" ] , [ "Foo" ] } , [ ext: ".xhtml" ] ++ opts ) ==
183
- "foo-bar.xhtml"
189
+ assert autolink ( ~m" [Foo](Foo Bar.md)" , [ ext: ".xhtml" ] ++ opts ) == ~m" [Foo](foo-bar.xhtml)"
184
190
185
- assert autolinked ( { :a , [ href: " Foo Bar.md#baz" ] , [ "Foo" ] } , opts ) == " foo-bar.html#baz"
191
+ assert autolink ( ~m " [ Foo](Foo Bar.md#baz) " , opts ) == ~m " [Foo]( foo-bar.html#baz) "
186
192
187
- assert_unchanged ( { :a , [ href: " http://example.com/foo.md" ] , [ "Foo" ] } , opts )
193
+ assert_unchanged ( ~m " [Foo]( http://example.com/foo.md) " , opts )
188
194
189
- assert_unchanged ( { :a , [ href: "#baz" ] , [ " Foo" ] } , opts )
195
+ assert_unchanged ( ~m " [ Foo](#baz) " , opts )
190
196
end
191
197
192
198
test "other link" do
193
- assert_unchanged ( { :a , [ href: " foo.html" ] , [ ~t " String " ] } )
194
- assert_unchanged ( { :a , [ href: "foo.html" ] , [ " custom" , " text" ] } )
199
+ assert_unchanged ( ~m " [`String`]( foo.html) " )
200
+ assert_unchanged ( ~m " [ custom text](foo.html) " )
195
201
end
196
202
197
203
test "other" do
198
- assert_unchanged ( ~t " String.upcase() / 2" )
199
- assert_unchanged ( ~t " String.upcase()/2 " )
200
- assert_unchanged ( ~t " String.upcase()/2" )
201
- assert_unchanged ( ~t " :\" atom\" " )
202
- assert_unchanged ( ~t " 1 + 2" )
204
+ assert_unchanged ( "String.upcase() / 2" )
205
+ assert_unchanged ( "String.upcase()/2 " )
206
+ assert_unchanged ( " String.upcase()/2" )
207
+ assert_unchanged ( ":\" atom\" " )
208
+ assert_unchanged ( "1 + 2" )
203
209
assert_unchanged ( { :p , [ ] , [ "hello" ] } )
204
210
end
205
211
end
@@ -306,30 +312,30 @@ defmodule ExDoc.AutolinkTest do
306
312
307
313
captured =
308
314
assert_warn ( fn ->
309
- assert_unchanged ( ~t " Foo.bar/1" , file: "lib/foo.ex" , line: 1 , id: nil )
315
+ assert_unchanged ( "Foo.bar/1" , file: "lib/foo.ex" , line: 1 , id: nil )
310
316
end )
311
317
312
318
assert captured =~ "documentation references function Foo.bar/1"
313
319
assert captured =~ ~r{ lib/foo.ex:1\n $}
314
320
315
321
captured =
316
322
assert_warn ( fn ->
317
- assert_unchanged ( ~t " Foo.bar/1" , file: "lib/foo.ex" , id: "Foo.foo/0" )
323
+ assert_unchanged ( "Foo.bar/1" , file: "lib/foo.ex" , id: "Foo.foo/0" )
318
324
end )
319
325
320
326
assert captured =~ "documentation references function Foo.bar/1"
321
327
assert captured =~ ~r{ lib/foo.ex: Foo.foo/0\n $}
322
328
323
329
assert_warn ( fn ->
324
- assert_unchanged ( ~t " String.upcase/9" )
330
+ assert_unchanged ( "String.upcase/9" )
325
331
end )
326
332
327
333
assert_warn ( fn ->
328
- assert_unchanged ( ~t " c:GenServer.handle_call/9" )
334
+ assert_unchanged ( "c:GenServer.handle_call/9" )
329
335
end )
330
336
331
337
assert_warn ( fn ->
332
- assert_unchanged ( ~t " t:Calendar.date/9" )
338
+ assert_unchanged ( "t:Calendar.date/9" )
333
339
end )
334
340
335
341
assert_warn ( fn ->
@@ -345,36 +351,36 @@ defmodule ExDoc.AutolinkTest do
345
351
captured =
346
352
assert_warn ( fn ->
347
353
opts = [ extras: [ ] ]
348
- assert_unchanged ( { :a , [ href: " Foo Bar.md" ] , [ "Foo" ] } , opts )
354
+ assert_unchanged ( ~m " [ Foo](Foo Bar.md) " , opts )
349
355
end )
350
356
351
357
assert captured =~ "documentation references file `Foo Bar.md` but it doesn't exists"
352
358
353
359
options = [ skip_undefined_reference_warnings_on: [ "MyModule" ] , module_id: "MyModule" ]
354
- assert_unchanged ( ~t " String.upcase/9" , options )
360
+ assert_unchanged ( "String.upcase/9" , options )
355
361
end
356
362
357
363
## Helpers
358
364
359
365
@ default_options [ app: :myapp , current_module: MyModule , module_id: "MyModule" , file: "nofile" ]
360
366
361
- defp autolinked ( node , options \\ [ ] ) do
362
- case ExDoc.Autolink . doc ( node , Keyword . merge ( @ default_options , options ) ) do
363
- { :a , [ href: url ] , _ } when is_binary ( url ) -> url
364
- _ -> raise "could not build link for `#{ inspect ( node ) } `"
365
- end
367
+ defp autolink ( ast_or_text , options \\ [ ] ) do
368
+ ExDoc.Autolink . doc ( ast ( ast_or_text ) , Keyword . merge ( @ default_options , options ) )
366
369
end
367
370
371
+ defp assert_unchanged ( ast_or_text , options \\ [ ] ) do
372
+ assert autolink ( ast_or_text , options ) == ast ( ast_or_text )
373
+ end
374
+
375
+ defp ast ( text ) when is_binary ( text ) , do: { :code , [ class: "inline" ] , [ text ] }
376
+ defp ast ( { _ , _ , _ } = ast ) , do: ast
377
+
368
378
defp assert_warn ( fun ) do
369
379
captured = capture_io ( :stderr , fun )
370
380
captured =~ "documentation references"
371
381
captured
372
382
end
373
383
374
- defp assert_unchanged ( node , options \\ [ ] ) do
375
- assert ExDoc.Autolink . doc ( node , Keyword . merge ( @ default_options , options ) ) == node
376
- end
377
-
378
384
defp typespec ( ast , options \\ [ ] ) do
379
385
ExDoc.Autolink . typespec ( ast , Keyword . merge ( @ default_options , options ) )
380
386
end
0 commit comments