File 5401-features-Don-t-warn-for-quoted-atoms-being-keywords.patch of Package erlang
From 7b1b33f1256468878b87b3c5ad1c46e8490d5e93 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Cons=20T=20=C3=85hs?= <cons@erlang.org>
Date: Tue, 10 May 2022 08:49:05 +0200
Subject: [PATCH 1/3] [features] Don't warn for quoted atoms being keywords
* Add new option to erl_scan:string/3 and erl_scan:tokens/3, a
function to specifiy when to keep original string.
---
lib/stdlib/doc/src/erl_scan.xml | 19 +++++-
lib/stdlib/src/epp.erl | 35 +++++++----
lib/stdlib/src/erl_lint.erl | 25 +++++---
lib/stdlib/src/erl_scan.erl | 97 ++++++++++++++++++------------
lib/stdlib/test/erl_scan_SUITE.erl | 80 +++++++++++++++++++++++-
5 files changed, 191 insertions(+), 65 deletions(-)
diff --git a/lib/stdlib/doc/src/erl_scan.xml b/lib/stdlib/doc/src/erl_scan.xml
index 4cfad284e7..960ff9d019 100644
--- a/lib/stdlib/doc/src/erl_scan.xml
+++ b/lib/stdlib/doc/src/erl_scan.xml
@@ -4,7 +4,7 @@
<erlref>
<header>
<copyright>
- <year>1996</year><year>2020</year>
+ <year>1996</year><year>2022</year>
<holder>Ericsson AB. All Rights Reserved.</holder>
</copyright>
<legalnotice>
@@ -70,6 +70,9 @@
<datatype>
<name name="tokens_result"></name>
</datatype>
+ <datatype>
+ <name name="text_fun"></name>
+ </datatype>
</datatypes>
<funcs>
@@ -220,9 +223,19 @@
<tag><c>return</c></tag>
<item><p>Short for <c>[return_comments, return_white_spaces]</c>.</p>
</item>
- <tag><c>text</c></tag>
+ <tag><marker id="text"/><c>text</c></tag>
<item><p>Include the token text in the token annotation. The
- text is the part of the input corresponding to the token.</p>
+ text is the part of the input corresponding to the token.
+ See also <seeerl marker="#text_fun"><c>text_fun</c></seeerl>.</p>
+ </item>
+ <tag><marker id="text_fun"/><c>{text_fun, text_fun()}</c></tag>
+ <item><p>A callback function used to determine whether the
+ full text for the token shall be included in the token
+ annotation. Arguments of the function are the category of
+ the token and the full token string. This is only used when
+ <seeerl marker="#text"><c>text</c></seeerl> is not present.
+ If neither are present the text will not be saved in the
+ token annotation.</p>
</item>
</taglist>
</desc>
diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index 95a933c9fa..9dfd3cbf28 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -627,7 +627,8 @@ init_server(Pid, FileName, Options, St0) ->
path=Path, location=AtLocation, macs=Ms1,
default_encoding=DefEncoding,
erl_scan_opts =
- [{reserved_word_fun, ResWordFun}],
+ [{text_fun, keep_ftr_keywords()},
+ {reserved_word_fun, ResWordFun}],
features = Features,
else_reserved = ResWordFun('else')},
From = wait_request(St),
@@ -639,6 +640,18 @@ init_server(Pid, FileName, Options, St0) ->
epp_reply(Pid, {error,E})
end.
+%% Return a function that keeps quoted atoms that are keywords in
+%% configurable features. Need in erl_lint to avoid warning about
+%% them.
+keep_ftr_keywords() ->
+ Features = erl_features:all(),
+ Keywords = lists:flatmap(fun erl_features:keywords/1, Features),
+ F = fun(Atom) -> atom_to_list(Atom) ++ "'" end,
+ Strings = lists:map(F, Keywords),
+ fun(atom, [$'|S]) -> lists:member(S, Strings);
+ (_, _) -> false
+ end.
+
%% predef_macros(FileName) -> Macrodict
%% Initialise the macro dictionary with the default predefined macros,
%% FILE, LINE, MODULE as undefined, MACHINE and MACHINE value.
@@ -1029,9 +1042,9 @@ scan_feature(Toks, {atom, _, Tag} = Token, From, St) ->
%% FIXME Rewrite this
update_features(St0, Ind, Ftr, Loc) ->
Ftrs0 = St0#epp.features,
- ScanOpts = St0#epp.erl_scan_opts,
+ ScanOpts0 = St0#epp.erl_scan_opts,
KeywordFun =
- case proplists:get_value(reserved_word_fun, ScanOpts) of
+ case proplists:get_value(reserved_word_fun, ScanOpts0) of
undefined -> fun erl_scan:f_reserved_word/1;
Fun -> Fun
end,
@@ -1041,15 +1054,13 @@ update_features(St0, Ind, Ftr, Loc) ->
{ok, {Ftrs1, ResWordFun1}} ->
Macs0 = St0#epp.macs,
Macs1 = Macs0#{'FEATURE_ENABLED' => [ftr_macro(Ftrs1)]},
- %% FIXME WE need to keep any other scan_opts
- %% present. Right now, there are no other, but
- %% that might change.
- StX = St0#epp{erl_scan_opts =
- [{reserved_word_fun, ResWordFun1}],
- features = Ftrs1,
- else_reserved = ResWordFun1('else'),
- macs = Macs1},
- {ok, StX}
+ ScanOpts1 = proplists:delete(reserved_word_fun, ScanOpts0),
+ St = St0#epp{erl_scan_opts =
+ [{reserved_word_fun, ResWordFun1}| ScanOpts1],
+ features = Ftrs1,
+ else_reserved = ResWordFun1('else'),
+ macs = Macs1},
+ {ok, St}
end.
%% scan_define(Tokens, DefineToken, From, EppState)
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index cc76090c59..1d9f723185 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -4172,17 +4172,24 @@ test_overriden_by_local(Anno, OldTest, Arity, St) ->
%% Add warning for atoms that will be reserved keywords in the future.
%% (Currently, no such keywords to warn for.)
keyword_warning(Anno, Atom, St) ->
+ Reserved =
+ fun(Ftr) ->
+ lists:member(Atom, erl_features:keywords(Ftr))
+ end,
+
case is_warn_enabled(keyword_warning, St) of
true ->
- Ftrs = erl_features:all(),
- Reserved =
- fun(Ftr) ->
- lists:member(Atom, erl_features:keywords(Ftr))
- end,
- case lists:filter(Reserved, Ftrs) of
- [] -> St;
- [Ftr] ->
- add_warning(Anno, {future_feature, Ftr, Atom}, St)
+ case erl_anno:text(Anno) of
+ [$'| _] ->
+ %% Don't warn for quoted atoms
+ St;
+ _ ->
+ Ftrs = erl_features:all(),
+ case lists:filter(Reserved, Ftrs) of
+ [] -> St;
+ [Ftr] ->
+ add_warning(Anno, {future_feature, Ftr, Atom}, St)
+ end
end;
false ->
St
diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl
index a30747b5e5..f2e9d2d7b9 100644
--- a/lib/stdlib/src/erl_scan.erl
+++ b/lib/stdlib/src/erl_scan.erl
@@ -90,8 +90,10 @@
-type category() :: atom().
-type resword_fun() :: fun((atom()) -> boolean()).
+-type text_fun() :: fun((atom(), string()) -> boolean()).
-type option() :: 'return' | 'return_white_spaces' | 'return_comments'
- | 'text' | {'reserved_word_fun', resword_fun()}.
+ | 'text' | {'reserved_word_fun', resword_fun()}
+ | {'text_fun', text_fun()}.
-type options() :: option() | [option()].
-type symbol() :: atom() | float() | integer() | string().
-type token() :: {category(), Anno :: erl_anno:anno(), symbol()}
@@ -102,10 +104,11 @@
%%% Local record.
-record(erl_scan,
- {resword_fun = fun reserved_word/1 :: resword_fun(),
- ws = false :: boolean(),
- comment = false :: boolean(),
- text = false :: boolean()}).
+ {resword_fun = fun reserved_word/1 :: resword_fun(),
+ text_fun = fun(_, _) -> false end :: text_fun(),
+ ws = false :: boolean(),
+ comment = false :: boolean(),
+ has_fun = false :: boolean()}).
%%----------------------------------------------------------------------------
@@ -283,10 +286,19 @@ options(Opts0) when is_list(Opts0) ->
Comment = proplists:get_bool(return_comments, Opts),
WS = proplists:get_bool(return_white_spaces, Opts),
Txt = proplists:get_bool(text, Opts),
+ TxtFunOpt = proplists:get_value(text_fun, Opts, none),
+ DefTxtFun = fun(_, _) -> Txt end,
+ {HasFun, TxtFun} =
+ if
+ Txt -> {Txt, DefTxtFun};
+ TxtFunOpt == none -> {Txt, DefTxtFun};
+ true -> {true, TxtFunOpt}
+ end,
#erl_scan{resword_fun = RW_fun,
comment = Comment,
ws = WS,
- text = Txt};
+ text_fun = TxtFun,
+ has_fun = HasFun};
options(Opt) ->
options([Opt]).
@@ -597,19 +609,24 @@ scan_name([], Ncs) ->
scan_name(Cs, Ncs) ->
{lists:reverse(Ncs),Cs}.
--define(STR(St, S), if St#erl_scan.text -> S; true -> [] end).
+-define(STR(Cl, St, S),
+ case (St#erl_scan.has_fun)
+ andalso (St#erl_scan.text_fun)(Cl, S) of
+ true -> S;
+ false -> []
+ end).
scan_dot([$%|_]=Cs, St, Line, Col, Toks, Ncs) ->
- Anno = anno(Line, Col, St, Ncs),
+ Anno = anno(Line, Col, St, ?STR(dot, St, Ncs)),
{ok,[{dot,Anno}|Toks],Cs,Line,incr_column(Col, 1)};
scan_dot([$\n=C|Cs], St, Line, Col, Toks, Ncs) ->
- Anno = anno(Line, Col, St, ?STR(St, Ncs++[C])),
+ Anno = anno(Line, Col, St, ?STR(dot, St, Ncs++[C])),
{ok,[{dot,Anno}|Toks],Cs,Line+1,new_column(Col, 1)};
scan_dot([C|Cs], St, Line, Col, Toks, Ncs) when ?WHITE_SPACE(C) ->
- Anno = anno(Line, Col, St, ?STR(St, Ncs++[C])),
+ Anno = anno(Line, Col, St, ?STR(dot, St, Ncs++[C])),
{ok,[{dot,Anno}|Toks],Cs,Line,incr_column(Col, 2)};
scan_dot(eof=Cs, St, Line, Col, Toks, Ncs) ->
- Anno = anno(Line, Col, St, Ncs),
+ Anno = anno(Line, Col, St, ?STR(dot, St, Ncs)),
{ok,[{dot,Anno}|Toks],Cs,Line,incr_column(Col, 1)};
scan_dot(Cs, St, Line, Col, Toks, Ncs) ->
tok2(Cs, St, Line, Col, Toks, Ncs, '.', 1).
@@ -663,34 +680,34 @@ scan_nl_tabs(Cs, St, Line, Col, Toks, N) ->
%% Note: returning {more,Cont} is meaningless here; one could just as
%% well return several tokens. But since tokens() scans up to a full
%% stop anyway, nothing is gained by not collecting all white spaces.
-scan_nl_white_space([$\n|Cs], #erl_scan{text = false}=St, Line, no_col=Col,
+scan_nl_white_space([$\n|Cs], #erl_scan{has_fun = false}=St, Line, no_col=Col,
Toks0, Ncs) ->
Toks = [{white_space,anno(Line),lists:reverse(Ncs)}|Toks0],
scan_newline(Cs, St, Line+1, Col, Toks);
scan_nl_white_space([$\n|Cs], St, Line, Col, Toks, Ncs0) ->
Ncs = lists:reverse(Ncs0),
- Anno = anno(Line, Col, St, Ncs),
+ Anno = anno(Line, Col, St, ?STR(white_space, St, Ncs)),
Token = {white_space,Anno,Ncs},
scan_newline(Cs, St, Line+1, new_column(Col, length(Ncs)), [Token|Toks]);
scan_nl_white_space([C|Cs], St, Line, Col, Toks, Ncs) when ?WHITE_SPACE(C) ->
scan_nl_white_space(Cs, St, Line, Col, Toks, [C|Ncs]);
scan_nl_white_space([]=Cs, _St, Line, Col, Toks, Ncs) ->
{more,{Cs,Col,Toks,Line,Ncs,fun scan_nl_white_space/6}};
-scan_nl_white_space(Cs, #erl_scan{text = false}=St, Line, no_col=Col,
+scan_nl_white_space(Cs, #erl_scan{has_fun = false}=St, Line, no_col=Col,
Toks, Ncs) ->
Anno = anno(Line),
scan1(Cs, St, Line+1, Col, [{white_space,Anno,lists:reverse(Ncs)}|Toks]);
scan_nl_white_space(Cs, St, Line, Col, Toks, Ncs0) ->
Ncs = lists:reverse(Ncs0),
- Anno = anno(Line, Col, St, Ncs),
+ Anno = anno(Line, Col, St, ?STR(white_space, St, Ncs)),
Token = {white_space,Anno,Ncs},
scan1(Cs, St, Line+1, new_column(Col, length(Ncs)), [Token|Toks]).
-newline_end(Cs, #erl_scan{text = false}=St, Line, no_col=Col,
+newline_end(Cs, #erl_scan{has_fun = false}=St, Line, no_col=Col,
Toks, _N, Ncs) ->
scan1(Cs, St, Line+1, Col, [{white_space,anno(Line),Ncs}|Toks]);
newline_end(Cs, St, Line, Col, Toks, N, Ncs) ->
- Anno = anno(Line, Col, St, Ncs),
+ Anno = anno(Line, Col, St, ?STR(white_space, St, Ncs)),
scan1(Cs, St, Line+1, new_column(Col, N), [{white_space,Anno,Ncs}|Toks]).
scan_spcs([$\s|Cs], St, Line, Col, Toks, N) when N < 16 ->
@@ -740,19 +757,19 @@ scan_char([$\\|Cs]=Cs0, St, Line, Col, Toks) ->
{eof,Ncol} ->
scan_error(char, Line, Col, Line, Ncol, eof);
{nl,Val,Str,Ncs,Ncol} ->
- Anno = anno(Line, Col, St, ?STR(St, "$\\"++Str)), %"
+ Anno = anno(Line, Col, St, ?STR(char, St, "$\\"++Str)), %"
Ntoks = [{char,Anno,Val}|Toks],
scan1(Ncs, St, Line+1, Ncol, Ntoks);
{Val,Str,Ncs,Ncol} ->
- Anno = anno(Line, Col, St, ?STR(St, "$\\"++Str)), %"
+ Anno = anno(Line, Col, St, ?STR(char, St, "$\\"++Str)), %"
Ntoks = [{char,Anno,Val}|Toks],
scan1(Ncs, St, Line, Ncol, Ntoks)
end;
scan_char([$\n=C|Cs], St, Line, Col, Toks) ->
- Anno = anno(Line, Col, St, ?STR(St, [$$,C])),
+ Anno = anno(Line, Col, St, ?STR(char, St, [$$,C])),
scan1(Cs, St, Line+1, new_column(Col, 1), [{char,Anno,C}|Toks]);
scan_char([C|Cs], St, Line, Col, Toks) when ?UNICODE(C) ->
- Anno = anno(Line, Col, St, ?STR(St, [$$,C])),
+ Anno = anno(Line, Col, St, ?STR(char, St, [$$,C])),
scan1(Cs, St, Line, incr_column(Col, 2), [{char,Anno,C}|Toks]);
scan_char([C|_Cs], _St, Line, Col, _Toks) when ?CHAR(C) ->
scan_error({illegal,character}, Line, Col, Line, incr_column(Col, 1), eof);
@@ -772,7 +789,7 @@ scan_string(Cs, St, Line, Col, Toks, {Wcs,Str,Line0,Col0}) ->
Estr = string:slice(Nwcs, 0, 16), % Expanded escape chars.
scan_error({string,$\",Estr}, Line0, Col0, Nline, Ncol, Ncs); %"
{Ncs,Nline,Ncol,Nstr,Nwcs} ->
- Anno = anno(Line0, Col0, St, Nstr),
+ Anno = anno(Line0, Col0, St, ?STR(string, St, Nstr)),
scan1(Ncs, St, Nline, Ncol, [{string,Anno,Nwcs}|Toks])
end.
@@ -789,16 +806,16 @@ scan_qatom(Cs, St, Line, Col, Toks, {Wcs,Str,Line0,Col0}) ->
{Ncs,Nline,Ncol,Nstr,Nwcs} ->
case catch list_to_atom(Nwcs) of
A when is_atom(A) ->
- Anno = anno(Line0, Col0, St, Nstr),
+ Anno = anno(Line0, Col0, St, ?STR(atom, St, Nstr)),
scan1(Ncs, St, Nline, Ncol, [{atom,Anno,A}|Toks]);
_ ->
scan_error({illegal,atom}, Line0, Col0, Nline, Ncol, Ncs)
end
end.
-scan_string0(Cs, #erl_scan{text=false}, Line, no_col=Col, Q, [], Wcs) ->
+scan_string0(Cs, #erl_scan{has_fun=false}, Line, no_col=Col, Q, [], Wcs) ->
scan_string_no_col(Cs, Line, Col, Q, Wcs);
-scan_string0(Cs, #erl_scan{text=true}, Line, no_col=Col, Q, Str, Wcs) ->
+scan_string0(Cs, #erl_scan{has_fun=true}, Line, no_col=Col, Q, Str, Wcs) ->
scan_string1(Cs, Line, Col, Q, Str, Wcs);
scan_string0(Cs, St, Line, Col, Q, [], Wcs) ->
scan_string_col(Cs, St, Line, Col, Q, Wcs);
@@ -818,7 +835,7 @@ scan_string_no_col(Cs, Line, Col, Q, Wcs) ->
%% Optimization. Col =/= no_col.
scan_string_col([Q|Cs], St, Line, Col, Q, Wcs0) ->
Wcs = lists:reverse(Wcs0),
- Str = ?STR(St, [Q|Wcs++[Q]]),
+ Str = ?STR(atom, St, [Q|Wcs++[Q]]),
{Cs,Line,Col+1,Str,Wcs};
scan_string_col([$\n=C|Cs], St, Line, _xCol, Q, Wcs) ->
scan_string_col(Cs, St, Line+1, 1, Q, [C|Wcs]);
@@ -1106,29 +1123,29 @@ scan_comment(Cs, St, Line, Col, Toks, Ncs0) ->
Ncs = lists:reverse(Ncs0),
tok3(Cs, St, Line, Col, Toks, comment, Ncs, Ncs).
-tok2(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, _Wcs, P) ->
+tok2(Cs, #erl_scan{has_fun = false}=St, Line, no_col=Col, Toks, _Wcs, P) ->
scan1(Cs, St, Line, Col, [{P,anno(Line)}|Toks]);
tok2(Cs, St, Line, Col, Toks, Wcs, P) ->
- Anno = anno(Line, Col, St, Wcs),
+ Anno = anno(Line, Col, St, ?STR(P, St, Wcs)),
scan1(Cs, St, Line, incr_column(Col, length(Wcs)), [{P,Anno}|Toks]).
-tok2(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, _Wcs, P, _N) ->
+tok2(Cs, #erl_scan{has_fun = false}=St, Line, no_col=Col, Toks, _Wcs, P, _N) ->
scan1(Cs, St, Line, Col, [{P,anno(Line)}|Toks]);
tok2(Cs, St, Line, Col, Toks, Wcs, P, N) ->
- Anno = anno(Line, Col, St, Wcs),
+ Anno = anno(Line, Col, St, ?STR(P,St,Wcs)),
scan1(Cs, St, Line, incr_column(Col, N), [{P,Anno}|Toks]).
-tok3(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, Item, _S, Sym) ->
+tok3(Cs, #erl_scan{has_fun = false}=St, Line, no_col=Col, Toks, Item, _S, Sym) ->
scan1(Cs, St, Line, Col, [{Item,anno(Line),Sym}|Toks]);
tok3(Cs, St, Line, Col, Toks, Item, String, Sym) ->
- Token = {Item,anno(Line, Col, St, String),Sym},
+ Token = {Item,anno(Line, Col, St, ?STR(Item, St, String)),Sym},
scan1(Cs, St, Line, incr_column(Col, length(String)), [Token|Toks]).
-tok3(Cs, #erl_scan{text = false}=St, Line, no_col=Col, Toks, Item,
+tok3(Cs, #erl_scan{has_fun = false}=St, Line, no_col=Col, Toks, Item,
_String, Sym, _Length) ->
scan1(Cs, St, Line, Col, [{Item,anno(Line),Sym}|Toks]);
tok3(Cs, St, Line, Col, Toks, Item, String, Sym, Length) ->
- Token = {Item,anno(Line, Col, St, String),Sym},
+ Token = {Item,anno(Line, Col, St, ?STR(Item, St, String)),Sym},
scan1(Cs, St, Line, incr_column(Col, Length), [Token|Toks]).
scan_error(Error, Line, Col, EndLine, EndCol, Rest) ->
@@ -1141,14 +1158,18 @@ scan_error(Error, ErrorLoc, EndLoc, Rest) ->
-compile({inline,[anno/4]}).
-anno(Line, no_col, #erl_scan{text = false}, _String) ->
+anno(Line, no_col, #erl_scan{has_fun = false}, _String) ->
+ anno(Line);
+anno(Line, no_col, #erl_scan{has_fun = true}, []) ->
anno(Line);
-anno(Line, no_col, #erl_scan{text = true}, String) ->
+anno(Line, no_col, #erl_scan{has_fun = true}, String) ->
Anno = anno(Line),
erl_anno:set_text(String, Anno);
-anno(Line, Col, #erl_scan{text = false}, _String) ->
+anno(Line, Col, #erl_scan{has_fun = false}, _String) ->
+ anno({Line, Col});
+anno(Line, Col, #erl_scan{has_fun = true}, []) ->
anno({Line, Col});
-anno(Line, Col, #erl_scan{text = true}, String) ->
+anno(Line, Col, #erl_scan{has_fun = true}, String) ->
Anno = anno({Line, Col}),
erl_anno:set_text(String, Anno).
diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl
index f853ad7ad7..ee8bc8420f 100644
--- a/lib/stdlib/test/erl_scan_SUITE.erl
+++ b/lib/stdlib/test/erl_scan_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2021. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2022. 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.
@@ -23,7 +23,8 @@
init_per_group/2,end_per_group/2]).
-export([error_1/1, error_2/1, iso88591/1, otp_7810/1, otp_10302/1,
- otp_10990/1, otp_10992/1, otp_11807/1, otp_16480/1, otp_17024/1]).
+ otp_10990/1, otp_10992/1, otp_11807/1, otp_16480/1, otp_17024/1,
+ text_fun/1]).
-import(lists, [nth/2,flatten/1]).
-import(io_lib, [print/1]).
@@ -58,7 +59,7 @@ suite() ->
all() ->
[{group, error}, iso88591, otp_7810, otp_10302, otp_10990, otp_10992,
- otp_11807, otp_16480, otp_17024].
+ otp_11807, otp_16480, otp_17024, text_fun].
groups() ->
[{error, [], [error_1, error_2]}].
@@ -1212,6 +1213,79 @@ otp_17024(Config) when is_list(Config) ->
{integer,Location,1} = erl_parse_abstract(1, Opts2),
ok.
+text_fun(Config) when is_list(Config) ->
+ KeepClass = fun(Class) ->
+ fun(C, _) -> C == Class end
+ end,
+
+ Join = fun(L, S) -> string:join(L, S) end,
+ String = fun(L) -> Join(L, " ") end,
+
+ TextAtom = KeepClass(atom),
+ TextInt = KeepClass(integer),
+ %% Keep text for integers written with a base.
+ TextBase = fun(C, S) ->
+ C == integer andalso string:find(S, "#") /= nomatch
+ end,
+ %% Keep text for long strings, regardless of class
+ TextLong = fun(_, S) -> length(S) > 10 end,
+
+ Texts = fun(Toks) -> [erl_scan:text(T) || T <- Toks] end,
+ Values = fun(Toks) -> [erl_scan:symbol(T) || T <- Toks] end,
+
+ Atom1 = "foo",
+ Atom2 = "'this is a long atom'",
+ Int1 = "42",
+ Int2 = "16#10",
+ Int3 = "8#20",
+ Int4 = "16",
+ Int5 = "12345678901234567890",
+ String1 = "\"A String\"",
+ String2 = "\"guitar string\"",
+ Name1 = "Short",
+ Name2 = "LongAndDescriptiveName",
+ Sep1 = "{",
+ Sep2 = "+",
+ Sep3 = "]",
+ Sep4 = "/",
+
+ All = [Atom1, Atom2, Int1, Int2, Int3, Int4, Int5,
+ String1, String2, Name1, Name2,
+ Sep1, Sep2, Sep3, Sep4],
+
+ {ok, Tokens0, 2} =
+ erl_scan:string(String([Atom1, Int1]), 2, [{text_fun, TextAtom}]),
+ [Atom1, undefined] = Texts(Tokens0),
+ [foo, 42] = Values(Tokens0),
+
+ {ok, Tokens1, 3} =
+ erl_scan:string(Join([Int2, Int3, Int4], "\n"), 1,
+ [{text_fun, TextInt}]),
+ [Int2, Int3, Int4] = Texts(Tokens1),
+ [16, 16, 16] = Values(Tokens1),
+
+ TS = [Int2, String1, Atom1, Int3, Int4, String2],
+ {ok, Tokens2, 6} =
+ %% If text is present, we supply text for *all* tokens.
+ erl_scan:string(Join(TS, "\n"), 1, [{text_fun, TextAtom}, text]),
+ TS = Texts(Tokens2),
+ [16, "A String", foo, 16, 16, "guitar string"] = Values(Tokens2),
+
+ Ints = [Int1, Int2, Int3, Int4],
+ {ok, Tokens3, 1} = erl_scan:string(String(Ints), 1, [{text_fun, TextBase}]),
+ [undefined, Int2, Int3, undefined] = Texts(Tokens3),
+ [42, 16, 16, 16] = Values(Tokens3),
+
+ Longs = lists:filter(fun(S) -> length(S) > 10 end, All),
+ {ok, Tokens4, 1} =
+ erl_scan:string(String(All), 1, [{text_fun, TextLong}]),
+ Longs = lists:filter(fun(T) -> T /= undefined end, Texts(Tokens4)),
+
+ {ok, Tokens5, 7} =
+ erl_scan:string(String(All), 7, [{text_fun, KeepClass('{')}]),
+ [Sep1] = lists:filter(fun(T) -> T /= undefined end, Texts(Tokens5)).
+
+
test_string(String, ExpectedWithCol) ->
{ok, ExpectedWithCol, _EndWithCol} = erl_scan_string(String, {1, 1}, []),
Expected = [ begin
--
2.35.3