diff --git a/lib/elixir/lib/access.ex b/lib/elixir/lib/access.ex index e9ed1e4799..7b6d944a78 100644 --- a/lib/elixir/lib/access.ex +++ b/lib/elixir/lib/access.ex @@ -35,61 +35,74 @@ defmodule Access do iex> nil[:a] nil - The access syntax can also be used with the `Kernel.put_in/2`, - `Kernel.update_in/2` and `Kernel.get_and_update_in/2` macros - to allow values to be set in nested data structures: - - iex> users = %{"john" => %{age: 27}, "meg" => %{age: 23}} - iex> put_in(users["john"][:age], 28) - %{"john" => %{age: 28}, "meg" => %{age: 23}} - ## Maps and structs While the access syntax is allowed in maps via `map[key]`, if your map is made of predefined atom keys, you should prefer to access those atom keys with `map.key` instead of `map[key]`, as `map.key` will raise if the key is missing (which is not - supposed to happen if the keys are predefined). + supposed to happen if the keys are predefined) or if `map` is + `nil`. Similarly, since structs are maps and structs have predefined keys, they only allow the `struct.key` syntax and they do not - allow the `struct[key]` access syntax. `Access.key/1` can also - be used to construct dynamic access to structs and maps. + allow the `struct[key]` access syntax. - In a nutshell, when using `put_in/2` and friends: + In other words, the `map[key]` syntax is loose, returning `nil` + for missing keys, while the `map.key` syntax is strict, raising + for both nil values and missing keys. - put_in(struct_or_map.key, :value) - put_in(keyword_or_map[:key], :value) + To bridge this gap, Elixir provides the `get_in/1` and `get_in/2` + functions, which are capable of traversing nested data structures, + even in the presence of `nil`s: - When using `put_in/3` and friends: + iex> users = %{"john" => %{age: 27}, "meg" => %{age: 23}} + iex> get_in(users["john"].age) + 27 + iex> get_in(users["unknown"].age) + nil - put_in(struct_or_map, [Access.key!(:key)], :value) - put_in(keyword_or_map, [:key], :value) + Notice how, even if no user was found, `get_in/1` returned `nil`. + Outside of `get_in/1`, trying to access the field `.age` on `nil` + would raise. - This covers the dual nature of maps in Elixir, as they can be - either for structured data or as a key-value store. See the `Map` - module for more information. + The `get_in/2` function takes one step further by allowing + different accessors to be mixed in. For example, given a user + map with the `:name` and `:languages` keys, here is how to + access the name of all programming languages: - ## Nested data structures + iex> languages = [ + ...> %{name: "elixir", type: :functional}, + ...> %{name: "c", type: :procedural} + ...> ] + iex> user = %{name: "john", languages: languages} + iex> get_in(user, [:languages, Access.all(), :name]) + ["elixir", "c"] - Both key-based access syntaxes can be used with the nested update - functions and macros in `Kernel`, such as `Kernel.get_in/2`, - `Kernel.put_in/3`, `Kernel.update_in/3`, `Kernel.pop_in/2`, and - `Kernel.get_and_update_in/3`. + This module provides convenience functions for traversing other + structures, like tuples and lists. As we will see next, they can + even be used to update nested data structures. + + If you want to learn more about the dual nature of maps in Elixir, + as they can be either for structured data or as a key-value store, + see the `Map` module. - For example, to update a map inside another map: + ## Updating nested data structures + + The access syntax can also be used with the `Kernel.put_in/2`, + `Kernel.update_in/2`, `Kernel.get_and_update_in/2`, and `Kernel.pop_in/1` + macros to further manipulate values in nested data structures: iex> users = %{"john" => %{age: 27}, "meg" => %{age: 23}} iex> put_in(users["john"].age, 28) %{"john" => %{age: 28}, "meg" => %{age: 23}} - This module provides convenience functions for traversing other - structures, like tuples and lists. These functions can be used - in all the `Access`-related functions and macros in `Kernel`. - - For instance, given a user map with the `:name` and `:languages` - keys, here is how to deeply traverse the map and convert all - language names to uppercase: + As shown in the previous section, you can also use the + `Kernel.put_in/3`, `Kernel.update_in/3`, `Kernel.pop_in/2`, and + `Kernel.get_and_update_in/3` functions to provide nested + custom accessors. For instance, given a user map with the + `:name` and `:languages` keys, here is how to deeply traverse + the map and convert all language names to uppercase: iex> languages = [ ...> %{name: "elixir", type: :functional}, diff --git a/lib/elixir/lib/kernel.ex b/lib/elixir/lib/kernel.ex index 8b5026f4af..fd428e1d7c 100644 --- a/lib/elixir/lib/kernel.ex +++ b/lib/elixir/lib/kernel.ex @@ -2680,16 +2680,12 @@ defmodule Kernel do end @doc """ - Gets a value from a nested structure. + Gets a value from a nested structure with nil-safe handling. Uses the `Access` module to traverse the structures according to the given `keys`, unless the `key` is a function, which is detailed in a later section. - Note that if none of the given keys are functions, - there is rarely a reason to use `get_in` over - writing "regular" Elixir code using `[]`. - ## Examples iex> users = %{"john" => %{age: 27}, "meg" => %{age: 23}} @@ -2717,18 +2713,6 @@ defmodule Kernel do iex> users["unknown"][:age] nil - iex> users = nil - iex> get_in(users, [Access.all(), :age]) - nil - - Alternatively, if you need to access complex data-structures, you can - use pattern matching: - - case users do - %{"john" => %{age: age}} -> age - _ -> default_value - end - ## Functions as keys If a key given to `get_in/2` is a function, the function will be invoked @@ -2758,13 +2742,19 @@ defmodule Kernel do get_in(some_struct, [:some_key, :nested_key]) - The good news is that structs have predefined shape. Therefore, - you can write instead: + There are two alternatives. Given structs have predefined keys, + we can use the `struct.field` notation: some_struct.some_key.nested_key - If, by any chance, `some_key` can return nil, you can always - fallback to pattern matching to provide nested struct handling: + However, the code above will fail if any of the values return `nil`. + If you also want to handle nil values, you can use `get_in/1`: + + get_in(some_struct.some_key.nested_key) + + Pattern-matching is another option for handling such cases, + which can be especially useful if you want to match on several + fields at once or provide custom return values: case some_struct do %{some_key: %{nested_key: value}} -> value @@ -2982,6 +2972,63 @@ defmodule Kernel do defp pop_in_data(data, [key | tail]), do: Access.get_and_update(data, key, &pop_in_data(&1, tail)) + @doc """ + Gets a key from the nested structure via the given `path`, with + nil-safe handling. + + This is similar to `get_in/2`, except the path is extracted via + a macro rather than passing a list. For example: + + get_in(opts[:foo][:bar]) + + Is equivalent to: + + get_in(opts, [:foo, :bar]) + + Additionally, this macro can traverse structs: + + get_in(struct.foo.bar) + + In case any of the keys returns `nil`, then `nil` will be returned + and `get_in/1` won't traverse any further. + + Note that in order for this macro to work, the complete path must always + be visible by this macro. For more information about the supported path + expressions, please check `get_and_update_in/2` docs. + + ## Examples + + iex> users = %{"john" => %{age: 27}, "meg" => %{age: 23}} + iex> get_in(users["john"].age) + 27 + iex> get_in(users["unknown"].age) + nil + + """ + defmacro get_in(path) do + {[h | t], _} = unnest(path, [], true, "get_in/1") + nest_get_in(h, quote(do: x), t) + end + + defp nest_get_in(h, _var, []) do + h + end + + defp nest_get_in(h, var, [{:map, key} | tail]) do + quote generated: true do + case unquote(h) do + %{unquote(key) => unquote(var)} -> unquote(nest_get_in(var, var, tail)) + nil -> nil + unquote(var) -> :erlang.error({:badkey, unquote(key), unquote(var)}) + end + end + end + + defp nest_get_in(h, var, [{:access, key} | tail]) do + h = quote do: Access.get(unquote(h), unquote(key)) + nest_get_in(h, var, tail) + end + @doc """ Puts a value in a nested structure via the given `path`. @@ -3017,7 +3064,7 @@ defmodule Kernel do defmacro put_in(path, value) do case unnest(path, [], true, "put_in/2") do {[h | t], true} -> - nest_update_in(h, t, quote(do: fn _ -> unquote(value) end)) + nest_map_update_in(h, t, quote(do: fn _ -> unquote(value) end)) {[h | t], false} -> expr = nest_get_and_update_in(h, t, quote(do: fn _ -> {nil, unquote(value)} end)) @@ -3094,7 +3141,7 @@ defmodule Kernel do defmacro update_in(path, fun) do case unnest(path, [], true, "update_in/2") do {[h | t], true} -> - nest_update_in(h, t, fun) + nest_map_update_in(h, t, fun) {[h | t], false} -> expr = nest_get_and_update_in(h, t, quote(do: fn x -> {nil, unquote(fun).(x)} end)) @@ -3160,17 +3207,17 @@ defmodule Kernel do nest_get_and_update_in(h, t, fun) end - defp nest_update_in([], fun), do: fun + defp nest_map_update_in([], fun), do: fun - defp nest_update_in(list, fun) do + defp nest_map_update_in(list, fun) do quote do - fn x -> unquote(nest_update_in(quote(do: x), list, fun)) end + fn x -> unquote(nest_map_update_in(quote(do: x), list, fun)) end end end - defp nest_update_in(h, [{:map, key} | t], fun) do + defp nest_map_update_in(h, [{:map, key} | t], fun) do quote do - Map.update!(unquote(h), unquote(key), unquote(nest_update_in(t, fun))) + Map.update!(unquote(h), unquote(key), unquote(nest_map_update_in(t, fun))) end end diff --git a/lib/elixir/pages/getting-started/keywords-and-maps.md b/lib/elixir/pages/getting-started/keywords-and-maps.md index 11b1c01cbf..dabcc720ce 100644 --- a/lib/elixir/pages/getting-started/keywords-and-maps.md +++ b/lib/elixir/pages/getting-started/keywords-and-maps.md @@ -217,7 +217,7 @@ Elixir developers typically prefer to use the `map.key` syntax and pattern match ## Nested data structures -Often we will have maps inside maps, or even keywords lists inside maps, and so forth. Elixir provides conveniences for manipulating nested data structures via the `put_in/2`, `update_in/2` and other macros giving the same conveniences you would find in imperative languages while keeping the immutable properties of the language. +Often we will have maps inside maps, or even keywords lists inside maps, and so forth. Elixir provides conveniences for manipulating nested data structures via the `get_in/1`, `put_in/2`, `update_in/2`, and other macros giving the same conveniences you would find in imperative languages while keeping the immutable properties of the language. Imagine you have the following structure: @@ -259,7 +259,7 @@ iex> users = update_in users[:mary].languages, fn languages -> List.delete(langu ] ``` -There is more to learn about `put_in/2` and `update_in/2`, including the `get_and_update_in/2` that allows us to extract a value and update the data structure at once. There are also `put_in/3`, `update_in/3` and `get_and_update_in/3` which allow dynamic access into the data structure. +There is more to learn about `get_in/1`, `pop_in/1` and others, including the `get_and_update_in/2` that allows us to extract a value and update the data structure at once. There are also `get_in/3`, `put_in/3`, `update_in/3`, `get_and_update_in/3`, `pop_in/2` which allow dynamic access into the data structure. ## Summary diff --git a/lib/elixir/test/elixir/kernel_test.exs b/lib/elixir/test/elixir/kernel_test.exs index 220702fb8d..25258e0e39 100644 --- a/lib/elixir/test/elixir/kernel_test.exs +++ b/lib/elixir/test/elixir/kernel_test.exs @@ -929,6 +929,22 @@ defmodule KernelTest do defstruct [:foo, :bar] end + test "get_in/1" do + users = %{"john" => %{age: 27}, :meg => %{age: 23}} + assert get_in(users["john"][:age]) == 27 + assert get_in(users["dave"][:age]) == nil + assert get_in(users["john"].age) == 27 + assert get_in(users["dave"].age) == nil + assert get_in(users.meg[:age]) == 23 + assert get_in(users.meg.age) == 23 + + is_nil = nil + assert get_in(is_nil.age) == nil + + assert_raise KeyError, ~r"key :unknown not found", fn -> get_in(users.unknown) end + assert_raise KeyError, ~r"key :unknown not found", fn -> get_in(users.meg.unknown) end + end + test "get_in/2" do users = %{"john" => %{age: 27}, "meg" => %{age: 23}} assert get_in(users, ["john", :age]) == 27