Skip to content

Commit

Permalink
Make scanner accept floating point literals in hex and binary
Browse files Browse the repository at this point in the history
  • Loading branch information
richcarl committed Nov 25, 2024
1 parent 429dc57 commit 637b7fc
Show file tree
Hide file tree
Showing 2 changed files with 208 additions and 14 deletions.
131 changes: 117 additions & 14 deletions lib/stdlib/src/erl_scan.erl
Original file line number Diff line number Diff line change
Expand Up @@ -165,6 +165,11 @@ format_error({illegal,Type}) ->
lists:flatten(io_lib:fwrite("illegal ~w", [Type]));
format_error({base,Base}) ->
lists:flatten(io_lib:fwrite("illegal base '~w'", [Base]));
format_error({float_base,Base}) ->
lists:flatten(io_lib:fwrite("illegal base '~w' - only 10, 16 or 2 are allowed for floating point literals", [Base]));
format_error({exponent,Base}) ->
C = if Base =:= 10 -> $e; true -> $p end,
lists:flatten(io_lib:fwrite("only '~c' allowed as exponent character in base ~w", [C, Base]));
format_error(indentation) ->
"bad indentation in triple-quoted string";
format_error(white_space) ->
Expand Down Expand Up @@ -1820,7 +1825,7 @@ scan_number([$#|Cs]=Cs0, St, Line, Col, Toks, Ncs0, Us) ->
try list_to_integer(remove_digit_separators(Ncs, Us)) of
B when is_integer(B), 2 =< B, B =< 1+$Z-$A+10 ->
Bcs = Ncs++[$#],
scan_based_int(Cs, St, Line, Col, Toks, B, [], Bcs, no_underscore);
scan_based_num(Cs, St, Line, Col, Toks, B, [], Bcs, no_underscore);
B when is_integer(B) ->
Len = length(Ncs),
scan_error({base,B}, Line, Col, Line, incr_column(Col, Len), Cs0)
Expand Down Expand Up @@ -1857,29 +1862,40 @@ remove_digit_separators(Number, with_underscore) ->
orelse (C >= $A andalso B > 10 andalso C < $A + B - 10)
orelse (C >= $a andalso B > 10 andalso C < $a + B - 10)))).

