Skip to content

Variables in default field values of records #9317

@ilya-klyuchnikov

Description

@ilya-klyuchnikov
  1. There is a mismatch between documentation and implementation. Documentation (https://www.erlang.org/doc/system/ref_man_records.html) states:

The default value for a field is an arbitrary expression, except that it must not use any variables.

Though it's possible to define records with variables in a default value for a field.

-record(r1, {
  a = [X || X <- [a, b, a], case X of Y -> true; _ -> false end
  ]}).
-record(r2, {
  f = fun(X) -> case X of Y -> Y end end
}).

(It's not possible to have an arbitrary variable in default values, - but it's possible to have a variable in some places inside lambdas of comprehensions, and such a variable may behave differently depending on the surrounding context).

  1. Such default field values are inlined as they are during conversion of records in erl_expand_records. Conversion of records happens after initial linting (erl_lint) and erl_lint doesn't account for possible variables in default values for record fields, this results into an inconsistent behaviour in edge cases.
-module(rec).

-export([test1/1, test2/2]).

-record(r1, {
  a = [X || X <- [a, b, a], case X of Y -> true; _ -> false end
  ]}).
-record(r2, {
  f = fun(X) -> case X of Y -> Y end end
}).

test1(Y) ->
  #r1{}.

test2(Y, Z) ->
  ((#r2{})#r2.f)(Z).
erlc rec.erl
rec.erl:6:39: Warning: variable 'Y' is unused
%    6|   a = [X || X <- [a, b, a], case X of Y -> true; _ -> false end
%     |                                       ^

rec.erl:12:7: Warning: variable 'Y' is unused
%   12| test1(Y) ->
%     |       ^

rec.erl:15:7: Warning: variable 'Y' is unused
%   15| test2(Y, Z) ->
%     |       ^

All warnings are wrong. Using erlc to just unfold the records and then compiling doesn't produce the same warnings.

The result of erlc -E rec.erl

-module(rec).

-export([test1/1,test2/2]).

test1(Y) ->
  {r1,
    [
      X ||
      X <- [a, b, a],
      case X of
        Y ->
          true;
        _ ->
          false
      end
    ]}.

test2(Y, Z) ->
  case
    {r2,
      fun(X) ->
        case X of
          Y ->
            Y
        end
      end}
  of
    {r2, REC0} ->
      REC0;
    REC0 ->
      error({badrecord, REC0})
  end(Z).

You can see now that Y vars in test1/1 and test2/1 are actually used and affect Y vars from the default values.

  1. Moreover, - it's possible to compile a code with an unsafe (after record unfolding) variable that otherwise would not compile.
-module(rec1).

-export([test3/1]).

-record(r2, {
  f = fun(X) -> case X of Y -> Y end end
}).

test3(Z) ->
  case Z of a -> Y = a; _ -> ok end,
  #r2{}.

This code compiles, while if we first perform record unfolding and then try to compile, it doesn't compile.

After erlc -E rec1.erl

test3(Z) ->
    case Z of
        a ->
            Y = a;
        _ ->
            ok
    end,
    {r2,
     fun(X) ->
            case X of
                Y ->
                    Y
            end
     end}.

Compiling this code would result into variable 'Y' unsafe in 'case'


I have no opinion what would be the correct behaviour (a simplest one would be to ban all variables in default values for record fields), but the current behaviour is inconsistent.

Metadata

Metadata

Assignees

Labels

team:VMAssigned to OTP team VM

Type

No type

Projects

No projects

Relationships

None yet

Development

No branches or pull requests

Issue actions