diff options
Diffstat (limited to 'lib/stdlib/src')
39 files changed, 573 insertions, 269 deletions
| diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl index 121f9febed..1a7b7d5a5e 100644 --- a/lib/stdlib/src/beam_lib.erl +++ b/lib/stdlib/src/beam_lib.erl @@ -904,7 +904,7 @@ call_crypto_server(Req) ->      end.  call_crypto_server_1(Req) -> -    gen_server:start({local,?CRYPTO_KEY_SERVER}, ?MODULE, [], []), +    {ok, _} = gen_server:start({local,?CRYPTO_KEY_SERVER}, ?MODULE, [], []),      erlang:yield(),      call_crypto_server(Req). diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl index 6e96e3d564..fb6b8c8661 100644 --- a/lib/stdlib/src/c.erl +++ b/lib/stdlib/src/c.erl @@ -694,7 +694,7 @@ pwd() ->        Dir :: file:name().  cd(Dir) -> -    file:set_cwd(Dir), +    _ = file:set_cwd(Dir),      pwd().  %% ls() diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl index 68b157c13c..44dad04f43 100644 --- a/lib/stdlib/src/dets.erl +++ b/lib/stdlib/src/dets.erl @@ -469,7 +469,7 @@ is_compatible_bchunk_format(Tab, Term) ->  is_dets_file(FileName) ->      case catch read_file_header(FileName, read, false) of  	{ok, Fd, FH} -> -	    file:close(Fd), +	    _ = file:close(Fd),  	    FH#fileheader.cookie =:= ?MAGIC;  	{error, {tooshort, _}} ->  	    false; @@ -1384,7 +1384,8 @@ do_apply_op(Op, From, Head, N) ->              end,              if                  From =/= self() -> -                    From ! {self(), {error, {dets_bug, Name, Op, Bad}}}; +                    From ! {self(), {error, {dets_bug, Name, Op, Bad}}}, +                    ok;                  true -> % auto_save | may_grow | {delayed_write, _}                      ok              end, @@ -1634,7 +1635,8 @@ start_auto_save_timer(Head) when Head#head.auto_save =:= infinity ->      ok;  start_auto_save_timer(Head) ->      Millis = Head#head.auto_save, -    erlang:send_after(Millis, self(), ?DETS_CALL(self(), auto_save)). +    _Ref = erlang:send_after(Millis, self(), ?DETS_CALL(self(), auto_save)), +    ok.  %% Version 9: Peek the message queue and try to evaluate several  %% lookup requests in parallel. Evalute delete_object, delete and @@ -1683,7 +1685,7 @@ stream_end(Head, Pids0, C, N, Next) ->  	    %%  replies to delete and insert requests even if the  	    %%  latter requests were made before the lookup requests,  	    %%  which can be confusing.) -	    lookup_replies(Found), +	    _ = lookup_replies(Found),  	    stream_end1(Pids0, Next, N, C, Head1, PwriteList);  	Head1 when is_record(Head1, head) ->  	    stream_end2(Pids0, Pids0, Next, N, C, Head1, ok);	     @@ -1733,7 +1735,7 @@ lookup_replies(Q) ->  lookup_replies(P, O, []) ->      lookup_reply(P, O);  lookup_replies(P, O, [{P2,O2} | L]) -> -    lookup_reply(P, O), +    _ = lookup_reply(P, O),      lookup_replies(P2, lists:append(O2), L).  %% If a list of Pid then op was {member, Key}. Inlined. @@ -1790,12 +1792,15 @@ fclose(Head) ->      {Head1, Res} = perform_save(Head, false),      case Head1#head.ram_file of  	true ->  -	    ignore; +            Res;  	false ->               dets_utils:stop_disk_map(), -	    file:close(Head1#head.fptr) -    end, -    Res. +	    Res2 = file:close(Head1#head.fptr), +            if +                Res2 =:= ok -> Res; +                true -> Res2 +            end +    end.  %% -> {NewHead, Res}  perform_save(Head, DoSync) when Head#head.update_mode =:= dirty; @@ -2002,7 +2007,7 @@ remove_fix(Head, Pid, How) ->      end.  do_stop(Head) -> -    unlink_fixing_procs(Head), +    _NewHead = unlink_fixing_procs(Head),      fclose(Head).  unlink_fixing_procs(Head) -> @@ -2010,7 +2015,7 @@ unlink_fixing_procs(Head) ->  	false ->  	    Head;  	{_, Counters} -> -	    lists:map(fun({Pid, _Counter}) -> unlink(Pid) end, Counters), +	    lists:foreach(fun({Pid, _Counter}) -> unlink(Pid) end, Counters),  	    Head#head{fixed = false,   		      freelists = dets_utils:get_freelists(Head)}      end. @@ -2021,8 +2026,9 @@ check_growth(Head) ->      NoThings = no_things(Head),      if  	NoThings > Head#head.next -> -	    erlang:send_after(200, self(),  -			      ?DETS_CALL(self(), may_grow)); % Catch up. +	    _Ref = erlang:send_after +                     (200, self(), ?DETS_CALL(self(), may_grow)), % Catch up. +            ok;  	true ->  	    ok      end. @@ -2123,7 +2129,7 @@ do_open_file([Fname, Verbose], 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), +	    _ = file:delete(OpenArgs#open_args.file),  	    do_open_file([Tab, OpenArgs, Verb], Parent, Server, Ref);  	{error, _Reason} = Error ->  	    err(Error); @@ -2671,11 +2677,11 @@ fopen_init_file(Tab, OpenArgs) ->      case catch Mod:initiate_file(Fd, Tab, Fname, Type, Kp, MinSlots, MaxSlots,  				 Ram, CacheSz, Auto, true) of  	{error, Reason} when Ram -> -	    file:close(Fd), +	    _ = file:close(Fd),  	    throw({error, Reason});  	{error, Reason} -> -	    file:close(Fd), -	    file:delete(Fname), +	    _ = file:close(Fd), +	    _ = file:delete(Fname),  	    throw({error, Reason});  	{ok, Head} ->  	    start_auto_save_timer(Head), @@ -2730,8 +2736,8 @@ compact(SourceHead) ->  	       {ok, H} ->  		   H;  	       Error -> -		   file:close(Fd), -                   file:delete(Tmp), +		   _ = file:close(Fd), +                   _ = file:delete(Tmp),  		   throw(Error)  	   end, @@ -2748,12 +2754,12 @@ compact(SourceHead) ->  	    if   		R =:= ok -> ok;  		true -> -		    file:delete(Tmp), +		    _ = file:delete(Tmp),  		    throw(R)  	    end;  	Err -> -	    file:close(Fd), -            file:delete(Tmp), +	    _ = file:close(Fd), +            _ = file:delete(Tmp),  	    throw(Err)      end. @@ -2777,7 +2783,7 @@ fsck(Fd, Tab, Fname, FH, MinSlotsArg, MaxSlotsArg, Version) ->  	    BetterSlotNumbers = {MinSlots, BetterNoSlots, MaxSlots},              case fsck_try(Fd, Tab, FH, Fname, BetterSlotNumbers, Version) of                  {try_again, _} -> -                    file:close(Fd), +                    _ = file:close(Fd),                      {error, {cannot_repair, Fname}};                  Else ->                      Else @@ -2818,15 +2824,15 @@ fsck_try(Fd, Tab, FH, Fname, SlotNumbers, Version) ->                      if   			R =:= ok -> ok;  			true -> -			    file:delete(Tmp), +			    _ = file:delete(Tmp),  			    R  		    end;  		TryAgainOrError -> -                    file:delete(Tmp), +                    _ = file:delete(Tmp),                      TryAgainOrError              end;  	Error ->  -	    file:close(Fd), +	    _ = file:close(Fd),  	    Error      end. @@ -2855,13 +2861,13 @@ fsck_try_est(Head, Fd, Fname, SlotNumbers, FH) ->      Bulk = false,      case Reply of           {ok, NoDups, H1} -> -            file:close(Fd), +            _ = file:close(Fd),              fsck_copy(SizeData, H1, Bulk, NoDups);          {try_again, _} = Return ->              close_files(Bulk, SizeData, Head),              Return;          Else -> -            file:close(Fd), +            _ = file:close(Fd),              close_files(Bulk, SizeData, Head),  	    Else      end. @@ -2896,14 +2902,20 @@ fsck_copy1([SzData | L], Head, Bulk, NoDups) ->      {LogSz, Pos, {FileName, Fd}, NoObjects} = SzData,      Size = if NoObjects =:= 0 -> 0; true -> ?POW(LogSz-1) end,      ExpectedSize = Size * NoObjects, -    close_tmp(Fd), -    case file:position(Out, Pos) of -	{ok, Pos} -> ok; -	PError -> dets_utils:file_error(FileName, PError) +    case close_tmp(Fd) of +        ok -> ok; +        Err -> +	    close_files(Bulk, L, Head), +	    dets_utils:file_error(FileName, Err)      end, -    {ok, Pos} = file:position(Out, Pos), +    case file:position(Out, Pos) of +        {ok, Pos} -> ok; +        Err2 -> +	    close_files(Bulk, L, Head), +	    dets_utils:file_error(Head#head.filename, Err2) +        end,      CR = file:copy({FileName, [raw,binary]}, Out), -    file:delete(FileName), +    _ = file:delete(FileName),      case CR of   	{ok, Copied} when Copied =:= ExpectedSize;  			  NoObjects =:= 0 -> % the segments @@ -2937,11 +2949,11 @@ free_n_objects(Head, Addr, Size, N) ->      free_n_objects(NewHead, NewAddr, Size, N-1).  close_files(false, SizeData, Head) -> -    file:close(Head#head.fptr), +    _ = file:close(Head#head.fptr),      close_files(true, SizeData, Head);  close_files(true, SizeData, _Head) ->      Fun = fun({_Size, _Pos, {FileName, Fd}, _No}) -> -		  close_tmp(Fd), +		  _ = close_tmp(Fd),  		  file:delete(FileName);  	     (_) ->  		  ok @@ -3261,7 +3273,7 @@ err(Error) ->  file_info(FileName) ->      case catch read_file_header(FileName, read, false) of  	{ok, Fd, FH} -> -	    file:close(Fd), +	    _ = file:close(Fd),              (FH#fileheader.mod):file_info(FH);  	Other ->  	    Other @@ -3290,7 +3302,7 @@ view(FileName) ->                          X ->                              X                      end -            after file:close(Fd) +            after _ = file:close(Fd)              end;  	X ->   	    X diff --git a/lib/stdlib/src/dets_server.erl b/lib/stdlib/src/dets_server.erl index 931112088e..268c201047 100644 --- a/lib/stdlib/src/dets_server.erl +++ b/lib/stdlib/src/dets_server.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 2001-2009. All Rights Reserved. +%% Copyright Ericsson AB 2001-2013. 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 @@ -241,8 +241,8 @@ ensure_started() ->  init() ->      set_verbose(verbose_flag()),      process_flag(trap_exit, true), -    ets:new(?REGISTRY, [set, named_table]), -    ets:new(?OWNERS, [set, named_table]), +    ?REGISTRY = ets:new(?REGISTRY, [set, named_table]), +    ?OWNERS = ets:new(?OWNERS, [set, named_table]),      ets:new(?STORE, [duplicate_bag]).  verbose_flag() -> @@ -338,7 +338,7 @@ handle_close(State, Req, {FromPid,_Tag}=From, Tab) ->                          [{Tab, _Counter, Pid}] ->  			    do_unlink(Store, FromPid),  			    true = ets:match_delete(Store, {FromPid, Tab}), -			    [true = ets:insert(Store, K) || K <- Keep], +                            true = ets:insert(Store, Keep),  			    ets:update_counter(?REGISTRY, Tab, -1),                              pending_call(Tab, Pid, make_ref(), From, [],                                           remove_user, State) diff --git a/lib/stdlib/src/dets_utils.erl b/lib/stdlib/src/dets_utils.erl index 7bbb34dd15..6c176ad513 100644 --- a/lib/stdlib/src/dets_utils.erl +++ b/lib/stdlib/src/dets_utils.erl @@ -230,8 +230,12 @@ write_file(Head, Bin) ->  	    {ok, Fd} ->  		R1 = file:write(Fd, Bin),  		R2 = file:sync(Fd), -		file:close(Fd), -		if R1 =:= ok -> R2; true -> R1 end; +		R3 = file:close(Fd), +                case {R1, R2, R3} of +                    {ok, ok, R3} -> R3; +                    {ok, R2, _} -> R2; +                    {R1, _, _} -> R1 +                end;  	    Else ->  		Else  	end, @@ -277,12 +281,7 @@ open(FileSpec, Args) ->      end.  truncate(Fd, FileName, Pos) -> -    if -	Pos =:= cur -> -	    ok; -	true -> -	    position(Fd, FileName, Pos) -    end, +    _ = [position(Fd, FileName, Pos) || Pos =/= cur],      case file:truncate(Fd) of  	ok    ->   	    ok; @@ -327,10 +326,10 @@ pread_close(Fd, FileName, Pos, Size) ->  	{error, Error} ->  	    file_error_close(Fd, FileName, {error, Error});  	{ok, Bin} when byte_size(Bin) < Size -> -	    file:close(Fd), +	    _ = file:close(Fd),  	    throw({error, {tooshort, FileName}});  	eof -> -	    file:close(Fd), +	    _ = file:close(Fd),  	    throw({error, {tooshort, FileName}});  	OK -> OK      end. @@ -339,7 +338,7 @@ file_error(FileName, {error, Reason}) ->      throw({error, {file_error, FileName, Reason}}).  file_error_close(Fd, FileName, {error, Reason}) -> -    file:close(Fd), +    _ = file:close(Fd),      throw({error, {file_error, FileName, Reason}}).  debug_mode() -> @@ -977,7 +976,8 @@ dm([{P,<<Sz:32,X:32>>} | Bs], T) ->      true = ets:insert(T, {P,{pointer,X,Sz}}),      if           Sz =:= 0 ->  -            X = 0;  +            X = 0, +            true;          true ->               true = ets:insert(T, {{pointer,X}, P})      end, diff --git a/lib/stdlib/src/dets_v8.erl b/lib/stdlib/src/dets_v8.erl index 24d6e06ec8..f188502017 100644 --- a/lib/stdlib/src/dets_v8.erl +++ b/lib/stdlib/src/dets_v8.erl @@ -199,10 +199,10 @@  %% -> ok | throw({NewHead,Error})  mark_dirty(Head) ->      Dirty = [{?CLOSED_PROPERLY_POS, <<?NOT_PROPERLY_CLOSED:32>>}], -    dets_utils:pwrite(Head, Dirty), -    dets_utils:sync(Head), -    dets_utils:position(Head, Head#head.freelists_p), -    dets_utils:truncate(Head, cur). +    {_NewHead, ok} = dets_utils:pwrite(Head, Dirty), +    ok = dets_utils:sync(Head), +    {ok, _Pos} = dets_utils:position(Head, Head#head.freelists_p), +    ok = dets_utils:truncate(Head, cur).  %% -> {ok, head()} | throw(Error)  initiate_file(Fd, Tab, Fname, Type, Kp, MinSlots, MaxSlots,  diff --git a/lib/stdlib/src/dets_v9.erl b/lib/stdlib/src/dets_v9.erl index 308f81c23b..2af93ec800 100644 --- a/lib/stdlib/src/dets_v9.erl +++ b/lib/stdlib/src/dets_v9.erl @@ -284,9 +284,9 @@  %% -> ok | throw({NewHead,Error})  mark_dirty(Head) ->      Dirty = [{?CLOSED_PROPERLY_POS, <<?NOT_PROPERLY_CLOSED:32>>}], -    dets_utils:pwrite(Head, Dirty), -    dets_utils:sync(Head), -    dets_utils:position(Head, Head#head.freelists_p), +    {_H, ok} = dets_utils:pwrite(Head, Dirty), +    ok = dets_utils:sync(Head), +    {ok, _Pos} = dets_utils:position(Head, Head#head.freelists_p),      dets_utils:truncate(Head, cur).  %% -> {ok, head()} | throw(Error) | throw(badarg) @@ -1385,13 +1385,13 @@ segment_file(SizeT, Head, FileData, SegEnd) ->  	case Data of  	    {InFile,In0} ->  		{OutFile, Out} = temp_file(Head, SizeT, I), -		file:close(In0), +		_ = file:close(In0),  		{ok, In} = dets_utils:open(InFile, [raw,binary,read]),  		{ok, 0} = dets_utils:position(In, InFile, bof),  		seg_file(SegAddr, SegAddr, In, InFile, Out, OutFile, SizeT,   			 SegEnd), -		file:close(In), -		file:delete(InFile), +		_ = file:close(In), +		_ = file:delete(InFile),  		{OutFile,Out};  	    Objects ->  		{LastAddr, B} = seg_file(Objects, SegAddr, SegAddr, SizeT, []), @@ -1702,7 +1702,7 @@ free_list_to_file(Ftab, H, Pos, Sz, Ws, WsSz) ->      free_list_to_file(Ftab, H, Pos+1, Sz, NWs, NWsSz).  free_lists_from_file(H, Pos) -> -    dets_utils:position(H#head.fptr, H#head.filename, Pos), +    {ok, Pos} = dets_utils:position(H#head.fptr, H#head.filename, Pos),      FL = dets_utils:empty_free_lists(),      case catch bin_to_tree([], H, start, FL, -1, []) of  	{'EXIT', _} -> diff --git a/lib/stdlib/src/dict.erl b/lib/stdlib/src/dict.erl index 4b42f64609..7e198a2469 100644 --- a/lib/stdlib/src/dict.erl +++ b/lib/stdlib/src/dict.erl @@ -1,8 +1,7 @@ -%% -*- coding: utf-8 -*-  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 2000-2012. All Rights Reserved. +%% Copyright Ericsson AB 2000-2013. 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 +36,7 @@  -module(dict).  %% Standard interface. --export([new/0,is_key/2,to_list/1,from_list/1,size/1]). +-export([new/0,is_key/2,to_list/1,from_list/1,size/1,is_empty/1]).  -export([fetch/2,find/2,fetch_keys/1,erase/2]).  -export([store/3,append/3,append_list/3,update/3,update/4,update_counter/3]).  -export([fold/3,map/2,filter/2,merge/3]). @@ -113,6 +112,11 @@ from_list(L) ->  size(#dict{size=N}) when is_integer(N), N >= 0 -> N.  +-spec is_empty(Dict) -> boolean() when +      Dict :: dict(). + +is_empty(#dict{size=N}) -> N =:= 0. +  -spec fetch(Key, Dict) -> Value when        Key :: term(),        Dict :: dict(), diff --git a/lib/stdlib/src/digraph_utils.erl b/lib/stdlib/src/digraph_utils.erl index 807b5c12a1..0e248df453 100644 --- a/lib/stdlib/src/digraph_utils.erl +++ b/lib/stdlib/src/digraph_utils.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 1999-2012. All Rights Reserved. +%% Copyright Ericsson AB 1999-2013. 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 @@ -370,5 +370,5 @@ condense('$end_of_table', _T, _SC, _G, _SCG, _I2C) ->  condense(I, T, SC, G, SCG, I2C) ->      [{_,C}] = ets:lookup(I2C, I),      digraph:add_vertex(SCG, C), -    [digraph:add_edge(SCG, SC, C) || C =/= SC], +    _ = [digraph:add_edge(SCG, SC, C) || C =/= SC],      condense(ets:next(T, I), T, SC, G, SCG, I2C). diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl index f5998c54fd..be9a4f5107 100644 --- a/lib/stdlib/src/edlin.erl +++ b/lib/stdlib/src/edlin.erl @@ -1,8 +1,7 @@ -%% -*- coding: utf-8 -*-  %%  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. 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 diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl index d1d060ebc8..dd0512be4d 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -219,7 +219,7 @@ parse_file(Epp) ->  	    [{eof,Location}]      end. --define(DEFAULT_ENCODING, latin1). +-define(DEFAULT_ENCODING, utf8).  -spec default_encoding() -> source_encoding(). @@ -644,7 +644,7 @@ leave_file(From, St) ->  		    enter_file_reply(From, OldName, CurrLoc, CurrLoc),                      case OldName2 =:= OldName of                          true -> -                            From; +                            ok;                          false ->                              NFrom = wait_request(NextSt),                              enter_file_reply(NFrom, OldName2, OldLoc, diff --git a/lib/stdlib/src/erl_compile.erl b/lib/stdlib/src/erl_compile.erl index 8c3d59467b..ed8fea5d78 100644 --- a/lib/stdlib/src/erl_compile.erl +++ b/lib/stdlib/src/erl_compile.erl @@ -21,10 +21,12 @@  -include("erl_compile.hrl").  -include("file.hrl"). --export([compile_cmdline/1]). +-export([compile_cmdline/0]).  -export_type([cmd_line_arg/0]). +-define(STDERR, standard_error).		%Macro to avoid misspellings. +  %% Mapping from extension to {M,F} to run the correct compiler.  compiler(".erl") ->    {compile,         compile}; @@ -47,9 +49,10 @@ compiler(_) ->         no.  -type cmd_line_arg() :: atom() | string(). --spec compile_cmdline([cmd_line_arg()]) -> no_return(). +-spec compile_cmdline() -> no_return(). -compile_cmdline(List) -> +compile_cmdline() -> +    List = init:get_plain_arguments(),      case compile(List) of  	ok -> my_halt(0);  	error -> my_halt(1); @@ -67,8 +70,12 @@ compile(List) ->      receive  	{'EXIT', Pid, {compiler_result, Result}} ->  	    Result; +	{'EXIT', Pid, {compiler_error, Error}} -> +	    io:put_chars(?STDERR, Error), +	    io:nl(?STDERR), +	    error;  	{'EXIT', Pid, Reason} -> -	    io:format("Runtime error: ~tp~n", [Reason]), +	    io:format(?STDERR, "Runtime error: ~tp~n", [Reason]),  	    error      end. @@ -83,66 +90,178 @@ compiler_runner(List) ->  %% Parses the first part of the option list. -compile1(['@cwd', Cwd|Rest]) -> -    CwdL = atom_to_list(Cwd), -    compile1(Rest, CwdL, #options{outdir=CwdL, cwd=CwdL});  compile1(Args) -> -    %% From R13B02, the @cwd argument is optional.      {ok, Cwd} = file:get_cwd(), -    compile1(Args, Cwd, #options{outdir=Cwd, cwd=Cwd}). +    compile1(Args, #options{outdir=Cwd,cwd=Cwd}).  %% Parses all options. -compile1(['@i', Dir|Rest], Cwd, Opts) -> +compile1(["--"|Files], Opts) -> +    compile2(Files, Opts); +compile1(["-"++Option|T], Opts) -> +    parse_generic_option(Option, T, Opts); +compile1(["+"++Option|Rest], Opts) -> +    Term = make_term(Option), +    Specific = Opts#options.specific, +    compile1(Rest, Opts#options{specific=[Term|Specific]}); +compile1(Files, Opts) -> +    compile2(Files, Opts). + +parse_generic_option("b"++Opt, T0, Opts) -> +    {OutputType,T} = get_option("b", Opt, T0), +    compile1(T, Opts#options{output_type=list_to_atom(OutputType)}); +parse_generic_option("D"++Opt, T0, #options{defines=Defs}=Opts) -> +    {Val0,T} = get_option("D", Opt, T0), +    {Key0,Val1} = split_at_equals(Val0, []), +    Key = list_to_atom(Key0), +    case Val1 of +	[] -> +	    compile1(T, Opts#options{defines=[Key|Defs]}); +	Val2 -> +	    Val = make_term(Val2), +	    compile1(T, Opts#options{defines=[{Key,Val}|Defs]}) +    end; +parse_generic_option("help", _, _Opts) -> +    usage(); +parse_generic_option("I"++Opt, T0, #options{cwd=Cwd}=Opts) -> +    {Dir,T} = get_option("I", Opt, T0),      AbsDir = filename:absname(Dir, Cwd), -    compile1(Rest, Cwd, Opts#options{includes=[AbsDir|Opts#options.includes]}); -compile1(['@outdir', Dir|Rest], Cwd, Opts) -> +    compile1(T, Opts#options{includes=[AbsDir|Opts#options.includes]}); +parse_generic_option("M"++Opt, T0, #options{specific=Spec}=Opts) -> +    case parse_dep_option(Opt, T0) of +	error -> +	    error; +	{SpecOpts,T} -> +	    compile1(T, Opts#options{specific=SpecOpts++Spec}) +    end; +parse_generic_option("o"++Opt, T0, #options{cwd=Cwd}=Opts) -> +    {Dir,T} = get_option("o", Opt, T0),      AbsName = filename:absname(Dir, Cwd),      case file_or_directory(AbsName) of  	file -> -	    compile1(Rest, Cwd, Opts#options{outfile=AbsName}); +	    compile1(T, Opts#options{outfile=AbsName});  	directory -> -	    compile1(Rest, Cwd, Opts#options{outdir=AbsName}) +	    compile1(T, Opts#options{outdir=AbsName})      end; -compile1(['@d', Name|Rest], Cwd, Opts) -> -    Defines = Opts#options.defines, -    compile1(Rest, Cwd, Opts#options{defines=[Name|Defines]}); -compile1(['@dv', Name, Term|Rest], Cwd, Opts) -> -    Defines = Opts#options.defines, -    Value = make_term(atom_to_list(Term)), -    compile1(Rest, Cwd, Opts#options{defines=[{Name, Value}|Defines]}); -compile1(['@warn', Level0|Rest], Cwd, Opts) -> -    case catch list_to_integer(atom_to_list(Level0)) of -	Level when is_integer(Level) -> -	    compile1(Rest, Cwd, Opts#options{warning=Level}); +parse_generic_option("O"++Opt, T, Opts) -> +    case Opt of +	"" -> +	    compile1(T, Opts#options{optimize=1});  	_ -> -	    compile1(Rest, Cwd, Opts) +	    Term = make_term(Opt), +	    compile1(T, Opts#options{optimize=Term})      end; -compile1(['@verbose', false|Rest], Cwd, Opts) -> -    compile1(Rest, Cwd, Opts#options{verbose=false}); -compile1(['@verbose', true|Rest], Cwd, Opts) -> -    compile1(Rest, Cwd, Opts#options{verbose=true}); -compile1(['@optimize', Atom|Rest], Cwd, Opts) -> -    Term = make_term(atom_to_list(Atom)), -    compile1(Rest, Cwd, Opts#options{optimize=Term}); -compile1(['@option', Atom|Rest], Cwd, Opts) -> -    Term = make_term(atom_to_list(Atom)), -    Specific = Opts#options.specific, -    compile1(Rest, Cwd, Opts#options{specific=[Term|Specific]}); -compile1(['@output_type', OutputType|Rest], Cwd, Opts) -> -    compile1(Rest, Cwd, Opts#options{output_type=OutputType}); -compile1(['@files'|Rest], Cwd, Opts) -> -    Includes = lists:reverse(Opts#options.includes), -    compile2(Rest, Cwd, Opts#options{includes=Includes}). - -compile2(Files, Cwd, Opts) -> -    case {Opts#options.outfile, length(Files)} of +parse_generic_option("v", T, Opts) -> +    compile1(T, Opts#options{verbose=true}); +parse_generic_option("W"++Warn, T, #options{specific=Spec}=Opts) -> +    case Warn of +	"all" -> +	    compile1(T, Opts#options{warning=999}); +	"error" -> +	    compile1(T, Opts#options{specific=[warnings_as_errors|Spec]}); +	"" -> +	    compile1(T, Opts#options{warning=1}); +	_ -> +	    try	list_to_integer(Warn) of +		Level -> +		    compile1(T, Opts#options{warning=Level}) +	    catch +		error:badarg -> +		    usage() +	    end +    end; +parse_generic_option("E", T, #options{specific=Spec}=Opts) -> +    compile1(T, Opts#options{specific=['E'|Spec]}); +parse_generic_option("P", T, #options{specific=Spec}=Opts) -> +    compile1(T, Opts#options{specific=['P'|Spec]}); +parse_generic_option("S", T, #options{specific=Spec}=Opts) -> +    compile1(T, Opts#options{specific=['S'|Spec]}); +parse_generic_option(Option, _T, _Opts) -> +    io:format(?STDERR, "Unknown option: -~s\n", [Option]), +    usage(). + +parse_dep_option("", T) -> +    {[makedep,{makedep_output,standard_io}],T}; +parse_dep_option("D", T) -> +    {[makedep],T}; +parse_dep_option("F"++Opt, T0) -> +    {File,T} = get_option("MF", Opt, T0), +    {[makedep,{makedep_output,File}],T}; +parse_dep_option("G", T) -> +    {[makedep_add_missing],T}; +parse_dep_option("P", T) -> +    {[makedep_phony],T}; +parse_dep_option("Q"++Opt, T0) -> +    {Target,T} = get_option("MT", Opt, T0), +    {[makedep_quote_target,{makedep_target,Target}],T}; +parse_dep_option("T"++Opt, T0) -> +    {Target,T} = get_option("MT", Opt, T0), +    {[{makedep_target,Target}],T}; +parse_dep_option(Opt, _T) -> +    io:format(?STDERR, "Unknown option: -M~s\n", [Opt]), +    usage(). + +usage() -> +    H = [{"-b type","type of output file (e.g. beam)"}, +	 {"-d","turn on debugging of erlc itself"}, +	 {"-Dname","define name"}, +	 {"-Dname=value","define name to have value"}, +	 {"-help","shows this help text"}, +	 {"-I path","where to search for include files"}, +	 {"-M","generate a rule for make(1) describing the dependencies"}, +	 {"-MF file","write the dependencies to 'file'"}, +	 {"-MT target","change the target of the rule emitted by dependency " +	  "generation"}, +	 {"-MQ target","same as -MT but quote characters special to make(1)"}, +	 {"-MG","consider missing headers as generated files and add them to " +	  "the dependencies"}, +	 {"-MP","add a phony target for each dependency"}, +	 {"-MD","same as -M -MT file (with default 'file')"}, +	 {"-o name","name output directory or file"}, +	 {"-pa path","add path to the front of Erlang's code path"}, +	 {"-pz path","add path to the end of Erlang's code path"}, +	 {"-smp","compile using SMP emulator"}, +	 {"-v","verbose compiler output"}, +	 {"-Werror","make all warnings into errors"}, +	 {"-W0","disable warnings"}, +	 {"-Wnumber","set warning level to number"}, +	 {"-Wall","enable all warnings"}, +	 {"-W","enable warnings (default; same as -W1)"}, +	 {"-E","generate listing of expanded code (Erlang compiler)"}, +	 {"-S","generate assembly listing (Erlang compiler)"}, +	 {"-P","generate listing of preprocessed code (Erlang compiler)"}, +	 {"+term","pass the Erlang term unchanged to the compiler"}], +    io:put_chars(?STDERR, +		 ["Usage: erlc [Options] file.ext ...\n", +		  "Options:\n", +		  [io_lib:format("~-14s ~s\n", [K,D]) || {K,D} <- H]]), +    error. + +get_option(_Name, [], [[C|_]=Option|T]) when C =/= $- -> +    {Option,T}; +get_option(_Name, [_|_]=Option, T) -> +    {Option,T}; +get_option(Name, _, _) -> +    exit({compiler_error,"No value given to -"++Name++" option"}). + +split_at_equals([$=|T], Acc) -> +    {lists:reverse(Acc),T}; +split_at_equals([H|T], Acc) -> +    split_at_equals(T, [H|Acc]); +split_at_equals([], Acc) -> +    {lists:reverse(Acc),[]}. + +compile2(Files, #options{cwd=Cwd,includes=Incl,outfile=Outfile}=Opts0) -> +    Opts = Opts0#options{includes=lists:reverse(Incl)}, +    case {Outfile,length(Files)} of  	{"", _} ->  	    compile3(Files, Cwd, Opts);  	{[_|_], 1} ->  	    compile3(Files, Cwd, Opts);  	{[_|_], _N} -> -	    io:format("Output file name given, but more than one input file.~n"), +	    io:put_chars(?STDERR, +			 "Output file name given, " +			 "but more than one input file.\n"),  	    error      end. @@ -170,23 +289,25 @@ compile3([], _Cwd, _Options) -> ok.  %% Invokes the appropriate compiler, depending on the file extension.  compile_file("", Input, _Output, _Options) -> -    io:format("File has no extension: ~ts~n", [Input]), +    io:format(?STDERR, "File has no extension: ~ts~n", [Input]),      error;  compile_file(Ext, Input, Output, Options) ->      case compiler(Ext) of  	no -> -	    io:format("Unknown extension: '~ts'\n", [Ext]), +	    io:format(?STDERR, "Unknown extension: '~ts'\n", [Ext]),  	    error;  	{M, F} ->  	    case catch M:F(Input, Output, Options) of  		ok -> ok;  		error -> error;  		{'EXIT',Reason} -> -		    io:format("Compiler function ~w:~w/3 failed:\n~p~n", +		    io:format(?STDERR, +			      "Compiler function ~w:~w/3 failed:\n~p~n",  			      [M,F,Reason]),  		    error;  		Other -> -		    io:format("Compiler function ~w:~w/3 returned:\n~p~n", +		    io:format(?STDERR, +			      "Compiler function ~w:~w/3 returned:\n~p~n",  			      [M,F,Other]),  		    error  	    end @@ -215,10 +336,10 @@ make_term(Str) ->  	    case erl_parse:parse_term(Tokens ++ [{dot, 1}]) of  		{ok, Term} -> Term;  		{error, {_,_,Reason}} -> -		    io:format("~ts: ~ts~n", [Reason, Str]), +		    io:format(?STDERR, "~ts: ~ts~n", [Reason, Str]),  		    throw(error)  	    end;  	{error, {_,_,Reason}, _} -> -	    io:format("~ts: ~ts~n", [Reason, Str]), +	    io:format(?STDERR, "~ts: ~ts~n", [Reason, Str]),  	    throw(error)      end. diff --git a/lib/stdlib/src/erl_internal.erl b/lib/stdlib/src/erl_internal.erl index 378e629ac9..28de7205ea 100644 --- a/lib/stdlib/src/erl_internal.erl +++ b/lib/stdlib/src/erl_internal.erl @@ -267,6 +267,7 @@ bif(bitstring_to_list, 1) -> true;  bif(byte_size, 1) -> true;  bif(check_old_code, 1) -> true;  bif(check_process_code, 2) -> true; +bif(check_process_code, 3) -> true;  bif(date, 0) -> true;  bif(delete_module, 1) -> true;  bif(demonitor, 1) -> true; @@ -286,6 +287,7 @@ bif(float_to_binary, 1) -> true;  bif(float_to_binary, 2) -> true;  bif(garbage_collect, 0) -> true;  bif(garbage_collect, 1) -> true; +bif(garbage_collect, 2) -> true;  bif(get, 0) -> true;  bif(get, 1) -> true;  bif(get_keys, 1) -> true; diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index f599881c07..bcf3ccef3b 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -281,6 +281,8 @@ format_error(utf_bittype_size_or_unit) ->      "neither size nor unit must be given for segments of type utf8/utf16/utf32";  format_error({bad_bitsize,Type}) ->      io_lib:format("bad ~s bit size", [Type]); +format_error(unsized_binary_in_bin_gen_pattern) -> +    "binary fields without size are not allowed in patterns of bit string generators";  %% --- behaviours ---  format_error({conflicting_behaviours,{Name,Arity},B,FirstL,FirstB}) ->      io_lib:format("conflicting behaviours - callback ~w/~w required by both '~p' " @@ -2882,7 +2884,8 @@ lc_quals([{generate,_Line,P,E} | Qs], Vt0, Uvt0, St0) ->      {Vt,Uvt,St} = handle_generator(P,E,Vt0,Uvt0,St0),      lc_quals(Qs, Vt, Uvt, St);  lc_quals([{b_generate,_Line,P,E} | Qs], Vt0, Uvt0, St0) -> -    {Vt,Uvt,St} = handle_generator(P,E,Vt0,Uvt0,St0), +    St1 = handle_bitstring_gen_pat(P,St0), +    {Vt,Uvt,St} = handle_generator(P,E,Vt0,Uvt0,St1),      lc_quals(Qs, Vt, Uvt, St);  lc_quals([F|Qs], Vt, Uvt, St0) ->      {Fvt,St1} = case is_guard_test2(F, St0#lint.records) of @@ -2910,6 +2913,22 @@ handle_generator(P,E,Vt,Uvt,St0) ->      Vt3 = vtupdate(vtsubtract(Vt2, Binvt), Binvt),      {Vt3,NUvt,St5}. +handle_bitstring_gen_pat({bin,_,Segments=[_|_]},St) -> +    case lists:last(Segments) of +        {bin_element,Line,{var,_,_},default,Flags} when is_list(Flags) -> +            case member(binary, Flags) orelse member(bits, Flags) +                                       orelse member(bitstring, Flags) of +                true -> +                    add_error(Line, unsized_binary_in_bin_gen_pattern, St); +                false -> +                    St +            end; +        _ -> +            St +    end; +handle_bitstring_gen_pat(_,St) -> +    St. +  %% fun_clauses(Clauses, ImportVarTable, State) ->  %%      {UsedVars, State}.  %%  Fun's cannot export any variables. diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl index d988a4d8c7..4ba6dd01fa 100644 --- a/lib/stdlib/src/erl_scan.erl +++ b/lib/stdlib/src/erl_scan.erl @@ -1,4 +1,3 @@ -%% -*- coding: utf-8 -*-  %%  %% %CopyrightBegin%  %% diff --git a/lib/stdlib/src/erl_tar.erl b/lib/stdlib/src/erl_tar.erl index 40ef6c8998..40b48d7999 100644 --- a/lib/stdlib/src/erl_tar.erl +++ b/lib/stdlib/src/erl_tar.erl @@ -45,10 +45,7 @@ open(Name, Mode) ->  open1({binary,Bin}, read, _Raw, Opts) ->      case file:open(Bin, [ram,binary,read]) of  	{ok,File} -> -	    case Opts of -		[compressed] -> ram_file:uncompress(File); -		[] -> ok -	    end, +            _ = [ram_file:uncompress(File) || Opts =:= [compressed]],  	    {ok,{read,File}};  	Error ->  	    Error diff --git a/lib/stdlib/src/error_logger_tty_h.erl b/lib/stdlib/src/error_logger_tty_h.erl index ad5891f191..e92142d154 100644 --- a/lib/stdlib/src/error_logger_tty_h.erl +++ b/lib/stdlib/src/error_logger_tty_h.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. 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 @@ -54,7 +54,7 @@ init([]) ->  handle_event({_Type, GL, _Msg}, State) when node(GL) =/= node() ->      {ok, State};  handle_event(Event, State) -> -    write_event(tag_event(Event),io), +    ok = write_event(tag_event(Event),io),      {ok, State}.  handle_info({'EXIT', User, _Reason}, {User, PrevHandler}) -> @@ -66,10 +66,10 @@ handle_info({'EXIT', User, _Reason}, {User, PrevHandler}) ->  	     PrevHandler, go_back}      end;  handle_info({emulator, GL, Chars}, State) when node(GL) == node() -> -    write_event(tag_event({emulator, GL, Chars}),io), +    ok = write_event(tag_event({emulator, GL, Chars}),io),      {ok, State};  handle_info({emulator, noproc, Chars}, State) -> -    write_event(tag_event({emulator, noproc, Chars}),io), +    ok = write_event(tag_event({emulator, noproc, Chars}),io),      {ok, State};  handle_info(_, State) ->      {ok, State}. @@ -99,10 +99,11 @@ set_group_leader() ->  tag_event(Event) ->          {erlang:universaltime(), Event}. +%% IOMOd is always 'io'  write_events(Events,IOMod) -> write_events1(lists:reverse(Events),IOMod).  write_events1([Event|Es],IOMod) -> -    write_event(Event,IOMod), +    ok = write_event(Event,IOMod),      write_events1(Es,IOMod);  write_events1([],_IOMod) ->      ok. diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl index fea718541d..35f6dff57e 100644 --- a/lib/stdlib/src/escript.erl +++ b/lib/stdlib/src/escript.erl @@ -771,9 +771,11 @@ interpret(Forms, HasRecs,  File, Args) ->      ArgsA = erl_parse:abstract(Args, 0),      Call = {call,0,{atom,0,main},[ArgsA]},      try -        erl_eval:expr(Call, -                      erl_eval:new_bindings(), -                      {value,fun(I, J) -> code_handler(I, J, Dict, File) end}), +        _ = erl_eval:expr(Call, +                          erl_eval:new_bindings(), +                          {value,fun(I, J) -> +                                         code_handler(I, J, Dict, File) +                                 end}),          my_halt(0)      catch          Class:Reason -> diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl index 77c8029f59..f05bfd12a7 100644 --- a/lib/stdlib/src/ets.erl +++ b/lib/stdlib/src/ets.erl @@ -719,7 +719,7 @@ tab2file(Tab, File) ->  tab2file(Tab, File, Options) ->      try  	{ok, FtOptions} = parse_ft_options(Options), -	file:delete(File), +	_ = file:delete(File),  	case file:read_file_info(File) of  	    {error, enoent} -> ok;  	    _ -> throw(eaccess) @@ -750,14 +750,18 @@ tab2file(Tab, File, Options) ->  		    {fun(Oldstate,Termlist) ->  			     {NewState,BinList} =   				 md5terms(Oldstate,Termlist), -			     disk_log:blog_terms(Name,BinList), -			     NewState +                             case disk_log:blog_terms(Name,BinList) of +                                 ok -> NewState; +                                 {error, Reason2} -> throw(Reason2) +                             end  		     end,  		     erlang:md5_init()};  		false ->  		    {fun(_,Termlist) -> -			     disk_log:log_terms(Name,Termlist), -			     true +                             case disk_log:log_terms(Name,Termlist) of +                                 ok -> true; +                                 {error, Reason2} -> throw(Reason2) +                             end  		     end,   		     true}  	    end, @@ -792,16 +796,16 @@ tab2file(Tab, File, Options) ->  	    disk_log:close(Name)  	catch  	    throw:TReason -> -		disk_log:close(Name), -		file:delete(File), +		_ = disk_log:close(Name), +		_ = file:delete(File),  		throw(TReason);  	    exit:ExReason -> -		disk_log:close(Name), -		file:delete(File), +		_ = disk_log:close(Name), +		_ = file:delete(File),  		exit(ExReason);  	    error:ErReason -> -		disk_log:close(Name), -		file:delete(File), +		_ = disk_log:close(Name), +		_ = file:delete(File),  	        erlang:raise(error,ErReason,erlang:get_stacktrace())  	end      catch @@ -892,25 +896,32 @@ file2tab(File, Opts) ->      try  	{ok,Verify,TabArg} = parse_f2t_opts(Opts,false,[]),  	Name = make_ref(), -	{ok, Major, Minor, FtOptions, MD5State, FullHeader, DLContext} =  +        {ok, Name} =  	    case disk_log:open([{name, Name},   				{file, File},   				{mode, read_only}]) of  		{ok, Name} -> -		    get_header_data(Name,Verify); +                    {ok, Name};  		{repaired, Name, _,_} -> %Uh? cannot happen?  		    case Verify of  			true -> -			    disk_log:close(Name), +			    _ = disk_log:close(Name),  			    throw(badfile);  			false -> -			    get_header_data(Name,Verify) +                            {ok, Name}  		    end;  		{error, Other1} ->  		    throw({read_error, Other1});  		Other2 ->  		    throw(Other2)  	    end, +	{ok, Major, Minor, FtOptions, MD5State, FullHeader, DLContext} = +            try get_header_data(Name, Verify) +            catch +                badfile -> +                    _ = disk_log:close(Name), +                    throw(badfile) +            end,  	try  	    if    		Major > ?MAJOR_F2T_VERSION ->  @@ -974,7 +985,7 @@ file2tab(File, Opts) ->  		    erlang:raise(error,ErReason,erlang:get_stacktrace())  	    end  	after -	    disk_log:close(Name) +	    _ = disk_log:close(Name)  	end      catch  	throw:TReason2 -> @@ -1293,20 +1304,30 @@ named_table(false) -> [].  tabfile_info(File) when is_list(File) ; is_atom(File) ->      try  	Name = make_ref(), -	{ok, Major, Minor, _FtOptions, _MD5State, FullHeader, _DLContext} =  +        {ok, Name} =  	    case disk_log:open([{name, Name},   				{file, File},   				{mode, read_only}]) of  		{ok, Name} -> -		    get_header_data(Name,false); +                    {ok, Name};  		{repaired, Name, _,_} -> %Uh? cannot happen? -		    get_header_data(Name,false); +		    {ok, Name};  		{error, Other1} ->  		    throw({read_error, Other1});  		Other2 ->  		    throw(Other2)  	    end, -	disk_log:close(Name), +	{ok, Major, Minor, _FtOptions, _MD5State, FullHeader, _DLContext} = +            try get_header_data(Name, false) +            catch +                badfile -> +                    _ = disk_log:close(Name), +                    throw(badfile) +            end, +        case disk_log:close(Name) of +            ok -> ok; +            {error, Reason} -> throw(Reason) +        end,  	{value, N} = lists:keysearch(name, 1, FullHeader),  	{value, Type} = lists:keysearch(type, 1, FullHeader),  	{value, P} = lists:keysearch(protection, 1, FullHeader), diff --git a/lib/stdlib/src/eval_bits.erl b/lib/stdlib/src/eval_bits.erl index e49cbc1fd1..75fe2c00c7 100644 --- a/lib/stdlib/src/eval_bits.erl +++ b/lib/stdlib/src/eval_bits.erl @@ -192,7 +192,7 @@ bin_gen_field({bin_element,Line,VE,Size0,Options0},          make_bit_type(Line, Size0, Options0),      V = erl_eval:partial_eval(VE),      NewV = coerce_to_float(V, Type), -    match_check_size(Mfun, Size1, BBs0), +    match_check_size(Mfun, Size1, BBs0, false),      {value, Size, _BBs} = Efun(Size1, BBs0),      bin_gen_field1(Bin, Type, Size, Unit, Sign, Endian, NewV, Bs0, BBs0, Mfun). @@ -380,20 +380,25 @@ make_bit_type(_Line, Size, Type0) -> %Size evaluates to an integer or 'all'          {error,Reason} -> error(Reason)      end. -match_check_size(Mfun, {var,_,V}, Bs) -> +match_check_size(Mfun, Size, Bs) -> +    match_check_size(Mfun, Size, Bs, true). + +match_check_size(Mfun, {var,_,V}, Bs, _AllowAll) ->      case Mfun(binding, {V,Bs}) of          {value,_} -> ok;  	unbound -> throw(invalid) % or, rather, error({unbound,V})      end; -match_check_size(_, {atom,_,all}, _Bs) -> +match_check_size(_, {atom,_,all}, _Bs, true) ->      ok; -match_check_size(_, {atom,_,undefined}, _Bs) -> +match_check_size(_, {atom,_,all}, _Bs, false) -> +    throw(invalid); +match_check_size(_, {atom,_,undefined}, _Bs, _AllowAll) ->      ok; -match_check_size(_, {integer,_,_}, _Bs) -> +match_check_size(_, {integer,_,_}, _Bs, _AllowAll) ->      ok; -match_check_size(_, {value,_,_}, _Bs) -> +match_check_size(_, {value,_,_}, _Bs, _AllowAll) ->      ok;	%From the debugger. -match_check_size(_, _, _Bs) -> +match_check_size(_, _, _Bs, _AllowAll) ->      throw(invalid).  %% error(Reason) -> exception thrown diff --git a/lib/stdlib/src/file_sorter.erl b/lib/stdlib/src/file_sorter.erl index 2bf88959b7..687d72b4bd 100644 --- a/lib/stdlib/src/file_sorter.erl +++ b/lib/stdlib/src/file_sorter.erl @@ -547,7 +547,7 @@ files(_I, L, _LSz, #w{seq = 1, out = Out}=W, []) ->              NW = close_input(W1),              outfun(close, NW);          Out -> -            write_run(L, W, Out), +            _ = write_run(L, W, Out),              ok      end;  files(_I, L, _LSz, W, []) -> @@ -638,7 +638,7 @@ last_merge(R, W) when length(R) =< W#w.no_files ->              NW = close_input(W2),              outfun(close, NW);          Out -> -            merge_files(R, W, Out), +            _ = merge_files(R, W, Out),              ok      end;  last_merge(R, W) -> @@ -1110,10 +1110,12 @@ read_fun2(Fd, Bin, Size, FileName, Owner) ->      end.  close_read_fun(Fd, _FileName, user) -> -    file:close(Fd); +    _ = file:close(Fd), +    ok;  close_read_fun(Fd, FileName, fsort) -> -    file:close(Fd), -    file:delete(FileName). +    _ = file:close(Fd), +    _ = file:delete(FileName), +    ok.  read_objs(Fd, FileName, I, L, Bin0, Size0, LSz, W) ->      Max = erlang:max(Size0, ?CHUNKSIZE), @@ -1481,10 +1483,10 @@ cleanup(W) ->      F = fun(IFun) when is_function(IFun) ->                   IFun(close);             ({Fd,FileName}) -> -                file:close(Fd), -                file:delete(FileName); +                _ = file:close(Fd), +                _= file:delete(FileName);             (FileName) ->  -                file:delete(FileName) +                _= file:delete(FileName)          end,      lists:foreach(F, W1#w.temp). @@ -1502,8 +1504,12 @@ close_out(_) ->  close_file(Fd, W) ->      {Fd, FileName} = lists:keyfind(Fd, 1, W#w.temp),      ?DEBUG("closing ~tp~n", [FileName]), -    file:close(Fd), -    W#w{temp = [FileName | lists:keydelete(Fd, 1, W#w.temp)]}. +    case file:close(Fd) of +        ok -> +            W#w{temp = [FileName | lists:keydelete(Fd, 1, W#w.temp)]}; +        Error -> +            file_error(FileName, Error, W) +    end.  %%%  %%% Format 'term'. @@ -1536,10 +1542,10 @@ file_rterms2(Fd, L, LSz, FileName, Files) when LSz < ?CHUNKSIZE ->              B = term_to_binary(Term),              file_rterms2(Fd, [B | L], LSz + byte_size(B), FileName, Files);          eof -> -            file:close(Fd), +            _ = file:close(Fd),              {lists:reverse(L), file_rterms(no_file, Files)};          _Error -> -            file:close(Fd), +            _ = file:close(Fd),              {error, {bad_term, FileName}}      end;  file_rterms2(Fd, L, _LSz, FileName, Files) -> @@ -1568,7 +1574,7 @@ write_terms(Fd, F, [B | Bs], Args) ->          ok ->               write_terms(Fd, F, Bs, Args);          {error, Reason} -> -            file:close(Fd), +            _ = file:close(Fd),              {error, {file_error, F, Reason}}      end;  write_terms(Fd, F, [], Args) -> diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl index b8c0576e56..a266daa084 100644 --- a/lib/stdlib/src/filelib.erl +++ b/lib/stdlib/src/filelib.erl @@ -234,7 +234,7 @@ ensure_dir(F) ->  	    %% Protect against infinite loop  	    {error,einval};  	false -> -	    ensure_dir(Dir), +	    _ = ensure_dir(Dir),  	    case file:make_dir(Dir) of  		{error,eexist}=EExist ->  		    case do_is_dir(Dir, file) of diff --git a/lib/stdlib/src/gb_sets.erl b/lib/stdlib/src/gb_sets.erl index ba35a7170a..237317ac94 100644 --- a/lib/stdlib/src/gb_sets.erl +++ b/lib/stdlib/src/gb_sets.erl @@ -1,8 +1,7 @@ -%% -*- coding: utf-8 -*-  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 2001-2012. All Rights Reserved. +%% Copyright Ericsson AB 2001-2013. 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 diff --git a/lib/stdlib/src/gb_trees.erl b/lib/stdlib/src/gb_trees.erl index de0c239e26..7a4dfe1a0b 100644 --- a/lib/stdlib/src/gb_trees.erl +++ b/lib/stdlib/src/gb_trees.erl @@ -1,8 +1,7 @@ -%% -*- coding: utf-8 -*-  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 2001-2012. All Rights Reserved. +%% Copyright Ericsson AB 2001-2013. 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 diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl index 9e9d4ee4bb..e9654322f1 100644 --- a/lib/stdlib/src/gen_fsm.erl +++ b/lib/stdlib/src/gen_fsm.erl @@ -549,7 +549,7 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, Debug) ->  	{stop, Reason, Reply, NStateData} when From =/= undefined ->  	    {'EXIT', R} = (catch terminate(Reason, Name, Msg, Mod,  					   StateName, NStateData, Debug)), -	    reply(Name, From, Reply, Debug, StateName), +	    _ = reply(Name, From, Reply, Debug, StateName),  	    exit(R);  	{'EXIT', What} ->  	    terminate(What, Name, Msg, Mod, StateName, StateData, Debug); diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index df68a37c06..5f14e48b0a 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -623,7 +623,7 @@ handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod, Debug) ->  	{stop, Reason, Reply, NState} ->  	    {'EXIT', R} =   		(catch terminate(Reason, Name, Msg, Mod, NState, Debug)), -	    reply(Name, From, Reply, NState, Debug), +	    _ = reply(Name, From, Reply, NState, Debug),  	    exit(R);  	Other ->  	    handle_common_reply(Other, Parent, Name, Msg, Mod, State, Debug) diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index 9e69601770..375d05f359 100644 --- a/lib/stdlib/src/io_lib.erl +++ b/lib/stdlib/src/io_lib.erl @@ -1,4 +1,3 @@ -%% -*- coding: utf-8 -*-  %%  %% %CopyrightBegin%  %% diff --git a/lib/stdlib/src/log_mf_h.erl b/lib/stdlib/src/log_mf_h.erl index 19b555a48c..6b42363979 100644 --- a/lib/stdlib/src/log_mf_h.erl +++ b/lib/stdlib/src/log_mf_h.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 1996-2012. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. 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 @@ -135,7 +135,12 @@ handle_event(Event, State) ->  			State#state{cur_fd = NewFd, curF = NewF, curB = 0}  		end,  	    [Hi,Lo] = put_int16(Size), -	    file:write(NewState#state.cur_fd, [Hi, Lo, Bin]), +            case file:write(NewState#state.cur_fd, [Hi, Lo, Bin]) of +                ok -> +                    ok; +                {error, Reason} -> +                    exit({file_exit, Reason}) +            end,  	    {ok, NewState#state{curB = NewState#state.curB + Size + 2}};  	_ ->  	    {ok, State} @@ -174,7 +179,7 @@ file_open(Dir, FileNo) ->  	    write_index_file(Dir, FileNo),  	    {ok, Fd};  	_ ->  -	    exit({file, open}) +	    exit(file_open)      end.  put_int16(I) -> @@ -211,7 +216,7 @@ write_index_file(Dir, Index) ->  	    ok = file:close(Fd),  	    ok = file:rename(TmpFile,File),  	    ok; -	_ -> exit(open_index_file) +	_ -> exit(write_index_file)      end.  inc(N, Max) -> diff --git a/lib/stdlib/src/orddict.erl b/lib/stdlib/src/orddict.erl index 45d3c84b3e..da60fc1bb6 100644 --- a/lib/stdlib/src/orddict.erl +++ b/lib/stdlib/src/orddict.erl @@ -20,7 +20,7 @@  -module(orddict).  %% Standard interface. --export([new/0,is_key/2,to_list/1,from_list/1,size/1]). +-export([new/0,is_key/2,to_list/1,from_list/1,size/1,is_empty/1]).  -export([fetch/2,find/2,fetch_keys/1,erase/2]).  -export([store/3,append/3,append_list/3,update/3,update/4,update_counter/3]).  -export([fold/3,map/2,filter/2,merge/3]). @@ -64,6 +64,12 @@ from_list(Pairs) ->  size(D) -> length(D). +-spec is_empty(Orddict) -> boolean() when +      Orddict :: orddict(). + +is_empty([]) -> true; +is_empty([_|_]) -> false. +  -spec fetch(Key, Orddict) -> Value when        Key :: term(),        Value :: term(), diff --git a/lib/stdlib/src/pool.erl b/lib/stdlib/src/pool.erl index a5eb191ab2..dfe6318dea 100644 --- a/lib/stdlib/src/pool.erl +++ b/lib/stdlib/src/pool.erl @@ -1,7 +1,7 @@  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 1996-2011. All Rights Reserved. +%% Copyright Ericsson AB 1996-2013. 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 @@ -63,7 +63,7 @@ start(Name) ->        Args :: string(),        Nodes :: [node()].  start(Name, Args) when is_atom(Name) -> -    gen_server:start({global, pool_master}, pool, [], []), +    _ = gen_server:start({global, pool_master}, pool, [], []),      Hosts = net_adm:host_file(),      Nodes = start_nodes(Hosts, Name, Args),      lists:foreach(fun attach/1, Nodes), diff --git a/lib/stdlib/src/re.erl b/lib/stdlib/src/re.erl index c5109ec455..afc63496d0 100644 --- a/lib/stdlib/src/re.erl +++ b/lib/stdlib/src/re.erl @@ -19,20 +19,21 @@  -module(re).  -export([grun/3,urun/3,ucompile/2,replace/3,replace/4,split/2,split/3]). -%-opaque mp() :: {re_pattern, _, _, _}. --type mp() :: {re_pattern, _, _, _}. +%-opaque mp() :: {re_pattern, _, _, _, _}. +-type mp() :: {re_pattern, _, _, _, _}.  -type nl_spec() :: cr | crlf | lf | anycrlf | any.  -type compile_option() :: unicode | anchored | caseless | dollar_endonly                          | dotall | extended | firstline | multiline                          | no_auto_capture | dupnames | ungreedy -                        | {newline, nl_spec()}| bsr_anycrlf -                        | bsr_unicode. +                        | {newline, nl_spec()} +                        | bsr_anycrlf | bsr_unicode +                        | no_start_optimize | ucp | never_utf.  %%% BIFs --export([compile/1, compile/2, run/2, run/3]). +-export([compile/1, compile/2, run/2, run/3, inspect/2]).  -spec compile(Regexp) -> {ok, MP} | {error, ErrSpec} when        Regexp :: iodata(), @@ -63,17 +64,21 @@ run(_, _) ->  -spec run(Subject, RE, Options) -> {match, Captured} |                                     match | -                                   nomatch when +                                   nomatch | +				   {error, ErrType} when        Subject :: iodata() | unicode:charlist(),        RE :: mp() | iodata() | unicode:charlist(),        Options :: [Option], -      Option :: anchored | global | notbol | noteol | notempty +      Option :: anchored | global | notbol | noteol | notempty  +	      | notempty_atstart | report_errors                | {offset, non_neg_integer()} | +		{match_limit, non_neg_integer()} | +		{match_limit_recursion, non_neg_integer()} |                  {newline, NLSpec :: nl_spec()} |                  bsr_anycrlf | bsr_unicode | {capture, ValueSpec} |                  {capture, ValueSpec, Type} | CompileOpt,        Type :: index | list | binary, -      ValueSpec :: all | all_but_first | first | none | ValueList, +      ValueSpec :: all | all_but_first | all_names | first | none | ValueList,        ValueList :: [ValueID],        ValueID :: integer() | string() | atom(),        CompileOpt :: compile_option(), @@ -83,11 +88,21 @@ run(_, _) ->                     | binary(),        ListConversionData :: string()                            | {error, string(), binary()} -                          | {incomplete, string(), binary()}. +                          | {incomplete, string(), binary()}, +      ErrType :: match_limit | match_limit_recursion | {compile,  CompileErr},  +      CompileErr :: {ErrString :: string(), Position :: non_neg_integer()}.  run(_, _, _) ->      erlang:nif_error(undef). +-spec inspect(MP,Item) -> {namelist, [ binary() ]} when +      MP :: mp(), +      Item :: namelist. + +inspect(_,_) -> +    erlang:nif_error(undef). +     +  %%% End of BIFs  -spec split(Subject, RE) -> SplitList when @@ -102,8 +117,10 @@ split(Subject,RE) ->        Subject :: iodata() | unicode:charlist(),        RE :: mp() | iodata() | unicode:charlist(),        Options :: [ Option ], -      Option :: anchored | notbol | noteol | notempty +      Option :: anchored | notbol | noteol | notempty | notempty_atstart                | {offset, non_neg_integer()} | {newline, nl_spec()} +              | {match_limit, non_neg_integer()}  +              | {match_limit_recursion, non_neg_integer()}                | bsr_anycrlf | bsr_unicode | {return, ReturnType}                | {parts, NumParts} | group | trim | CompileOpt,        NumParts :: non_neg_integer() | infinity, @@ -266,7 +283,7 @@ extend_subpatterns([],N) ->  extend_subpatterns([H|T],N) ->      [H | extend_subpatterns(T,N-1)]. -compile_split({re_pattern,N,_,_} = Comp, Options) -> +compile_split({re_pattern,N,_,_,_} = Comp, Options) ->      {Comp,N,Options};  compile_split(Pat,Options0) when not is_tuple(Pat) ->      Options = lists:filter(fun(O) -> @@ -275,7 +292,7 @@ compile_split(Pat,Options0) when not is_tuple(Pat) ->      case re:compile(Pat,Options) of  	{error,Err} ->  	    {error,Err}; -	{ok, {re_pattern,N,_,_} = Comp} -> +	{ok, {re_pattern,N,_,_,_} = Comp} ->  	    NewOpt = lists:filter(fun(OO) -> (not copt(OO)) end, Options0),  	    {Comp,N,NewOpt}      end; @@ -295,8 +312,11 @@ replace(Subject,RE,Replacement) ->        RE :: mp() | iodata() | unicode:charlist(),        Replacement :: iodata() | unicode:charlist(),        Options :: [Option], -      Option :: anchored | global | notbol | noteol | notempty +      Option :: anchored | global | notbol | noteol | notempty  +	      | notempty_atstart                | {offset, non_neg_integer()} | {newline, NLSpec} | bsr_anycrlf +              | {match_limit, non_neg_integer()}  +              | {match_limit_recursion, non_neg_integer()}                | bsr_unicode | {return, ReturnType} | CompileOpt,        ReturnType :: iodata | list | binary,        CompileOpt :: compile_option(), @@ -352,6 +372,8 @@ process_repl_params([],Convert,Unicode) ->  process_repl_params([unicode|T],C,_U) ->      {NT,NC,NU} = process_repl_params(T,C,true),       {[unicode|NT],NC,NU}; +process_repl_params([report_errors|_],_,_) -> +    throw(badopt);  process_repl_params([{capture,_,_}|_],_,_) ->      throw(badopt);  process_repl_params([{capture,_}|_],_,_) -> @@ -387,6 +409,8 @@ process_split_params([group|T],C,U,L,S,_G) ->      process_split_params(T,C,U,L,S,true);   process_split_params([global|_],_,_,_,_,_) ->      throw(badopt); +process_split_params([report_errors|_],_,_,_,_,_) -> +    throw(badopt);  process_split_params([{capture,_,_}|_],_,_,_,_,_) ->      throw(badopt);  process_split_params([{capture,_}|_],_,_,_,_,_) -> @@ -487,17 +511,31 @@ do_replace(Subject,Repl,SubExprs0) ->        end || Part <- Repl ]. -check_for_unicode({re_pattern,_,1,_},_) -> +check_for_unicode({re_pattern,_,1,_,_},_) ->      true; -check_for_unicode({re_pattern,_,0,_},_) -> +check_for_unicode({re_pattern,_,0,_,_},_) ->      false;  check_for_unicode(_,L) ->      lists:member(unicode,L). + +check_for_crlf({re_pattern,_,_,1,_},_) -> +    true; +check_for_crlf({re_pattern,_,_,0,_},_) -> +    false; +check_for_crlf(_,L) -> +    case lists:keysearch(newline,1,L) of +	{value,{newline,any}} -> true; +	{value,{newline,crlf}} -> true; +	{value,{newline,anycrlf}} -> true; +	_ -> false +    end.  % SelectReturn = false | all | stirpfirst | none   % ConvertReturn = index | list | binary  % {capture, all} -> all (untouchded) -% {capture, first} -> kept in argumentt list and Select all +% {capture, all_names} -> if names are present: treated as a name {capture, [...]}  +%                                      else:    same as {capture, []} +% {capture, first} -> kept in argument list and Select all  % {capture, all_but_first} -> removed from argument list and selects stripfirst  % {capture, none} ->  removed from argument list and selects none  % {capture, []} -> removed from argument list and selects none @@ -506,23 +544,30 @@ check_for_unicode(_,L) ->  % Call as process_parameters([],0,false,index,NeedClean) -process_parameters([],InitialOffset, SelectReturn, ConvertReturn,_) -> +process_parameters([],InitialOffset, SelectReturn, ConvertReturn,_,_) ->      {[], InitialOffset, SelectReturn, ConvertReturn}; -process_parameters([{offset, N} | T],_Init0,Select0,Return0,CC) -> -    process_parameters(T,N,Select0,Return0,CC); -process_parameters([global | T],Init0,Select0,Return0,CC) -> -    process_parameters(T,Init0,Select0,Return0,CC); -process_parameters([{capture,Values,Type}|T],Init0,Select0,_Return0,CC) -> -    process_parameters([{capture,Values}|T],Init0,Select0,Type,CC); -process_parameters([{capture,Values}|T],Init0,Select0,Return0,CC) -> +process_parameters([{offset, N} | T],_Init0,Select0,Return0,CC,RE) -> +    process_parameters(T,N,Select0,Return0,CC,RE); +process_parameters([global | T],Init0,Select0,Return0,CC,RE) -> +    process_parameters(T,Init0,Select0,Return0,CC,RE); +process_parameters([{capture,Values,Type}|T],Init0,Select0,_Return0,CC,RE) -> +    process_parameters([{capture,Values}|T],Init0,Select0,Type,CC,RE); +process_parameters([{capture,Values}|T],Init0,Select0,Return0,CC,RE) ->      % First process the rest to see if capture was already present      {NewTail, Init1, Select1, Return1} =  -	process_parameters(T,Init0,Select0,Return0,CC), +	process_parameters(T,Init0,Select0,Return0,CC,RE),      case Select1 of  	false ->  	    case Values of  		all ->  		    {[{capture,all} | NewTail], Init1, all, Return0};  +		all_names -> +		    case re:inspect(RE,namelist) of +			{namelist, []} -> +			    {[{capture,first} | NewTail], Init1, none, Return0}; +			{namelist, List} -> +			    {[{capture,[0|List]} | NewTail], Init1, stripfirst, Return0} +		    end;   		first ->  		    {[{capture,first} | NewTail], Init1, all, Return0};  		all_but_first -> @@ -541,20 +586,20 @@ process_parameters([{capture,Values}|T],Init0,Select0,Return0,CC) ->  	    % Found overriding further down list, ignore this one  	    {NewTail, Init1, Select1, Return1}      end; -process_parameters([H|T],Init0,Select0,Return0,true) -> +process_parameters([H|T],Init0,Select0,Return0,true,RE) ->      case copt(H) of  	true -> -	    process_parameters(T,Init0,Select0,Return0,true); +	    process_parameters(T,Init0,Select0,Return0,true,RE);  	false ->  	    {NewT,Init,Select,Return} = -		process_parameters(T,Init0,Select0,Return0,true),	 +		process_parameters(T,Init0,Select0,Return0,true,RE),	  	    {[H|NewT],Init,Select,Return}      end; -process_parameters([H|T],Init0,Select0,Return0,false) -> +process_parameters([H|T],Init0,Select0,Return0,false,RE) ->      {NewT,Init,Select,Return} = -		process_parameters(T,Init0,Select0,Return0,false), +		process_parameters(T,Init0,Select0,Return0,false,RE),      {[H|NewT],Init,Select,Return}; -process_parameters(_,_,_,_,_) -> +process_parameters(_,_,_,_,_,_) ->      throw(badlist).  postprocess({match,[]},_,_,_,_) -> @@ -662,7 +707,7 @@ urun2(Subject0,RE0,Options0) ->      RE = case RE0 of  	     BinRE when is_binary(BinRE) ->  		 BinRE; -	     {re_pattern,_,_,_} = ReCompiled -> +	     {re_pattern,_,_,_,_} = ReCompiled ->  		 ReCompiled;  	     ListRE ->  		 unicode:characters_to_binary(ListRE,unicode) @@ -703,38 +748,46 @@ grun(Subject,RE,{Options,NeedClean,OrigRE}) ->  grun2(Subject,RE,{Options,NeedClean}) ->      Unicode = check_for_unicode(RE,Options), +    CRLF = check_for_crlf(RE,Options),      FlatSubject = to_binary(Subject, Unicode), -    do_grun(FlatSubject,Subject,Unicode,RE,{Options,NeedClean}). +    do_grun(FlatSubject,Subject,Unicode,CRLF,RE,{Options,NeedClean}). -do_grun(FlatSubject,Subject,Unicode,RE,{Options0,NeedClean}) -> +do_grun(FlatSubject,Subject,Unicode,CRLF,RE,{Options0,NeedClean}) ->      {StrippedOptions, InitialOffset,       SelectReturn, ConvertReturn} =   	case (catch  -		  process_parameters(Options0, 0, false, index, NeedClean)) of +		  process_parameters(Options0, 0, false, index, NeedClean,RE)) of  	    badlist ->  		erlang:error(badarg,[Subject,RE,Options0]);  	    CorrectReturn ->  		CorrectReturn  	end, -    postprocess(loopexec(FlatSubject,RE,InitialOffset, -			 byte_size(FlatSubject), -			 Unicode,StrippedOptions), -		SelectReturn,ConvertReturn,FlatSubject,Unicode). +    try +	postprocess(loopexec(FlatSubject,RE,InitialOffset, +			     byte_size(FlatSubject), +			     Unicode,CRLF,StrippedOptions), +		    SelectReturn,ConvertReturn,FlatSubject,Unicode) +    catch +	throw:ErrTuple -> +	    ErrTuple +    end. -loopexec(_,_,X,Y,_,_) when X > Y -> +loopexec(_,_,X,Y,_,_,_) when X > Y ->      {match,[]}; -loopexec(Subject,RE,X,Y,Unicode,Options) -> +loopexec(Subject,RE,X,Y,Unicode,CRLF,Options) ->      case re:run(Subject,RE,[{offset,X}]++Options) of +	{error, Err} -> +	    throw({error,Err});  	nomatch ->  	    {match,[]};  	{match,[{A,B}|More]} ->  	    {match,Rest} =   		case B>0 of  		    true -> -			loopexec(Subject,RE,A+B,Y,Unicode,Options); +			loopexec(Subject,RE,A+B,Y,Unicode,CRLF,Options);  		    false ->  			{match,M} =  -			    case re:run(Subject,RE,[{offset,X},notempty, +			    case re:run(Subject,RE,[{offset,X},notempty_atstart,  						anchored]++Options) of  				nomatch ->  				    {match,[]}; @@ -745,10 +798,10 @@ loopexec(Subject,RE,X,Y,Unicode,Options) ->  				   [{_,NStep}|_] when NStep > 0 ->  				       A+NStep;  				   _ -> -				       forward(Subject,A,1,Unicode) +				       forward(Subject,A,1,Unicode,CRLF)  			       end,  			{match,MM} = loopexec(Subject,RE,NewA,Y, -					      Unicode,Options), +					      Unicode,CRLF,Options),  			case M of   			    [] ->  				{match,MM}; @@ -759,11 +812,22 @@ loopexec(Subject,RE,X,Y,Unicode,Options) ->  	    {match,[[{A,B}|More] | Rest]}      end. -forward(_Chal,A,0,_) -> +forward(_Chal,A,0,_,_) ->      A; -forward(_Chal,A,N,false) -> -    A+N; -forward(Chal,A,N,true) -> +forward(Chal,A,N,U,true) -> +    <<_:A/binary,Tl/binary>> = Chal, +    case Tl of +	<<$\r,$\n,_/binary>> -> +	    forward(Chal,A+2,N-1,U,true); +	_ ->  +	    forward2(Chal,A,N,U,true) +    end; +forward(Chal,A,N,U,false) -> +    forward2(Chal,A,N,U,false). + +forward2(Chal,A,N,false,CRLF) -> +    forward(Chal,A+1,N-1,false,CRLF); +forward2(Chal,A,N,true,CRLF) ->      <<_:A/binary,Tl/binary>> = Chal,      Forw = case Tl of  	       <<1:1,1:1,0:1,_:5,_/binary>>  -> @@ -775,10 +839,16 @@ forward(Chal,A,N,true) ->  	       _ ->  		   1  	   end, -    forward(Chal,A+Forw,N-1,true). +    forward(Chal,A+Forw,N-1,true,CRLF).  copt(caseless) ->      true; +copt(no_start_optimize) -> +    true; +copt(never_utf) -> +    true; +copt(ucp) -> +    true;  copt(dollar_endonly) ->      true;  copt(dotall) -> @@ -809,6 +879,8 @@ copt(_) ->  runopt(notempty) ->      true; +runopt(notempty_atstart) -> +    true;  runopt(notbol) ->      true;  runopt(noteol) -> @@ -821,6 +893,10 @@ runopt({capture,_}) ->      true;  runopt(global) ->      true; +runopt({match_limit,_}) -> +    true; +runopt({match_limit_recursion,_}) -> +    true;  runopt(_) ->      false. diff --git a/lib/stdlib/src/sets.erl b/lib/stdlib/src/sets.erl index e6f05b71d4..ebf011a7d9 100644 --- a/lib/stdlib/src/sets.erl +++ b/lib/stdlib/src/sets.erl @@ -1,8 +1,7 @@ -%% -*- coding: utf-8 -*-  %%  %% %CopyrightBegin%  %%  -%% Copyright Ericsson AB 2000-2012. All Rights Reserved. +%% Copyright Ericsson AB 2000-2013. 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 diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index c6c706c3a7..0d2fc47d13 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -58,7 +58,7 @@ start(NoCtrlG) ->      start(NoCtrlG, false).  start(NoCtrlG, StartSync) -> -    code:ensure_loaded(user_default), +    _ = code:ensure_loaded(user_default),      spawn(fun() -> server(NoCtrlG, StartSync) end).  %% Find the pid of the current evaluator process. @@ -677,8 +677,10 @@ exprs([E0|Es], Bs1, RT, Lf, Ef, Bs0, W) ->              if                  Es =:= [] ->                      VS = pp(V0, 1, RT), -                    [io:requests([{put_chars, unicode, VS}, nl]) || -                        W =:= cmd], +                    case W of +                        cmd -> io:requests([{put_chars, unicode, VS}, nl]); +                        pmt -> ok +                    end,                      %% Don't send the result back if it will be                      %% discarded anyway.                      V = if diff --git a/lib/stdlib/src/slave.erl b/lib/stdlib/src/slave.erl index 9c74041f56..3e647635bc 100644 --- a/lib/stdlib/src/slave.erl +++ b/lib/stdlib/src/slave.erl @@ -289,7 +289,8 @@ register_unique_name(Number) ->  %% If the node should run on the local host, there is  %% no need to use rsh. -mk_cmd(Host, Name, Args, Waiter, Prog) -> +mk_cmd(Host, Name, Args, Waiter, Prog0) -> +    Prog = quote_progname(Prog0),      BasicCmd = lists:concat([Prog,  			     " -detached -noinput -master ", node(),  			     " ", long_or_short(), Name, "@", Host, @@ -309,6 +310,31 @@ mk_cmd(Host, Name, Args, Waiter, Prog) ->  	    end      end. +%% This is an attempt to distinguish between spaces in the program +%% path and spaces that separate arguments. The program is quoted to +%% allow spaces in the path. +%% +%% Arguments could exist either if the executable is excplicitly given +%% (through start/5) or if the -program switch to beam is used and +%% includes arguments (typically done by cerl in OTP test environment +%% in order to ensure that slave/peer nodes are started with the same +%% emulator and flags as the test node. The return from lib:progname() +%% could then typically be '/<full_path_to>/cerl -gcov'). +quote_progname(Progname) -> +    do_quote_progname(string:tokens(to_list(Progname)," ")). + +do_quote_progname([Prog]) -> +    "\""++Prog++"\""; +do_quote_progname([Prog,Arg|Args]) -> +    case os:find_executable(Prog) of +	false -> +	    do_quote_progname([Prog++" "++Arg | Args]); +	_ -> +	    %% this one has an executable - we assume the rest are arguments +	    "\""++Prog++"\""++ +		lists:flatten(lists:map(fun(X) -> [" ",X] end, [Arg|Args])) +    end. +  %% Give the user an opportunity to run another program,  %% than the "rsh".  On HP-UX rsh is called remsh; thus HP users  %% must start erlang as erl -rsh remsh. diff --git a/lib/stdlib/src/stdlib.appup.src b/lib/stdlib/src/stdlib.appup.src index 55c8087475..4c828e4434 100644 --- a/lib/stdlib/src/stdlib.appup.src +++ b/lib/stdlib/src/stdlib.appup.src @@ -1,7 +1,7 @@  %% -*- erlang -*-  %% %CopyrightBegin%  %% -%% Copyright Ericsson AB 1999-2011. All Rights Reserved. +%% Copyright Ericsson AB 1999-2013. 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 @@ -17,11 +17,11 @@  %% %CopyrightEnd%  {"%VSN%",   %% Up from - max two major revisions back - [{<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R16 -  {<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R15 -  {<<"1\\.17(\\.[0-9]+)*">>,[restart_new_emulator]}],%% R14 + [{<<"1\\.20(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R17 +  {<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R16 +  {<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}],%% R15   %% Down to - max two major revisions back - [{<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R16 -  {<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R15 -  {<<"1\\.17(\\.[0-9]+)*">>,[restart_new_emulator]}] %% R14 + [{<<"1\\.20(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R17 +  {<<"1\\.19(\\.[0-9]+)*">>,[restart_new_emulator]}, %% R16 +  {<<"1\\.18(\\.[0-9]+)*">>,[restart_new_emulator]}] %% R15  }. diff --git a/lib/stdlib/src/string.erl b/lib/stdlib/src/string.erl index d0bd0cb26e..f9b083a56d 100644 --- a/lib/stdlib/src/string.erl +++ b/lib/stdlib/src/string.erl @@ -1,4 +1,3 @@ -%% -*- coding: utf-8 -*-  %%  %% %CopyrightBegin%  %%  diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl index 6d8e25b1de..d18387568d 100644 --- a/lib/stdlib/src/supervisor.erl +++ b/lib/stdlib/src/supervisor.erl @@ -260,7 +260,7 @@ init_children(State, StartSpec) ->                  {ok, NChildren} ->                      {ok, State#state{children = NChildren}};                  {error, NChildren, Reason} -> -                    terminate_children(NChildren, SupName), +                    _ = terminate_children(NChildren, SupName),                      {stop, {shutdown, Reason}}              end;          Error -> @@ -752,10 +752,16 @@ restart(Child, State) ->  		    Id = if ?is_simple(State) -> Child#child.pid;  			    true -> Child#child.name  			 end, -		    timer:apply_after(0,?MODULE,try_again_restart,[self(),Id]), +		    {ok, _TRef} = timer:apply_after(0, +                                                    ?MODULE, +                                                    try_again_restart, +                                                    [self(),Id]),  		    {ok,NState2};  		{try_again, NState2, #child{name=ChName}} -> -		    timer:apply_after(0,?MODULE,try_again_restart,[self(),ChName]), +		    {ok, _TRef} = timer:apply_after(0, +						    ?MODULE, +						    try_again_restart, +						    [self(),ChName]),  		    {ok,NState2};  		Other ->  		    Other @@ -850,7 +856,7 @@ terminate_children(Children, SupName) ->  %% we do want them to be shut down as many functions from this module  %% use this function to just clear everything.  terminate_children([Child = #child{restart_type=temporary} | Children], SupName, Res) -> -    do_terminate(Child, SupName), +    _ = do_terminate(Child, SupName),      terminate_children(Children, SupName, Res);  terminate_children([Child | Children], SupName, Res) ->      NChild = do_terminate(Child, SupName), @@ -1008,7 +1014,7 @@ wait_dynamic_children(_Child, _Pids, 0, undefined, EStack) ->  wait_dynamic_children(_Child, _Pids, 0, TRef, EStack) ->  	%% If the timer has expired before its cancellation, we must empty the  	%% mail-box of the 'timeout'-message. -    erlang:cancel_timer(TRef), +    _ = erlang:cancel_timer(TRef),      receive          {timeout, TRef, kill} ->              EStack diff --git a/lib/stdlib/src/sys.erl b/lib/stdlib/src/sys.erl index c186eab940..04f8dfb61b 100644 --- a/lib/stdlib/src/sys.erl +++ b/lib/stdlib/src/sys.erl @@ -317,10 +317,10 @@ handle_system_msg(Msg, From, Parent, Mod, Debug, Misc, Hib) ->  handle_system_msg(SysState, Msg, From, Parent, Mod, Debug, Misc, Hib) ->      case do_cmd(SysState, Msg, Parent, Mod, Debug, Misc) of  	{suspended, Reply, NDebug, NMisc} -> -	    gen:reply(From, Reply), +	    _ = gen:reply(From, Reply),  	    suspend_loop(suspended, Parent, Mod, NDebug, NMisc, Hib);  	{running, Reply, NDebug, NMisc} -> -	    gen:reply(From, Reply), +	    _ = gen:reply(From, Reply),              Mod:system_continue(Parent, NDebug, NMisc)      end. diff --git a/lib/stdlib/src/timer.erl b/lib/stdlib/src/timer.erl index 3cf358630f..72a2dd9616 100644 --- a/lib/stdlib/src/timer.erl +++ b/lib/stdlib/src/timer.erl @@ -258,7 +258,7 @@ ensure_started() ->  	undefined ->   	    C = {timer_server, {?MODULE, start_link, []}, permanent, 1000,   		 worker, [?MODULE]}, -	    supervisor:start_child(kernel_safe_sup, C),  % kernel_safe_sup +	    _ = supervisor:start_child(kernel_safe_sup, C),  	    ok;  	_ -> ok      end. | 
