]> git.ipfire.org Git - thirdparty/gcc.git/blob - gcc/testsuite/gfortran.dg/bessel_7.f90
re PR fortran/36158 (Transformational function BESSEL_YN(n1,n2,x) and BESSEL_JN missing)
[thirdparty/gcc.git] / gcc / testsuite / gfortran.dg / bessel_7.f90
1 ! { dg-do run }
2 !
3 ! PR fortran/36158
4 ! PR fortran/33197
5 !
6 ! Run-time tests for transformations BESSEL_YN
7 !
8 implicit none
9 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]
10 real,parameter :: myeps(size(values)) = epsilon(0.0) &
11 * [2, 2, 2, 5, 5, 2, 12, 2, 4, 3, 30, 130 ]
12 ! The following is sufficient for me - the values above are a bit
13 ! more tolerant
14 ! * [0, 0, 0, 3, 3, 0, 9, 0, 2, 1, 22, 130 ]
15 integer,parameter :: nit(size(values)) = &
16 [100, 100, 100, 100, 100, 100, 10, 100, 100, 100, 10, 25 ]
17 integer, parameter :: Nmax = 100
18 real :: rec(0:Nmax), lib(0:Nmax)
19 integer :: i
20
21 do i = 1, ubound(values,dim=1)
22 call compare(values(i), myeps(i), nit(i), 3*epsilon(0.0))
23 end do
24
25 contains
26
27 subroutine compare(X, myeps, nit, myeps2)
28
29 integer :: i, nit
30 real X, myeps, myeps2
31
32 rec = BESSEL_YN(0, Nmax, X)
33 lib = [ (BESSEL_YN(i, X), i=0,Nmax) ]
34
35 !print *, 'YN for X = ', X, ' -- Epsilon = ',epsilon(x)
36 do i = 0, Nmax
37 ! print '(i2,2e17.9,e12.2,f14.10,2l3)', i, rec(i), lib(i), &
38 ! rec(i)-lib(i), ((rec(i)-lib(i))/rec(i))/epsilon(x), &
39 ! i > nit .or. rec(i) == lib(i) &
40 ! .or. abs((rec(i)-lib(i))/rec(i)) < myeps2, &
41 ! rec(i) == lib(i) .or. abs((rec(i)-lib(i))/rec(i)) < myeps
42 if (.not. (i > nit .or. rec(i) == lib(i) &
43 .or. abs((rec(i)-lib(i))/rec(i)) < myeps2)) &
44 call abort ()
45 if (.not. (rec(i) == lib(i) .or. abs((rec(i)-lib(i))/rec(i)) < myeps)) &
46 call abort ()
47 end do
48
49 end
50 end