diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/dict.erl | 3 | ||||
-rw-r--r-- | lib/stdlib/src/epp.erl | 30 | ||||
-rw-r--r-- | lib/stdlib/src/erl_compile.erl | 18 | ||||
-rw-r--r-- | lib/stdlib/src/erl_lint.erl | 91 | ||||
-rw-r--r-- | lib/stdlib/src/erl_parse.yrl | 64 | ||||
-rw-r--r-- | lib/stdlib/src/escript.erl | 10 | ||||
-rw-r--r-- | lib/stdlib/src/io.erl | 10 | ||||
-rw-r--r-- | lib/stdlib/src/sets.erl | 5 | ||||
-rw-r--r-- | lib/stdlib/src/stdlib.app.src | 5 |
9 files changed, 143 insertions, 93 deletions
diff --git a/lib/stdlib/src/dict.erl b/lib/stdlib/src/dict.erl index 6088e1a2dd..cf8fb3114a 100644 --- a/lib/stdlib/src/dict.erl +++ b/lib/stdlib/src/dict.erl @@ -55,8 +55,7 @@ -define(exp_size, (?seg_size * ?expand_load)). -define(con_size, (?seg_size * ?contract_load)). --type segs(K, V) :: tuple() - | {K, V}. % dummy +-type segs(_Key, _Value) :: tuple(). %% Define a hashtable. The default values are the standard ones. -record(dict, diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl index d212a55b47..9b506b0a44 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -33,23 +33,33 @@ -export_type([source_encoding/0]). --type macros() :: [{atom(), term()}]. +-type macros() :: [atom() | {atom(), term()}]. -type epp_handle() :: pid(). -type source_encoding() :: latin1 | utf8. +-type ifdef() :: 'ifdef' | 'ifndef' | 'else'. + +-type name() :: {'atom', atom()}. +-type argspec() :: 'none' %No arguments + | non_neg_integer(). %Number of arguments +-type tokens() :: [erl_scan:token()]. +-type used() :: {name(), argspec()}. + -define(DEFAULT_ENCODING, utf8). %% Epp state record. --record(epp, {file, %Current file +-record(epp, {file :: file:io_device(), %Current file location=1, %Current location - delta, %Offset from Location (-file) - name="", %Current file name - name2="", %-"-, modified by -file - istk=[], %Ifdef stack - sstk=[], %State stack - path=[], %Include-path - macs = dict:new() :: dict:dict(),%Macros (don't care locations) - uses = dict:new() :: dict:dict(),%Macro use structure + delta=0 :: non_neg_integer(), %Offset from Location (-file) + name="" :: file:name(), %Current file name + name2="" :: file:name(), %-"-, modified by -file + istk=[] :: [ifdef()], %Ifdef stack + sstk=[] :: [#epp{}], %State stack + path=[] :: [file:name()], %Include-path + macs = dict:new() %Macros (don't care locations) + :: dict:dict(name(), {argspec(), tokens()}), + uses = dict:new() %Macro use structure + :: dict:dict(name(), [{argspec(), [used()]}]), default_encoding = ?DEFAULT_ENCODING :: source_encoding(), pre_opened = false :: boolean() }). diff --git a/lib/stdlib/src/erl_compile.erl b/lib/stdlib/src/erl_compile.erl index ed8fea5d78..caed4d41d6 100644 --- a/lib/stdlib/src/erl_compile.erl +++ b/lib/stdlib/src/erl_compile.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2013. All Rights Reserved. +%% Copyright Ericsson AB 1997-2014. 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 @@ -66,7 +66,7 @@ my_halt(Reason) -> compile(List) -> process_flag(trap_exit, true), - Pid = spawn_link(fun() -> compiler_runner(List) end), + Pid = spawn_link(compiler_runner(List)), receive {'EXIT', Pid, {compiler_result, Result}} -> Result; @@ -79,14 +79,16 @@ compile(List) -> error end. --spec compiler_runner([cmd_line_arg()]) -> no_return(). +-spec compiler_runner([cmd_line_arg()]) -> fun(() -> no_return()). compiler_runner(List) -> - %% We don't want the current directory in the code path. - %% Remove it. - Path = [D || D <- code:get_path(), D =/= "."], - true = code:set_path(Path), - exit({compiler_result, compile1(List)}). + fun() -> + %% We don't want the current directory in the code path. + %% Remove it. + Path = [D || D <- code:get_path(), D =/= "."], + true = code:set_path(Path), + exit({compiler_result, compile1(List)}) + end. %% Parses the first part of the option list. diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 4c0261a1ad..c4c94fbee4 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -80,13 +80,17 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) -> -type fa() :: {atom(), arity()}. % function+arity -type ta() :: {atom(), arity()}. % type+arity +-record(typeinfo, {attr, line}). + %% Usage of records, functions, and imports. The variable table, which %% is passed on as an argument, holds the usage of variables. -record(usage, { calls = dict:new(), %Who calls who imported = [], %Actually imported functions - used_records=sets:new() :: sets:set(),%Used record definitions - used_types = dict:new() :: dict:dict()%Used type definitions + used_records = sets:new() %Used record definitions + :: sets:set(atom()), + used_types = dict:new() %Used type definitions + :: dict:dict(ta(), line()) }). %% Define the lint state record. @@ -95,13 +99,17 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) -> -record(lint, {state=start :: 'start' | 'attribute' | 'function', module=[], %Module behaviour=[], %Behaviour - exports=gb_sets:empty() :: gb_sets:set(),%Exports - imports=[], %Imports + exports=gb_sets:empty() :: gb_sets:set(fa()),%Exports + imports=[] :: [fa()], %Imports, an orddict() compile=[], %Compile flags - records=dict:new() :: dict:dict(), %Record definitions - locals=gb_sets:empty() :: gb_sets:set(),%All defined functions (prescanned) - no_auto=gb_sets:empty() :: gb_sets:set() | 'all',%Functions explicitly not autoimported - defined=gb_sets:empty() :: gb_sets:set(),%Defined fuctions + records=dict:new() %Record definitions + :: dict:dict(atom(), {line(),Fields :: term()}), + locals=gb_sets:empty() %All defined functions (prescanned) + :: gb_sets:set(fa()), + no_auto=gb_sets:empty() %Functions explicitly not autoimported + :: gb_sets:set(fa()) | 'all', + defined=gb_sets:empty() %Defined fuctions + :: gb_sets:set(fa()), on_load=[] :: [fa()], %On-load function on_load_line=0 :: line(), %Line for on_load clashes=[], %Exported functions named as BIFs @@ -116,12 +124,16 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) -> %outside any fun or lc xqlc= false :: boolean(), %true if qlc.hrl included new = false :: boolean(), %Has user-defined 'new/N' - called= [] :: [{fa(),line()}], %Called functions + called= [] :: [{fa(),line()}], %Called functions usage = #usage{} :: #usage{}, - specs = dict:new() :: dict:dict(), %Type specifications - callbacks = dict:new() :: dict:dict(), %Callback types - types = dict:new() :: dict:dict(), %Type definitions - exp_types=gb_sets:empty():: gb_sets:set()%Exported types + specs = dict:new() %Type specifications + :: dict:dict(mfa(), line()), + callbacks = dict:new() %Callback types + :: dict:dict(mfa(), line()), + types = dict:new() %Type definitions + :: dict:dict(ta(), #typeinfo{}), + exp_types=gb_sets:empty() %Exported types + :: gb_sets:set(ta()) }). -type lint_state() :: #lint{}. @@ -319,10 +331,14 @@ format_error({undefined_type, {TypeName, Arity}}) -> io_lib:format("type ~w~s undefined", [TypeName, gen_type_paren(Arity)]); format_error({unused_type, {TypeName, Arity}}) -> io_lib:format("type ~w~s is unused", [TypeName, gen_type_paren(Arity)]); -format_error({new_builtin_type, {TypeName, Arity}}) -> - io_lib:format("type ~w~s is a new builtin type; " +%% format_error({new_builtin_type, {TypeName, Arity}}) -> +%% io_lib:format("type ~w~s is a new builtin type; " +%% "its (re)definition is allowed only until the next release", +%% [TypeName, gen_type_paren(Arity)]); +format_error({new_var_arity_type, TypeName}) -> + io_lib:format("type ~w is a new builtin type; " "its (re)definition is allowed only until the next release", - [TypeName, gen_type_paren(Arity)]); + [TypeName]); format_error({builtin_type, {TypeName, Arity}}) -> io_lib:format("type ~w~s is a builtin type; it cannot be redefined", [TypeName, gen_type_paren(Arity)]); @@ -1170,7 +1186,7 @@ export_type(Line, ETs, #lint{usage = Usage, exp_types = ETs0} = St0) -> add_error(Line, {bad_export_type, ETs}, St0) end. --spec exports(lint_state()) -> gb_sets:set(). +-spec exports(lint_state()) -> gb_sets:set(fa()). exports(#lint{compile = Opts, defined = Defs, exports = Es}) -> case lists:member(export_all, Opts) of @@ -2574,8 +2590,6 @@ find_field(_F, []) -> error. %% Attr :: 'type' | 'opaque' %% Checks that a type definition is valid. --record(typeinfo, {attr, line}). - type_def(_Attr, _Line, {record, _RecName}, Fields, [], St0) -> %% The record field names and such are checked in the record format. %% We only need to check the types. @@ -2596,23 +2610,30 @@ type_def(Attr, Line, TypeName, ProtoType, Args, St0) -> true -> case is_obsolete_builtin_type(TypePair) of true -> StoreType(St0); - false -> - case is_newly_introduced_builtin_type(TypePair) of - %% allow some types just for bootstrapping - true -> - Warn = {new_builtin_type, TypePair}, - St1 = add_warning(Line, Warn, St0), - StoreType(St1); - false -> - add_error(Line, {builtin_type, TypePair}, St0) - end + false -> add_error(Line, {builtin_type, TypePair}, St0) +%% case is_newly_introduced_builtin_type(TypePair) of +%% %% allow some types just for bootstrapping +%% true -> +%% Warn = {new_builtin_type, TypePair}, +%% St1 = add_warning(Line, Warn, St0), +%% StoreType(St1); +%% false -> +%% add_error(Line, {builtin_type, TypePair}, St0) +%% end end; false -> case - dict:is_key(TypePair, TypeDefs) - orelse is_var_arity_type(TypeName) + dict:is_key(TypePair, TypeDefs) orelse + is_var_arity_type(TypeName) of - true -> add_error(Line, {redefine_type, TypePair}, St0); + true -> + case is_newly_introduced_var_arity_type(TypeName) of + true -> + Warn = {new_var_arity_type, TypeName}, + add_warning(Line, Warn, St0); + false -> + add_error(Line, {redefine_type, TypePair}, St0) + end; false -> St1 = case Attr =:= opaque andalso @@ -2847,8 +2868,10 @@ is_default_type({timeout, 0}) -> true; is_default_type({var, 1}) -> true; is_default_type(_) -> false. -%% OTP 17.0 -is_newly_introduced_builtin_type({Name, _}) when is_atom(Name) -> false. +is_newly_introduced_var_arity_type(map) -> true; +is_newly_introduced_var_arity_type(_) -> false. + +%% is_newly_introduced_builtin_type({Name, _}) when is_atom(Name) -> false. is_obsolete_builtin_type(TypePair) -> obsolete_builtin_type(TypePair) =/= no. diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 6316db7054..1dc5fc52a7 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -2,7 +2,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-2014. 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 @@ -919,59 +919,63 @@ normalise_list([]) -> Data :: term(), AbsTerm :: abstract_expr(). abstract(T) -> - abstract(T, 0, epp:default_encoding()). + abstract(T, 0, enc_func(epp:default_encoding())). + +-type encoding_func() :: fun((non_neg_integer()) -> boolean()). %%% abstract/2 takes line and encoding options -spec abstract(Data, Options) -> AbsTerm when Data :: term(), Options :: Line | [Option], Option :: {line, Line} | {encoding, Encoding}, - Encoding :: latin1 | unicode | utf8, + Encoding :: 'latin1' | 'unicode' | 'utf8' | 'none' | encoding_func(), Line :: erl_scan:line(), AbsTerm :: abstract_expr(). abstract(T, Line) when is_integer(Line) -> - abstract(T, Line, epp:default_encoding()); + abstract(T, Line, enc_func(epp:default_encoding())); abstract(T, Options) when is_list(Options) -> Line = proplists:get_value(line, Options, 0), Encoding = proplists:get_value(encoding, Options,epp:default_encoding()), - abstract(T, Line, Encoding). + EncFunc = enc_func(Encoding), + abstract(T, Line, EncFunc). -define(UNICODE(C), - is_integer(C) andalso - (C >= 0 andalso C < 16#D800 orelse + (C < 16#D800 orelse C > 16#DFFF andalso C < 16#FFFE orelse C > 16#FFFF andalso C =< 16#10FFFF)). +enc_func(latin1) -> fun(C) -> C < 256 end; +enc_func(unicode) -> fun(C) -> ?UNICODE(C) end; +enc_func(utf8) -> fun(C) -> ?UNICODE(C) end; +enc_func(none) -> none; +enc_func(Fun) when is_function(Fun, 1) -> Fun; +enc_func(Term) -> erlang:error({badarg, Term}). + abstract(T, L, _E) when is_integer(T) -> {integer,L,T}; abstract(T, L, _E) when is_float(T) -> {float,L,T}; abstract(T, L, _E) when is_atom(T) -> {atom,L,T}; abstract([], L, _E) -> {nil,L}; abstract(B, L, _E) when is_bitstring(B) -> {bin, L, [abstract_byte(Byte, L) || Byte <- bitstring_to_list(B)]}; -abstract([C|T], L, unicode=E) when ?UNICODE(C) -> - abstract_unicode_string(T, [C], L, E); -abstract([C|T], L, utf8=E) when ?UNICODE(C) -> - abstract_unicode_string(T, [C], L, E); -abstract([C|T], L, latin1=E) when is_integer(C), 0 =< C, C < 256 -> - abstract_string(T, [C], L, E); -abstract([H|T], L, E) -> +abstract([H|T], L, none=E) -> {cons,L,abstract(H, L, E),abstract(T, L, E)}; +abstract(List, L, E) when is_list(List) -> + abstract_list(List, [], L, E); abstract(Tuple, L, E) when is_tuple(Tuple) -> - {tuple,L,abstract_list(tuple_to_list(Tuple), L, E)}. - -abstract_string([C|T], String, L, E) when is_integer(C), 0 =< C, C < 256 -> - abstract_string(T, [C|String], L, E); -abstract_string([], String, L, _E) -> - {string, L, lists:reverse(String)}; -abstract_string(T, String, L, E) -> - not_string(String, abstract(T, L, E), L, E). - -abstract_unicode_string([C|T], String, L, E) when ?UNICODE(C) -> - abstract_unicode_string(T, [C|String], L, E); -abstract_unicode_string([], String, L, _E) -> + {tuple,L,abstract_tuple_list(tuple_to_list(Tuple), L, E)}. + +abstract_list([H|T], String, L, E) -> + case is_integer(H) andalso H >= 0 andalso E(H) of + true -> + abstract_list(T, [H|String], L, E); + false -> + AbstrList = {cons,L,abstract(H, L, E),abstract(T, L, E)}, + not_string(String, AbstrList, L, E) + end; +abstract_list([], String, L, _E) -> {string, L, lists:reverse(String)}; -abstract_unicode_string(T, String, L, E) -> +abstract_list(T, String, L, E) -> not_string(String, abstract(T, L, E), L, E). not_string([C|T], Result, L, E) -> @@ -979,9 +983,9 @@ not_string([C|T], Result, L, E) -> not_string([], Result, _L, _E) -> Result. -abstract_list([H|T], L, E) -> - [abstract(H, L, E)|abstract_list(T, L, E)]; -abstract_list([], _L, _E) -> +abstract_tuple_list([H|T], L, E) -> + [abstract(H, L, E)|abstract_tuple_list(T, L, E)]; +abstract_tuple_list([], _L, _E) -> []. abstract_byte(Byte, L) when is_integer(Byte) -> diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl index 35f6dff57e..a8a82272d6 100644 --- a/lib/stdlib/src/escript.erl +++ b/lib/stdlib/src/escript.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2007-2013. All Rights Reserved. +%% Copyright Ericsson AB 2007-2014. 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 @@ -289,6 +289,8 @@ start(EscriptOptions) -> my_halt(127) end. +-spec parse_and_run(_, _, _) -> no_return(). + parse_and_run(File, Args, Options) -> CheckOnly = lists:member("s", Options), {Source, Module, FormsOrBin, HasRecs, Mode} = @@ -727,6 +729,8 @@ epp_parse_file2(Epp, S, Forms, Parsed) -> %% Evaluate script %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +-spec debug(_, _, _) -> no_return(). + debug(Module, AbsMod, Args) -> case hidden_apply(debugger, debugger, start, []) of {ok, _} -> @@ -742,6 +746,8 @@ debug(Module, AbsMod, Args) -> fatal("Cannot start the debugger") end. +-spec run(_, _) -> no_return(). + run(Module, Args) -> try Module:main(Args), @@ -751,6 +757,8 @@ run(Module, Args) -> fatal(format_exception(Class, Reason)) end. +-spec interpret(_, _, _, _) -> no_return(). + interpret(Forms, HasRecs, File, Args) -> %% Basic validation before execution case erl_lint:module(Forms) of diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl index b11d41e2eb..27e2a82b41 100644 --- a/lib/stdlib/src/io.erl +++ b/lib/stdlib/src/io.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-2014. 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 @@ -177,13 +177,15 @@ get_password(Io) -> | {'expand_fun', expand_fun()} | {'encoding', encoding()}. --spec getopts() -> [opt_pair()]. +-spec getopts() -> [opt_pair()] | {'error', Reason} when + Reason :: term(). getopts() -> getopts(default_input()). --spec getopts(IoDevice) -> [opt_pair()] when - IoDevice :: device(). +-spec getopts(IoDevice) -> [opt_pair()] | {'error', Reason} when + IoDevice :: device(), + Reason :: term(). getopts(Io) -> request(Io, getopts). diff --git a/lib/stdlib/src/sets.erl b/lib/stdlib/src/sets.erl index be4b600f25..167a676281 100644 --- a/lib/stdlib/src/sets.erl +++ b/lib/stdlib/src/sets.erl @@ -55,9 +55,8 @@ %%------------------------------------------------------------------------------ --type seg() :: tuple(). --type segs(E) :: tuple() - | E. % dummy +-type seg() :: tuple(). +-type segs(_Element) :: tuple(). %% Define a hash set. The default values are the standard ones. -record(set, diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src index a64b8e13c0..d388410de0 100644 --- a/lib/stdlib/src/stdlib.app.src +++ b/lib/stdlib/src/stdlib.app.src @@ -102,5 +102,8 @@ {registered,[timer_server,rsh_starter,take_over_monitor,pool_master, dets]}, {applications, [kernel]}, - {env, []}]}. + {env, []}, + {runtime_dependencies, ["sasl-2.4","kernel-3.0","erts-6.0","crypto-3.3", + "compiler-5.0"]} +]}. |