diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/edlin.erl | 5 | ||||
-rw-r--r-- | lib/stdlib/src/erl_parse.yrl | 2 | ||||
-rw-r--r-- | lib/stdlib/src/io.erl | 12 | ||||
-rw-r--r-- | lib/stdlib/src/io_lib.erl | 29 | ||||
-rw-r--r-- | lib/stdlib/src/io_lib_pretty.erl | 3 |
5 files changed, 7 insertions, 44 deletions
diff --git a/lib/stdlib/src/edlin.erl b/lib/stdlib/src/edlin.erl index f027d05f55..6078c5e67b 100644 --- a/lib/stdlib/src/edlin.erl +++ b/lib/stdlib/src/edlin.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2018. All Rights Reserved. +%% Copyright Ericsson AB 1996-2019. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -352,9 +352,6 @@ do_op({blink,C,M}, Bef=[$$,$$|_], Aft, Rs) -> %% don't blink after a $ do_op({blink,C,_}, Bef=[$$|_], Aft, Rs) -> do_op({insert,C}, Bef, Aft, Rs); -%do_op({blink,C,M}, Bef, [], Rs) -> -% N = over_paren(Bef, C, M), -% {blink,N+1,{[C|Bef],[]},[{move_rel,-(N+1)},{put_chars,[C]}|Rs]}; do_op({blink,C,M}, Bef, Aft, Rs) -> case over_paren(Bef, C, M) of beep -> diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 4ad94f2507..ca53f992f6 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -604,6 +604,8 @@ Erlang code. -export_type([abstract_clause/0, abstract_expr/0, abstract_form/0, abstract_type/0, form_info/0, error_info/0]). +%% The following types are exported because they are used by syntax_tools +-export_type([af_binelement/1, af_generator/0, af_remote_function/0]). %% Start of Abstract Format diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl index 63c9a6bddf..1848aa3628 100644 --- a/lib/stdlib/src/io.erl +++ b/lib/stdlib/src/io.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2018. All Rights Reserved. +%% Copyright Ericsson AB 1996-2019. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -106,7 +106,6 @@ nl() -> IoDevice :: device(). nl(Io) -> -% o_request(Io, {put_chars,io_lib:nl()}). o_request(Io, nl, nl). -spec columns() -> {'ok', pos_integer()} | {'error', 'enotsup'}. @@ -255,8 +254,6 @@ read(Io, Prompt) -> case request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[1]}) of {ok,Toks,_EndLine} -> erl_parse:parse_term(Toks); -% {error, Reason} when atom(Reason) -> -% erlang:error(conv_reason(read, Reason), [Io, Prompt]); {error,E,_EndLine} -> {error,E}; {eof,_EndLine} -> @@ -352,12 +349,7 @@ fread(Prompt, Format) -> | server_no_data(). fread(Io, Prompt, Format) -> - case request(Io, {fread,Prompt,Format}) of -% {error, Reason} when atom(Reason) -> -% erlang:error(conv_reason(fread, Reason), [Io, Prompt, Format]); - Other -> - Other - end. + request(Io, {fread,Prompt,Format}). -spec format(Format) -> 'ok' when Format :: format(). diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index 21d66c5529..e2823b70f2 100644 --- a/lib/stdlib/src/io_lib.erl +++ b/lib/stdlib/src/io_lib.erl @@ -78,7 +78,7 @@ %% Utilities for collecting characters. -export([collect_chars/3, collect_chars/4, - collect_line/2, collect_line/3, collect_line/4, + collect_line/3, collect_line/4, get_until/3, get_until/4]). %% The following functions were used by Yecc's include-file. @@ -851,6 +851,7 @@ collect_chars({binary,Stack,N}, Data,latin1, _) -> end; collect_chars({list,Stack,N}, Data, _,_) -> collect_chars_list(Stack, N, Data); + %% collect_chars(Continuation, MoreChars, Count) %% Returns: %% {done,Result,RestChars} @@ -881,32 +882,6 @@ collect_chars_list(Stack, N, []) -> collect_chars_list(Stack,N, [H|T]) -> collect_chars_list([H|Stack], N-1, T). -%% collect_line(Continuation, MoreChars) -%% Returns: -%% {done,Result,RestChars} -%% {more,Continuation} -%% -%% XXX Can be removed when compatibility with pre-R12B-5 nodes -%% is no longer required. -%% -collect_line([], Chars) -> - collect_line1(Chars, []); -collect_line({SoFar}, More) -> - collect_line1(More, SoFar). - -collect_line1([$\r, $\n|Rest], Stack) -> - collect_line1([$\n|Rest], Stack); -collect_line1([$\n|Rest], Stack) -> - {done,lists:reverse([$\n|Stack], []),Rest}; -collect_line1([C|Rest], Stack) -> - collect_line1(Rest, [C|Stack]); -collect_line1(eof, []) -> - {done,eof,[]}; -collect_line1(eof, Stack) -> - {done,lists:reverse(Stack, []),[]}; -collect_line1([], Stack) -> - {more,{Stack}}. - %% collect_line(State, Data, _). New in R9C. %% Returns: %% {stop,Result,RestData} diff --git a/lib/stdlib/src/io_lib_pretty.erl b/lib/stdlib/src/io_lib_pretty.erl index 77f02eafe0..838d412d0c 100644 --- a/lib/stdlib/src/io_lib_pretty.erl +++ b/lib/stdlib/src/io_lib_pretty.erl @@ -895,9 +895,6 @@ write_string(S, _Uni) -> io_lib:write_string(S, $"). %" expand({_, _, _Dots=0, no_more} = If, _T, _Dd) -> If; -%% expand({{list,L}, _Len, _, no_more}, T, Dd) -> -%% {NL, NLen, NDots} = expand_list(L, T, Dd, 2), -%% {{list,NL}, NLen, NDots, no_more}; expand({{tuple,IsTagged,L}, _Len, _, no_more}, T, Dd) -> {NL, NLen, NDots} = expand_list(L, T, Dd, 2), {{tuple,IsTagged,NL}, NLen, NDots, no_more}; |