OSDN Git Service

9511317901c86e828851d22bc995c3e57a359558
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / large_integer_kind_1.f90
1 ! { dg-do run }
2 ! { dg-require-effective-target fortran_large_int }
3
4 module testmod
5   integer,parameter :: k = selected_int_kind (range (0_8) + 1)
6 contains
7   subroutine testoutput (a,b,length,f)
8     integer(kind=k),intent(in) :: a
9     integer(kind=8),intent(in) ::  b
10     integer,intent(in) :: length
11     character(len=*),intent(in) :: f
12
13     character(len=length) :: ca
14     character(len=length) :: cb
15
16     write (ca,f) a
17     write (cb,f) b
18     if (ca /= cb) call abort
19   end subroutine testoutput
20 end module testmod
21
22
23 ! Testing I/O of large integer kinds (larger than kind=8)
24 program test
25   use testmod
26   implicit none
27
28   integer(kind=k) :: x
29   character(len=50) :: c1, c2
30
31   call testoutput (0_k,0_8,50,'(I50)')
32   call testoutput (1_k,1_8,50,'(I50)')
33   call testoutput (-1_k,-1_8,50,'(I50)')
34   x = huge(0_8)
35   call testoutput (x,huge(0_8),50,'(I50)')
36   x = -huge(0_8)
37   call testoutput (x,-huge(0_8),50,'(I50)')
38 end program test