[I am going to try to maintain a grip on my professionalism.  A
professional does not give in to the urge to say, "I told you so".]

This program, compiled with the most recent level of patching, is
generating the result

        IDENTIFICATION DIVISION.
        PROGRAM-ID. float-sub1.
        DATA DIVISION.
        WORKING-STORAGE SECTION.
        01 S1 PIC 999V99 DISPLAY        VALUE 111.11 .
        01 D1 PIC 999V99 DISPLAY        VALUE 666.66 .
        PROCEDURE DIVISION.
            DISPLAY "S1 should be 111.11"
            DISPLAY "S1        is " S1.
            DISPLAY "D1 should be 666.66"
            DISPLAY "D1        is " D1.
        END PROGRAM float-sub1.

    S1 should be 111.11
    S1        is 111.10
    D1 should be 666.66
    D1        is 666.66

Those values are NumericDisplay.  They are each stored as five ASCII
characters.  They are not floating point numbers.  They never are floating
point numbers.  They are operated on as the smallest binary integers I can
make them be.  I do that partly for speed, although the actual operations
are swamped by the conversions from string to binary.  Mainly I operate on
them as fixed-point values for the sake of accuracy.  In fixed-point, 0.1
is 0.1

But, many months back, I allowed my concerns about having them
*initialized* from the _Float128 "value" member of the cbl_field_t to be
overridden.  

I worked out ways of making that work, but I have never been happy about
it, and now those chickens have come home to roost. 

So.  Anyway.  Jim and I may end up discussing this again, and I may well
end up refactoring the code so as to *not* use the floating-point "value"
member for 
initialization of fixed-point variables.  But I can't try to do that while
you are trying to fix the front-end arithmetic.

In any event, this is the next obvious cause of reasons for test failures.


I look forward to seeing what marvels you perform while I am sleeping.

Oh, wait.  It's the weekend.  Maybe the marvels will be postponed until
Monday.

All this said, I am more than a little astonished at the progress that's
being made here.

Bob D.

> -----Original Message-----
> From: Richard Biener <rguent...@suse.de>
> Sent: Friday, March 21, 2025 15:25
> To: Jakub Jelinek <ja...@redhat.com>
> Cc: Robert Dubner <rdub...@symas.com>; gcc-patches@gcc.gnu.org
> Subject: Re: [PATCH] change cbl_field_data_t::etc_t::value from
_Float128
> to tree
> 
> On Fri, 21 Mar 2025, Jakub Jelinek wrote:
> 
> > On Fri, Mar 21, 2025 at 01:47:05PM -0500, Robert Dubner wrote:
> > > > -----Original Message-----
> > > > From: Robert Dubner <rdub...@symas.com>
> > > > Sent: Friday, March 21, 2025 14:23
> > > > To: Richard Biener <rguent...@suse.de>
> > > > Cc: gcc-patches@gcc.gnu.org; Jakub Jelinek <ja...@redhat.com>
> > > > Subject: RE: [PATCH] change cbl_field_data_t::etc_t::value from
> > > _Float128
> > > > to tree
> > > >
> > > > Crossed in the mail.
> > > >
> > > > I applied your fixes below.
> > > >
> > > > The output of the one-liner program is now 1.2345678E+07, as
> expected.
> > > >
> > > > The .00 instead of .01 problem still exists; source code coming
> soon.
> > >
> > > This program
> > >
> > >         IDENTIFICATION DIVISION.
> > >         PROGRAM-ID.  numeds.
> > >         DATA DIVISION.
> > >         WORKING-STORAGE SECTION.
> > >         01 VARP9  PIC P9  VALUE 0.01.
> > >         PROCEDURE DIVISION.
> > >             DISPLAY "VARP9 should be .01"
> > >             DISPLAY "VARP9        is " VARP9.
> > >         END PROGRAM numeds.
> > >
> > > generates
> > >
> > >      VARP9 should be .01
> > >      VARP9        is .00
> > >
> > > As usual, it's COBOL, so it comes with a lecture:
> > >
> > > The variable
> > >
> > >         01 VARP9  PIC P9  VALUE 0.01.
> > >
> > > means that it is a NUMERIC DISPLAY variable, which is represented in
> > > memory as ASCII digits.  There is but one '9' in the PICTURE, so it
is
> a
> > > one-digit number.  The prefix 'P', in the "P9", means that the
actual
> > > value of the variable is scaled by 0.01  So, the value 0.01 is
> represented
> > > in memory by a single "1".
> > >
> > > If it were "PIC 9PPP", then 1,000 would be represented in memory as
a
> > > single "1".
> >
> > The following incremental patch should fix that (but otherwise
> untested).
> >
> > --- gcc/cobol/parse.y.jj    2025-03-21 17:49:43.571440176 +0100
> > +++ gcc/cobol/parse.y       2025-03-21 20:15:24.852414777 +0100
> > @@ -4331,7 +4331,8 @@ value_clause:   VALUE all LITERAL[lit] {
> >                    cbl_field_t *field = current_field();
> >                    auto orig_str = original_number();
> >               REAL_VALUE_TYPE orig_val;
> > -             real_from_string (&orig_val, orig_str);
> > +             real_from_string3 (&orig_val, orig_str,
> > +                                TYPE_MODE (float128_type_node));
> >                    char *initial = NULL;
> >
> >                    if( real_identical (&orig_val, &$value) ) {
> > @@ -6922,7 +6923,8 @@ cce_expr:       cce_factor
> >  cce_factor:     NUMSTR {
> >                    /* ???  real_from_string does not allow arbitrary
> radix.  */
> >                    // $$ = numstr2i($1.string, $1.radix);
> > -             real_from_string (&$$, $1.string);
> > +             real_from_string3 (&$$, $1.string,
> > +                                TYPE_MODE (float128_type_node));
> >                  }
> >                  ;
> >
> >
> > The old code was just using _Float128 which has the IEEE quad
precision,
> > but REAL_VALUE_TYPE in GCC actually has larger internal precision than
> that,
> > so if it isn't rounded to the IEEE quad precision first and builds
> REAL_CST,
> > it isn't the expected 0.0100000000000000000000000000000000002 but
> > 0.009999999999...
> 
> Hmm, but I see that digits_from_float128 from
> 
> (gdb) p debug (value)
> 1.0e+0
> 
> produces via real_to_integer zero:
> 
> (gdb) s
> real_to_integer (r=0x7fffffff69a0, fail=0x7fffffff685f, precision=128)
>     at ../../src/gcc/gcc/real.cc:1483
> (gdb) p debug (*r)
> 1.0e+0
> (gdb) n
> 1485      switch (r->cl)
> (gdb)
> 1502          if (r->decimal)
> (gdb)
> 1505          exp = REAL_EXP (r);
> (gdb)
> 1506          if (exp <= 0)
> (gdb)
> 1507            goto underflow;
> (gdb)
> 1489          return wi::zero (precision);
> 
> we've come from initial_from_float128 which does
> 
>       REAL_VALUE_TYPE pow10
>         = real_powi10 (field->data.digits + field->data.rdigits);
>       real_arithmetic (&value, MULT_EXPR, &value, &pow10);
> 
> which produces the 1.0e+0 - do I need to process this to be "normal"?
> 
> Richard.

Reply via email to