aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/io.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/io.erl')
-rw-r--r--lib/stdlib/src/io.erl194
1 files changed, 132 insertions, 62 deletions
diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl
index 9f65bbfa3a..ecf2aeb375 100644
--- a/lib/stdlib/src/io.erl
+++ b/lib/stdlib/src/io.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2012. 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
@@ -22,28 +22,28 @@
get_chars/2,get_chars/3,get_line/1,get_line/2,
get_password/0, get_password/1,
setopts/1, setopts/2, getopts/0, getopts/1]).
--export([write/1,write/2,read/1,read/2,read/3]).
+-export([write/1,write/2,read/1,read/2,read/3,read/4]).
-export([columns/0,columns/1,rows/0,rows/1]).
-export([fwrite/1,fwrite/2,fwrite/3,fread/2,fread/3,
format/1,format/2,format/3]).
--export([scan_erl_exprs/1,scan_erl_exprs/2,scan_erl_exprs/3,
- scan_erl_form/1,scan_erl_form/2,scan_erl_form/3,
+-export([scan_erl_exprs/1,scan_erl_exprs/2,scan_erl_exprs/3,scan_erl_exprs/4,
+ scan_erl_form/1,scan_erl_form/2,scan_erl_form/3,scan_erl_form/4,
parse_erl_exprs/1,parse_erl_exprs/2,parse_erl_exprs/3,
- parse_erl_form/1,parse_erl_form/2,parse_erl_form/3]).
+ parse_erl_exprs/4,parse_erl_form/1,parse_erl_form/2,
+ parse_erl_form/3,parse_erl_form/4]).
-export([request/1,request/2,requests/1,requests/2]).
--export_type([device/0, format/0]).
+-export_type([device/0, format/0, server_no_data/0]).
%%-------------------------------------------------------------------------
-type device() :: atom() | pid().
-type prompt() :: atom() | string().
--type error_description() :: term(). % Whatever the io-server sends.
--type request_error() :: {'error',error_description()}.
+%% ErrorDescription is whatever the I/O-server sends.
+-type server_no_data() :: {'error', ErrorDescription :: term()} | 'eof'.
-%% XXX: Some uses of line() in this file may need to read erl_scan:location()
--type line() :: pos_integer().
+-type location() :: erl_scan:location().
%%-------------------------------------------------------------------------
@@ -73,9 +73,9 @@ o_request(Io, Request, Func) ->
put_chars(Chars) ->
put_chars(default_output(), Chars).
--spec put_chars(IoDevice, IoData) -> 'ok' when
+-spec put_chars(IoDevice, CharData) -> 'ok' when
IoDevice :: device(),
- IoData :: unicode:chardata().
+ CharData :: unicode:chardata().
put_chars(Io, Chars) ->
o_request(Io, {put_chars,unicode,Chars}, put_chars).
@@ -124,7 +124,7 @@ rows(Io) ->
{error,enotsup}
end.
--spec get_chars(Prompt, Count) -> Data | 'eof' when
+-spec get_chars(Prompt, Count) -> Data | server_no_data() when
Prompt :: prompt(),
Count :: non_neg_integer(),
Data :: [unicode:unicode_char()] | unicode:unicode_binary().
@@ -132,25 +132,23 @@ rows(Io) ->
get_chars(Prompt, N) ->
get_chars(default_input(), Prompt, N).
--spec get_chars(IoDevice, Prompt, Count) -> Data | 'eof' | {error, Reason} when
+-spec get_chars(IoDevice, Prompt, Count) -> Data | server_no_data() when
IoDevice :: device(),
Prompt :: prompt(),
Count :: non_neg_integer(),
- Reason :: term(),
Data :: [unicode:unicode_char()] | unicode:unicode_binary().
get_chars(Io, Prompt, N) when is_integer(N), N >= 0 ->
request(Io, {get_chars,unicode,Prompt,N}).
--spec get_line(Prompt) -> Data | 'eof' | {'error', Reason} when
+-spec get_line(Prompt) -> Data | server_no_data() when
Prompt :: prompt(),
- Reason :: term(),
Data :: [unicode:unicode_char()] | unicode:unicode_binary().
get_line(Prompt) ->
get_line(default_input(), Prompt).
--spec get_line(IoDevice, Prompt) -> Data | 'eof' | {'error', term()} when
+-spec get_line(IoDevice, Prompt) -> Data | server_no_data() when
IoDevice :: device(),
Prompt :: prompt(),
Data :: [unicode:unicode_char()] | unicode:unicode_binary().
@@ -219,8 +217,9 @@ write(Io, Term) ->
-spec read(Prompt) -> Result when
Prompt :: prompt(),
Result :: {'ok', Term :: term()}
- | 'eof'
- | {'error', ErrorInfo :: erl_scan:error_info()}.
+ | server_no_data()
+ | {'error', ErrorInfo},
+ ErrorInfo :: erl_scan:error_info() | erl_parse:error_info().
% Read does not use get_until as erl_scan does not work with unicode
% XXX:PaN fixme?
@@ -231,8 +230,9 @@ read(Prompt) ->
IoDevice :: device(),
Prompt :: prompt(),
Result :: {'ok', Term :: term()}
- | 'eof'
- | {'error', ErrorInfo :: erl_scan:error_info()}.
+ | server_no_data()
+ | {'error', ErrorInfo},
+ ErrorInfo :: erl_scan:error_info() | erl_parse:error_info().
read(Io, Prompt) ->
case request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[1]}) of
@@ -248,24 +248,41 @@ read(Io, Prompt) ->
Other
end.
--spec read(IoDevice, Prompt, StartLine) -> Result when
+-spec read(IoDevice, Prompt, StartLocation) -> Result when
+ IoDevice :: device(),
+ Prompt :: prompt(),
+ StartLocation :: location(),
+ Result :: {'ok', Term :: term(), EndLocation :: location()}
+ | {'eof', EndLocation :: location()}
+ | server_no_data()
+ | {'error', ErrorInfo, ErrorLocation :: location()},
+ ErrorInfo :: erl_scan:error_info() | erl_parse:error_info().
+
+read(Io, Prompt, Pos0) ->
+ read(Io, Prompt, Pos0, []).
+
+-spec read(IoDevice, Prompt, StartLocation, Options) -> Result when
IoDevice :: device(),
Prompt :: prompt(),
- StartLine :: line(),
- Result :: {'ok', Term :: term(), EndLine :: line()}
- | {'eof', EndLine :: line()}
- | {'error', ErrorInfo :: erl_scan:error_info(), ErrorLine :: line()}.
-
-read(Io, Prompt, StartLine) when is_integer(StartLine) ->
- case request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[StartLine]}) of
- {ok,Toks,EndLine} ->
+ StartLocation :: location(),
+ Options :: erl_scan:options(),
+ Result :: {'ok', Term :: term(), EndLocation :: location()}
+ | {'eof', EndLocation :: location()}
+ | server_no_data()
+ | {'error', ErrorInfo, ErrorLocation :: location()},
+ ErrorInfo :: erl_scan:error_info() | erl_parse:error_info().
+
+read(Io, Prompt, Pos0, Options) ->
+ Args = [Pos0,Options],
+ case request(Io, {get_until,unicode,Prompt,erl_scan,tokens,Args}) of
+ {ok,Toks,EndLocation} ->
case erl_parse:parse_term(Toks) of
- {ok,Term} -> {ok,Term,EndLine};
- {error,ErrorInfo} -> {error,ErrorInfo,EndLine}
+ {ok,Term} -> {ok,Term,EndLocation};
+ {error,ErrorInfo} -> {error,ErrorInfo,EndLocation}
end;
- {error,_E,_EndLine} = Error ->
+ {error,_E,_EndLocation} = Error ->
Error;
- {eof,_EndLine} = Eof ->
+ {eof,_EndLocation} = Eof ->
Eof;
Other ->
Other
@@ -313,7 +330,9 @@ fread(Prompt, Format) ->
IoDevice :: device(),
Prompt :: prompt(),
Format :: format(),
- Result :: {'ok', Terms :: [term()]} | 'eof' | {'error', What :: term()}.
+ Result :: {'ok', Terms :: [term()]}
+ | {'error', FreadError :: io_lib:fread_error()}
+ | server_no_data().
fread(Io, Prompt, Format) ->
case request(Io, {fread,Prompt,Format}) of
@@ -348,7 +367,7 @@ format(Io, Format, Args) ->
-spec scan_erl_exprs(Prompt) -> Result when
Prompt :: prompt(),
- Result :: erl_scan:tokens_result() | request_error().
+ Result :: erl_scan:tokens_result() | server_no_data().
scan_erl_exprs(Prompt) ->
scan_erl_exprs(default_input(), Prompt, 1).
@@ -356,23 +375,33 @@ scan_erl_exprs(Prompt) ->
-spec scan_erl_exprs(Device, Prompt) -> Result when
Device :: device(),
Prompt :: prompt(),
- Result :: erl_scan:tokens_result() | request_error().
+ Result :: erl_scan:tokens_result() | server_no_data().
scan_erl_exprs(Io, Prompt) ->
scan_erl_exprs(Io, Prompt, 1).
--spec scan_erl_exprs(Device, Prompt, StartLine) -> Result when
+-spec scan_erl_exprs(Device, Prompt, StartLocation) -> Result when
Device :: device(),
Prompt :: prompt(),
- StartLine :: line(),
- Result :: erl_scan:tokens_result() | request_error().
+ StartLocation :: location(),
+ Result :: erl_scan:tokens_result() | server_no_data().
scan_erl_exprs(Io, Prompt, Pos0) ->
- request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[Pos0]}).
+ scan_erl_exprs(Io, Prompt, Pos0, []).
+
+-spec scan_erl_exprs(Device, Prompt, StartLocation, Options) -> Result when
+ Device :: device(),
+ Prompt :: prompt(),
+ StartLocation :: location(),
+ Options :: erl_scan:options(),
+ Result :: erl_scan:tokens_result() | server_no_data().
+
+scan_erl_exprs(Io, Prompt, Pos0, Options) ->
+ request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[Pos0,Options]}).
-spec scan_erl_form(Prompt) -> Result when
Prompt :: prompt(),
- Result :: erl_scan:tokens_result() | request_error().
+ Result :: erl_scan:tokens_result() | server_no_data().
scan_erl_form(Prompt) ->
scan_erl_form(default_input(), Prompt, 1).
@@ -380,26 +409,41 @@ scan_erl_form(Prompt) ->
-spec scan_erl_form(IoDevice, Prompt) -> Result when
IoDevice :: device(),
Prompt :: prompt(),
- Result :: erl_scan:tokens_result() | request_error().
+ Result :: erl_scan:tokens_result() | server_no_data().
scan_erl_form(Io, Prompt) ->
scan_erl_form(Io, Prompt, 1).
--spec scan_erl_form(IoDevice, Prompt, StartLine) -> Result when
+-spec scan_erl_form(IoDevice, Prompt, StartLocation) -> Result when
IoDevice :: device(),
Prompt :: prompt(),
- StartLine :: line(),
- Result :: erl_scan:tokens_result() | request_error().
+ StartLocation :: location(),
+ Result :: erl_scan:tokens_result() | server_no_data().
scan_erl_form(Io, Prompt, Pos0) ->
- request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[Pos0]}).
+ scan_erl_form(Io, Prompt, Pos0, []).
+
+-spec scan_erl_form(IoDevice, Prompt, StartLocation, Options) -> Result when
+ IoDevice :: device(),
+ Prompt :: prompt(),
+ StartLocation :: location(),
+ Options :: erl_scan:options(),
+ Result :: erl_scan:tokens_result() | server_no_data().
+
+scan_erl_form(Io, Prompt, Pos0, Options) ->
+ request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[Pos0,Options]}).
%% Parsing Erlang code.
--type parse_ret() :: {'ok', ExprList :: erl_parse:abstract_expr(), EndLine :: line()}
- | {'eof', EndLine :: line()}
- | {'error', ErrorInfo :: erl_scan:error_info(), ErrorLine :: line()}
- | request_error().
+-type parse_ret() :: {'ok',
+ ExprList :: erl_parse:abstract_expr(),
+ EndLocation :: location()}
+ | {'eof', EndLocation :: location()}
+ | {'error',
+ ErrorInfo :: erl_scan:error_info()
+ | erl_parse:error_info(),
+ ErrorLocation :: location()}
+ | server_no_data().
-spec parse_erl_exprs(Prompt) -> Result when
Prompt :: prompt(),
@@ -416,14 +460,24 @@ parse_erl_exprs(Prompt) ->
parse_erl_exprs(Io, Prompt) ->
parse_erl_exprs(Io, Prompt, 1).
--spec parse_erl_exprs(IoDevice, Prompt, StartLine) -> Result when
+-spec parse_erl_exprs(IoDevice, Prompt, StartLocation) -> Result when
IoDevice :: device(),
Prompt :: prompt(),
- StartLine :: line(),
+ StartLocation :: location(),
Result :: parse_ret().
parse_erl_exprs(Io, Prompt, Pos0) ->
- case request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[Pos0]}) of
+ parse_erl_exprs(Io, Prompt, Pos0, []).
+
+-spec parse_erl_exprs(IoDevice, Prompt, StartLocation, Options) -> Result when
+ IoDevice :: device(),
+ Prompt :: prompt(),
+ StartLocation :: location(),
+ Options :: erl_scan:options(),
+ Result :: parse_ret().
+
+parse_erl_exprs(Io, Prompt, Pos0, Options) ->
+ case request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[Pos0,Options]}) of
{ok,Toks,EndPos} ->
case erl_parse:parse_exprs(Toks) of
{ok,Exprs} -> {ok,Exprs,EndPos};
@@ -433,10 +487,15 @@ parse_erl_exprs(Io, Prompt, Pos0) ->
Other
end.
--type parse_form_ret() :: {'ok', AbsForm :: erl_parse:abstract_form(), EndLine :: line()}
- | {'eof', EndLine :: line()}
- | {'error', ErrorInfo :: erl_scan:error_info(), ErrorLine :: line()}
- | request_error().
+-type parse_form_ret() :: {'ok',
+ AbsForm :: erl_parse:abstract_form(),
+ EndLocation :: location()}
+ | {'eof', EndLocation :: location()}
+ | {'error',
+ ErrorInfo :: erl_scan:error_info()
+ | erl_parse:error_info(),
+ ErrorLocation :: location()}
+ | server_no_data().
-spec parse_erl_form(Prompt) -> Result when
Prompt :: prompt(),
@@ -453,14 +512,25 @@ parse_erl_form(Prompt) ->
parse_erl_form(Io, Prompt) ->
parse_erl_form(Io, Prompt, 1).
--spec parse_erl_form(IoDevice, Prompt, StartLine) -> Result when
+-spec parse_erl_form(IoDevice, Prompt, StartLocation) -> Result when
IoDevice :: device(),
Prompt :: prompt(),
- StartLine :: line(),
+ StartLocation :: location(),
Result :: parse_form_ret().
parse_erl_form(Io, Prompt, Pos0) ->
- case request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[Pos0]}) of
+ parse_erl_form(Io, Prompt, Pos0, []).
+
+-spec parse_erl_form(IoDevice, Prompt, StartLocation, Options) -> Result when
+ IoDevice :: device(),
+ Prompt :: prompt(),
+ StartLocation :: location(),
+ Options :: erl_scan:options(),
+ Result :: parse_form_ret().
+
+parse_erl_form(Io, Prompt, Pos0, Options) ->
+ Args = [Pos0, Options],
+ case request(Io, {get_until,unicode,Prompt,erl_scan,tokens,Args}) of
{ok,Toks,EndPos} ->
case erl_parse:parse_form(Toks) of
{ok,Exprs} -> {ok,Exprs,EndPos};