scan_based_int(Cs, #erl_scan{}=St, Line, Col, Toks, {B,NCs,BCs,Us})
scan_based_num(Cs, #erl_scan{}=St, Line, Col, Toks, {B,NCs,BCs,Us})
when is_integer(B), 2 =< B, B =< 1+$Z-$A+10 ->
scan_based_int(Cs, St, Line, Col, Toks, B, NCs, BCs, Us).
scan_based_num(Cs, St, Line, Col, Toks, B, NCs, BCs, Us).

scan_based_int([C|Cs], St, Line, Col, Toks, B, Ncs, Bcs, Us) when
scan_based_num([C|Cs], St, Line, Col, Toks, B, Ncs, Bcs, Us) when
?BASED_DIGIT(C, B) ->
scan_based_int(Cs, St, Line, Col, Toks, B, [C|Ncs], Bcs, Us);
scan_based_int([$_,Next|Cs], St, Line, Col, Toks, B, [Prev|_]=Ncs, Bcs, _Us)
scan_based_num(Cs, St, Line, Col, Toks, B, [C|Ncs], Bcs, Us);
scan_based_num([$_,Next|Cs], St, Line, Col, Toks, B, [Prev|_]=Ncs, Bcs, _Us)
when ?BASED_DIGIT(Next, B) andalso ?BASED_DIGIT(Prev, B) ->
scan_based_int(Cs, St, Line, Col, Toks, B, [Next,$_|Ncs], Bcs,
scan_based_num(Cs, St, Line, Col, Toks, B, [Next,$_|Ncs], Bcs,
with_underscore);
scan_based_int([$_]=Cs, St, Line, Col, Toks, B, NCs, BCs, Us) ->
{more,{Cs,St,Col,Toks,Line,{B,NCs,BCs,Us},fun scan_based_int/6}};
scan_based_int([C|_]=Cs0, _St, Line, Col, _Toks, _B, Ncs, Bcs, _Us) when ?NAMECHAR(C) ->
scan_based_num([$_]=Cs, St, Line, Col, Toks, B, NCs, BCs, Us) ->
{more,{Cs,St,Col,Toks,Line,{B,NCs,BCs,Us},fun scan_based_num/6}};
scan_based_num([$.,C|Cs], St, Line, Col, Toks, B, Ncs, BCs, Us) when ?BASED_DIGIT(C, B) ->
if B =:= 10; B =:= 2; B =:= 16 ->
scan_based_fraction(Cs, St, Line, Col, Toks, B, [C,$.|Ncs], BCs, Us);
true ->
Ncol = incr_column(Col, length(Ncs) + length(BCs)),
scan_error({float_base, B}, Line, Col, Line, Ncol, Cs)
end;
scan_based_num([$.,C|_]=Cs0, _St, Line, Col, _Toks, _B, Ncs, Bcs, _Us) when ?NAMECHAR(C) ->
scan_error({illegal,float}, Line, Col, Line, incr_column(Col, length(Ncs) + length(Bcs)), Cs0);
scan_based_num([$.]=Cs, St, Line, Col, Toks, B, Ncs, BCs, Us) ->
{more,{Cs,St,Col,Toks,Line,{B,Ncs,BCs,Us},fun scan_based_num/6}};
scan_based_num([C|_]=Cs0, _St, Line, Col, _Toks, _B, Ncs, Bcs, _Us) when ?NAMECHAR(C) ->
scan_error({illegal,integer}, Line, Col, Line, incr_column(Col, length(Ncs) + length(Bcs)), Cs0);
scan_based_int([]=Cs, St, Line, Col, Toks, B, NCs, BCs, Us) ->
{more,{Cs,St,Col,Toks,Line,{B,NCs,BCs,Us},fun scan_based_int/6}};
scan_based_int(Cs, _St, Line, Col, _Toks, _B, [], Bcs, _Us) ->
scan_based_num([]=Cs, St, Line, Col, Toks, B, NCs, BCs, Us) ->
{more,{Cs,St,Col,Toks,Line,{B,NCs,BCs,Us},fun scan_based_num/6}};
scan_based_num(Cs, _St, Line, Col, _Toks, _B, [], Bcs, _Us) ->
%% No actual digits following the base.
Len = length(Bcs),
Ncol = incr_column(Col, Len),
scan_error({illegal,integer}, Line, Col, Line, Ncol, Cs);
scan_based_int(Cs, St, Line, Col, Toks, B, Ncs0, [_|_]=Bcs, Us) ->
scan_based_num(Cs, St, Line, Col, Toks, B, Ncs0, [_|_]=Bcs, Us) ->
Ncs = lists:reverse(Ncs0),
try list_to_integer(remove_digit_separators(Ncs, Us), B) of
N ->
Expand All @@ -1892,6 +1908,93 @@ scan_based_int(Cs, St, Line, Col, Toks, B, Ncs0, [_|_]=Bcs, Us) ->
scan_error({illegal,integer}, Line, Col, Line, Ncol, Cs)
end.

scan_based_fraction(Cs, #erl_scan{}=St, Line, Col, Toks, {B,Ncs,BCs,Us}) ->
scan_based_fraction(Cs, St, Line, Col, Toks, B, Ncs, BCs, Us).

scan_based_fraction([C|Cs], St, Line, Col, Toks, B, Ncs, BCs, Us) when ?BASED_DIGIT(C, B) ->
scan_based_fraction(Cs, St, Line, Col, Toks, B, [C|Ncs], BCs, Us);
scan_based_fraction([$_,Next|Cs], St, Line, Col, Toks, B, [Prev|_]=Ncs, BCs, _Us) when
?BASED_DIGIT(Next, B) andalso ?BASED_DIGIT(Prev, B) ->
scan_based_fraction(Cs, St, Line, Col, Toks, B, [Next,$_|Ncs], BCs, with_underscore);
scan_based_fraction([$_]=Cs, St, Line, Col, Toks, B, Ncs, BCs, Us) ->
{more,{Cs,St,Col,Toks,Line,{B,Ncs,BCs,Us},fun scan_based_fraction/6}};
scan_based_fraction([E|Cs], St, Line, Col, Toks, B, Ncs, BCs, Us) when E =:= $e; E =:= $E ->
if B =:= 10 ->
scan_based_exponent_sign(Cs, St, Line, Col, Toks, B, Ncs, BCs, [E], Us);
true ->
Ncol = incr_column(Col, length(Ncs)+length(BCs)),
scan_error({exponent,B}, Line, Col, Line, Ncol, Cs)
end;
scan_based_fraction([E|Cs], St, Line, Col, Toks, B, Ncs, BCs, Us) when E =:= $p; E =:= $P ->
if B =/= 10 ->
scan_based_exponent_sign(Cs, St, Line, Col, Toks, B, Ncs, BCs, [E], Us);
true ->
Ncol = incr_column(Col, length(Ncs)+length(BCs)),
scan_error({exponent,B}, Line, Col, Line, Ncol, Cs)
end;
scan_based_fraction([C|_]=Cs0, _St, Line, Col, _Toks, _B, Ncs, BCs, _Us) when ?NAMECHAR(C) ->
scan_error({illegal,float}, Line, Col, Line, incr_column(Col, length(Ncs) + length(BCs)), Cs0);
scan_based_fraction([]=Cs, St, Line, Col, Toks, B, Ncs, BCs, Us) ->
{more,{Cs,St,Col,Toks,Line,{B,Ncs,BCs,Us},fun scan_based_fraction/6}};
scan_based_fraction(Cs, St, Line, Col, Toks, B, Ncs, BCs, Us) ->
based_float_end(Cs, St, Line, Col, Toks, B, Ncs, BCs, [], Us).

scan_based_exponent_sign(Cs, #erl_scan{}=St, Line, Col, Toks, {B,Ncs,BCs,ECs,Us}) ->
scan_based_exponent_sign(Cs, St, Line, Col, Toks, B, Ncs, BCs, ECs, Us).

scan_based_exponent_sign([C|Cs], St, Line, Col, Toks, B, Ncs, BCs, ECs, Us) when
C =:= $+; C =:= $- ->
scan_based_exponent(Cs, St, Line, Col, Toks, B, Ncs, BCs, [C|ECs], Us);
scan_based_exponent_sign([]=Cs, St, Line, Col, Toks, B, Ncs, BCs, ECs, Us) ->
{more,{Cs,St,Col,Toks,Line,{B,Ncs,BCs, ECs,Us},fun scan_based_exponent_sign/6}};
scan_based_exponent_sign(Cs, St, Line, Col, Toks, B, Ncs, BCs, ECs, Us) ->
scan_based_exponent(Cs, St, Line, Col, Toks, B, Ncs, BCs, ECs, Us).

scan_based_exponent(Cs, #erl_scan{}=St, Line, Col, Toks, {B,Ncs,BCs,ECs,Us}) ->
scan_based_exponent(Cs, St, Line, Col, Toks, B, Ncs, BCs, ECs, Us).

scan_based_exponent([C|Cs], St, Line, Col, Toks, B, Ncs, BCs, ECs, Us) when ?DIGIT(C) ->
scan_based_exponent(Cs, St, Line, Col, Toks, B, Ncs, BCs, [C|ECs], Us);
scan_based_exponent([$_,Next|Cs], St, Line, Col, Toks, B, Ncs, BCs, [Prev|_]=ECs, _) when
?DIGIT(Next) andalso ?DIGIT(Prev) ->
scan_based_exponent(Cs, St, Line, Col, Toks, B, Ncs, BCs, [Next,$_|ECs], with_underscore);
scan_based_exponent([$_]=Cs, St, Line, Col, Toks, B, Ncs, BCs, ECs, Us) ->
{more,{Cs,St,Col,Toks,Line,{B,Ncs,BCs,ECs,Us},fun scan_based_exponent/6}};
scan_based_exponent([]=Cs, St, Line, Col, Toks, B, Ncs, BCs, ECs, Us) ->
{more,{Cs,St,Col,Toks,Line,{B,Ncs,BCs,ECs, Us},fun scan_based_exponent/6}};
scan_based_exponent(Cs, St, Line, Col, Toks, B, Ncs, BCs, ECs, Us) ->
based_float_end(Cs, St, Line, Col, Toks, B, Ncs, BCs, ECs, Us).

% Note: the base and exponent parts are always in decimal
based_float_end(Cs, St, Line, Col, Toks, 10, Ncs0, BCs, ECs, Us) ->
Ncs = lists:reverse(Ncs0),
Fcs = Ncs ++ lists:reverse(ECs),
try list_to_float(remove_digit_separators(Fcs, Us)) of
F ->
Tcs = BCs ++ Fcs,
tok3(Cs, St, Line, Col, Toks, float, Tcs, F)
catch
_:_ ->
Ncol = incr_column(Col, length(Ncs) + length(BCs)),
scan_error({illegal,float}, Line, Col, Line, Ncol, Cs)
end;
based_float_end(Cs, St, Line, Col, Toks, B, Ncs0, BCs, ECs0, Us) when B =/= 10 ->
ECs = lists:reverse(ECs0),
Exp = case ECs of
[] -> 0;
_ -> list_to_integer(remove_digit_separators(tl(ECs), Us))
end,
Tcs = BCs ++ lists:reverse(Ncs0) ++ ECs,
Ncs = trim_float_zeros(lists:reverse(trim_float_zeros(remove_digit_separators(Ncs0, Us)))),
FBits = (length(Ncs) - string:chr(Ncs, $.)) * case B of 2 -> 1; 16 -> 4 end,
%% note that there will always be at least one digit in the fraction, even if 0
F = list_to_integer(lists:delete($.,Ncs), B) * math:pow(2, Exp-FBits),
tok3(Cs, St, Line, Col, Toks, float, Tcs, F).

trim_float_zeros([$0, $. | _]=Cs) -> Cs;
trim_float_zeros([$0 | Cs]) -> trim_float_zeros(Cs);
trim_float_zeros(Cs) -> Cs.

scan_fraction(Cs, #erl_scan{}=St, Line, Col, Toks, {Ncs,Us}) ->
scan_fraction(Cs, St, Line, Col, Toks, Ncs, Us).

Expand Down
91 changes: 91 additions & 0 deletions lib/stdlib/test/erl_scan_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -165,6 +165,7 @@ otp_7810(Config) when is_list(Config) ->
ok = integers(),
ok = base_integers(),
ok = floats(),
ok = base_floats(),
ok = dots(),
ok = chars(),
ok = variables(),
Expand Down Expand Up @@ -465,6 +466,96 @@ floats() ->
end, FloatErrors),
ok.

base_floats() ->
[begin
Ts = [{float,{1,1},F}],
test_string(FS, Ts)
end || {FS, F} <- [{"10#1.0",1.0},
{"10#012345.625", 012345.625},
{"10#3.31200",3.31200},
{"10#1.0e0",1.0e0},
{"10#1.0E17",1.0E17},
{"10#34.21E-18", 34.21E-18},
{"10#17.0E+14", 17.0E+14},
{"10#12345.625e3", 12345.625e3},
{"10#12345.625E-3", 12345.625E-3},

{"2#1.0", 1.0},
{"2#101.0", 5.0},
{"2#101.1", 5.5},
{"2#101.101", 5.625},
{"2#101.1p0", 5.5},
{"2#1.0p+3", 8.0},
{"2#1.0p-3", 0.125},
{"2#000100.001000", 4.125},
{"2#0.10000000000000000000000000000000000000000000000000001", 0.5000000000000001}, % 53 bits
{"2#0.100000000000000000000000000000000000000000000000000001", 0.5}, % not 54 bits
{"2#0.11001001000011111101101010100010001000010110100011000p+2", math:pi()}, % pi to 53 bits

{"16#100.0", 256.0},
{"16#ff.d", 16#ffd/16},
{"16#1.0", 1.0},
{"16#abc.def", 16#abcdef/16#1000},
{"16#00100.001000", 256.0 + 1/16#1000},
{"16#0.80000000000008", 0.5000000000000001}, % 53-bit fraction
{"16#0.80000000000004", 0.5}, % not 54 bits
{"16#fe.8p0", 254.5},
{"16#f.0p+3", 120.0},
{"16#c.0p-3", 1.5},
{"16#0.0e0", 16#e/16#100}, % e is a hex digit, not exponent
{"16#0.0E0", 16#e/16#100}, % same for E
{"16#0.c90fdaa22168c0p+2", math:pi()} % pi to 53 bits
]],

[begin
{error,{1,erl_scan,{illegal,float}},1} = erl_scan:string(S),
{error,{{1,1},erl_scan,{illegal,float}},{1,_}} =
erl_scan:string(S, {1,1}, [])
end || S <- ["1.14Ea"]],

UnderscoreSamples =
[{"1_6#000_100.0_0", 256.0},
{"16#0.c90f_daa2_2168_c0p+2", math:pi()},
{"16#c90f_daa2.2168_c0p-30", math:pi()},
{"16#c90f_daa2_2168.c0p-4_6", math:pi()},
{"2#1.010101010101010101010p+2_1", 2796202.0}],
lists:foreach(
fun({S, I}) ->
test_string(S, [{float, {1, 1}, I}])
end, UnderscoreSamples),
FloatErrors =
[
"10#12345.a25",
"10#12345.6a5",
"16#a0.gf23",
"16#a0.2fg3",
"2#10.201",
"2#10.120",
"3#102.3"
],
lists:foreach(
fun(S) ->
case erl_scan:string(S) of
{error,{1,erl_scan,{illegal,float}},_} ->
ok;
{error,Err,_} ->
error({unexpected_error, S, Err});
Succ ->
error({unexpected_success, S, Succ})
end
end, FloatErrors),
{error,{{1,1},erl_scan,{float_base,3}},{1,6}} =
erl_scan:string("3#102.12", {1,1}, []),
{error,{{1,1},erl_scan,{exponent,10}},{1,13}} =
erl_scan:string("10#12345.625p3", {1,1}, []),
{error,{{1,1},erl_scan,{exponent,10}},{1,13}} =
erl_scan:string("10#12345.625P3", {1,1}, []),
{error,{{1,1},erl_scan,{exponent,2}},{1,8}} =
erl_scan:string("2#10.01e3", {1,1}, []),
{error,{{1,1},erl_scan,{exponent,2}},{1,8}} =
erl_scan:string("2#10.01E3", {1,1}, []),
ok.

dots() ->
Dot = [{".", {ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,2}}},
{". ", {ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,3}}},
Expand Down

0 comments on commit 637b7fc

Please sign in to comment.