Merge from mainline (165734:167278).
[official-gcc/graphite-test-results.git] / gcc / testsuite / gfortran.dg / quad_1.f90
blob7d4322e5a748e3dacf6328e5d0d4c9266494340d
1 ! { dg-do link }
3 ! This test checks whether the largest possible
4 ! floating-point number works. That's usually
5 ! REAL(16) -- either because the hardware supports it or
6 ! because of libquadmath. However, it can also be
7 ! REAL(10) or REAL(8)
9 program test_qp
10 use iso_fortran_env, only: real_kinds
11 implicit none
12 integer, parameter :: QP = real_kinds(ubound(real_kinds,dim=1))
13 real(QP), parameter :: Z1 = 1,HALF_PI = asin(Z1),PI = HALF_PI+HALF_PI
14 real(QP) :: x = 0.124_QP
15 complex(QP) :: z = 0.124_QP
16 print *, 'kind = ', qp
17 print *, x
18 print *, PI
19 print *, 16*atan(0.2_QP)-4*atan(Z1/239)
20 print *, sin(PI)
21 print *, cos(HALF_PI)
22 print *, asinh(PI)
23 print *, erfc(Z1)
24 print *, epsilon(x)
25 print *, precision(x)
26 print *, digits(x)
28 print *, z
29 print *, PI*cmplx(0.0_qp, 1.0_qp)
30 print *, 16*atan(0.2_QP)-4*atan(Z1/239)
31 print *, sin(z)
32 print *, cos(z)
33 print *, sinh(z) ! asinh not implemented, cf. PR 46416
34 print *, precision(z)
35 end program test_qp