diff --git a/json.c b/json.c index e35e371..1130142 100644 --- a/json.c +++ b/json.c @@ -38,6 +38,8 @@ #include +static predicate_t PREDICATE_mk_rational3; /* +Integer, +NumberOfDecimals, -Rational */ + /******************************* * READ * *******************************/ @@ -95,26 +97,45 @@ put_byte(text *t, int c) static foreign_t -json_read_number(term_t stream, term_t c0, term_t number) +json_read_number(term_t stream, term_t c0, term_t use_rdiv, term_t number) { IOSTREAM *in; text t; int rc = FALSE; int c; term_t tmp; + int decimal_places = 0; + int is_decimal = 0; + int preserve_precision = FALSE; + if ( !PL_get_bool_ex(use_rdiv, &preserve_precision) ) + return FALSE; if ( !PL_get_stream(stream, &in, SIO_INPUT) || !PL_get_char_ex(c0, &c, FALSE) ) return FALSE; init_text(&t); put_byte(&t, c); + if (c == '.') + is_decimal = 1; for(;;) { c = Speekcode(in); - if ( (c >= '0' && c <= '9') || c == '.' || c == '-' || c == '+' || c == 'e' || c == 'E' ) - { if ( put_byte(&t, c) != 0 ) + { if (preserve_precision && c == '.') + { is_decimal = 1; + (void)Sgetcode(in); + continue; + } + else if (c == 'e' || c == 'E') + { /* We cannot hope to have a perfect-precision result if the input contains an e + or E, so just give back a float in this case */ + is_decimal = 0; + } + else if (preserve_precision && is_decimal) + { decimal_places++; + } + if ( put_byte(&t, c) != 0 ) { rc = PL_resource_error("memory"); break; } @@ -126,11 +147,19 @@ json_read_number(term_t stream, term_t c0, term_t number) { rc = PL_resource_error("memory"); break; } - - rc = ( (tmp = PL_new_term_ref()) && - PL_chars_to_term(t.t, tmp) && - PL_unify(tmp, number) ); - + if (is_decimal) + { fid_t fid = PL_open_foreign_frame(); + term_t av = PL_new_term_refs(3); + rc = (PL_chars_to_term(t.t, av+0) && + PL_put_integer(av+1, decimal_places) && + PL_call_predicate(NULL, PL_Q_NORMAL, PREDICATE_mk_rational3, av) && + PL_unify(number, av+2)); + PL_close_foreign_frame(fid); + } else + { rc = ( (tmp = PL_new_term_ref()) && + PL_chars_to_term(t.t, tmp) && + PL_unify(tmp, number) ); + } break; } free_text(&t); @@ -302,7 +331,9 @@ json_write_indent(term_t stream, term_t indent, term_t tab) install_t install_json() -{ PL_register_foreign("json_read_number", 3, json_read_number, 0); +{ PREDICATE_mk_rational3 = PL_predicate("mk_rational", 3, "json"); + + PL_register_foreign("json_read_number", 4, json_read_number, 0); PL_register_foreign("json_skip_ws", 3, json_skip_ws, 0); PL_register_foreign("json_write_string", 2, json_write_string, 0); PL_register_foreign("json_write_indent", 3, json_write_indent, 0); diff --git a/json.pl b/json.pl index bc35484..d926fa1 100644 --- a/json.pl +++ b/json.pl @@ -142,10 +142,11 @@ end_of_file:ground = error, value_string_as:oneof([atom,string]) = atom, tag:atom = '', - default_tag:atom). + default_tag:atom, + decimal_as:oneof([float, rdiv]) = float). default_json_dict_options( - json_options(null, true, false, error, string, '', _)). + json_options(null, true, false, error, string, '', _, float)). /******************************* @@ -258,6 +259,10 @@ % The alternative is `string`, producing a packed string object. % Please note that `codes` or `chars` would produce ambiguous % output and are therefore not supported. +% - decimal_as(+Type) +% Prolog type used for non-integer numbers. Default is +% =float=. The alternative is =rdiv=, which produces a +% rdiv/2 term which guarantees no loss of precision. % % @see json_read_dict/3 to read a JSON term using the version 7 % extended data types. @@ -313,13 +318,19 @@ json_string_codes(C1, Stream, Codes), json_options_value_string_as(Options, Type), codes_to_type(Type, Codes, String). -json_term_top(0'-, Stream, Number, _Options) :- +json_term_top(0'-, Stream, Number, Options) :- !, - json_read_number(Stream, 0'-, Number). -json_term_top(D, Stream, Number, _Options) :- + ( json_options_decimal_as(Options, rdiv) + -> json_read_number(Stream, 0'-, true, Number) + ; json_read_number(Stream, 0'-, false, Number) + ). +json_term_top(D, Stream, Number, Options) :- between(0'0, 0'9, D), !, - json_read_number(Stream, D, Number). + ( json_options_decimal_as(Options, rdiv) + -> json_read_number(Stream, D, true, Number) + ; json_read_number(Stream, D, false, Number) + ). json_term_top(C, Stream, Constant, Options) :- json_read_constant(C, Stream, ID), json_constant(ID, Constant, Options). @@ -455,6 +466,11 @@ line_position(Read, LinePos), line_count(Read, Line). +mk_rational(Integer, NumberOfDecimals, Rational):- + Rational is Integer rdiv (10 ** NumberOfDecimals). + + + /******************************* * JSON OUTPUT * @@ -960,6 +976,11 @@ % Prolog type used for strings used as value. Default % is `string`. The alternative is `atom`, producing a % packed string object. +% * decimal_as(+Type) +% Prolog type used for non-integer numbers. Default is +% =float=. The alternative is =rdiv=, which produces a +% rdiv/2 term which guarantees no loss of precision. + json_read_dict(Stream, Dict) :- json_read_dict(Stream, Dict, []). @@ -991,6 +1012,10 @@ atomic(Value0), Value0 \== [], !, Value = Value0. +term_to_dict(Rational0, Rational, _Options) :- + rational(Rational0), + !, + Rational = Rational0. term_to_dict(List0, List, Options) :- is_list(List0), !,