Bug 34345 - gfortran compiles SLATEC library, but the executable fails
Summary: gfortran compiles SLATEC library, but the executable fails
Status: RESOLVED FIXED
Alias: None
Product: gcc
Classification: Unclassified
Component: fortran (show other bugs)
Version: unknown
: P3 normal
Target Milestone: 4.3.0
Assignee: Tobias Burnus
URL:
Keywords:
Depends on:
Blocks:
 
Reported: 2007-12-05 11:11 UTC by Fabio Subba
Modified: 2007-12-08 21:59 UTC (History)
2 users (show)

See Also:
Host:
Target:
Build:
Known to work:
Known to fail:
Last reconfirmed: 2007-12-06 21:34:52


Attachments

Note You need to log in before you can comment on or make changes to this bug.
Description Fabio Subba 2007-12-05 11:11:12 UTC
Overview Description: 
 A very simple TEST.F code using D1MACH.F from SLATEC (to initialize machine constants) compiles correctly using GFORTRAN, but the produced executable gives nonsense results.

Steps to Reproduce:
1. Save the following program TEST.F and the routine D1MACH.F

**************
      program test
      implicit none
      real(8) d1mach
      write(6,*)1,d1mach(1)
      write(6,*)2,d1mach(2)
      write(6,*)3,d1mach(3)
      write(6,*)4,d1mach(4)
      write(6,*)5,d1mach(5)
      stop
      end program test
**************
      DOUBLE PRECISION FUNCTION D1MACH (I)
C
      INTEGER SMALL(4)
      INTEGER LARGE(4)
      INTEGER RIGHT(4)
      INTEGER DIVER(4)
      INTEGER LOG10(4)
C
      DOUBLE PRECISION DMACH(5)
      SAVE DMACH

      EQUIVALENCE (DMACH(1),SMALL(1))
      EQUIVALENCE (DMACH(2),LARGE(1))
      EQUIVALENCE (DMACH(3),RIGHT(1))
      EQUIVALENCE (DMACH(4),DIVER(1))
      EQUIVALENCE (DMACH(5),LOG10(1))
C
C     MACHINE CONSTANTS FOR THE INTEL i860
C
      DATA DMACH(1) / Z'0010000000000000' /
      DATA DMACH(2) / Z'7FEFFFFFFFFFFFFF' /
      DATA DMACH(3) / Z'3CA0000000000000' /
      DATA DMACH(4) / Z'3CB0000000000000' /
      DATA DMACH(5) / Z'3FD34413509F79FF' /
C***FIRST EXECUTABLE STATEMENT  D1MACH
      D1MACH = DMACH(I)
      RETURN
C
      END
**************

2. Compile with the command 
       gfortran test.f d1mach.f -o test.exe

3. Run ./test.exe 


Actual results:
./test.exe
           1   4503599627370496.0     
           2  9.21886843722740531E+018
           3  4.36849163854938112E+018
           4  4.37299523817675162E+018
           5  4.59909449422310451E+018


Expected results:
./test.exe

 1 2.2250738585072014E-308
 2 1.7976931348623157E+308
 3 1.1102230246251565E-16
 4 2.220446049250313E-16
 5 0.3010299956639812

Build date and platform:
 Dec.05.2007, WinXP (cygwin environment)


Additional information:

1. gfortran --version
GNU Fortran (GCC) 4.3.0 20071017 (experimental) [trunk revision 129419]

2. gcc --version
gcc.exe (GCC) 4.3.0 20071017 (experimental) [trunk revision 129419]
Comment 1 Tobias Burnus 2007-12-05 12:55:07 UTC
I think the problem is the interpretation of:

      DATA DMACH(1) / Z'0010000000000000' /

as DMACH is REAL. The Fortran standard only allows BOZ in DATA for integers.
Fortran 2003 also allows, e.g.,
     real :: r = REAL(Z'00000000')
where REAL() is mandatory.

The problem for you program is that gfortran interprets Z'0010000000000000' as bit-pattern for an integer and converts the integer *then* to a REAL.

Other compilers regard that BOZ as bitpattern of the REAL variable. This bug is probably a duplicate of either of PR 34342, PR 18026 or PR 29471.
Comment 2 Jerry DeLisle 2007-12-06 03:42:16 UTC
Reading through PR 18026 I am convinced this is a duplicate.  We need to decide how we want to handle this situation.  It looks like at least one other compiler treats the boz as an integer and converts to real for the case of f95 and treats it as a direct map to real for f2003.

