Merge from google/integration.
[official-gcc.git] / gcc / testsuite / gfortran.dg / bessel_7.f90
blob10a6e966dfa0b99ff052fee55250dd59a8ff785d
1 ! { dg-do run { xfail *-*-mingw* spu-*-* } }
3 ! PR fortran/36158
4 ! PR fortran/33197
6 ! For mingw targets this test is disabled as the MS implementation
7 ! of BESSEL_YN(n,x) has different results. It returns NAN rather than
8 ! -INF for "x=0.0" and all "n".
10 ! XFAILed for SPU targets since we don't have an accurate library
11 ! implementation of the single-precision Bessel functions.
13 ! Run-time tests for transformations BESSEL_YN
15 implicit none
16 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]
17 real,parameter :: myeps(size(values)) = epsilon(0.0) &
18 * [2, 3, 4, 5, 8, 2, 12, 6, 7, 6, 31, 168 ]
19 ! The following is sufficient for me - the values above are a bit
20 ! more tolerant
21 ! * [0, 0, 0, 3, 3, 0, 9, 0, 2, 1, 22, 130 ]
22 integer,parameter :: nit(size(values)) = &
23 [100, 100, 100, 25, 15, 100, 10, 31, 7, 100, 7, 25 ]
24 integer, parameter :: Nmax = 100
25 real :: rec(0:Nmax), lib(0:Nmax)
26 integer :: i
28 do i = 1, ubound(values,dim=1)
29 call compare(values(i), myeps(i), nit(i), 6*epsilon(0.0))
30 end do
32 contains
34 subroutine compare(X, myeps, nit, myeps2)
36 integer :: i, nit
37 real X, myeps, myeps2
39 rec = BESSEL_YN(0, Nmax, X)
40 lib = [ (BESSEL_YN(i, X), i=0,Nmax) ]
42 !print *, 'YN for X = ', X, ' -- Epsilon = ',epsilon(x)
43 do i = 0, Nmax
44 ! print '(i2,2e17.9,e12.2,f14.10,2l3)', i, rec(i), lib(i), &
45 ! rec(i)-lib(i), ((rec(i)-lib(i))/rec(i))/epsilon(x), &
46 ! i > nit .or. rec(i) == lib(i) &
47 ! .or. abs((rec(i)-lib(i))/rec(i)) < myeps2, &
48 ! rec(i) == lib(i) .or. abs((rec(i)-lib(i))/rec(i)) < myeps
49 if (.not. (i > nit .or. rec(i) == lib(i) &
50 .or. abs((rec(i)-lib(i))/rec(i)) < myeps2)) &
51 call abort ()
52 if (.not. (rec(i) == lib(i) .or. abs((rec(i)-lib(i))/rec(i)) < myeps)) &
53 call abort ()
54 end do
56 end
57 end