blob: b77a90c240dc4b71111b4015a54d3b4750304145 [file] [log] [blame]
! { dg-do run }
! { dg-require-effective-target sse2_runtime { target { i?86-*-* x86_64-*-* } } }
! { dg-additional-options "-msse2 -mfpmath=sse" { target { i?86-*-* x86_64-*-* } } }
program test_underflow_control
use ieee_arithmetic
use iso_fortran_env
logical l
real, volatile :: x
double precision, volatile :: y
integer, parameter :: kx = kind(x), ky = kind(y)
if (ieee_support_underflow_control(x)) then
x = tiny(x)
call ieee_set_underflow_mode(.true.)
x = x / 2000._kx
if (x == 0) call abort
call ieee_get_underflow_mode(l)
if (.not. l) call abort
x = tiny(x)
call ieee_set_underflow_mode(.false.)
x = x / 2000._kx
if (x > 0) call abort
call ieee_get_underflow_mode(l)
if (l) call abort
end if
if (ieee_support_underflow_control(y)) then
y = tiny(y)
call ieee_set_underflow_mode(.true.)
y = y / 2000._ky
if (y == 0) call abort
call ieee_get_underflow_mode(l)
if (.not. l) call abort
y = tiny(y)
call ieee_set_underflow_mode(.false.)
y = y / 2000._ky
if (y > 0) call abort
call ieee_get_underflow_mode(l)
if (l) call abort
end if
end program