aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/erl_expand_records.erl
diff options
context:
space:
mode:
authorHans Bolinder <[email protected]>2015-03-09 16:26:09 +0100
committerBjörn Gustavsson <[email protected]>2015-04-30 12:14:30 +0200
commit87a0af476ef82ca2f33d0e15ce324afcfafe3aad (patch)
treea2b3614bfab4f6d58ec739edb86f8f15d7e7bcd3 /lib/stdlib/src/erl_expand_records.erl
parentd20cf6b7d18fd45d6c1beaa39aa87be90080f30b (diff)
downloadotp-87a0af476ef82ca2f33d0e15ce324afcfafe3aad.tar.gz
otp-87a0af476ef82ca2f33d0e15ce324afcfafe3aad.tar.bz2
otp-87a0af476ef82ca2f33d0e15ce324afcfafe3aad.zip
stdlib: Use module erl_anno
Diffstat (limited to 'lib/stdlib/src/erl_expand_records.erl')
-rw-r--r--lib/stdlib/src/erl_expand_records.erl40
1 files changed, 19 insertions, 21 deletions
diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl
index dc74d611a3..0d3debae22 100644
--- a/lib/stdlib/src/erl_expand_records.erl
+++ b/lib/stdlib/src/erl_expand_records.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2005-2014. All Rights Reserved.
+%% Copyright Ericsson AB 2005-2015. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -38,8 +38,6 @@
checked_ra=[] % successfully accessed records
}).
--define(REC_OFFSET, 100000000). % A hundred millions. Also in v3_core.
-
-spec(module(AbsForms, CompileOptions) -> AbsForms when
AbsForms :: [erl_parse:abstract_form()],
CompileOptions :: [compile:option()]).
@@ -149,7 +147,7 @@ pattern({record_index,Line,Name,Field}, St) ->
pattern({record,Line0,Name,Pfs}, St0) ->
Fs = record_fields(Name, St0),
{TMs,St1} = pattern_list(pattern_fields(Fs, Pfs), St0),
- Line = record_offset(Line0, St1),
+ Line = mark_record(Line0, St1),
{{tuple,Line,[{atom,Line0,Name} | TMs]},St1};
pattern({bin,Line,Es0}, St0) ->
{Es1,St1} = pattern_bin(Es0, St0),
@@ -243,7 +241,7 @@ record_test_in_guard(Line, Term, Name, St) ->
expr({atom,Line,false}, St);
false ->
Fs = record_fields(Name, St),
- NLine = neg_line(Line),
+ NLine = no_compiler_warning(Line),
expr({call,NLine,{remote,NLine,{atom,NLine,erlang},{atom,NLine,is_record}},
[Term,{atom,Line,Name},{integer,Line,length(Fs)+1}]},
St)
@@ -269,7 +267,7 @@ record_test_in_body(Line, Expr, Name, St0) ->
%% evaluate to a tuple properly.
Fs = record_fields(Name, St0),
{Var,St} = new_var(Line, St0),
- NLine = neg_line(Line),
+ NLine = no_compiler_warning(Line),
expr({block,Line,
[{match,Line,Var,Expr},
{call,NLine,{remote,NLine,{atom,NLine,erlang},
@@ -333,7 +331,7 @@ expr({record_index,Line,Name,F}, St) ->
I = index_expr(Line, F, Name, record_fields(Name, St)),
expr(I, St);
expr({record,Line0,Name,Is}, St) ->
- Line = record_offset(Line0, St),
+ Line = mark_record(Line0, St),
expr({tuple,Line,[{atom,Line0,Name} |
record_inits(record_fields(Name, St), Is)]},
St);
@@ -459,7 +457,7 @@ strict_record_access(E0, St0) ->
conj([], _E) ->
empty;
conj([{{Name,_Rp},L,R,Sz} | AL], E) ->
- NL = neg_line(L),
+ NL = no_compiler_warning(L),
T1 = {op,NL,'orelse',
{call,NL,
{remote,NL,{atom,NL,erlang},{atom,NL,is_record}},
@@ -575,8 +573,8 @@ strict_get_record_field(Line, R, {atom,_,F}=Index, Name, St0) ->
Fs = record_fields(Name, St),
I = index_expr(F, Fs, 2),
P = record_pattern(2, I, Var, length(Fs)+1, Line, [{atom,Line,Name}]),
- NLine = neg_line(Line),
- RLine = record_offset(NLine, St),
+ NLine = no_compiler_warning(Line),
+ RLine = mark_record(NLine, St),
E = {'case',NLine,R,
[{clause,NLine,[{tuple,RLine,P}],[],[Var]},
{clause,NLine,[{var,NLine,'_'}],[],
@@ -590,7 +588,8 @@ strict_get_record_field(Line, R, {atom,_,F}=Index, Name, St0) ->
I = index_expr(Line, Index, Name, Fs),
{ExpR,St1} = expr(R, St0),
%% Just to make comparison simple:
- ExpRp = erl_lint:modify_line(ExpR, fun(_L) -> 0 end),
+ A0 = erl_anno:new(0),
+ ExpRp = erl_parse:map_anno(fun(_A) -> A0 end, ExpR),
RA = {{Name,ExpRp},Line,ExpR,length(Fs)+1},
St2 = St1#exprec{strict_ra = [RA | St1#exprec.strict_ra]},
{{call,Line,
@@ -691,8 +690,8 @@ record_update(R, Name, Fs, Us0, St0) ->
record_match(R, Name, Lr, Fs, Us, St0) ->
{Ps,News,St1} = record_upd_fs(Fs, Us, St0),
- NLr = neg_line(Lr),
- RLine = record_offset(Lr, St1),
+ NLr = no_compiler_warning(Lr),
+ RLine = mark_record(Lr, St1),
{{'case',Lr,R,
[{clause,Lr,[{tuple,RLine,[{atom,Lr,Name} | Ps]}],[],
[{tuple,RLine,[{atom,Lr,Name} | News]}]},
@@ -723,8 +722,8 @@ record_setel(R, Name, Fs, Us0) ->
Us = [T || {_,T} <- Us2],
Lr = element(2, hd(Us)),
Wildcards = duplicate(length(Fs), {var,Lr,'_'}),
- NLr = neg_line(Lr),
- %% Note: calling record_offset() here is not necessary since it is
+ NLr = no_compiler_warning(Lr),
+ %% Note: calling mark_record() here is not necessary since it is
%% targeted at Dialyzer which always calls the compiler with
%% 'strict_record_updates' meaning that record_setel() will never
%% be called.
@@ -956,12 +955,11 @@ opt_remove_2({call,Line,{atom,_,is_record},
end;
opt_remove_2(A, _) -> A.
-neg_line(L) ->
- erl_parse:set_line(L, fun(Line) -> -abs(Line) end).
+no_compiler_warning(Anno) ->
+ erl_anno:set_generated(true, Anno).
-record_offset(L, St) ->
+mark_record(Anno, St) ->
case lists:member(dialyzer, St#exprec.compile) of
- true when L >= 0 -> L+?REC_OFFSET;
- true when L < 0 -> L-?REC_OFFSET;
- false -> L
+ true -> erl_anno:set_record(true, Anno);
+ false -> Anno
end.