OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [nearest_2.f90] - Rev 749

Go to most recent revision | Compare with Previous | Blame | View Log

! { dg-do run }
! { dg-options "-fno-range-check" }
! { dg-add-options ieee }
!
! PR fortran/34192
!
! Test compile-time implementation of NEAREST
!
program test
  implicit none

! Single precision

  ! 0+ > 0
  if (nearest(0.0, 1.0) &
      <= 0.0) &
    call abort()
  ! 0++ > 0+
  if (nearest(nearest(0.0, 1.0), 1.0) &
      <= nearest(0.0, 1.0)) &
    call abort()
  ! 0+++ > 0++
  if (nearest(nearest(nearest(0.0, 1.0), 1.0), 1.0) &
      <= nearest(nearest(0.0, 1.0), 1.0)) &
    call abort()
  ! 0+- = 0
  if (nearest(nearest(0.0, 1.0), -1.0) &
      /= 0.0) &
    call abort()
  ! 0++- = 0+
  if (nearest(nearest(nearest(0.0, 1.0), 1.0), -1.0) &
      /= nearest(0.0, 1.0)) &
    call abort()
  ! 0++-- = 0
  if (nearest(nearest(nearest(nearest(0.0, 1.0), 1.0), -1.0), -1.0) &
      /= 0.0) &
    call abort()

  ! 0- < 0
  if (nearest(0.0, -1.0) &
      >= 0.0) &
    call abort()
  ! 0-- < 0+
  if (nearest(nearest(0.0, -1.0), -1.0) &
      >= nearest(0.0, -1.0)) &
    call abort()
  ! 0--- < 0--
  if (nearest(nearest(nearest(0.0, -1.0), -1.0), -1.0) &
      >= nearest(nearest(0.0, -1.0), -1.0)) &
    call abort()
  ! 0-+ = 0
  if (nearest(nearest(0.0, -1.0), 1.0) &
      /= 0.0) &
    call abort()
  ! 0--+ = 0-
  if (nearest(nearest(nearest(0.0, -1.0), -1.0), 1.0) &
      /= nearest(0.0, -1.0)) &
    call abort()
  ! 0--++ = 0
  if (nearest(nearest(nearest(nearest(0.0, -1.0), -1.0), 1.0), 1.0) &
      /= 0.0) &
    call abort()

  ! 42++ > 42+
  if (nearest(nearest(42.0, 1.0), 1.0) &
      <= nearest(42.0, 1.0)) &
    call abort()
  ! 42-- < 42-
  if (nearest(nearest(42.0, -1.0), -1.0) &
      >= nearest(42.0, -1.0)) &
    call abort()
  ! 42-+ = 42
  if (nearest(nearest(42.0, -1.0), 1.0) &
      /= 42.0) &
    call abort()
  ! 42+- = 42
  if (nearest(nearest(42.0, 1.0), -1.0) &
      /= 42.0) &
    call abort()

  ! INF+ = INF
  if (nearest(1.0/0.0, 1.0) /= 1.0/0.0) call abort()
  ! -INF- = -INF
  if (nearest(-1.0/0.0, -1.0) /= -1.0/0.0) call abort()
  ! NAN- = NAN
  if (.not.isnan(nearest(0.0d0/0.0,  1.0))) call abort()
  ! NAN+ = NAN
  if (.not.isnan(nearest(0.0d0/0.0, -1.0))) call abort()

! Double precision

  ! 0+ > 0
  if (nearest(0.0d0, 1.0) &
      <= 0.0d0) &
    call abort()
  ! 0++ > 0+
  if (nearest(nearest(0.0d0, 1.0), 1.0) &
      <= nearest(0.0d0, 1.0)) &
    call abort()
  ! 0+++ > 0++
  if (nearest(nearest(nearest(0.0d0, 1.0), 1.0), 1.0) &
      <= nearest(nearest(0.0d0, 1.0), 1.0)) &
    call abort()
  ! 0+- = 0
  if (nearest(nearest(0.0d0, 1.0), -1.0) &
      /= 0.0d0) &
    call abort()
  ! 0++- = 0+
  if (nearest(nearest(nearest(0.0d0, 1.0), 1.0), -1.0) &
      /= nearest(0.0d0, 1.0)) &
    call abort()
  ! 0++-- = 0
  if (nearest(nearest(nearest(nearest(0.0d0, 1.0), 1.0), -1.0), -1.0) &
      /= 0.0d0) &
    call abort()

  ! 0- < 0
  if (nearest(0.0d0, -1.0) &
      >= 0.0d0) &
    call abort()
  ! 0-- < 0+
  if (nearest(nearest(0.0d0, -1.0), -1.0) &
      >= nearest(0.0d0, -1.0)) &
    call abort()
  ! 0--- < 0--
  if (nearest(nearest(nearest(0.0d0, -1.0), -1.0), -1.0) &
      >= nearest(nearest(0.0d0, -1.0), -1.0)) &
    call abort()
  ! 0-+ = 0
  if (nearest(nearest(0.0d0, -1.0), 1.0) &
      /= 0.0d0) &
    call abort()
  ! 0--+ = 0-
  if (nearest(nearest(nearest(0.0d0, -1.0), -1.0), 1.0) &
      /= nearest(0.0d0, -1.0)) &
    call abort()
  ! 0--++ = 0
  if (nearest(nearest(nearest(nearest(0.0d0, -1.0), -1.0), 1.0), 1.0) &
      /= 0.0d0) &
    call abort()

  ! 42++ > 42+
  if (nearest(nearest(42.0d0, 1.0), 1.0) &
      <= nearest(42.0d0, 1.0)) &
    call abort()
  ! 42-- < 42-
  if (nearest(nearest(42.0d0, -1.0), -1.0) &
      >= nearest(42.0d0, -1.0)) &
    call abort()
  ! 42-+ = 42
  if (nearest(nearest(42.0d0, -1.0), 1.0) &
      /= 42.0d0) &
    call abort()
  ! 42+- = 42
  if (nearest(nearest(42.0d0, 1.0), -1.0) &
      /= 42.0d0) &
    call abort()

  ! INF+ = INF
  if (nearest(1.0d0/0.0d0, 1.0) /= 1.0d0/0.0d0) call abort()
  ! -INF- = -INF
  if (nearest(-1.0d0/0.0d0, -1.0) /= -1.0d0/0.0d0) call abort()
  ! NAN- = NAN
  if (.not.isnan(nearest(0.0d0/0.0,  1.0))) call abort()
  ! NAN+ = NAN
  if (.not.isnan(nearest(0.0d0/0.0, -1.0))) call abort()
end program test

Go to most recent revision | Compare with Previous | Blame | View Log

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.