@@ -29,15 +29,15 @@ defmodule ExUnit.CaptureIO do
29
29
30
30
Returns the binary which is the captured output.
31
31
32
- By default, `capture_io` replaces the `group_leader` (`:stdio`)
33
- for the current process. Capturing the group leader is done per
34
- process and therefore can be done concurrently.
32
+ By default, `capture_io` replaces the `Process.group_leader/0` of the current
33
+ process, which is the process used by default for all IO operations. Capturing
34
+ the group leader of the current process is safe to run concurrently, under
35
+ `async: true` tests. You may also explicitly capture the group leader of
36
+ another process, however that is not safe to do concurrently.
35
37
36
- However, the capturing of any other named device, such as `:stderr`,
37
- happens globally and persists until the function has ended. While this means
38
- it is safe to run your tests with `async: true` in many cases, captured output
39
- may include output from a different test and care must be taken when using
40
- `capture_io` with a named process asynchronously.
38
+ You may also capture any other named IO device, such as `:stderr`. This is
39
+ also safe to run concurrently but, if several tests are writting to the same
40
+ device at once, captured output may include output from a different test.
41
41
42
42
A developer can set a string as an input. The default input is an empty
43
43
string. If capturing a named device asynchronously, an input can only be given
@@ -51,15 +51,28 @@ defmodule ExUnit.CaptureIO do
51
51
52
52
## IO devices
53
53
54
- You may capture the IO from any registered IO device. The device name given
55
- must be an atom representing the name of a registered process. In addition,
56
- Elixir provides two shortcuts :
54
+ You may capture the IO of the group leader of any process, by passing a `pid`
55
+ as argument, or from any registered IO device given as an `atom`. Here are
56
+ some example values :
57
57
58
- * `:stdio` - a shortcut for `:standard_io`, which maps to
59
- the current `Process.group_leader/0` in Erlang
58
+ * `:stdio`, `:standard_io` - a shortcut for capturing the group leader
59
+ of the current process. It is equivalent to passing `self()` as the
60
+ first argument. This is safe to run concurrently and captures only
61
+ the of the current process or any child process spawned inside the
62
+ given function
60
63
61
- * `:stderr` - a shortcut for the named process `:standard_error`
62
- provided in Erlang
64
+ * `:stderr`, `:standard_error` - captures all IO to standard error
65
+ (represented internally by an Erlang process named `:standard_error`).
66
+ This is safe to run concurrently but it will capture the output
67
+ of any other test writing to the same named device
68
+
69
+ * any other atom - captures all IO to the given device given by the
70
+ atom. This is safe to run concurrently but it will capture the output
71
+ of any other test writing to the same named device
72
+
73
+ * any other pid (since v1.17.0) - captures all IO to the group leader
74
+ of the given process. This option is not safe to run concurrently
75
+ if the pid is not `self()`. Tests using this value must set `async: true`
63
76
64
77
## Options
65
78
@@ -91,10 +104,10 @@ defmodule ExUnit.CaptureIO do
91
104
...> end) == "this is input"
92
105
true
93
106
94
- Note it is fine to use `==` with standard IO, because the content is captured
95
- per test process. However, `:stderr` is shared across all tests, so you will
96
- want to use `=~` instead of `==` for assertions on `:stderr` if your tests
97
- are async:
107
+ Note it is fine to use `==` with `:stdio` ( the default IO device), because
108
+ the content is captured per test process. However, `:stderr` is shared
109
+ across all tests, so you will want to use `=~` instead of `==` for assertions
110
+ on `:stderr` if your tests are async:
98
111
99
112
iex> capture_io(:stderr, fn -> IO.write(:stderr, "john") end) =~ "john"
100
113
true
@@ -110,6 +123,14 @@ defmodule ExUnit.CaptureIO do
110
123
Otherwise, if the standard error of any other test is captured, the test will
111
124
fail.
112
125
126
+ To capture the IO from another process, you can pass a `pid`:
127
+
128
+ capture_io(GenServer.whereis(MyServer), fn ->
129
+ GenServer.call(MyServer, :do_something)
130
+ end)
131
+
132
+ Tests that directly capture a PID cannot run concurrently.
133
+
113
134
## Returning values
114
135
115
136
As seen in the examples above, `capture_io` returns the captured output.
@@ -127,14 +148,19 @@ defmodule ExUnit.CaptureIO do
127
148
128
149
See `capture_io/1` for more information.
129
150
"""
130
- @ spec capture_io ( atom ( ) | String . t ( ) | keyword ( ) , ( -> any ( ) ) ) :: String . t ( )
131
- def capture_io ( device_input_or_options , fun )
151
+ @ spec capture_io ( atom ( ) | pid ( ) | String . t ( ) | keyword ( ) , ( -> any ( ) ) ) :: String . t ( )
152
+ def capture_io ( device_pid_input_or_options , fun )
132
153
133
154
def capture_io ( device , fun ) when is_atom ( device ) and is_function ( fun , 0 ) do
134
155
{ _result , capture } = with_io ( device , fun )
135
156
capture
136
157
end
137
158
159
+ def capture_io ( pid , fun ) when is_pid ( pid ) and is_function ( fun , 0 ) do
160
+ { _result , capture } = with_io ( pid , fun )
161
+ capture
162
+ end
163
+
138
164
def capture_io ( input , fun ) when is_binary ( input ) and is_function ( fun , 0 ) do
139
165
{ _result , capture } = with_io ( input , fun )
140
166
capture
@@ -150,8 +176,8 @@ defmodule ExUnit.CaptureIO do
150
176
151
177
See `capture_io/1` for more information.
152
178
"""
153
- @ spec capture_io ( atom ( ) , String . t ( ) | keyword ( ) , ( -> any ( ) ) ) :: String . t ( )
154
- def capture_io ( device , input_or_options , fun )
179
+ @ spec capture_io ( atom ( ) | pid ( ) , String . t ( ) | keyword ( ) , ( -> any ( ) ) ) :: String . t ( )
180
+ def capture_io ( device_or_pid , input_or_options , fun )
155
181
156
182
def capture_io ( device , input , fun )
157
183
when is_atom ( device ) and is_binary ( input ) and is_function ( fun , 0 ) do
@@ -165,6 +191,18 @@ defmodule ExUnit.CaptureIO do
165
191
capture
166
192
end
167
193
194
+ def capture_io ( pid , input , fun )
195
+ when is_pid ( pid ) and is_binary ( input ) and is_function ( fun , 0 ) do
196
+ { _result , capture } = with_io ( pid , input , fun )
197
+ capture
198
+ end
199
+
200
+ def capture_io ( pid , options , fun )
201
+ when is_pid ( pid ) and is_list ( options ) and is_function ( fun , 0 ) do
202
+ { _result , capture } = with_io ( pid , options , fun )
203
+ capture
204
+ end
205
+
168
206
@ doc ~S"""
169
207
Invokes the given `fun` and returns the result and captured output.
170
208
@@ -194,13 +232,17 @@ defmodule ExUnit.CaptureIO do
194
232
See `with_io/1` for more information.
195
233
"""
196
234
@ doc since: "1.13.0"
197
- @ spec with_io ( atom ( ) | String . t ( ) | keyword ( ) , ( -> any ( ) ) ) :: { any ( ) , String . t ( ) }
198
- def with_io ( device_input_or_options , fun )
235
+ @ spec with_io ( atom ( ) | pid ( ) | String . t ( ) | keyword ( ) , ( -> any ( ) ) ) :: { any ( ) , String . t ( ) }
236
+ def with_io ( device_pid_input_or_options , fun )
199
237
200
238
def with_io ( device , fun ) when is_atom ( device ) and is_function ( fun , 0 ) do
201
239
with_io ( device , [ ] , fun )
202
240
end
203
241
242
+ def with_io ( pid , fun ) when is_pid ( pid ) and is_function ( fun , 0 ) do
243
+ with_io ( pid , [ ] , fun )
244
+ end
245
+
204
246
def with_io ( input , fun ) when is_binary ( input ) and is_function ( fun , 0 ) do
205
247
with_io ( :stdio , [ input: input ] , fun )
206
248
end
@@ -215,8 +257,8 @@ defmodule ExUnit.CaptureIO do
215
257
See `with_io/1` for more information.
216
258
"""
217
259
@ doc since: "1.13.0"
218
- @ spec with_io ( atom ( ) , String . t ( ) | keyword ( ) , ( -> any ( ) ) ) :: { any ( ) , String . t ( ) }
219
- def with_io ( device , input_or_options , fun )
260
+ @ spec with_io ( atom ( ) | pid ( ) , String . t ( ) | keyword ( ) , ( -> any ( ) ) ) :: { any ( ) , String . t ( ) }
261
+ def with_io ( device_or_pid , input_or_options , fun )
220
262
221
263
def with_io ( device , input , fun )
222
264
when is_atom ( device ) and is_binary ( input ) and is_function ( fun , 0 ) do
@@ -228,23 +270,35 @@ defmodule ExUnit.CaptureIO do
228
270
do_with_io ( map_dev ( device ) , options , fun )
229
271
end
230
272
273
+ def with_io ( pid , input , fun )
274
+ when is_pid ( pid ) and is_binary ( input ) and is_function ( fun , 0 ) do
275
+ with_io ( pid , [ input: input ] , fun )
276
+ end
277
+
278
+ def with_io ( pid , options , fun )
279
+ when is_pid ( pid ) and is_list ( options ) and is_function ( fun , 0 ) do
280
+ do_with_io ( pid , options , fun )
281
+ end
282
+
231
283
defp map_dev ( :stdio ) , do: :standard_io
232
284
defp map_dev ( :stderr ) , do: :standard_error
233
285
defp map_dev ( other ) , do: other
234
286
235
- defp do_with_io ( :standard_io , options , fun ) do
287
+ defp do_with_io ( device_or_pid , options , fun )
288
+ when device_or_pid == :standard_io or is_pid ( device_or_pid ) do
236
289
prompt_config = Keyword . get ( options , :capture_prompt , true )
237
290
encoding = Keyword . get ( options , :encoding , :unicode )
238
291
input = Keyword . get ( options , :input , "" )
239
292
240
293
original_gl = Process . group_leader ( )
241
294
{ :ok , capture_gl } = StringIO . open ( input , capture_prompt: prompt_config , encoding: encoding )
295
+ pid = if is_pid ( device_or_pid ) , do: device_or_pid , else: self ( )
242
296
243
297
try do
244
- Process . group_leader ( self ( ) , capture_gl )
298
+ Process . group_leader ( pid , capture_gl )
245
299
do_capture_gl ( capture_gl , fun )
246
300
after
247
- Process . group_leader ( self ( ) , original_gl )
301
+ Process . group_leader ( pid , original_gl )
248
302
end
249
303
end
250
304
0 commit comments