URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [nan_1.f90] - Rev 694
Compare with Previous | Blame | View Log
! Test if MIN and MAX intrinsics behave correctly when passed NaNs! as arguments!! { dg-do run }! { dg-add-options ieee }! { dg-skip-if "NaN not supported" { spu-*-* } { "*" } { "" } }!module aux2interface isnanmodule procedure isnan_rmodule procedure isnan_dend interface isnaninterface isinfmodule procedure isinf_rmodule procedure isinf_dend interface isinfcontainspure function isnan_r(x) result (isnan)logical :: isnanreal, intent(in) :: xisnan = (.not.(x == x))end function isnan_rpure function isnan_d(x) result (isnan)logical :: isnandouble precision, intent(in) :: xisnan = (.not.(x == x))end function isnan_dpure function isinf_r(x) result (isinf)logical :: isinfreal, intent(in) :: xisinf = (x > huge(x)) .or. (x < -huge(x))end function isinf_rpure function isinf_d(x) result (isinf)logical :: isinfdouble precision, intent(in) :: xisinf = (x > huge(x)) .or. (x < -huge(x))end function isinf_dend module aux2program testuse aux2implicit nonereal :: nan, large, inf! Create a NaN and check itnan = 0nan = nan / nanif (nan == nan .or. nan > nan .or. nan < nan .or. nan >= nan &.or. nan <= nan) call abortif (isnan (2.d0) .or. (.not. isnan(nan)) .or. &(.not. isnan(real(nan,kind=kind(2.d0))))) call abort! Create an INF and check itlarge = huge(large)inf = 2 * largeif (isinf(nan) .or. isinf(large) .or. .not. isinf(inf)) call abortif (isinf(-nan) .or. isinf(-large) .or. .not. isinf(-inf)) call abort! Check that MIN and MAX behave correctlyif (max(2.0, nan) /= 2.0) call abortif (min(2.0, nan) /= 2.0) call abortif (max(nan, 2.0) /= 2.0) call abortif (min(nan, 2.0) /= 2.0) call abortif (max(2.d0, nan) /= 2.d0) call abort ! { dg-warning "Extension: Different type kinds" }if (min(2.d0, nan) /= 2.d0) call abort ! { dg-warning "Extension: Different type kinds" }if (max(nan, 2.d0) /= 2.d0) call abort ! { dg-warning "Extension: Different type kinds" }if (min(nan, 2.d0) /= 2.d0) call abort ! { dg-warning "Extension: Different type kinds" }if (.not. isnan(min(nan,nan))) call abortif (.not. isnan(max(nan,nan))) call abort! Same thing, with more argumentsif (max(3.0, 2.0, nan) /= 3.0) call abortif (min(3.0, 2.0, nan) /= 2.0) call abortif (max(3.0, nan, 2.0) /= 3.0) call abortif (min(3.0, nan, 2.0) /= 2.0) call abortif (max(nan, 3.0, 2.0) /= 3.0) call abortif (min(nan, 3.0, 2.0) /= 2.0) call abortif (max(3.d0, 2.d0, nan) /= 3.d0) call abort ! { dg-warning "Extension: Different type kinds" }if (min(3.d0, 2.d0, nan) /= 2.d0) call abort ! { dg-warning "Extension: Different type kinds" }if (max(3.d0, nan, 2.d0) /= 3.d0) call abort ! { dg-warning "Extension: Different type kinds" }if (min(3.d0, nan, 2.d0) /= 2.d0) call abort ! { dg-warning "Extension: Different type kinds" }if (max(nan, 3.d0, 2.d0) /= 3.d0) call abort ! { dg-warning "Extension: Different type kinds" }if (min(nan, 3.d0, 2.d0) /= 2.d0) call abort ! { dg-warning "Extension: Different type kinds" }if (.not. isnan(min(nan,nan,nan))) call abortif (.not. isnan(max(nan,nan,nan))) call abortif (.not. isnan(min(nan,nan,nan,nan))) call abortif (.not. isnan(max(nan,nan,nan,nan))) call abortif (.not. isnan(min(nan,nan,nan,nan,nan))) call abortif (.not. isnan(max(nan,nan,nan,nan,nan))) call abort! Large values, INF and NaNsif (.not. isinf(max(large, inf))) call abortif (isinf(min(large, inf))) call abortif (.not. isinf(max(nan, large, inf))) call abortif (isinf(min(nan, large, inf))) call abortif (.not. isinf(max(large, nan, inf))) call abortif (isinf(min(large, nan, inf))) call abortif (.not. isinf(max(large, inf, nan))) call abortif (isinf(min(large, inf, nan))) call abortif (.not. isinf(min(-large, -inf))) call abortif (isinf(max(-large, -inf))) call abortif (.not. isinf(min(nan, -large, -inf))) call abortif (isinf(max(nan, -large, -inf))) call abortif (.not. isinf(min(-large, nan, -inf))) call abortif (isinf(max(-large, nan, -inf))) call abortif (.not. isinf(min(-large, -inf, nan))) call abortif (isinf(max(-large, -inf, nan))) call abortend program test! { dg-final { cleanup-modules "aux2" } }