Should we take a vote?
Comment 3 kargls 2007-12-06 04:39:49 UTC
(In reply to comment #2)
> Reading through PR 18026 I am convinced this is a duplicate.  We need to decide
> how we want to handle this situation.  It looks like at least one other
> compiler treats the boz as an integer and converts to real for the case of f95
> and treats it as a direct map to real for f2003.
> 
> Should we take a vote?

My vote is gfortran is doing the correct thing. The user
needs to read and understand the standard.  Then, the
the user can use TRANSFER() as intended by J3.

In particular, a DATA statement is essentially an assignment.
In an assignment the RHS is evaluated without reference to the
LHS type, kind type parameter, or rank.

If you want to promote a BOZ to some glorified representation 
of any numeric value, then you'll need to introduce BT_BOZ,
and add a member to gfc_symbol to hold the BOZ string and do
the conversion to the what the user wants at the last moment.
This, of course, violates the independence of the RHS-LHS 
assumption.


Comment 4 Dale Ranta 2007-12-06 14:56:33 UTC
I have several programs (f77 and f90) that do this and their intent is clear - just put the bit patterns into to words as requested - no data conversion - no range checking. BOZ seems to have been created for this purpose, but the committee seems the have lost track of why programs need specific bit patterns and how they are used. How about adding something like a "-fhex" enhancement that does this ?
Comment 5 kargls 2007-12-06 19:13:44 UTC
(In reply to comment #4)
> I have several programs (f77 and f90) that do this and their intent is clear -
> just put the bit patterns into to words as requested - no data conversion - no
> range checking.

Which is of course nonstandard.  The F95 standard is quite clear on
where a BOZ can appear and that a BOZ is an integer.

> BOZ seems to have been created for this purpose,

Maybe.  BOZ doesn't appear in my copy of the F77 standard
(on a quick scan), and I don't have a copy of F90 to
check.  However, F95 is quite clear on BOZ 

> but the committee seems the have lost track of why programs need specific
> bit patterns and how they are used.

See the TRANSFER intrinsic.  I think J3 recognized the problems with
specify a bit pattern.  J3 also appears to have recognized the limitations
on TRANSFER because they have allowed BOZ to appear in REAL, INT, DBLE, and
COMPLX.  Unfortunately, J3 didn't define what this means!

> How about adding something like a "-fhex" enhancement
> that does this ?

This is a very nontrivial option to add, and it opens the
door to (mis)feature creep of a extension.

What happens with

  subroutine add(y, x)
  real x, y
  do i = 1, 10000000
     x = y + Z'deadbeef' + 42
  end do
  end subroutine

Is Z'deadbeef' an integer or a real?  If one uses the normal rules of
Fortran and using BOZ for short, a compiler can do either

  x = (y + BOZ) + 42  ! Conversion of BOZ to real???

or
 
  x = y + (BOZ + 42)  ! Conversion of BOZ to integer???

Note, the latter form allows the compiler to constant fold 
and hoist (BOZ + 42) out of the loop; thereby saving 1 million
additions.  I suppose one could argue that the scanner can
recognize that a BOZ is present in the expression and then 
promote it to the highest type.  The above would then become

  x = y + REAL(BOZ, kind(y)) + 42 

or, perhaps,

  x = y + REAL(BOZ, kind(x)) + 42  ! x is double prec and y is REAL?

because the programmer obviously meant the BOZ should have the 
same kind as the LHS.  In the end, one would probably want

  x = y + REAL(BOZ, max(kind(x), kind(y))) + 42

to avoid possible loss of precision in the BOZ.


Here's a more complicated example

  module fun
    interface whoops
       module procedure p_int
       module procedure p_real
    end interface
    contains
       subroutine p_int(x)
         integer, intent(in) :: x
         print '(I0)', x
       end subroutine p_int
       subroutine p_real(x)
         real, intent(in) :: x
         print '(ES12.4)', x
       end subroutine p_real
   end module fun

   use fun
   call whoops(Z'deadbeef')  ! Is this an integer or real???
   end program

I suppose that one can argue that gfortran can restrict BOZ to
the simplest form of an initialization expression.

  real, parameter :: x = z'deadbeef'    ! Allowed real bit pattern
  real, parameter :: y = z'deadbeef'+1. ! Not allowed, BOZ in a RHS expression

This argument, IMHO, boils down to "I don't care what gfortan does as
along as it does what I want."

Now for the fun.  How is z'deadbeef' interpreted on big and little endian
hardware?  Before you scoff, realize that gfortran has to convert the
BOZ into something that MPFR can digest.  This means that gfortran has
do something like  z'deadbeef' --> -0X3.ABC123p2 where the number 
following p is the exponent in base 16.  I've, of course, not discussed 
whether the exponent portion of z'deadbeef' is a biased or unbiased
exponent.  I guess gfortran will assume that it is biased.  Now, what
integer value are you subtracting to get the 2 that follows the p?
There's even more fun if the BOZ is too small.  What does gfortran do
with z'dead'?  Is this z'dead0000' or z'0000dead' or is this literally
only 2 bytes and the other 2 bytes are whatever is currently in memory?

Having spent a considerable amount of time thinking about ways to
"fix", I can assure you that it isn't a simple matter of just adding
-fhex.
Comment 6 Tobias Burnus 2007-12-06 21:34:52 UTC
> > but the committee seems the have lost track of why programs need specific
> > bit patterns and how they are used.
> 
> See the TRANSFER intrinsic.  I think J3 recognized the problems with
> specify a bit pattern.  J3 also appears to have recognized the limitations
> on TRANSFER because they have allowed BOZ to appear in REAL, INT, DBLE, and
> COMPLX.  Unfortunately, J3 didn't define what this means!

Well, if they had specified what it means, having different hard ware (e.g. decimal numbers in silicon) would have been more complicated.

> > How about adding something like a "-fhex" enhancement
> > that does this ?
> This is a very nontrivial option to add, and it opens the
> door to (mis)feature creep of a extension.

Well, to allow BOZ in DATA statements (for non-integers) and for
  real r = 'b0'z
it is relatively easy.

> What happens with
>      x = y + Z'deadbeef' + 42
> Is Z'deadbeef' an integer or a real?

With my patch, it is an integer, only in
   variable = boz
boz might be a real/complex bit patter. As soon as you have expressions on the right-hand side, the boz is regarded as integer.

I find this clear than all the "boz + integer" is "integer+integer" but "boz + 1.0" is "real+real" convention some compilers have.

>    call whoops(Z'deadbeef')  ! Is this an integer or real???

With my patch it is an integer (no assignment and not in a DATA statement).

> I suppose that one can argue that gfortran can restrict BOZ to
> the simplest form of an initialization expression.
> 
>   real, parameter :: x = z'deadbeef'    ! Allowed real bit pattern
>   real, parameter :: y = z'deadbeef'+1. ! Not allowed, BOZ in a RHS expression

This plus BOZ in DATA statements is what my patch (to be submitted in a moment) does. (Well, it does not reject the second version but regards it as integer pattern.) The patch also gives some better diagnostic with -std=f95 and -Wsurprising.
Comment 7 Tobias Burnus 2007-12-08 21:47:18 UTC
Subject: Bug 34345

Author: burnus
Date: Sat Dec  8 21:46:56 2007
New Revision: 130713

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=130713
Log:
2007-12-08  Tobias Burnus  <burnus@net-b.de>

        PR fortran/34342
        PR fortran/34345
        PR fortran/18026
        PR fortran/29471

        * gfortran.texi (BOZ literal constants): Improve documentation
        and adapt for BOZ changes.
        * Make-lang.ini (resolve.o): Add target-memory.h dependency.
        * gfortran.h (gfc_expr): Add is_boz flag.
        * expr.c: Include target-memory.h.
        (gfc_check_assign): Support transferring BOZ for real/cmlx.
        * resolve.c: Include target-memory.h
        (resolve_ordinary_assign): Support transferring BOZ for real/cmlx.
        * target-memory.c (gfc_convert_boz): New function.
        * target-memory.c (gfc_convert_boz): Add prototype.
        * primary.c (match_boz_constant): Set is_boz, enable F95 error
        also without -pedantic, and allow for Fortran 2003 BOZ.
        (match_real_constant): Fix comment.
        * simplify.c
        * (simplify_cmplx,gfc_simplify_dble,gfc_simplify_float,
        gfc_simplify_real): Support Fortran 2003 BOZ.

2007-12-08  Tobias Burnus  <burnus@net-b.de>

        PR fortran/34342
        PR fortran/34345
        PR fortran/18026
        PR fortran/29471

        * gfortran.dg/boz_8.f90: New.
        * gfortran.dg/boz_9.f90: New.
        * gfortran.dg/boz_10.f90: New.
        * gfortran.dg/boz_7.f90: Update dg-warning.
        * gfortran.dg/pr16433.f: Add dg-error.
        * gfortan.dg/ibits.f90: Update dg-warning.
        * gfortran.dg/unf_io_convert_1.f90: Update/delete dg-warning.
        * gfortran.dg/unf_io_convert_2.f90: Ditto.


Added:
    trunk/gcc/testsuite/gfortran.dg/boz_10.f90
    trunk/gcc/testsuite/gfortran.dg/boz_8.f90
    trunk/gcc/testsuite/gfortran.dg/boz_9.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/Make-lang.in
    trunk/gcc/fortran/expr.c
    trunk/gcc/fortran/gfortran.h
    trunk/gcc/fortran/gfortran.texi
    trunk/gcc/fortran/primary.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/simplify.c
    trunk/gcc/fortran/target-memory.c
    trunk/gcc/fortran/target-memory.h
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/boz_7.f90
    trunk/gcc/testsuite/gfortran.dg/ibits.f90
    trunk/gcc/testsuite/gfortran.dg/pr16433.f
    trunk/gcc/testsuite/gfortran.dg/unf_io_convert_1.f90
    trunk/gcc/testsuite/gfortran.dg/unf_io_convert_2.f90

Comment 8 Tobias Burnus 2007-12-08 21:59:54 UTC
FIXED on the trunk (4.3.0).

gfortran now transfers
   DATA DMACH(2) / Z'7FEFFFFFFFFFFFFF' /
bitwise for real/complex variables. Note: For -std=f95/f2003 this is rejected.

For details how non-standard BOZ are (now) interpreted, see
http://gcc.gnu.org/onlinedocs/gfortran/BOZ-literal-constants.html

(Wait a day for the update of that page.)