diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/dets.erl | 12 | ||||
-rw-r--r-- | lib/stdlib/src/dict.erl | 3 | ||||
-rw-r--r-- | lib/stdlib/src/epp.erl | 177 | ||||
-rw-r--r-- | lib/stdlib/src/erl_compile.erl | 18 | ||||
-rw-r--r-- | lib/stdlib/src/erl_eval.erl | 25 | ||||
-rw-r--r-- | lib/stdlib/src/erl_lint.erl | 345 | ||||
-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/gen.erl | 6 | ||||
-rw-r--r-- | lib/stdlib/src/gen_event.erl | 37 | ||||
-rw-r--r-- | lib/stdlib/src/gen_fsm.erl | 20 | ||||
-rw-r--r-- | lib/stdlib/src/gen_server.erl | 16 | ||||
-rw-r--r-- | lib/stdlib/src/io.erl | 10 | ||||
-rw-r--r-- | lib/stdlib/src/maps.erl | 15 | ||||
-rw-r--r-- | lib/stdlib/src/qlc_pt.erl | 11 | ||||
-rw-r--r-- | lib/stdlib/src/sets.erl | 5 | ||||
-rw-r--r-- | lib/stdlib/src/stdlib.app.src | 5 | ||||
-rw-r--r-- | lib/stdlib/src/sys.erl | 65 |
18 files changed, 546 insertions, 298 deletions
diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl index 44dad04f43..c32da1624f 100644 --- a/lib/stdlib/src/dets.erl +++ b/lib/stdlib/src/dets.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 @@ -1785,6 +1785,7 @@ read_file_header(FileName, Access, RamFile) -> Version =:= 9 -> dets_v9:read_file_header(Fd, FileName); true -> + _ = file:close(Fd), throw({error, {not_a_dets_file, FileName}}) end. @@ -2113,6 +2114,8 @@ test_bchunk_format(Head, Term) -> do_open_file([Fname, Verbose], Parent, Server, Ref) -> case catch fopen2(Fname, Ref) of + {error, {tooshort, _}} -> + err({error, {not_a_dets_file, Fname}}); {error, _Reason} = Error -> err(Error); {ok, Head} -> @@ -2126,11 +2129,10 @@ do_open_file([Fname, Verbose], Parent, Server, Ref) -> [Bad]), {error, {dets_bug, Fname, Bad}} end; -do_open_file([Tab, OpenArgs, Verb], Parent, Server, Ref) -> +do_open_file([Tab, OpenArgs, Verb], Parent, Server, _Ref) -> case catch fopen3(Tab, OpenArgs) of {error, {tooshort, _}} -> - _ = file:delete(OpenArgs#open_args.file), - do_open_file([Tab, OpenArgs, Verb], Parent, Server, Ref); + err({error, {not_a_dets_file, OpenArgs#open_args.file}}); {error, _Reason} = Error -> err(Error); {ok, Head} -> @@ -2486,7 +2488,6 @@ fopen2(Fname, Tab) -> {ok, _} -> Acc = read_write, Ram = false, - %% Fd is not always closed upon error, but exit is soon called. {ok, Fd, FH} = read_file_header(Fname, Acc, Ram), Mod = FH#fileheader.mod, Do = case Mod:check_file_header(FH, Fd) of @@ -2542,7 +2543,6 @@ fopen_existing_file(Tab, OpenArgs) -> ram_file = Ram, delayed_write = CacheSz, auto_save = Auto, access = Acc, version = Version, debug = Debug} = OpenArgs, - %% Fd is not always closed upon error, but exit is soon called. {ok, Fd, FH} = read_file_header(Fname, Acc, Ram), V9 = (Version =:= 9) or (Version =:= default), MinF = (MinSlots =:= default) or (MinSlots =:= FH#fileheader.min_no_slots), 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 68e079b7e5..9b506b0a44 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -20,12 +20,12 @@ %% An Erlang code preprocessor. --export([open/2,open/3,open/5,close/1,format_error/1]). +-export([open/1, open/2,open/3,open/5,close/1,format_error/1]). -export([scan_erl_form/1,parse_erl_form/1,macro_defs/1]). --export([parse_file/1, parse_file/3]). +-export([parse_file/1, parse_file/2, parse_file/3]). -export([default_encoding/0, encoding_to_string/1, read_encoding_from_binary/1, read_encoding_from_binary/2, - set_encoding/1, read_encoding/1, read_encoding/2]). + set_encoding/1, set_encoding/2, read_encoding/1, read_encoding/2]). -export([interpret_file_attribute/1]). -export([normalize_typed_record_fields/1,restore_typed_record_fields/1]). @@ -33,21 +33,34 @@ -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 - location, %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 +-record(epp, {file :: file:io_device(), %Current file + location=1, %Current location + 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() }). @@ -58,6 +71,7 @@ %%% distinction in the internal representation would simplify the code %%% a little. +%% open(Options) %% open(FileName, IncludePath) %% open(FileName, IncludePath, PreDefMacros) %% open(FileName, IoDevice, StartLocation, IncludePath, PreDefMacros) @@ -65,6 +79,7 @@ %% scan_erl_form(Epp) %% parse_erl_form(Epp) %% parse_file(Epp) +%% parse_file(FileName, Options) %% parse_file(FileName, IncludePath, PreDefMacros) %% macro_defs(Epp) @@ -87,14 +102,43 @@ open(Name, Path) -> ErrorDescriptor :: term(). open(Name, Path, Pdm) -> - Self = self(), - Epp = spawn(fun() -> server(Self, Name, Path, Pdm) end), - epp_request(Epp). + internal_open([{name, Name}, {includes, Path}, {macros, Pdm}], #epp{}). open(Name, File, StartLocation, Path, Pdm) -> - Self = self(), - Epp = spawn(fun() -> server(Self, Name, File, StartLocation,Path,Pdm) end), - epp_request(Epp). + internal_open([{name, Name}, {includes, Path}, {macros, Pdm}], + #epp{file=File, pre_opened=true, location=StartLocation}). + +-spec open(Options) -> + {'ok', Epp} | {'ok', Epp, Extra} | {'error', ErrorDescriptor} when + Options :: [{'default_encoding', DefEncoding :: source_encoding()} | + {'includes', IncludePath :: [DirectoryName :: file:name()]} | + {'macros', PredefMacros :: macros()} | + {'name',FileName :: file:name()} | + 'extra'], + Epp :: epp_handle(), + Extra :: [{'encoding', source_encoding() | 'none'}], + ErrorDescriptor :: term(). + +open(Options) -> + internal_open(Options, #epp{}). + +internal_open(Options, St) -> + case proplists:get_value(name, Options) of + undefined -> + erlang:error(badarg); + Name -> + Self = self(), + Epp = spawn(fun() -> server(Self, Name, Options, St) end), + case epp_request(Epp) of + {ok, Pid, Encoding} -> + case proplists:get_bool(extra, Options) of + true -> {ok, Pid, [{encoding, Encoding}]}; + false -> {ok, Pid} + end; + Other -> + Other + end + end. -spec close(Epp) -> 'ok' when Epp :: epp_handle(). @@ -170,9 +214,6 @@ format_error({'NYI',What}) -> io_lib:format("not yet implemented '~s'", [What]); format_error(E) -> file:format_error(E). -%% parse_file(FileName, IncludePath, [PreDefMacro]) -> -%% {ok,[Form]} | {error,OpenError} - -spec parse_file(FileName, IncludePath, PredefMacros) -> {'ok', [Form]} | {error, OpenError} when FileName :: file:name(), @@ -184,17 +225,40 @@ format_error(E) -> file:format_error(E). OpenError :: file:posix() | badarg | system_limit. parse_file(Ifile, Path, Predefs) -> - case open(Ifile, Path, Predefs) of + parse_file(Ifile, [{includes, Path}, {macros, Predefs}]). + +-spec parse_file(FileName, Options) -> + {'ok', [Form]} | {'ok', [Form], Extra} | {error, OpenError} when + FileName :: file:name(), + Options :: [{'includes', IncludePath :: [DirectoryName :: file:name()]} | + {'macros', PredefMacros :: macros()} | + {'default_encoding', DefEncoding :: source_encoding()} | + 'extra'], + Form :: erl_parse:abstract_form() | {'error', ErrorInfo} | {'eof',Line}, + Line :: erl_scan:line(), + ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(), + Extra :: [{'encoding', source_encoding() | 'none'}], + OpenError :: file:posix() | badarg | system_limit. + +parse_file(Ifile, Options) -> + case internal_open([{name, Ifile} | Options], #epp{}) of {ok,Epp} -> Forms = parse_file(Epp), close(Epp), {ok,Forms}; + {ok,Epp,Extra} -> + Forms = parse_file(Epp), + close(Epp), + {ok,Forms,Extra}; {error,E} -> {error,E} end. -%% parse_file(Epp) -> -%% [Form] +-spec parse_file(Epp) -> [Form] when + Epp :: epp_handle(), + Form :: erl_parse:abstract_form() | {'error', ErrorInfo} | {'eof',Line}, + Line :: erl_scan:line(), + ErrorInfo :: erl_scan:error_info() | erl_parse:error_info(). parse_file(Epp) -> case parse_erl_form(Epp) of @@ -219,8 +283,6 @@ parse_file(Epp) -> [{eof,Location}] end. --define(DEFAULT_ENCODING, utf8). - -spec default_encoding() -> source_encoding(). default_encoding() -> @@ -258,9 +320,16 @@ read_encoding(Name, Options) -> File :: io:device(). % pid(); raw files don't work set_encoding(File) -> + set_encoding(File, ?DEFAULT_ENCODING). + +-spec set_encoding(File, Default) -> source_encoding() | none when + Default :: source_encoding(), + File :: io:device(). % pid(); raw files don't work + +set_encoding(File, Default) -> Encoding = read_encoding_from_file(File, true), Enc = case Encoding of - none -> default_encoding(); + none -> Default; Encoding -> Encoding end, ok = io:setopts(File, [{encoding, Enc}]), @@ -446,35 +515,37 @@ restore_typed_record_fields([{attribute,La,type,{{record,Record},Fields,[]}}| restore_typed_record_fields([Form|Forms]) -> [Form|restore_typed_record_fields(Forms)]. -%% server(StarterPid, FileName, Path, PreDefMacros) - -server(Pid, Name, Path, Pdm) -> +server(Pid, Name, Options, #epp{pre_opened=PreOpened}=St) -> process_flag(trap_exit, true), - case file:open(Name, [read]) of - {ok,File} -> - Location = 1, - init_server(Pid, Name, File, Location, Path, Pdm, false); - {error,E} -> - epp_reply(Pid, {error,E}) + case PreOpened of + false -> + case file:open(Name, [read]) of + {ok,File} -> + init_server(Pid, Name, Options, St#epp{file = File}); + {error,E} -> + epp_reply(Pid, {error,E}) + end; + true -> + init_server(Pid, Name, Options, St) end. -%% server(StarterPid, FileName, IoDevice, Location, Path, PreDefMacros) -server(Pid, Name, File, AtLocation, Path, Pdm) -> - process_flag(trap_exit, true), - init_server(Pid, Name, File, AtLocation, Path, Pdm, true). - -init_server(Pid, Name, File, AtLocation, Path, Pdm, Pre) -> +init_server(Pid, Name, Options, St0) -> + Pdm = proplists:get_value(macros, Options, []), Ms0 = predef_macros(Name), case user_predef(Pdm, Ms0) of {ok,Ms1} -> - _ = set_encoding(File), - epp_reply(Pid, {ok,self()}), + #epp{file = File, location = AtLocation} = St0, + DefEncoding = proplists:get_value(default_encoding, Options, + ?DEFAULT_ENCODING), + Encoding = set_encoding(File, DefEncoding), + epp_reply(Pid, {ok,self(),Encoding}), %% ensure directory of current source file is %% first in path - Path1 = [filename:dirname(Name) | Path], - St = #epp{file=File, location=AtLocation, delta=0, - name=Name, name2=Name, path=Path1, macs=Ms1, - pre_opened = Pre}, + Path = [filename:dirname(Name) | + proplists:get_value(includes, Options, [])], + St = St0#epp{delta=0, name=Name, name2=Name, + path=Path, macs=Ms1, + default_encoding=DefEncoding}, From = wait_request(St), enter_file_reply(From, Name, AtLocation, AtLocation), wait_req_scan(St); @@ -600,9 +671,11 @@ enter_file2(NewF, Pname, From, St0, AtLocation) -> %% the path) must be dropped, otherwise the path used within the current %% file will depend on the order of file inclusions in the parent files Path = [filename:dirname(Pname) | tl(St0#epp.path)], - _ = set_encoding(NewF), + DefEncoding = St0#epp.default_encoding, + _ = set_encoding(NewF, DefEncoding), #epp{file=NewF,location=Loc,name=Pname,name2=Pname,delta=0, - sstk=[St0|St0#epp.sstk],path=Path,macs=Ms}. + sstk=[St0|St0#epp.sstk],path=Path,macs=Ms, + default_encoding=DefEncoding}. enter_file_reply(From, Name, Location, AtLocation) -> Attr = loc_attr(AtLocation), 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_eval.erl b/lib/stdlib/src/erl_eval.erl index 3a4108e297..acde3ad5d6 100644 --- a/lib/stdlib/src/erl_eval.erl +++ b/lib/stdlib/src/erl_eval.erl @@ -18,6 +18,9 @@ %% -module(erl_eval). +%% Guard is_map/1 is not yet supported in HiPE. +-compile(no_native). + %% An evaluator for Erlang abstract syntax. -export([exprs/2,exprs/3,exprs/4,expr/2,expr/3,expr/4,expr/5, @@ -243,11 +246,18 @@ expr({record,_,_,Name,_}, _Bs, _Lf, _Ef, _RBs) -> %% map expr({map,_, Binding,Es}, Bs0, Lf, Ef, RBs) -> {value, Map0, Bs1} = expr(Binding, Bs0, Lf, Ef, RBs), - {Vs,Bs} = eval_map_fields(Es, Bs1, Lf, Ef), - ret_expr(lists:foldl(fun - ({map_assoc,K,V}, Mi) -> maps:put(K,V,Mi); - ({map_exact,K,V}, Mi) -> maps:update(K,V,Mi) - end, Map0, Vs), Bs, RBs); + case Map0 of + #{} -> + {Vs,Bs} = eval_map_fields(Es, Bs1, Lf, Ef), + Map1 = lists:foldl(fun ({map_assoc,K,V}, Mi) -> + maps:put(K, V, Mi); + ({map_exact,K,V}, Mi) -> + maps:update(K, V, Mi) + end, Map0, Vs), + ret_expr(Map1, Bs, RBs); + _ -> + erlang:raise(error, {badarg,Map0}, stacktrace()) + end; expr({map,_,Es}, Bs0, Lf, Ef, RBs) -> {Vs,Bs} = eval_map_fields(Es, Bs0, Lf, Ef), ret_expr(lists:foldl(fun @@ -1113,9 +1123,10 @@ match1({tuple,_,Elts}, Tuple, Bs, BBs) match_tuple(Elts, Tuple, 1, Bs, BBs); match1({tuple,_,_}, _, _Bs, _BBs) -> throw(nomatch); -match1({map,_,Fs}, Map, Bs, BBs) -> +match1({map,_,Fs}, #{}=Map, Bs, BBs) -> match_map(Fs, Map, Bs, BBs); - +match1({map,_,_}, _, _Bs, _BBs) -> + throw(nomatch); match1({bin, _, Fs}, <<_/bitstring>>=B, Bs0, BBs) -> eval_bits:match_bits(Fs, B, Bs0, BBs, match_fun(BBs), diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 9f5be2da37..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{}. @@ -225,6 +237,8 @@ format_error({too_many_arguments,Arity}) -> "maximum allowed is ~w", [Arity,?MAX_ARGUMENTS]); %% --- patterns and guards --- format_error(illegal_pattern) -> "illegal pattern"; +format_error(illegal_map_key) -> + "illegal map key"; format_error({illegal_map_key_variable,K}) -> io_lib:format("illegal use of variable ~w in map",[K]); format_error(illegal_bin_pattern) -> @@ -317,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)]); @@ -344,10 +362,19 @@ format_error(spec_wrong_arity) -> "spec has the wrong arity"; format_error(callback_wrong_arity) -> "callback has the wrong arity"; -format_error({deprecated_type, {Name, Arity}, {Mod, NewName}, Rel}) -> +format_error({deprecated_builtin_type, {Name, Arity}, + Replacement, Rel}) -> + UseS = case Replacement of + {Mod, NewName} -> + io_lib:format("use ~w:~w/~w", [Mod, NewName, Arity]); + {Mod, NewName, NewArity} -> + io_lib:format("use ~w:~w/~w or preferably ~w:~w/~w", + [Mod, NewName, Arity, + Mod, NewName, NewArity]) + end, io_lib:format("type ~w/~w is deprecated and will be " - "removed in ~s; use ~w:~w/~w", - [Name, Arity, Rel, Mod, NewName, Arity]); + "removed in ~s; use ~s", + [Name, Arity, Rel, UseS]); format_error({not_exported_opaque, {TypeName, Arity}}) -> io_lib:format("opaque type ~w~s is not exported", [TypeName, gen_type_paren(Arity)]); @@ -499,6 +526,9 @@ start(File, Opts) -> {deprecated_function, bool_option(warn_deprecated_function, nowarn_deprecated_function, true, Opts)}, + {deprecated_type, + bool_option(warn_deprecated_type, nowarn_deprecated_type, + true, Opts)}, {obsolete_guard, bool_option(warn_obsolete_guard, nowarn_obsolete_guard, true, Opts)}, @@ -1156,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 @@ -1373,18 +1403,20 @@ pattern({cons,_Line,H,T}, Vt, Old, Bvt, St0) -> pattern({tuple,_Line,Ps}, Vt, Old, Bvt, St) -> pattern_list(Ps, Vt, Old, Bvt, St); pattern({map,_Line,Ps}, Vt, Old, Bvt, St) -> - pattern_list(Ps, Vt, Old, Bvt, St); -pattern({map_field_assoc,Line,_,_}, _, _, _, St) -> - {[],[],add_error(Line, illegal_pattern, St)}; -pattern({map_field_exact,Line,KP,VP}, Vt, Old, Bvt0, St0) -> - %% if the key pattern has variables we should fail - case expr(KP,[],St0) of - {[],_} -> - pattern(VP, Vt, Old, Bvt0, St0); - {[Var|_],_} -> - %% found variables in key expression - {Vt,Old,add_error(Line,{illegal_map_key_variable,element(1,Var)},St0)} - end; + foldl(fun + ({map_field_assoc,L,_,_}, {Psvt,Bvt0,St0}) -> + {Psvt,Bvt0,add_error(L, illegal_pattern, St0)}; + ({map_field_exact,L,KP,VP}, {Psvt,Bvt0,St0}) -> + case is_valid_map_key(KP, St0) of + true -> + {Pvt,Bvt1,St1} = pattern(VP, Vt, Old, Bvt, St0), + {vtmerge_pat(Pvt, Psvt),vtmerge_pat(Bvt0, Bvt1), St1}; + false -> + {Psvt,Bvt0,add_error(L, illegal_map_key, St0)}; + {false,variable,Var} -> + {Psvt,Bvt0,add_error(L, {illegal_map_key_variable,Var}, St0)} + end + end, {[],[],St}, Ps); %%pattern({struct,_Line,_Tag,Ps}, Vt, Old, Bvt, St) -> %% pattern_list(Ps, Vt, Old, Bvt, St); pattern({record_index,Line,Name,Field}, _Vt, _Old, _Bvt, St) -> @@ -1773,13 +1805,11 @@ gexpr({cons,_Line,H,T}, Vt, St) -> gexpr({tuple,_Line,Es}, Vt, St) -> gexpr_list(Es, Vt, St); gexpr({map,_Line,Es}, Vt, St) -> - gexpr_list(Es, Vt, St); + map_fields(Es, Vt, check_assoc_fields(Es, St), fun gexpr_list/3); gexpr({map,_Line,Src,Es}, Vt, St) -> - gexpr_list([Src|Es], Vt, St); -gexpr({map_field_assoc,_Line,K,V}, Vt, St) -> - gexpr_list([K,V], Vt, St); -gexpr({map_field_exact,_Line,K,V}, Vt, St) -> - gexpr_list([K,V], Vt, St); + {Svt,St1} = gexpr(Src, Vt, St), + {Fvt,St2} = map_fields(Es, Vt, St1, fun gexpr_list/3), + {vtmerge(Svt, Fvt),St2}; gexpr({record_index,Line,Name,Field}, _Vt, St) -> check_record(Line, Name, St, fun (Dfs, St1) -> record_field(Field, Name, Dfs, St1) end ); @@ -1852,6 +1882,10 @@ gexpr({op,Line,Op,A}, Vt, St0) -> true -> {Avt,St1}; false -> {Avt,add_error(Line, illegal_guard_expr, St1)} end; +gexpr({op,_,'andalso',L,R}, Vt, St) -> + gexpr_list([L,R], Vt, St); +gexpr({op,_,'orelse',L,R}, Vt, St) -> + gexpr_list([L,R], Vt, St); gexpr({op,Line,Op,L,R}, Vt, St0) -> {Avt,St1} = gexpr_list([L,R], Vt, St0), case is_gexpr_op(Op, 2) of @@ -1938,12 +1972,14 @@ is_gexpr({call,L,{tuple,Lt,[{atom,Lm,erlang},{atom,Lf,F}]},As}, RDs) -> is_gexpr({call,L,{remote,Lt,{atom,Lm,erlang},{atom,Lf,F}},As}, RDs); is_gexpr({op,_L,Op,A}, RDs) -> is_gexpr_op(Op, 1) andalso is_gexpr(A, RDs); +is_gexpr({op,_L,'andalso',A1,A2}, RDs) -> + is_gexpr_list([A1,A2], RDs); +is_gexpr({op,_L,'orelse',A1,A2}, RDs) -> + is_gexpr_list([A1,A2], RDs); is_gexpr({op,_L,Op,A1,A2}, RDs) -> is_gexpr_op(Op, 2) andalso is_gexpr_list([A1,A2], RDs); is_gexpr(_Other, _RDs) -> false. -is_gexpr_op('andalso', 2) -> true; -is_gexpr_op('orelse', 2) -> true; is_gexpr_op(Op, A) -> try erl_internal:op_type(Op, A) of arith -> true; @@ -1997,24 +2033,12 @@ expr({bc,_Line,E,Qs}, Vt, St) -> handle_comprehension(E, Qs, Vt, St); expr({tuple,_Line,Es}, Vt, St) -> expr_list(Es, Vt, St); -expr({map,Line,Es}, Vt, St) -> - {Rvt,St1} = expr_list(Es,Vt,St), - case is_valid_map_construction(Es) of - true -> {Rvt,St1}; - false -> {[],add_error(Line,illegal_map_construction,St1)} - end; +expr({map,_Line,Es}, Vt, St) -> + map_fields(Es, Vt, check_assoc_fields(Es, St), fun expr_list/3); expr({map,_Line,Src,Es}, Vt, St) -> - expr_list([Src|Es], Vt, St); -expr({map_field_assoc,Line,K,V}, Vt, St) -> - case is_valid_map_key(K,St) of - true -> expr_list([K,V], Vt, St); - {false,Var} -> {[],add_error(Line,{illegal_map_key_variable,Var},St)} - end; -expr({map_field_exact,Line,K,V}, Vt, St) -> - case is_valid_map_key(K,St) of - true -> expr_list([K,V], Vt, St); - {false,Var} -> {[],add_error(Line,{illegal_map_key_variable,Var},St)} - end; + {Svt,St1} = expr(Src, Vt, St), + {Fvt,St2} = map_fields(Es, Vt, St1, fun expr_list/3), + {vtupdate(Svt, Fvt),St2}; expr({record_index,Line,Name,Field}, _Vt, St) -> check_record(Line, Name, St, fun (Dfs, St1) -> record_field(Field, Name, Dfs, St1) end); @@ -2222,6 +2246,26 @@ record_expr(Line, Rec, Vt, St0) -> St1 = warn_invalid_record(Line, Rec, St0), expr(Rec, Vt, St1). +check_assoc_fields([{map_field_exact,Line,_,_}|Fs], St) -> + check_assoc_fields(Fs, add_error(Line, illegal_map_construction, St)); +check_assoc_fields([{map_field_assoc,_,_,_}|Fs], St) -> + check_assoc_fields(Fs, St); +check_assoc_fields([], St) -> + St. + +map_fields([{Tag,Line,K,V}|Fs], Vt, St, F) when Tag =:= map_field_assoc; + Tag =:= map_field_exact -> + St1 = case is_valid_map_key(K, St) of + true -> St; + false -> add_error(Line, illegal_map_key, St); + {false,variable,Var} -> add_error(Line, {illegal_map_key_variable,Var}, St) + end, + {Pvt,St2} = F([K,V], Vt, St1), + {Vts,St3} = map_fields(Fs, Vt, St2, F), + {vtupdate(Pvt, Vts),St3}; +map_fields([], Vt, St, _) -> + {Vt,St}. + %% warn_invalid_record(Line, Record, State0) -> State %% Adds warning if the record is invalid. @@ -2274,18 +2318,64 @@ is_valid_call(Call) -> _ -> true end. -%% check_map_construction -%% Only #{ K => V }, i.e. assoc is a valid construction -is_valid_map_construction([{map_field_assoc,_,_,_}|Es]) -> - is_valid_map_construction(Es); -is_valid_map_construction([]) -> true; -is_valid_map_construction(_) -> false. +%% is_valid_map_key(K,St) -> true | false | {false, Var::atom()} +%% check for value expression without variables is_valid_map_key(K,St) -> case expr(K,[],St) of - {[],_} -> true; + {[],_} -> + is_valid_map_key_value(K); {[Var|_],_} -> - {false,element(1,Var)} + {false,variable,element(1,Var)} + end. + +is_valid_map_key_value(K) -> + case K of + {char,_,_} -> true; + {integer,_,_} -> true; + {float,_,_} -> true; + {string,_,_} -> true; + {nil,_} -> true; + {atom,_,_} -> true; + {cons,_,H,T} -> + is_valid_map_key_value(H) andalso + is_valid_map_key_value(T); + {tuple,_,Es} -> + foldl(fun(E,B) -> + B andalso is_valid_map_key_value(E) + end,true,Es); + {map,_,Arg,Ps} -> + % only check for value expressions to be valid + % invalid map expressions are later checked in + % core and kernel + is_valid_map_key_value(Arg) andalso foldl(fun + ({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc; + Tag =:= map_field_exact -> + B andalso is_valid_map_key_value(Ke) + andalso is_valid_map_key_value(Ve) + end,true,Ps); + {map,_,Ps} -> + foldl(fun + ({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc; + Tag =:= map_field_exact -> + B andalso is_valid_map_key_value(Ke) + andalso is_valid_map_key_value(Ve) + end, true, Ps); + {record,_,_,Fs} -> + foldl(fun + ({record_field,_,Ke,Ve},B) -> + B andalso is_valid_map_key_value(Ke) + andalso is_valid_map_key_value(Ve) + end,true,Fs); + {bin,_,Es} -> + % only check for value expressions to be valid + % invalid binary expressions are later checked in + % core and kernel + foldl(fun + ({bin_element,_,E,_,_},B) -> + B andalso is_valid_map_key_value(E) + end,true,Es); + _ -> false end. %% record_def(Line, RecordName, [RecField], State) -> State. @@ -2500,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. @@ -2518,32 +2606,46 @@ type_def(Attr, Line, TypeName, ProtoType, Args, St0) -> CheckType = {type, -1, product, [ProtoType|Args]}, check_type(CheckType, St#lint{types=NewDefs}) end, - case (dict:is_key(TypePair, TypeDefs) orelse is_var_arity_type(TypeName)) of - true -> - case is_default_type(TypePair) of - true -> - 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, {redefine_type, TypePair}, St0) - end; - false -> - St1 = case - Attr =:= opaque andalso - is_underspecified(ProtoType, Arity) - of - true -> - Warn = {underspecified_opaque, TypePair}, - add_warning(Line, Warn, St0); - false -> St0 - end, - StoreType(St1) + case is_default_type(TypePair) of + true -> + case is_obsolete_builtin_type(TypePair) of + true -> StoreType(St0); + 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) + of + 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 + is_underspecified(ProtoType, Arity) + of + true -> + Warn = {underspecified_opaque, TypePair}, + add_warning(Line, Warn, St0); + false -> St0 + end, + StoreType(St1) + end end. is_underspecified({type,_,term,[]}, 0) -> true; @@ -2637,10 +2739,11 @@ check_type({type, La, TypeName, Args}, SeenVars, St) -> St1 = case is_var_arity_type(TypeName) of true -> St; false -> - Obsolete = obsolete_type(TypePair), + Obsolete = (is_warn_enabled(deprecated_type, St) + andalso obsolete_builtin_type(TypePair)), IsObsolete = case Obsolete of - {deprecated, {M, _}, _} when M =/= Module -> + {deprecated, Repl, _} when element(1, Repl) =/= Module -> case dict:find(TypePair, Types) of {ok, _} -> false; error -> true @@ -2650,7 +2753,8 @@ check_type({type, La, TypeName, Args}, SeenVars, St) -> case IsObsolete of true -> {deprecated, Replacement, Rel} = Obsolete, - W = {deprecated_type, TypePair, Replacement, Rel}, + Tag = deprecated_builtin_type, + W = {Tag, TypePair, Replacement, Rel}, add_warning(La, W, St); false -> OldUsed = Usage#usage.used_types, @@ -2701,6 +2805,7 @@ check_record_types([], _Name, _DefFields, SeenVars, St, _SeenFields) -> {SeenVars, St}. is_var_arity_type(tuple) -> true; +is_var_arity_type(map) -> true; is_var_arity_type(product) -> true; is_var_arity_type(union) -> true; is_var_arity_type(record) -> true; @@ -2733,7 +2838,6 @@ is_default_type({iodata, 0}) -> true; is_default_type({iolist, 0}) -> true; is_default_type({list, 0}) -> true; is_default_type({list, 1}) -> true; -is_default_type({map, 0}) -> true; is_default_type({maybe_improper_list, 0}) -> true; is_default_type({maybe_improper_list, 2}) -> true; is_default_type({mfa, 0}) -> true; @@ -2764,31 +2868,32 @@ is_default_type({timeout, 0}) -> true; is_default_type({var, 1}) -> true; is_default_type(_) -> false. -%% R13 -is_newly_introduced_builtin_type({arity, 0}) -> true; -is_newly_introduced_builtin_type({array, 0}) -> true; % opaque -is_newly_introduced_builtin_type({bitstring, 0}) -> true; -is_newly_introduced_builtin_type({dict, 0}) -> true; % opaque -is_newly_introduced_builtin_type({digraph, 0}) -> true; % opaque -is_newly_introduced_builtin_type({gb_set, 0}) -> true; % opaque -is_newly_introduced_builtin_type({gb_tree, 0}) -> true; % opaque -is_newly_introduced_builtin_type({iodata, 0}) -> true; -is_newly_introduced_builtin_type({queue, 0}) -> true; % opaque -is_newly_introduced_builtin_type({set, 0}) -> true; % opaque -%% R13B01 -is_newly_introduced_builtin_type({boolean, 0}) -> true; -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. %% Obsolete in OTP 17.0. -obsolete_type({array, 0}) -> {deprecated, {array, array}, "OTP 18.0"}; -obsolete_type({dict, 0}) -> {deprecated, {dict, dict}, "OTP 18.0"}; -obsolete_type({digraph, 0}) -> {deprecated, {digraph, graph}, "OTP 18.0"}; -obsolete_type({gb_set, 0}) -> {deprecated, {gb_sets, set}, "OTP 18.0"}; -obsolete_type({gb_tree, 0}) -> {deprecated, {gb_trees, tree}, "OTP 18.0"}; -obsolete_type({queue, 0}) -> {deprecated, {queue, queue}, "OTP 18.0"}; -obsolete_type({set, 0}) -> {deprecated, {sets, set}, "OTP 18.0"}; -obsolete_type({tid, 0}) -> {deprecated, {ets, tid}, "OTP 18.0"}; -obsolete_type({Name, _}) when is_atom(Name) -> no. +obsolete_builtin_type({array, 0}) -> + {deprecated, {array, array, 1}, "OTP 18.0"}; +obsolete_builtin_type({dict, 0}) -> + {deprecated, {dict, dict, 2}, "OTP 18.0"}; +obsolete_builtin_type({digraph, 0}) -> + {deprecated, {digraph, graph}, "OTP 18.0"}; +obsolete_builtin_type({gb_set, 0}) -> + {deprecated, {gb_sets, set, 1}, "OTP 18.0"}; +obsolete_builtin_type({gb_tree, 0}) -> + {deprecated, {gb_trees, tree, 2}, "OTP 18.0"}; +obsolete_builtin_type({queue, 0}) -> + {deprecated, {queue, queue, 1}, "OTP 18.0"}; +obsolete_builtin_type({set, 0}) -> + {deprecated, {sets, set, 1}, "OTP 18.0"}; +obsolete_builtin_type({tid, 0}) -> + {deprecated, {ets, tid}, "OTP 18.0"}; +obsolete_builtin_type({Name, A}) when is_atom(Name), is_integer(A) -> no. %% spec_decl(Line, Fun, Types, State) -> State. 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/gen.erl b/lib/stdlib/src/gen.erl index 7281549ea7..63116fa16e 100644 --- a/lib/stdlib/src/gen.erl +++ b/lib/stdlib/src/gen.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 @@ -37,7 +37,9 @@ %%----------------------------------------------------------------- -type linkage() :: 'link' | 'nolink'. --type emgr_name() :: {'local', atom()} | {'global', term()} | {via, atom(), term()}. +-type emgr_name() :: {'local', atom()} + | {'global', term()} + | {'via', Module :: module(), Name :: term()}. -type start_ret() :: {'ok', pid()} | 'ignore' | {'error', term()}. diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl index 7629e88fbf..d39dd89d3a 100644 --- a/lib/stdlib/src/gen_event.erl +++ b/lib/stdlib/src/gen_event.erl @@ -40,6 +40,8 @@ system_continue/3, system_terminate/4, system_code_change/4, + system_get_state/1, + system_replace_state/2, format_status/2]). -export_type([handler/0, handler_args/0, add_handler_ret/0, @@ -229,24 +231,6 @@ wake_hib(Parent, ServerName, MSL, Debug) -> fetch_msg(Parent, ServerName, MSL, Debug, Hib) -> receive - {system, From, get_state} -> - States = [{Mod,Id,State} || #handler{module=Mod, id=Id, state=State} <- MSL], - sys:handle_system_msg(get_state, From, Parent, ?MODULE, Debug, - {States, [ServerName, MSL, Hib]}, Hib); - {system, From, {replace_state, StateFun}} -> - {NMSL, NStates} = - lists:unzip([begin - Cur = {Mod,Id,State}, - try - NState = {Mod,Id,NS} = StateFun(Cur), - {HS#handler{state=NS}, NState} - catch - _:_ -> - {HS, Cur} - end - end || #handler{module=Mod, id=Id, state=State}=HS <- MSL]), - sys:handle_system_msg(replace_state, From, Parent, ?MODULE, Debug, - {NStates, [ServerName, NMSL, Hib]}, Hib); {system, From, Req} -> sys:handle_system_msg(Req, From, Parent, ?MODULE, Debug, [ServerName, MSL, Hib],Hib); @@ -383,6 +367,23 @@ system_code_change([ServerName, MSL, Hib], Module, OldVsn, Extra) -> MSL), {ok, [ServerName, MSL1, Hib]}. +system_get_state([_ServerName, MSL, _Hib]) -> + {ok, [{Mod,Id,State} || #handler{module=Mod, id=Id, state=State} <- MSL]}. + +system_replace_state(StateFun, [ServerName, MSL, Hib]) -> + {NMSL, NStates} = + lists:unzip([begin + Cur = {Mod,Id,State}, + try + NState = {Mod,Id,NS} = StateFun(Cur), + {HS#handler{state=NS}, NState} + catch + _:_ -> + {HS, Cur} + end + end || #handler{module=Mod, id=Id, state=State}=HS <- MSL]), + {ok, NStates, [ServerName, NMSL, Hib]}. + %%----------------------------------------------------------------- %% Format debug messages. Print them as the call-back module sees %% them, not as the real erlang messages. Use trace for that. diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl index e9654322f1..e914f7d0b2 100644 --- a/lib/stdlib/src/gen_fsm.erl +++ b/lib/stdlib/src/gen_fsm.erl @@ -118,6 +118,8 @@ system_continue/3, system_terminate/4, system_code_change/4, + system_get_state/1, + system_replace_state/2, format_status/2]). -import(error_logger, [format/2]). @@ -422,17 +424,6 @@ wake_hib(Parent, Name, StateName, StateData, Mod, Debug) -> decode_msg(Msg,Parent, Name, StateName, StateData, Mod, Time, Debug, Hib) -> case Msg of - {system, From, get_state} -> - Misc = [Name, StateName, StateData, Mod, Time], - sys:handle_system_msg(get_state, From, Parent, ?MODULE, Debug, - {{StateName, StateData}, Misc}, Hib); - {system, From, {replace_state, StateFun}} -> - State = {StateName, StateData}, - NState = {NStateName, NStateData} = try StateFun(State) - catch _:_ -> State end, - NMisc = [Name, NStateName, NStateData, Mod, Time], - sys:handle_system_msg(replace_state, From, Parent, ?MODULE, Debug, - {NState, NMisc}, Hib); {system, From, Req} -> sys:handle_system_msg(Req, From, Parent, ?MODULE, Debug, [Name, StateName, StateData, Mod, Time], Hib); @@ -467,6 +458,13 @@ system_code_change([Name, StateName, StateData, Mod, Time], Else -> Else end. +system_get_state([_Name, StateName, StateData, _Mod, _Time]) -> + {ok, {StateName, StateData}}. + +system_replace_state(StateFun, [Name, StateName, StateData, Mod, Time]) -> + Result = {NStateName, NStateData} = StateFun({StateName, StateData}), + {ok, Result, [Name, NStateName, NStateData, Mod, Time]}. + %%----------------------------------------------------------------- %% Format debug messages. Print them as the call-back module sees %% them, not as the real erlang messages. Use trace for that. diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index 5f14e48b0a..202a931fae 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -98,6 +98,8 @@ -export([system_continue/3, system_terminate/4, system_code_change/4, + system_get_state/1, + system_replace_state/2, format_status/2]). %% Internal exports @@ -372,13 +374,6 @@ wake_hib(Parent, Name, State, Mod, Debug) -> decode_msg(Msg, Parent, Name, State, Mod, Time, Debug, Hib) -> case Msg of - {system, From, get_state} -> - sys:handle_system_msg(get_state, From, Parent, ?MODULE, Debug, - {State, [Name, State, Mod, Time]}, Hib); - {system, From, {replace_state, StateFun}} -> - NState = try StateFun(State) catch _:_ -> State end, - sys:handle_system_msg(replace_state, From, Parent, ?MODULE, Debug, - {NState, [Name, NState, Mod, Time]}, Hib); {system, From, Req} -> sys:handle_system_msg(Req, From, Parent, ?MODULE, Debug, [Name, State, Mod, Time], Hib); @@ -687,6 +682,13 @@ system_code_change([Name, State, Mod, Time], _Module, OldVsn, Extra) -> Else -> Else end. +system_get_state([_Name, State, _Mod, _Time]) -> + {ok, State}. + +system_replace_state(StateFun, [Name, State, Mod, Time]) -> + NState = StateFun(State), + {ok, NState, [Name, NState, Mod, Time]}. + %%----------------------------------------------------------------- %% Format debug messages. Print them as the call-back module sees %% them, not as the real erlang messages. Use trace for that. 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/maps.erl b/lib/stdlib/src/maps.erl index 57b5072639..1f94d9e69d 100644 --- a/lib/stdlib/src/maps.erl +++ b/lib/stdlib/src/maps.erl @@ -45,7 +45,6 @@ -compile(no_native). -%% Shadowed by erl_bif_types: maps:get/3 -spec get(Key,Map) -> Value when Key :: term(), Map :: map(), @@ -54,7 +53,6 @@ get(_,_) -> erlang:nif_error(undef). -%% Shadowed by erl_bif_types: maps:find/3 -spec find(Key,Map) -> {ok, Value} | error when Key :: term(), Map :: map(), @@ -63,8 +61,8 @@ get(_,_) -> erlang:nif_error(undef). find(_,_) -> erlang:nif_error(undef). -%% Shadowed by erl_bif_types: maps:from_list/1 --spec from_list([{Key,Value}]) -> Map when +-spec from_list(List) -> Map when + List :: [{Key,Value}], Key :: term(), Value :: term(), Map :: map(). @@ -72,7 +70,6 @@ find(_,_) -> erlang:nif_error(undef). from_list(_) -> erlang:nif_error(undef). -%% Shadowed by erl_bif_types: maps:is_key/2 -spec is_key(Key,Map) -> boolean() when Key :: term(), Map :: map(). @@ -80,7 +77,6 @@ from_list(_) -> erlang:nif_error(undef). is_key(_,_) -> erlang:nif_error(undef). -%% Shadowed by erl_bif_types: maps:keys/1 -spec keys(Map) -> Keys when Map :: map(), Keys :: [Key], @@ -89,7 +85,6 @@ is_key(_,_) -> erlang:nif_error(undef). keys(_) -> erlang:nif_error(undef). -%% Shadowed by erl_bif_types: maps:merge/2 -spec merge(Map1,Map2) -> Map3 when Map1 :: map(), Map2 :: map(), @@ -99,14 +94,12 @@ merge(_,_) -> erlang:nif_error(undef). -%% Shadowed by erl_bif_types: maps:new/0 -spec new() -> Map when Map :: map(). new() -> erlang:nif_error(undef). -%% Shadowed by erl_bif_types: maps:put/3 -spec put(Key,Value,Map1) -> Map2 when Key :: term(), Value :: term(), @@ -116,7 +109,6 @@ new() -> erlang:nif_error(undef). put(_,_,_) -> erlang:nif_error(undef). -%% Shadowed by erl_bif_types: maps:put/3 -spec remove(Key,Map1) -> Map2 when Key :: term(), Map1 :: map(), @@ -125,7 +117,6 @@ put(_,_,_) -> erlang:nif_error(undef). remove(_,_) -> erlang:nif_error(undef). -%% Shadowed by erl_bif_types: maps:to_list/1 -spec to_list(Map) -> [{Key,Value}] when Map :: map(), Key :: term(), @@ -134,7 +125,6 @@ remove(_,_) -> erlang:nif_error(undef). to_list(_) -> erlang:nif_error(undef). -%% Shadowed by erl_bif_types: maps:update/3 -spec update(Key,Value,Map1) -> Map2 when Key :: term(), Value :: term(), @@ -144,7 +134,6 @@ to_list(_) -> erlang:nif_error(undef). update(_,_,_) -> erlang:nif_error(undef). -%% Shadowed by erl_bif_types: maps:values/1 -spec values(Map) -> Keys when Map :: map(), Keys :: [Key], diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl index c26764eb18..b6bb758dfb 100644 --- a/lib/stdlib/src/qlc_pt.erl +++ b/lib/stdlib/src/qlc_pt.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2013. All Rights Reserved. +%% Copyright Ericsson AB 2004-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 @@ -1218,13 +1218,14 @@ lu_skip(ColConstants, FilterData, PatternFrame, PatternVars, %% column, the filter will not be skipped. %% (an example: {X=1} <- ..., X =:= 1). length(D = Cols -- PatternColumns) =:= 1, - Frame <- SFs, - begin + {{_,Col} = Column, Constants} <- D, + %% Check that the following holds for all frames. + lists:all( + fun(Frame) -> %% The column is compared/matched against a constant. %% If there are no more comparisons/matches then %% the filter can be replaced by the lookup of %% the constant. - [{{_,Col} = Column, Constants}] = D, {VarI, FrameI} = unify_column(Frame, PV, Col, BindFun, Imported), VarValues = deref_skip(VarI, FrameI, LookupOp, Imported), @@ -1253,7 +1254,7 @@ lu_skip(ColConstants, FilterData, PatternFrame, PatternVars, length(VarValues) =< 1 andalso (Constants -- LookedUpConstants =:= []) andalso bindings_is_subset(Frame, F2, Imported) - end], + end, SFs)], ColFils = family_list(ColFil), %% The skip tag 'all' means that all filters are covered by the lookup. %% It does not imply that there is only one generator as is the case 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"]} +]}. diff --git a/lib/stdlib/src/sys.erl b/lib/stdlib/src/sys.erl index 04f8dfb61b..e25cc25f57 100644 --- a/lib/stdlib/src/sys.erl +++ b/lib/stdlib/src/sys.erl @@ -102,20 +102,31 @@ get_status(Name, Timeout) -> send_system_msg(Name, get_status, Timeout). -spec get_state(Name) -> State when Name :: name(), State :: term(). -get_state(Name) -> send_system_msg(Name, get_state). +get_state(Name) -> + case send_system_msg(Name, get_state) of + {error, Reason} -> error(Reason); + State -> State + end. -spec get_state(Name, Timeout) -> State when Name :: name(), Timeout :: timeout(), State :: term(). -get_state(Name, Timeout) -> send_system_msg(Name, get_state, Timeout). +get_state(Name, Timeout) -> + case send_system_msg(Name, get_state, Timeout) of + {error, Reason} -> error(Reason); + State -> State + end. -spec replace_state(Name, StateFun) -> NewState when Name :: name(), StateFun :: fun((State :: term()) -> NewState :: term()), NewState :: term(). replace_state(Name, StateFun) -> - send_system_msg(Name, {replace_state, StateFun}). + case send_system_msg(Name, {replace_state, StateFun}) of + {error, Reason} -> error(Reason); + State -> State + end. -spec replace_state(Name, StateFun, Timeout) -> NewState when Name :: name(), @@ -123,7 +134,10 @@ replace_state(Name, StateFun) -> Timeout :: timeout(), NewState :: term(). replace_state(Name, StateFun, Timeout) -> - send_system_msg(Name, {replace_state, StateFun}, Timeout). + case send_system_msg(Name, {replace_state, StateFun}, Timeout) of + {error, Reason} -> error(Reason); + State -> State + end. -spec change_code(Name, Module, OldVsn, Extra) -> 'ok' | {error, Reason} when Name :: name(), @@ -390,10 +404,11 @@ do_cmd(_, suspend, _Parent, _Mod, Debug, Misc) -> {suspended, ok, Debug, Misc}; do_cmd(_, resume, _Parent, _Mod, Debug, Misc) -> {running, ok, Debug, Misc}; -do_cmd(SysState, get_state, _Parent, _Mod, Debug, {State, Misc}) -> - {SysState, State, Debug, Misc}; -do_cmd(SysState, replace_state, _Parent, _Mod, Debug, {State, Misc}) -> - {SysState, State, Debug, Misc}; +do_cmd(SysState, get_state, _Parent, Mod, Debug, Misc) -> + {SysState, do_get_state(Mod, Misc), Debug, Misc}; +do_cmd(SysState, {replace_state, StateFun}, _Parent, Mod, Debug, Misc) -> + {Res, NMisc} = do_replace_state(StateFun, Mod, Misc), + {SysState, Res, Debug, NMisc}; do_cmd(SysState, get_status, Parent, Mod, Debug, Misc) -> Res = get_status(SysState, Parent, Mod, Debug, Misc), {SysState, Res, Debug, Misc}; @@ -407,6 +422,40 @@ do_cmd(suspended, {change_code, Module, Vsn, Extra}, _Parent, do_cmd(SysState, Other, _Parent, _Mod, Debug, Misc) -> {SysState, {error, {unknown_system_msg, Other}}, Debug, Misc}. +do_get_state(Mod, Misc) -> + case erlang:function_exported(Mod, system_get_state, 1) of + true -> + try + {ok, State} = Mod:system_get_state(Misc), + State + catch + Cl:Exc -> + {error, {callback_failed,{Mod,system_get_state},{Cl,Exc}}} + end; + false -> + Misc + end. + +do_replace_state(StateFun, Mod, Misc) -> + case erlang:function_exported(Mod, system_replace_state, 2) of + true -> + try + {ok, State, NMisc} = Mod:system_replace_state(StateFun, Misc), + {State, NMisc} + catch + Cl:Exc -> + {{error, {callback_failed,{Mod,system_replace_state},{Cl,Exc}}}, Misc} + end; + false -> + try + NMisc = StateFun(Misc), + {NMisc, NMisc} + catch + Cl:Exc -> + {{error, {callback_failed,StateFun,{Cl,Exc}}}, Misc} + end + end. + get_status(SysState, Parent, Mod, Debug, Misc) -> PDict = get(), FmtMisc = |