Skip to content

Commit 9bc8925

Browse files
author
José Valim
committed
Ensure defrecord and defstruct executes its args
1 parent 30d7114 commit 9bc8925

File tree

8 files changed

+68
-78
lines changed

8 files changed

+68
-78
lines changed

lib/elixir/lib/file.ex

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,5 @@
11
require Record
22

3-
record = Record.extract(:file_info, from_lib: "kernel/include/file.hrl")
4-
keys = :lists.map(&elem(&1, 0), record)
5-
vals = :lists.map(&{&1, [], nil}, keys)
6-
pairs = :lists.zip(keys, vals)
7-
83
defmodule File.Stat do
94
@moduledoc """
105
A struct responsible to hold file information.
@@ -43,7 +38,12 @@ defmodule File.Stat do
4338
`:universal`, or `:posix`. Default is `:local`.
4439
"""
4540

46-
defstruct unquote(keys)
41+
record = Record.extract(:file_info, from_lib: "kernel/include/file.hrl")
42+
keys = :lists.map(&elem(&1, 0), record)
43+
vals = :lists.map(&{&1, [], nil}, keys)
44+
pairs = :lists.zip(keys, vals)
45+
46+
defstruct keys
4747

4848
@doc """
4949
Converts a `File.Stat` struct to a `:file_info` record.

lib/elixir/lib/inspect/algebra.ex

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -116,16 +116,16 @@ defmodule Inspect.Algebra do
116116

117117
require Record
118118

119-
@opaque doc_cons :: {:doc_cons, t, t}
119+
@typep doc_cons :: {:doc_cons, t, t}
120120
Record.defrecordp :doc_cons, left: :doc_nil, right: :doc_nil
121121

122-
@opaque doc_nest :: {:doc_nest, non_neg_integer, t}
122+
@typep doc_nest :: {:doc_nest, non_neg_integer, t}
123123
Record.defrecordp :doc_nest, indent: 1, doc: :doc_nil
124124

125-
@opaque doc_break :: {:doc_break, binary}
125+
@typep doc_break :: {:doc_break, binary}
126126
Record.defrecordp :doc_break, str: " "
127127

128-
@opaque doc_group :: {:doc_group, t}
128+
@typep doc_group :: {:doc_group, t}
129129
Record.defrecordp :doc_group, doc: :doc_nil
130130

131131
defmacrop is_doc(doc) do

lib/elixir/lib/kernel.ex

Lines changed: 25 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -3299,21 +3299,34 @@ defmodule Kernel do
32993299
In case a struct does not declare a field type, it defaults to `term`.
33003300
"""
33013301
defmacro defstruct(kv) do
3302-
kv = Macro.escape(kv, unquote: true)
3303-
quote bind_quoted: [kv: kv] do
3304-
# Expand possible macros that return KVs.
3305-
kv = Macro.expand(kv, __ENV__)
3306-
{fields, types} = Record.Backend.split_fields_and_types(:defstruct, kv)
3307-
3308-
if :code.ensure_loaded(Kernel.Typespec) == {:module, Kernel.Typespec} and
3309-
not Kernel.Typespec.defines_type?(__MODULE__, :t, 0) do
3310-
@type t :: %{unquote_splicing(types), __struct__: __MODULE__}
3302+
{fields, types} = Record.Backend.split_fields_and_types(:defstruct, kv)
3303+
3304+
fields =
3305+
quote bind_quoted: [fields: fields] do
3306+
fields = Enum.map(fields, fn
3307+
{ key, _ } = pair when is_atom(key) -> pair
3308+
key when is_atom(key) -> { key, nil }
3309+
other -> raise ArgumentError, message: "struct fields must be atoms, got: #{inspect other}"
3310+
end)
3311+
3312+
def __struct__() do
3313+
%{unquote_splicing(Macro.escape(fields)), __struct__: __MODULE__}
3314+
end
33113315
end
33123316

3313-
def __struct__() do
3314-
%{unquote_splicing(fields), __struct__: __MODULE__}
3317+
types =
3318+
case bootstraped?(Kernel.Typespec) do
3319+
true ->
3320+
quote do
3321+
unless Kernel.Typespec.defines_type?(__MODULE__, :t, 0) do
3322+
@type t :: %{unquote_splicing(types), __struct__: __MODULE__}
3323+
end
3324+
end
3325+
false ->
3326+
nil
33153327
end
3316-
end
3328+
3329+
[types, fields]
33173330
end
33183331

33193332
@doc ~S"""

lib/elixir/lib/record.ex

Lines changed: 2 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -155,14 +155,9 @@ defmodule Record do
155155
156156
"""
157157
defmacro defrecord(name, tag \\ nil, kv) do
158-
kv = Macro.escape(kv, unquote: true)
159-
160158
quote bind_quoted: [name: name, tag: tag, kv: kv] do
161159
tag = tag || name
162-
kv = Macro.expand(kv, __ENV__)
163-
164-
{fields, _types} = Record.Backend.split_fields_and_types(:defrecord, kv)
165-
fields = Macro.escape(fields)
160+
fields = Macro.escape(kv)
166161

