From 97ea102a7900503302d21e8e0dad5003d3dce4e1 Mon Sep 17 00:00:00 2001 From: Yuki Ito Date: Thu, 23 May 2013 00:44:47 +0900 Subject: [PATCH 1/2] Enable ExUnitCaptureIO.capture_io to receive input --- lib/ex_unit/lib/ex_unit/capture_io.ex | 150 ++++++++++++++++--- lib/ex_unit/test/ex_unit/capture_io_test.exs | 117 ++++++++++++++- 2 files changed, 247 insertions(+), 20 deletions(-) diff --git a/lib/ex_unit/lib/ex_unit/capture_io.ex b/lib/ex_unit/lib/ex_unit/capture_io.ex index 437ea883e9..f4639ae3e3 100644 --- a/lib/ex_unit/lib/ex_unit/capture_io.ex +++ b/lib/ex_unit/lib/ex_unit/capture_io.ex @@ -28,7 +28,8 @@ defmodule ExUnit.CaptureIO do named device like `:stderr` is also possible globally by giving the registered device name explicitly as argument. - The input is mocked to return `:eof`. + A developer can set a string as an input. The default + input is `:eof`. ## Examples @@ -38,19 +39,36 @@ defmodule ExUnit.CaptureIO do true iex> capture_io(:stderr, fn -> IO.write(:stderr, "josé") end) == "josé" true + iex> capture_io("this is input", fn-> + ...> input = IO.gets "" + ...> IO.write input + ...> end) == "this is input" + true """ - def capture_io(device // :stdio, fun) when is_atom(device) do - do_capture_io(map_dev(device), fun) + def capture_io(device, input, fun) do + do_capture_io(map_dev(device), input, fun) + end + + def capture_io(device, fun) when is_atom(device) do + do_capture_io(map_dev(device), "", fun) + end + + def capture_io(input, fun) when is_binary(input) do + do_capture_io(:standard_io, input, fun) + end + + def capture_io(fun) do + do_capture_io(:standard_io, "", fun) end defp map_dev(:stdio), do: :standard_io defp map_dev(:stderr), do: :standard_error defp map_dev(other), do: other - defp do_capture_io(:standard_io, fun) do + defp do_capture_io(:standard_io, input, fun) do original_gl = :erlang.group_leader - capture_gl = new_group_leader(self) + capture_gl = new_group_leader(self, input) :erlang.group_leader(capture_gl, self) try do @@ -65,13 +83,13 @@ defmodule ExUnit.CaptureIO do end end - defp do_capture_io(device, fun) do + defp do_capture_io(device, input, fun) do unless original_io = Process.whereis(device) do raise "could not find IO device registered at #{inspect device}" end Process.unregister(device) - capture_io = new_group_leader(self) + capture_io = new_group_leader(self, input) Process.register(capture_io, device) try do @@ -87,14 +105,36 @@ defmodule ExUnit.CaptureIO do end end - defp new_group_leader(runner) do - spawn_link(fn -> group_leader_process(runner) end) + defp new_group_leader(runner, input) do + spawn_link(fn -> group_leader_process(runner, input) end) end - defp group_leader_process(runner) do + defp group_leader_process(runner, input) do + register_input(input) group_leader_loop(runner, :infinity, []) end + defp register_input(nil) do + set_input(nil) + end + + defp register_input(input) do + chars = :unicode.characters_to_list(input) + set_input(chars) + end + + defp set_input(:eof) do + set_input([]) + end + + defp set_input(input) do + Process.put(:capture_io_input, input) + end + + defp get_input do + Process.get(:capture_io_input) + end + defp group_leader_loop(runner, wait, buf) do receive do { :io_request, from, reply_as, req } -> @@ -141,24 +181,28 @@ defmodule ExUnit.CaptureIO do io_request({ :put_chars, mod, func, args }, buf) end - defp io_request({ :get_chars, _enc, _propmpt, _n }, buf) do - { :eof, buf } + defp io_request({ :get_chars, _enc, _propmpt, n }, buf) when n >= 0 do + { get_chars(n), buf } end - defp io_request({ :get_chars, _prompt, _n }, buf) do - { :eof, buf } + defp io_request({ :get_chars, _prompt, n }, buf) when n >= 0 do + { get_chars(n), buf } end defp io_request({ :get_line, _prompt }, buf) do - { :eof, buf } + { get_line, buf } end defp io_request({ :get_line, _enc, _prompt }, buf) do - { :eof, buf } + { get_line, buf } end - defp io_request({ :get_until, _prompt, _m, _f, _as }, buf) do - { :eof, buf } + defp io_request({ :get_until, _prompt, mod, fun, args }, buf) do + { get_until(mod, fun, args), buf } + end + + defp io_request({ :get_until, _encoding, _prompt, mod, fun, args}, buf) do + { get_until(mod, fun, args), buf } end defp io_request({ :setopts, _opts }, buf) do @@ -193,6 +237,76 @@ defmodule ExUnit.CaptureIO do result end + defp get_line do + input = get_input + + case input do + [] -> + :eof + _ -> + { line, rest } = Enum.split_while(input, fn(char) -> char != ?\n end) + case rest do + [] -> + set_input([]) + :unicode.characters_to_binary(line) + [_|t] -> + set_input(t) + :unicode.characters_to_binary(line ++ '\n') + end + end + end + + defp get_chars(n) do + input = get_input + + case input do + [] -> + :eof + _ -> + { chars, rest } = Enum.split(input, n) + set_input(rest) + :unicode.characters_to_binary(chars) + end + end + + defp get_until(mod, fun, args) do + input = get_input + do_get_until(input, mod, fun, args) + end + + defp do_get_until([], mod, fun, args, continuation // []) do + case apply(mod, fun, [continuation, :eof | args]) do + { :done, result, rest_chars } -> + set_input(rest_chars) + result + { :more, next_continuation } -> + do_get_until([], mod, fun, args, next_continuation) + end + end + + defp do_get_until(input, mod, fun, args, continuation // []) do + { line, rest } = Enum.split_while(input, fn(char) -> char != ?\n end) + + case rest do + [] -> + case apply(mod, fun, [continuation, line | args]) do + { :done, result, rest_chars } -> + set_input(rest_chars) + result + { :more, next_continuation } -> + do_get_until([], mod, fun, args, next_continuation) + end + [_|t] -> + case apply(mod, fun, [continuation, line ++ '\n' | args]) do + { :done, result, rest_chars } -> + set_input(rest_chars ++ t) + result + { :more, next_continuation } -> + do_get_until(t, mod, fun, args, next_continuation) + end + end + end + defp buffer_to_result([]) do nil end diff --git a/lib/ex_unit/test/ex_unit/capture_io_test.exs b/lib/ex_unit/test/ex_unit/capture_io_test.exs index 3e63d5f923..1ca6330a14 100644 --- a/lib/ex_unit/test/ex_unit/capture_io_test.exs +++ b/lib/ex_unit/test/ex_unit/capture_io_test.exs @@ -6,6 +6,30 @@ end alias ExUnit.CaptureIOTest.Value +defmodule ExUnit.CaptureIOTest.GetUntil do + def until_new_line(_, :eof, _) do + { :done, :eof, [] } + end + + def until_new_line(this_far, chars, stop_char) do + case Enum.split_while(chars, fn(c) -> c != stop_char end) do + { l, [] } -> + { :more, this_far ++ l } + { l, [stop_char|rest] } -> + { :done, this_far ++ l ++ [stop_char], rest } + end + end + + def get_line(device // Process.group_leader) do + device <- { :io_request, self, device, { :get_until, :unicode, "", __MODULE__, :until_new_line, [?\n] } } + receive do + { :io_reply, _, data } -> data + end + end +end + +alias ExUnit.CaptureIOTest.GetUntil + defmodule ExUnit.CaptureIOTest do use ExUnit.Case, async: true @@ -36,6 +60,10 @@ defmodule ExUnit.CaptureIOTest do :io.put_chars("josé") end) == "josé" + assert capture_io(fn -> + spawn(fn -> :io.put_chars("a") end) + end) == "a" + assert capture_io(fn -> assert :io.put_chars("a") == :ok end) @@ -55,6 +83,22 @@ defmodule ExUnit.CaptureIOTest do capture_io(fn -> assert :io.get_chars(">", 3) == :eof end) + + capture_io("", fn -> + assert :io.get_chars(">", 3) == :eof + end) + + capture_io("abc\ndef", fn -> + assert :io.get_chars(">", 3) == "abc" + assert :io.get_chars(">", 5) == "\ndef" + assert :io.get_chars(">", 7) == :eof + end) + + capture_io("あいう", fn -> + assert :io.get_chars(">", 2) == "あい" + assert :io.get_chars(">", 1) == "う" + assert :io.get_chars(">", 1) == :eof + end) end test :capture_io_with_get_line do @@ -65,15 +109,84 @@ defmodule ExUnit.CaptureIOTest do capture_io(fn -> assert :io.get_line(">") == :eof end) + + capture_io("", fn -> + assert :io.get_line(">") == :eof + end) + + capture_io("\n", fn -> + assert :io.get_line(">") == "\n" + assert :io.get_line(">") == :eof + end) + + capture_io("a", fn -> + assert :io.get_line(">") == "a" + assert :io.get_line(">") == :eof + end) + + capture_io("a\n", fn -> + assert :io.get_line(">") == "a\n" + assert :io.get_line(">") == :eof + end) + + capture_io("a\nb", fn -> + assert :io.get_line(">") == "a\n" + assert :io.get_line(">") == "b" + assert :io.get_line(">") == :eof + end) + + capture_io("あい\nう", fn -> + assert :io.get_line(">") == "あい\n" + assert :io.get_line(">") == "う" + assert :io.get_line(">") == :eof + end) end test :capture_io_with_get_until do assert capture_io(fn -> - send_and_receive_io({ :get_until, '>', :m, :f, :as }) + assert :io.scan_erl_form('>') end) == nil capture_io(fn -> - assert send_and_receive_io({ :get_until, '>', :m, :f, :as }) == :eof + assert :io.scan_erl_form('>') == { :eof, 1 } + end) + + capture_io("1", fn -> + assert :io.scan_erl_form('>') == { :ok, [{ :integer, 1, 1 }], 1 } + assert :io.scan_erl_form('>') == { :eof, 1 } + end) + + capture_io("1\n.", fn -> + assert :io.scan_erl_form('>') == { :ok, [{ :integer, 1, 1 }, { :dot, 2 }], 2 } + assert :io.scan_erl_form('>') == { :eof, 1 } + end) + + capture_io("1.\n.", fn -> + assert :io.scan_erl_form('>') == { :ok, [{ :integer, 1, 1 }, { :dot, 1 }], 2 } + assert :io.scan_erl_form('>') == { :ok, [dot: 1], 1} + assert :io.scan_erl_form('>') == { :eof, 1 } + end) + + capture_io("\"a", fn -> + assert :io.scan_erl_form('>') == { :error, { 1, :erl_scan, { :string, 34, 'a' } }, 1 } + assert :io.scan_erl_form('>') == { :eof, 1 } + end) + + capture_io("\"a\n\"", fn -> + assert :io.scan_erl_form('>') == { :ok, [{ :string, 1, 'a\n' }], 2 } + assert :io.scan_erl_form('>') == { :eof, 1 } + end) + + capture_io(":erl. mof*,,l", fn -> + assert :io.scan_erl_form('>') == { :ok, [{ :":", 1 }, { :atom, 1, :erl }, { :dot, 1 }], 1 } + assert :io.scan_erl_form('>') == { :ok, [{ :atom, 1, :mof }, { :*, 1 }, { :"," , 1 }, { :",", 1 }, { :atom, 1, :l }], 1 } + assert :io.scan_erl_form('>') == { :eof, 1 } + end) + + capture_io("a\nb\nc", fn -> + assert GetUntil.get_line == 'a\n' + assert GetUntil.get_line == 'b\n' + assert GetUntil.get_line == :eof end) end From 2403d0c4b9b9fb9b2242b0f01ce21a96b5bfe73d Mon Sep 17 00:00:00 2001 From: Yuki Ito Date: Thu, 23 May 2013 00:47:49 +0900 Subject: [PATCH 2/2] IEx.Server break out of the loop when accepting :eof as input --- lib/ex_unit/lib/ex_unit/capture_io.ex | 2 +- lib/iex/lib/iex/server.ex | 29 +++++++++++++++------------ 2 files changed, 17 insertions(+), 14 deletions(-) diff --git a/lib/ex_unit/lib/ex_unit/capture_io.ex b/lib/ex_unit/lib/ex_unit/capture_io.ex index f4639ae3e3..0cd32d7534 100644 --- a/lib/ex_unit/lib/ex_unit/capture_io.ex +++ b/lib/ex_unit/lib/ex_unit/capture_io.ex @@ -181,7 +181,7 @@ defmodule ExUnit.CaptureIO do io_request({ :put_chars, mod, func, args }, buf) end - defp io_request({ :get_chars, _enc, _propmpt, n }, buf) when n >= 0 do + defp io_request({ :get_chars, _enc, _prompt, n }, buf) when n >= 0 do { get_chars(n), buf } end diff --git a/lib/iex/lib/iex/server.ex b/lib/iex/lib/iex/server.ex index da6e858eee..8ba6547a7e 100644 --- a/lib/iex/lib/iex/server.ex +++ b/lib/iex/lib/iex/server.ex @@ -30,20 +30,22 @@ defmodule IEx.Server do code = config.cache line = io_get(config) - new_config = - try do - eval(code, line, counter, config) - rescue - exception -> - print_exception(exception, System.stacktrace) - config.cache('') - catch - kind, error -> - print_error(kind, error, System.stacktrace) - config.cache('') - end + unless line == :eof do + new_config = + try do + eval(code, line, counter, config) + rescue + exception -> + print_exception(exception, System.stacktrace) + config.cache('') + catch + kind, error -> + print_error(kind, error, System.stacktrace) + config.cache('') + end - do_loop(new_config) + do_loop(new_config) + end end # Instead of doing just `:elixir.eval`, we first parse the expression to see @@ -148,6 +150,7 @@ defmodule IEx.Server do end case IO.gets(:stdio, prompt) do + :eof -> :eof { :error, _ } -> '' data -> :unicode.characters_to_list(data) end