Skip to content
Merged
Show file tree
Hide file tree
Changes from 1 commit
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
34 changes: 31 additions & 3 deletions lib/elixir/lib/record.ex
Original file line number Diff line number Diff line change
Expand Up @@ -139,6 +139,10 @@ defmodule Record do
records flexibility at the cost of performance since
there is more work happening at runtime.

The above calls (new and update) can interchangeably accept both
atom and string keys for field names. Please note, however, that
atom keys are faster.

To sum up, `defrecordp` should be used when you don't want
to expose the record information while `defrecord` should be used
whenever you want to share a record within your code or with other
Expand Down Expand Up @@ -625,7 +629,17 @@ defmodule Record do
# the given key from the ordered dict, falling back to the
# default value if one does not exist.
selective = lc { k, v } inlist values do
quote do: Keyword.get(opts, unquote(k), unquote(v))
string_k = atom_to_binary(k)
quote do
case :lists.keyfind(unquote(k), 1, opts) do
false ->
case :lists.keyfind(unquote(string_k), 1, opts) do
false -> unquote(v)
{_, value} -> value
end
{_, value} -> value
end
end
end

quote do
Expand Down Expand Up @@ -727,9 +741,17 @@ defmodule Record do
defp updater(values) do
fields =
lc {key, _default} inlist values do
string_key = atom_to_binary(key)
index = find_index(values, key, 1)
quote do
Keyword.get(keywords, unquote(key), elem(record, unquote(index)))
case :lists.keyfind(unquote(key), 1, keywords) do
false ->
case :lists.keyfind(unquote(string_key), 1, keywords) do
false -> elem(record, unquote(index))
{_, value} -> value
end
{_, value} -> value
end
end
end

Expand Down Expand Up @@ -765,14 +787,15 @@ defmodule Record do
defp core_specs(values) do
types = lc { _, _, spec } inlist values, do: spec
options = if values == [], do: [], else: [options_specs(values)]
values_specs = if values == [], do: [], else: values_specs(values)

quote do
unless Kernel.Typespec.defines_type?(__MODULE__, :t, 0) do
@type t :: { __MODULE__, unquote_splicing(types) }
end

unless Kernel.Typespec.defines_type?(__MODULE__, :options, 0) do
@type options :: unquote(options)
@type options :: unquote(options) | [{String.t, unquote(values_specs)}]
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I assume "attribute_name" wouldn't be a valid type?

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I am just cutting out what is used in options_spec. I think that's right.

Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yeah, I know. The thing is that options_spec has something like this: [{ :bar, integer } | { :baz, string }], so we have types per option. I am wondering if we can't have the same here, but the strings as keys.

end

@spec new :: t
Expand All @@ -790,6 +813,11 @@ defmodule Record do
{ :|, [], [{ k, v }, acc] }
end, { k, v }, t
end
defp values_specs([{ _, _, v }|t]) do
:lists.foldl fn { _, _, v }, acc ->
{ :|, [], [v, acc] }
end, v, t
end

defp accessor_specs([{ :__exception__, _, _ }|t], 1, acc) do
accessor_specs(t, 2, acc)
Expand Down
18 changes: 18 additions & 0 deletions lib/elixir/test/elixir/record_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,8 @@ defmodule RecordTest.Macros do
defrecord Record, [a: 1, b: 2]
end

defrecord RecordTest.FooTest, foo: nil, bar: nil

defmodule RecordTest do
use ExUnit.Case, async: true

Expand Down Expand Up @@ -162,6 +164,22 @@ defmodule RecordTest do
assert is_record(namespace, :xmlNamespace)
end

test :string_names do
a = RecordTest.FooTest.new([{:foo, 1}, {"bar", 1}])
assert a.foo == 1
assert a.bar == 1
a = a.update([{"foo", 2}, {:bar, 2}])
assert a.foo == 2
assert a.bar == 2
end

test :string_names_import do
record = RecordTest.FileInfo.new([{"type", :regular}, {:access, 100}])
assert record.type == :regular
assert record.access == 100
assert record.update([{"access", 101}]).access == 101
end

defp empty_tuple, do: {}
defp a_tuple, do: { :foo, :bar, :baz }
defp a_list, do: [ :foo, :bar, :baz ]
Expand Down