167162
defmacro(unquote(name)(args \\ [])) do
168163
Record.Backend.access(unquote(tag), unquote(fields), args, __CALLER__)
@@ -178,14 +173,9 @@ defmodule Record do
178173
Same as `defrecord/3` but generates private macros.
179174
"""
180175
defmacro defrecordp(name, tag \\ nil, kv) do
181-
kv = Macro.escape(kv, unquote: true)
182-
183176
quote bind_quoted: [name: name, tag: tag, kv: kv] do
184177
tag = tag || name
185-
kv = Macro.expand(kv, __ENV__)
186-
187-
{fields, _types} = Record.Backend.split_fields_and_types(:defrecordp, kv)
188-
fields = Macro.escape(fields)
178+
fields = Macro.escape(kv)
189179

190180
defmacrop(unquote(name)(args \\ [])) do
191181
Record.Backend.access(unquote(tag), unquote(fields), args, __CALLER__)

lib/elixir/lib/record/backend.ex

Lines changed: 8 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -7,30 +7,26 @@ defmodule Record.Backend do
77
88
This logic is shared by records and structs.
99
"""
10-
def split_fields_and_types(tag, kv) when is_list(kv) do
11-
split_fields_and_types(tag, kv, [], [])
12-
end
13-
14-
def split_fields_and_types(tag, other) do
15-
raise ArgumentError, message: "#{tag} fields must be a keyword list, got: #{Macro.to_string other}"
10+
def split_fields_and_types(tag, kv) do
11+
if Keyword.keyword?(kv) do
12+
split_fields_and_types(tag, kv, [], [])
13+
else
14+
{kv, []}
15+
end
1616
end
1717

1818
defp split_fields_and_types(tag, [{field, {:::, _, [default, type]}}|t], fields, types) do
1919
split_fields_and_types(tag, t, [{field, default}|fields], [{field, type}|types])
2020
end
2121

22-
defp split_fields_and_types(tag, [{field, default}|t], fields, types) when is_atom(field) do
22+
defp split_fields_and_types(tag, [{field, default}|t], fields, types) do
2323
split_fields_and_types(tag, t, [{field, default}|fields], [{field, quote(do: term)}|types])
2424
end
2525

26-
defp split_fields_and_types(tag, [field|t], fields, types) when is_atom(field) do
26+
defp split_fields_and_types(tag, [field|t], fields, types) do
2727
split_fields_and_types(tag, t, [{field, nil}|fields], [{field, quote(do: term)}|types])
2828
end
2929

30-
defp split_fields_and_types(tag, [other|_], _fields, _types) do
31-
raise ArgumentError, message: "#{tag} fields must be atoms, got: #{Macro.to_string other}"
32-
end
33-
3430
defp split_fields_and_types(_tag, [], fields, types) do
3531
{:lists.reverse(fields), :lists.reverse(types)}
3632
end

lib/elixir/src/elixir_map.erl

Lines changed: 20 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -89,42 +89,33 @@ translate_struct(Meta, Name, {'%{}', MapMeta, Args}, S) ->
8989

9090
%% Helpers
9191

92-
load_struct(Meta, Module, S) ->
92+
load_struct(Meta, Name, S) ->
9393
Local =
94-
elixir_module:is_open(Module) andalso
94+
elixir_module:is_open(Name) andalso
9595
(case lists:keyfind(struct, 1, Meta) of
9696
{struct, context} -> true;
97-
_ -> wait_for_struct(Module)
97+
_ -> wait_for_struct(Name)
9898
end),
9999

100-
case Local of
101-
true ->
102-
try
103-
(elixir_locals:local_for(Module, '__struct__', 0, def))()
104-
catch
105-
error:undef -> get_struct(Meta, Module, S);
106-
error:badarg -> get_struct(Meta, Module, S)
107-
end;
108-
false ->
109-
get_struct(Meta, Module, S)
110-
end.
111-
112-
get_struct(Meta, Module, S) ->
113-
case code:ensure_loaded(Module) of
114-
{module, Module} ->
115-
case erlang:function_exported(Module, '__struct__', 0) of
116-
true -> Module:'__struct__'();
117-
false -> raise_struct(Meta, Module, S)
118-
end;
119-
{error, _} ->
120-
raise_struct(Meta, Module, S)
100+
try
101+
case Local of
102+
true ->
103+
try
104+
(elixir_locals:local_for(Name, '__struct__', 0, def))()
105+
catch
106+
error:undef -> Name:'__struct__'();
107+
error:badarg -> Name:'__struct__'()
108+
end;
109+
false ->
110+
Name:'__struct__'()
111+
end
112+
catch
113+
error:undef ->
114+
Inspected = elixir_aliases:inspect(Name),
115+
compile_error(Meta, S#elixir_scope.file, "~ts.__struct__/0 is undefined, "
116+
"cannot expand struct ~ts", [Inspected, Inspected])
121117
end.
122118

123-
raise_struct(Meta, Module, S) ->
124-
Inspected = elixir_aliases:inspect(Module),
125-
compile_error(Meta, S#elixir_scope.file, "~ts.__struct__/0 is undefined, "
126-
"cannot expand struct ~ts", [Inspected, Inspected]).
127-
128119
wait_for_struct(Module) ->
129120
case erlang:get(elixir_compiler_pid) of
130121
undefined ->

lib/elixir/test/elixir/kernel/errors_test.exs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -203,10 +203,10 @@ defmodule Kernel.ErrorsTest do
203203

204204
test :struct_fields_on_defstruct do
205205
assert_compile_fail ArgumentError,
206-
"defstruct fields must be a keyword list, got: my_fields",
206+
"struct fields must be atoms, got: 1",
207207
'''
208208
defmodule TZ do
209-
defstruct my_fields
209+
defstruct [1, 2, 3]
210210
end
211211
'''
212212
end

lib/elixir/test/elixir/map_test.exs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -129,7 +129,7 @@ defmodule MapTest do
129129
defstruct []
130130
end
131131

132-
defstruct name: "josé", nested: %NestedUser{}
132+
defstruct name: "josé", nested: struct(NestedUser)
133133

134134
def new do
135135
%LocalUser{}

0 commit comments

Comments
 (0)