diff options
Diffstat (limited to 'lib/stdlib/src')
| -rw-r--r-- | lib/stdlib/src/dets.erl | 4 | ||||
| -rw-r--r-- | lib/stdlib/src/digraph.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/src/edlin.erl | 30 | ||||
| -rw-r--r-- | lib/stdlib/src/erl_lint.erl | 47 | ||||
| -rw-r--r-- | lib/stdlib/src/filelib.erl | 23 | ||||
| -rw-r--r-- | lib/stdlib/src/gen_server.erl | 4 | ||||
| -rw-r--r-- | lib/stdlib/src/io.erl | 2 | ||||
| -rw-r--r-- | lib/stdlib/src/io_lib.erl | 9 | ||||
| -rw-r--r-- | lib/stdlib/src/io_lib_fread.erl | 9 | 
9 files changed, 87 insertions, 43 deletions
diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl index 50812cc532..68b157c13c 100644 --- a/lib/stdlib/src/dets.erl +++ b/lib/stdlib/src/dets.erl @@ -951,10 +951,10 @@ do_trav(Proc, Acc, Fun) ->  	    Error      end. -do_trav(#dets_cont{bin = eof}, _Proc, Acc, _Fun) -> -    Acc;  do_trav(State, Proc, Acc, Fun) ->      case req(Proc, {match_init, State, safe}) of +        '$end_of_table'-> +            Acc;  	{cont, {Bins, NewState}} ->  	    do_trav_bins(NewState, Proc, Acc, Fun, lists:reverse(Bins));  	Error -> diff --git a/lib/stdlib/src/digraph.erl b/lib/stdlib/src/digraph.erl index e3f87d2c57..78f74631dc 100644 --- a/lib/stdlib/src/digraph.erl +++ b/lib/stdlib/src/digraph.erl @@ -36,7 +36,7 @@  -export([get_short_path/3, get_short_cycle/2]). --export_type([digraph/0, d_type/0, vertex/0]). +-export_type([digraph/0, d_type/0, vertex/0, edge/0]).  -record(digraph, {vtab = notable :: ets:tab(),  		  etab = notable :: ets:tab(), diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl index 3192879f09..f5998c54fd 100644 --- a/lib/stdlib/src/edlin.erl +++ b/lib/stdlib/src/edlin.erl @@ -79,6 +79,14 @@ edit([C|Cs], P, {Bef,Aft}, Prefix, Rs0) ->      case key_map(C, Prefix) of  	meta ->  	    edit(Cs, P, {Bef,Aft}, meta, Rs0); +    meta_o -> +        edit(Cs, P, {Bef,Aft}, meta_o, Rs0); +    meta_csi -> +        edit(Cs, P, {Bef,Aft}, meta_csi, Rs0); +    meta_meta -> +        edit(Cs, P, {Bef,Aft}, meta_meta, Rs0); +    {csi, _} = Csi -> +        edit(Cs, P, {Bef,Aft}, Csi, Rs0);  	meta_left_sq_bracket ->  	    edit(Cs, P, {Bef,Aft}, meta_left_sq_bracket, Rs0);  	search_meta -> @@ -178,6 +186,7 @@ key_map($\^U, none) -> ctlu;  key_map($\^], none) -> auto_blink;  key_map($\^X, none) -> ctlx;  key_map($\^Y, none) -> yank; +key_map($\^W, none) -> backward_kill_word;  key_map($\e, none) -> meta;  key_map($), Prefix) when Prefix =/= meta,                           Prefix =/= search, @@ -198,11 +207,29 @@ key_map($d, meta) -> kill_word;  key_map($f, meta) -> forward_word;  key_map($t, meta) -> transpose_word;  key_map($y, meta) -> yank_pop; +key_map($O, meta) -> meta_o; +key_map($H, meta_o) -> beginning_of_line; +key_map($F, meta_o) -> end_of_line;  key_map($\177, none) -> backward_delete_char;  key_map($\177, meta) -> backward_kill_word;  key_map($[, meta) -> meta_left_sq_bracket;  key_map($D, meta_left_sq_bracket) -> backward_char;  key_map($C, meta_left_sq_bracket) -> forward_char; +% support a few <CTRL>+<CURSOR LEFT|RIGHT> combinations... +%  - forward:  \e\e[C, \e[5C, \e[1;5C +%  - backward: \e\e[D, \e[5D, \e[1;5D +key_map($\e, meta) -> meta_meta; +key_map($[, meta_meta) -> meta_csi; +key_map($C, meta_csi) -> forward_word; +key_map($D, meta_csi) -> backward_word; +key_map($1, meta_left_sq_bracket) -> {csi, "1"}; +key_map($5, meta_left_sq_bracket) -> {csi, "5"}; +key_map($5, {csi, "1;"}) -> {csi, "1;5"}; +key_map($C, {csi, "5"}) -> forward_word; +key_map($C, {csi, "1;5"}) -> forward_word; +key_map($D, {csi, "5"})  -> backward_word; +key_map($D, {csi, "1;5"}) -> backward_word; +key_map($;, {csi, "1"}) -> {csi, "1;"};  key_map(C, none) when C >= $\s ->      {insert,C};  %% for search, we need smarter line handling and so @@ -363,6 +390,9 @@ do_op(end_of_line, Bef, [C|Aft], Rs) ->      {{reverse(Aft, [C|Bef]),[]},[{move_rel,length(Aft)+1}|Rs]};  do_op(end_of_line, Bef, [], Rs) ->      {{Bef,[]},Rs}; +do_op(ctlu, Bef, Aft, Rs) -> +    put(kill_buffer, Bef), +    {{[], Aft}, [{delete_chars, -length(Bef)} | Rs]};  do_op(beep, Bef, Aft, Rs) ->      {{Bef,Aft},[beep|Rs]};  do_op(_, Bef, Aft, Rs) -> diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 08b8541014..f599881c07 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -1953,12 +1953,10 @@ expr({string,_Line,_S}, _Vt, St) -> {[],St};  expr({nil,_Line}, _Vt, St) -> {[],St};  expr({cons,_Line,H,T}, Vt, St) ->      expr_list([H,T], Vt, St); -expr({lc,_Line,E,Qs}, Vt0, St0) -> -    {Vt,St} = handle_comprehension(E, Qs, Vt0, St0), -    {vtold(Vt, Vt0),St};                      %Don't export local variables -expr({bc,_Line,E,Qs}, Vt0, St0) -> -    {Vt,St} = handle_comprehension(E, Qs, Vt0, St0), -    {vtold(Vt,Vt0),St};			 %Don't export local variables +expr({lc,_Line,E,Qs}, Vt, St) -> +    handle_comprehension(E, Qs, Vt, St); +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({record_index,Line,Name,Field}, _Vt, St) -> @@ -2012,8 +2010,7 @@ expr({'fun',Line,Body}, Vt, St) ->      %%No one can think funs export!      case Body of          {clauses,Cs} -> -            {Bvt, St1} = fun_clauses(Cs, Vt, St), -            {vtupdate(Bvt, Vt), St1}; +            fun_clauses(Cs, Vt, St);          {function,F,A} ->  	    %% BifClash - Fun expression              %% N.B. Only allows BIFs here as well, NO IMPORTS!! @@ -2111,12 +2108,12 @@ expr({'try',Line,Es,Scs,Ccs,As}, Vt, St0) ->      {Evt0,St1} = exprs(Es, Vt, St0),      TryLine = {'try',Line},      Uvt = vtunsafe(vtnames(vtnew(Evt0, Vt)), TryLine, []), -    Evt1 = vtupdate(Uvt, vtupdate(Evt0, Vt)), -    {Sccs,St2} = icrt_clauses(Scs++Ccs, TryLine, Evt1, St1), +    Evt1 = vtupdate(Uvt, vtsubtract(Evt0, Uvt)), +    {Sccs,St2} = icrt_clauses(Scs++Ccs, TryLine, vtupdate(Evt1, Vt), St1),      Rvt0 = Sccs,      Rvt1 = vtupdate(vtunsafe(vtnames(vtnew(Rvt0, Vt)), TryLine, []), Rvt0),      Evt2 = vtmerge(Evt1, Rvt1), -    {Avt0,St} = exprs(As, Evt2, St2), +    {Avt0,St} = exprs(As, vtupdate(Evt2, Vt), St2),      Avt1 = vtupdate(vtunsafe(vtnames(vtnew(Avt0, Vt)), TryLine, []), Avt0),      Avt = vtmerge(Evt2, Avt1),      {Avt,St}; @@ -2150,10 +2147,11 @@ expr({remote,Line,_M,_F}, _Vt, St) ->  %%      {UsedVarTable,State}  expr_list(Es, Vt, St) -> -    foldl(fun (E, {Esvt,St0}) -> -                  {Evt,St1} = expr(E, Vt, St0), -                  {vtmerge(Evt, Esvt),St1} -          end, {[],St}, Es). +    {Vt1,St1} = foldl(fun (E, {Esvt,St0}) -> +                              {Evt,St1} = expr(E, Vt, St0), +                              {vtmerge_pat(Evt, Esvt),St1} +                      end, {[],St}, Es), +    {vtmerge(vtnew(Vt1, Vt), vtold(Vt1, Vt)),St1}.  record_expr(Line, Rec, Vt, St0) ->      St1 = warn_invalid_record(Line, Rec, St0), @@ -2310,7 +2308,7 @@ check_fields(Fs, Name, Fields, Vt, St0, CheckFun) ->  check_field({record_field,Lf,{atom,La,F},Val}, Name, Fields,              Vt, St, Sfs, CheckFun) ->      case member(F, Sfs) of -        true -> {Sfs,{Vt,add_error(Lf, {redefine_field,Name,F}, St)}}; +        true -> {Sfs,{[],add_error(Lf, {redefine_field,Name,F}, St)}};          false ->              {[F|Sfs],               case find_field(F, Fields) of @@ -2843,7 +2841,9 @@ icrt_export(Csvt, Vt, In, St) ->      Uvt = vtmerge(Evt, Unused),      %% Make exported and unsafe unused variables unused in subsequent code:      Vt2 = vtmerge(Uvt, vtsubtract(Vt1, Uvt)), -    {Vt2,St}. +    %% Forget about old variables which were not used: +    Vt3 = vtmerge(vtnew(Vt2, Vt), vt_no_unused(vtold(Vt2, Vt))), +    {Vt3,St}.  handle_comprehension(E, Qs, Vt0, St0) ->      {Vt1, Uvt, St1} = lc_quals(Qs, Vt0, St0), @@ -2856,7 +2856,11 @@ handle_comprehension(E, Qs, Vt0, St0) ->      %% Local variables that have not been shadowed.      {_,St} = check_unused_vars(Vt2, Vt0, St4),      Vt3 = vtmerge(vtsubtract(Vt2, Uvt), Uvt), -    {Vt3,St}. +    %% Don't export local variables. +    Vt4 = vtold(Vt3, Vt0), +    %% Forget about old variables which were not used. +    Vt5 = vt_no_unused(Vt4), +    {Vt5,St}.  %% lc_quals(Qualifiers, ImportVarTable, State) ->  %%      {VarTable,ShadowedVarTable,State} @@ -2920,7 +2924,7 @@ fun_clauses(Cs, Vt, St) ->                                {Cvt,St1} = fun_clause(C, Vt, St0),                                {vtmerge(Cvt, Bvt0),St1}                        end, {[],St#lint{recdef_top = false}}, Cs), -    {Bvt,St2#lint{recdef_top = OldRecDef}}. +    {vt_no_unused(vtold(Bvt, Vt)),St2#lint{recdef_top = OldRecDef}}.  fun_clause({clause,_Line,H,G,B}, Vt0, St0) ->      {Hvt,Binvt,St1} = head(H, Vt0, [], St0), % No imported pattern variables @@ -3181,6 +3185,8 @@ vt_no_unsafe(Vt) -> [V || {_,{S,_U,_L}}=V <- Vt,                                _ -> true                            end]. +vt_no_unused(Vt) -> [V || {_,{_,U,_L}}=V <- Vt, U =/= unused]. +  %% vunion(VarTable1, VarTable2) -> [VarName].  %% vunion([VarTable]) -> [VarName].  %% vintersection(VarTable1, VarTable2) -> [VarName]. @@ -3219,7 +3225,8 @@ modify_line(T, F0) ->  %% Forms.  modify_line1({function,F,A}, _Mf) -> {function,F,A}; -modify_line1({function,M,F,A}, _Mf) -> {function,M,F,A}; +modify_line1({function,M,F,A}, Mf) -> +    {function,modify_line1(M, Mf),modify_line1(F, Mf),modify_line1(A, Mf)};  modify_line1({attribute,L,record,{Name,Fields}}, Mf) ->      {attribute,Mf(L),record,{Name,modify_line1(Fields, Mf)}};  modify_line1({attribute,L,spec,{Fun,Types}}, Mf) -> diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl index 42ef3679a2..9ef4954194 100644 --- a/lib/stdlib/src/filelib.erl +++ b/lib/stdlib/src/filelib.erl @@ -41,6 +41,9 @@  -type filename() :: file:name().  -type dirname() :: filename(). +-type filename_all() :: file:name_all(). +-type dirname_all() :: filename_all(). +  %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%  -spec wildcard(Wildcard) -> [file:filename()] when @@ -62,29 +65,29 @@ wildcard(Pattern, Cwd, Mod)      ?HANDLE_ERROR(do_wildcard(Pattern, Cwd, Mod)).  -spec is_dir(Name) -> boolean() when -      Name :: filename() | dirname(). +      Name :: filename_all() | dirname_all().  is_dir(Dir) ->      do_is_dir(Dir, file). --spec is_dir(file:name(), atom()) -> boolean(). +-spec is_dir(file:name_all(), atom()) -> boolean().  is_dir(Dir, Mod) when is_atom(Mod) ->      do_is_dir(Dir, Mod).  -spec is_file(Name) -> boolean() when -      Name :: filename() | dirname(). +      Name :: filename_all() | dirname_all().  is_file(File) ->      do_is_file(File, file). --spec is_file(file:name(), atom()) -> boolean(). +-spec is_file(file:name_all(), atom()) -> boolean().  is_file(File, Mod) when is_atom(Mod) ->      do_is_file(File, Mod).  -spec is_regular(Name) -> boolean() when -      Name :: filename(). +      Name :: filename_all().  is_regular(File) ->      do_is_regular(File, file). --spec is_regular(file:name(), atom()) -> boolean(). +-spec is_regular(file:name_all(), atom()) -> boolean().  is_regular(File, Mod) when is_atom(Mod) ->      do_is_regular(File, Mod). @@ -103,16 +106,16 @@ fold_files(Dir, RegExp, Recursive, Fun, Acc, Mod) when is_atom(Mod) ->      do_fold_files(Dir, RegExp, Recursive, Fun, Acc, Mod).  -spec last_modified(Name) -> file:date_time() | 0 when -      Name :: filename() | dirname(). +      Name :: filename_all() | dirname_all().  last_modified(File) ->      do_last_modified(File, file). --spec last_modified(file:name(), atom()) -> file:date_time() | 0. +-spec last_modified(file:name_all(), atom()) -> file:date_time() | 0.  last_modified(File, Mod) when is_atom(Mod) ->      do_last_modified(File, Mod).  -spec file_size(Filename) -> non_neg_integer() when -      Filename :: filename(). +      Filename :: filename_all().  file_size(File) ->      do_file_size(File, file). @@ -218,7 +221,7 @@ do_file_size(File, Mod) ->  %% ensures that the directory name required to create D exists  -spec ensure_dir(Name) -> 'ok' | {'error', Reason} when -      Name :: filename() | dirname(), +      Name :: filename_all() | dirname_all(),        Reason :: file:posix().  ensure_dir("/") ->      ok; diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index bc76c9fd10..7f65131f67 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -124,7 +124,7 @@      {noreply, NewState :: term()} |      {noreply, NewState :: term(), timeout() | hibernate} |      {stop, Reason :: term(), NewState :: term()}. --callback handle_info(Info :: timeout() | term(), State :: term()) -> +-callback handle_info(Info :: timeout | term(), State :: term()) ->      {noreply, NewState :: term()} |      {noreply, NewState :: term(), timeout() | hibernate} |      {stop, Reason :: term(), NewState :: term()}. @@ -217,7 +217,7 @@ reply({To, Tag}, Reply) ->      catch To ! {Tag, Reply}.  %% -----------------------------------------------------------------  -%% Asyncronous broadcast, returns nothing, it's just send'n prey +%% Asynchronous broadcast, returns nothing, it's just send 'n' pray  %%-----------------------------------------------------------------    abcast(Name, Request) when is_atom(Name) ->      do_abcast([node() | nodes()], Name, cast_msg(Request)). diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl index 53728237ca..b11d41e2eb 100644 --- a/lib/stdlib/src/io.erl +++ b/lib/stdlib/src/io.erl @@ -40,7 +40,7 @@  %%-------------------------------------------------------------------------  -type device() :: atom() | pid(). --type prompt() :: atom() | string(). +-type prompt() :: atom() | unicode:chardata().  %% ErrorDescription is whatever the I/O-server sends.  -type server_no_data() :: {'error', ErrorDescription :: term()} | 'eof'. diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index a9b6d4131e..92a086b077 100644 --- a/lib/stdlib/src/io_lib.erl +++ b/lib/stdlib/src/io_lib.erl @@ -83,7 +83,8 @@  -export([write_unicode_string/1, write_unicode_char/1,           deep_unicode_char_list/1]). --export_type([chars/0, latin1_string/0, continuation/0, fread_error/0]). +-export_type([chars/0, latin1_string/0, continuation/0, +              fread_error/0, fread_item/0]).  %%---------------------------------------------------------------------- @@ -106,6 +107,8 @@                       | 'string'                       | 'unsigned'. +-type fread_item() :: string() | atom() | integer() | float(). +  %%----------------------------------------------------------------------  %% Interface calls to sub-modules. @@ -120,7 +123,7 @@ fwrite(Format, Args) ->  -spec fread(Format, String) -> Result when        Format :: string(),        String :: string(), -      Result :: {'ok', InputList :: [term()], LeftOverChars :: string()} +      Result :: {'ok', InputList :: [fread_item()], LeftOverChars :: string()}                | {'more', RestFormat :: string(),                   Nchars :: non_neg_integer(),                   InputStack :: chars()} @@ -135,7 +138,7 @@ fread(Chars, Format) ->        Format :: string(),        Return :: {'more', Continuation1 :: continuation()}                | {'done', Result, LeftOverChars :: string()}, -      Result :: {'ok', InputList :: [term()]} +      Result :: {'ok', InputList :: [fread_item()]}                | 'eof'                | {'error', {'fread', What :: fread_error()}}. diff --git a/lib/stdlib/src/io_lib_fread.erl b/lib/stdlib/src/io_lib_fread.erl index 92a34995b8..491e1f40d7 100644 --- a/lib/stdlib/src/io_lib_fread.erl +++ b/lib/stdlib/src/io_lib_fread.erl @@ -41,9 +41,9 @@        Format :: string(),        Return :: {'more', Continuation1 :: io_lib:continuation()}                | {'done', Result, LeftOverChars :: string()}, -      Result :: {'ok', InputList :: io_lib:chars()} +      Result :: {'ok', InputList :: [io_lib:fread_item()]}                | 'eof' -              | {'error', {'read', What :: io_lib:fread_error()}}. +              | {'error', {'fread', What :: io_lib:fread_error()}}.  fread([], Chars, Format) ->      %%io:format("FREAD: ~w `~s'~n", [Format,Chars]), @@ -101,11 +101,12 @@ fread_line(Format0, Line, N0, Results0, More, Newline) ->  -spec fread(Format, String) -> Result when        Format :: string(),        String :: string(), -      Result :: {'ok', InputList :: io_lib:chars(), LeftOverChars :: string()} +      Result :: {'ok', InputList :: [io_lib:fread_item()], +                 LeftOverChars :: string()}                | {'more', RestFormat :: string(),                   Nchars :: non_neg_integer(),                   InputStack :: io_lib:chars()} -              | {'error', What :: term()}. +              | {'error', {'fread', What :: io_lib:fread_error()}}.  fread(Format, Line) ->      fread(Format, Line, 0, []).  | 
