This is the mail archive of the gcc-bugs@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

[Bug fortran/88342] Possible bug with IEEE_POSITIVE_INF and -ffpe-trap=overflow


https://gcc.gnu.org/bugzilla/show_bug.cgi?id=88342

kargl at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Priority|P3                          |P4

--- Comment #3 from kargl at gcc dot gnu.org ---
(In reply to kargl from comment #2)
> (In reply to kargl from comment #1)
> > (In reply to Matt Thompson from comment #0)
> > > All,
> > > 
> > > A colleague of mine encountered an issue with 8.2.0 (but it's also in 7.3.0
> > > at least). We believe it might be a bug since our reading of the Standard
> > > seems to make it legal.
> > > 
> > > Namely if this program:
> > > 
> > > PROGRAM test
> > >    USE, INTRINSIC :: ieee_arithmetic
> > >    IMPLICIT NONE
> > >    REAL :: inf
> > >    inf = IEEE_VALUE(inf,  IEEE_POSITIVE_INF)
> > > END PROGRAM test
> > > 
> > > is compiled with -ffpe-trap=overflow the code FPEs:
> > 
> > gfortran's IEEE modules and the -ffpe-trap option are independent
> > of each other.  As the manual states, -ffpe-trap is a *debugging*
> > option, and will enabling traps on floating point exceptions.  You
> > specifically requested an overflow trap.  What do you expect to
> > happen?
> > 
> > The likely correct solution is to manipulate the halting 
> > behavior with a combination of IEEE_GET_HALTING_MODE and
> > IEEE_SET_HALTING_MODE.  In fact, F2018, 17.11.6 contains
> > this exact example.
> > 
> >    Example. To store the halting mode for IEEE_OVERFLOW, do a
> >    calculation without halting, and restore the halting mode later:
> > 
> >    USE, INTRINSIC :: IEEE_ARITHMETIC
> >    LOGICAL HALTING
> >    ...
> >    CALL IEEE_GET_HALTING_MODE (IEEE_OVERFLOW, HALTING) ! Store halting mode
> >    CALL IEEE_SET_HALTING_MODE (IEEE_OVERFLOW, .FALSE.) ! No halting
> >    ... ! calculation without halting
> >    CALL IEEE_SET_HALTING_MODE (IEEE_OVERFLOW, HALTING) ! Restore halting mode
> > 
> > whether or not these functions works is something that I
> > haven't investigated.
> 
> Just tested.
> 
> program test
>    use, intrinsic :: ieee_arithmetic
>    implicit none
>    real :: inf
>    logical h
>    call ieee_get_halting_mode(ieee_overflow, h)       ! store halting mode
>    call ieee_set_halting_mode(ieee_overflow, .false.) ! no halting
>    inf = ieee_value(inf, ieee_positive_inf)
>    print *, inf
>    call ieee_set_halting_mode(ieee_overflow, h)       ! restore halting mode
> end program test
> 
> % gfcx -o z a.f90 && ./z
>          Infinity
> % gfcx -o z -ffpe-trap=overflow a.f90 && ./z
>          Infinity
> 
> This seems to give the desired behavior.

Something like the following is probably want people want.
I don't know how robust this is.

Index: libgfortran/ieee/ieee_arithmetic.F90
===================================================================
--- libgfortran/ieee/ieee_arithmetic.F90        (revision 266766)
+++ libgfortran/ieee/ieee_arithmetic.F90        (working copy)
@@ -861,6 +861,7 @@ contains

     real(kind=4), intent(in) :: X
     type(IEEE_CLASS_TYPE), intent(in) :: CLASS
+    logical flag

     select case (CLASS%hidden)
       case (1)     ! IEEE_SIGNALING_NAN
@@ -888,8 +889,15 @@ contains
       case (9)     ! IEEE_POSITIVE_NORMAL
         res = 42
       case (10)    ! IEEE_POSITIVE_INF
+        if (ieee_support_halting(ieee_overflow)) then
+           call ieee_get_halting_mode(ieee_overflow, flag)
+           call ieee_set_halting_mode(ieee_overflow, .false.)
+        end if
         res = huge(res)
         res = res * res
+        if (ieee_support_halting(ieee_overflow)) then
+           call ieee_set_halting_mode(ieee_overflow, flag)
+        end if
       case default ! IEEE_OTHER_VALUE, should not happen
         res = 0
      end select

Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]