2017-11-09 Steven G. Kargl <kargl@gcc.gnu.org>
[official-gcc.git] / gcc / testsuite / gfortran.dg / bessel_7.f90
blobc6b5f7407f76f84946e1b7f547ff8561c17e5c3c
1 ! { dg-do run { xfail *-*-mingw* spu-*-* } }
2 ! { dg-add-options ieee }
4 ! PR fortran/36158
5 ! PR fortran/33197
7 ! For mingw targets this test is disabled as the MS implementation
8 ! of BESSEL_YN(n,x) has different results. It returns NAN rather than
9 ! -INF for "x=0.0" and all "n".
11 ! XFAILed for SPU targets since we don't have an accurate library
12 ! implementation of the single-precision Bessel functions.
14 ! Run-time tests for transformations BESSEL_YN
16 implicit none
17 real,parameter :: values(*) = [0.0, 0.5, 1.0, 0.9, 1.8,2.0,3.0,4.0,4.25,8.0,34.53, 475.78]
18 real,parameter :: myeps(size(values)) = epsilon(0.0) &
19 * [2, 3, 4, 5, 8, 2, 13, 6, 7, 6, 36, 168 ]
20 ! The following is sufficient for me - the values above are a bit
21 ! more tolerant
22 ! * [0, 0, 0, 3, 3, 0, 9, 0, 2, 1, 22, 130 ]
23 integer,parameter :: nit(size(values)) = &
24 [100, 100, 100, 25, 15, 100, 10, 31, 7, 100, 7, 25 ]
25 integer, parameter :: Nmax = 100
26 real :: rec(0:Nmax), lib(0:Nmax)
27 integer :: i
29 do i = 1, ubound(values,dim=1)
30 call compare(values(i), myeps(i), nit(i), 6*epsilon(0.0))
31 end do
33 contains
35 subroutine compare(X, myeps, nit, myeps2)
37 integer :: i, nit
38 real X, myeps, myeps2
40 rec = BESSEL_YN(0, Nmax, X)
41 lib = [ (BESSEL_YN(i, X), i=0,Nmax) ]
43 !print *, 'YN for X = ', X, ' -- Epsilon = ',epsilon(x)
44 do i = 0, Nmax
45 ! print '(i2,2e17.9,e12.2,f14.10,2l3)', i, rec(i), lib(i), &
46 ! rec(i)-lib(i), ((rec(i)-lib(i))/rec(i))/epsilon(x), &
47 ! i > nit .or. rec(i) == lib(i) &
48 ! .or. abs((rec(i)-lib(i))/rec(i)) < myeps2, &
49 ! rec(i) == lib(i) .or. abs((rec(i)-lib(i))/rec(i)) < myeps
50 if (.not. (i > nit .or. rec(i) == lib(i) &
51 .or. abs((rec(i)-lib(i))/rec(i)) < myeps2)) &
52 call abort ()
53 if (.not. (rec(i) == lib(i) .or. abs((rec(i)-lib(i))/rec(i)) < myeps)) &
54 call abort ()
55 end do
57 end
58 end