Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
12 changes: 6 additions & 6 deletions lib/elixir/lib/kernel.ex
Original file line number Diff line number Diff line change
Expand Up @@ -3621,15 +3621,15 @@ defmodule Kernel do
case is_binary(string) do
true ->
case mod do
?b -> lc p inlist String.split(string), p != "", do: p
?a -> lc p inlist String.split(string), p != "", do: binary_to_atom(p)
?c -> lc p inlist String.split(string), p != "", do: String.to_char_list!(p)
?b -> String.split(string)
?a -> lc p inlist String.split(string), do: binary_to_atom(p)
?c -> lc p inlist String.split(string), do: String.to_char_list!(p)
end
false ->
case mod do
?b -> quote do: lc(p inlist String.split(unquote(string)), p != "", do: p)
?a -> quote do: lc(p inlist String.split(unquote(string)), p != "", do: binary_to_atom(p))
?c -> quote do: lc(p inlist String.split(unquote(string)), p != "", do: String.to_char_list!(p))
?b -> quote do: String.split(unquote(string))
?a -> quote do: lc(p inlist String.split(unquote(string)), do: binary_to_atom(p))
?c -> quote do: lc(p inlist String.split(unquote(string)), do: String.to_char_list!(p))
end
end
end
Expand Down
19 changes: 10 additions & 9 deletions lib/elixir/lib/regex.ex
Original file line number Diff line number Diff line change
Expand Up @@ -264,16 +264,17 @@ defmodule Regex do
def split(regex, string, options // [])

def split(regex(re_pattern: compiled), string, options) do
parts =
cond do
Keyword.get(options, :global) == false -> 2
p = Keyword.get(options, :parts) -> p
true -> :infinity
end
defaults = [global: true, trim: true, parts: :infinity, return: return_for(string)]
options = Keyword.merge(defaults, options)

return = Keyword.get(options, :return, return_for(string))
opts = [return: return, parts: parts]
:re.split(string, compiled, opts)
unless options[:global], do: options = Keyword.put(options, :parts, 2)

valid_options = Dict.take(options, [:parts, :return])
splits = :re.split(string, compiled, valid_options)

if options[:trim], do: splits = Enum.filter(splits, &(&1 != ""))

splits
end

@doc %B"""
Expand Down
22 changes: 17 additions & 5 deletions lib/elixir/lib/string.ex
Original file line number Diff line number Diff line change
Expand Up @@ -140,7 +140,7 @@ defmodule String do

@doc """
Splits a string on substrings at each Unicode whitespace
occurrence.
occurrence with leading and trailing whitespace ignored.

## Examples

Expand All @@ -149,7 +149,7 @@ defmodule String do
iex> String.split("foo" <> <<194, 133>> <> "bar")
["foo", "bar"]
iex> String.split(" foo bar ")
["", "foo", "bar", ""]
["foo", "bar"]

"""
@spec split(t) :: [t]
Expand All @@ -163,12 +163,17 @@ defmodule String do
The string is split into as many parts as possible by
default, unless the `global` option is set to `false`.

Empty strings are removed from the result, unless the
`trim` option is set to `false`.

## Examples

iex> String.split("a,b,c", ",")
["a", "b", "c"]
iex> String.split("a,b,c", ",", global: false)
["a", "b,c"]
iex> String.split(" a b c ", " ", trim: false)
["", "a", "b", "c", ""]

iex> String.split("1,2 3,4", [" ", ","])
["1", "2", "3", "4"]
Expand All @@ -188,12 +193,19 @@ defmodule String do
def split("", _pattern, _options), do: [""]

def split(binary, pattern, options) when is_regex(pattern) do
Regex.split(pattern, binary, global: options[:global])
Regex.split(pattern, binary, options)
end

def split(binary, pattern, options) do
opts = if options[:global] != false, do: [:global], else: []
:binary.split(binary, pattern, opts)
defaults = [global: true, trim: true]
options = Keyword.merge(defaults, options)

option_keys = Enum.filter_map(options, &elem(&1, 1), &elem(&1, 0))
splits = :binary.split(binary, pattern, option_keys)

if options[:trim], do: splits = Enum.filter(splits, &(&1 != ""))

splits
end

@doc """
Expand Down
12 changes: 10 additions & 2 deletions lib/elixir/priv/unicode.ex
Original file line number Diff line number Diff line change
Expand Up @@ -145,7 +145,11 @@ defmodule String.Unicode do

lc codepoint inlist whitespace do
defp do_split(unquote(codepoint) <> rest, buffer, acc) do
do_split(rest, "", [buffer | acc])
if buffer != "" do
do_split(rest, "", [buffer | acc])
else
do_split(rest, buffer, acc)
end
end
end

Expand All @@ -154,7 +158,11 @@ defmodule String.Unicode do
end

defp do_split(<<>>, buffer, acc) do
[buffer | acc]
if buffer != "" do
[buffer | acc]
else
acc
end
end

# Graphemes
Expand Down
7 changes: 4 additions & 3 deletions lib/elixir/test/elixir/regex_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -113,13 +113,14 @@ defmodule Regex.BinaryTest do
end
test :split do
assert Regex.split(%r",", "") == [""]
assert Regex.split(%r",", "") == []
assert Regex.split(%r" ", "foo bar baz") == ["foo", "bar", "baz"]
assert Regex.split(%r" ", "foo bar baz", parts: 2) == ["foo", "bar baz"]
assert Regex.split(%r"\s", "foobar") == ["foobar"]
assert Regex.split(%r" ", "foo bar baz") == ["foo", "bar", "baz"]
assert Regex.split(%r"=", "key=") == ["key", ""]
assert Regex.split(%r"=", "=value") == ["", "value"]
assert Regex.split(%r" ", " foo bar baz ", trim: false) == ["", "foo", "bar", "baz", ""]
assert Regex.split(%r"=", "key=") == ["key"]
assert Regex.split(%r"=", "=value") == ["value"]
end
test :replace do
Expand Down
14 changes: 10 additions & 4 deletions lib/elixir/test/elixir/string_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -18,27 +18,33 @@ defmodule StringTest do
test :split do
assert String.split("") == [""]
assert String.split("foo bar") == ["foo", "bar"]
assert String.split(" foo bar") == ["", "foo", "bar"]
assert String.split("foo bar ") == ["foo", "bar", ""]
assert String.split(" foo bar ") == ["", "foo", "bar", ""]
assert String.split("foo\t\n\v\f\r\sbar\n") == ["foo", "", "", "", "", "", "bar", ""]
assert String.split(" foo bar") == ["foo", "bar"]
assert String.split("foo bar ") == ["foo", "bar"]
assert String.split(" foo bar ") == ["foo", "bar"]
assert String.split("foo\t\n\v\f\r\sbar\n") == ["foo", "bar"]
assert String.split("foo" <> <<31>> <> "bar") == ["foo", "bar"]
assert String.split("foo" <> <<194, 133>> <> "bar") == ["foo", "bar"]

assert String.split("", ",") == [""]
assert String.split("a,b,c", ",") == ["a", "b", "c"]
assert String.split("a,b", ".") == ["a,b"]
assert String.split("1,2 3,4", [" ", ","]) == ["1", "2", "3", "4"]
assert String.split(" a b c ", " ") == ["a", "b", "c"]

assert String.split("a,b,c", ",", global: false) == ["a", "b,c"]
assert String.split("1,2 3,4", [" ", ","], global: false) == ["1", "2 3,4"]

assert String.split(" a b c ", " ", trim: false) == ["", "a", "b", "c", ""]
assert String.split(" a b c ", " ", trim: false, global: false) == ["", "a b c "]
end

test :split_with_regex do
assert String.split("", %r{,}) == [""]
assert String.split("a,b", %r{,}) == ["a", "b"]
assert String.split("a,b,c", %r{,}) == ["a", "b", "c"]
assert String.split("a,b,c", %r{,}, global: false) == ["a", "b,c"]
assert String.split("a,b.c ", %r{\W}) == ["a", "b", "c"]
assert String.split("a,b.c ", %r{\W}, trim: false) == ["a", "b", "c", ""]
assert String.split("a,b", %r{\.}) == ["a,b"]
end

Expand Down
2 changes: 1 addition & 1 deletion lib/ex_unit/lib/ex_unit/doc_test.ex
Original file line number Diff line number Diff line change
Expand Up @@ -331,7 +331,7 @@ defmodule ExUnit.DocTest do
end

defp extract_tests(line, doc) do
lines = String.split(doc, %r/\n/) |> adjust_indent
lines = String.split(doc, %r/\n/, trim: false) |> adjust_indent
extract_tests(lines, line, "", "", [], true)
end

Expand Down
2 changes: 1 addition & 1 deletion lib/iex/test/iex/helpers_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -133,7 +133,7 @@ defmodule IEx.HelpersTest do
assert ["ebin", "lib", "mix.exs", "test"]
= capture_io(fn -> ls end)
|> String.split
|> Enum.filter(&(&1 != ""))
|> Enum.map(String.strip(&1))
|> Enum.sort
assert capture_io(fn -> ls "~" end) == capture_io(fn -> ls System.user_home end)
end
Expand Down