PR rtl-optimization/82913
[official-gcc.git] / gcc / testsuite / gfortran.dg / fmt_g0_7.f08
blobd0b572e23e16119a40b7edfe765573d34c0d1854
1 ! { dg-do run }
2 ! { dg-options "-std=gnu" }
3 ! PR58722
4 program testit
5 use ISO_FORTRAN_ENV
6   implicit none
7   integer, parameter :: j(size(real_kinds)+4)=[REAL_KINDS, [4, 4, 4, 4]]
8   character(50) :: astring
9   integer :: i, l, n
11   n = 0
12   do i=1,size(real_kinds)
13     if (i == 1) then
14       write(astring, '(ru,g0)') 1.0/real(10.0, kind=j(1))
15     else if (i == 2) then
16       write(astring, '(ru,g0)') 1.0/real(10.0, kind=j(2))
17     else if (i == 3) then
18       write(astring, '(ru,g0)') 1.0/real(10.0, kind=j(3))
19     else if (i == 4) then
20       write(astring, '(ru,g0)') 1.0/real(10.0, kind=j(4))
21     end if
22     if (astring(2:2) /= '9') then
23       l = index(astring, 'E')
24       if (l /= 0) then
25         !print *, i, l, trim(astring)
26         n = n + l
27       end if
28     end if
29   end do
30   if (n /= 0) call abort
31 end program