view gcc/testsuite/gfortran.dg/large_integer_kind_1.f90 @ 120:f93fa5091070

fix conv1.c
author mir3636
date Thu, 08 Mar 2018 14:53:42 +0900
parents 04ced10e8804
children 84e7813d76e9
line wrap: on
line source

! { dg-do run }
! { dg-require-effective-target fortran_large_int }

module testmod
  integer,parameter :: k = selected_int_kind (range (0_8) + 1)
contains
  subroutine testoutput (a,b,length,f)
    integer(kind=k),intent(in) :: a
    integer(kind=8),intent(in) ::  b
    integer,intent(in) :: length
    character(len=*),intent(in) :: f

    character(len=length) :: ca
    character(len=length) :: cb

    write (ca,f) a
    write (cb,f) b
    if (ca /= cb) call abort
  end subroutine testoutput
end module testmod


! Testing I/O of large integer kinds (larger than kind=8)
program test
  use testmod
  implicit none

  integer(kind=k) :: x
  character(len=50) :: c1, c2

  call testoutput (0_k,0_8,50,'(I50)')
  call testoutput (1_k,1_8,50,'(I50)')
  call testoutput (-1_k,-1_8,50,'(I50)')
  x = huge(0_8)
  call testoutput (x,huge(0_8),50,'(I50)')
  x = -huge(0_8)
  call testoutput (x,-huge(0_8),50,'(I50)')
end program test