OpenCores
URL https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk

Subversion Repositories openrisc_2011-10-31

[/] [openrisc/] [tags/] [gnu-src/] [gcc-4.5.1/] [gcc-4.5.1-or32-1.0rc2/] [gcc/] [testsuite/] [gfortran.dg/] [large_integer_kind_1.f90] - Diff between revs 302 and 384

Only display areas with differences | Details | Blame | View Log

Rev 302 Rev 384
! { dg-do run }
! { dg-do run }
! { dg-require-effective-target fortran_large_int }
! { dg-require-effective-target fortran_large_int }
module testmod
module testmod
  integer,parameter :: k = selected_int_kind (range (0_8) + 1)
  integer,parameter :: k = selected_int_kind (range (0_8) + 1)
contains
contains
  subroutine testoutput (a,b,length,f)
  subroutine testoutput (a,b,length,f)
    integer(kind=k),intent(in) :: a
    integer(kind=k),intent(in) :: a
    integer(kind=8),intent(in) ::  b
    integer(kind=8),intent(in) ::  b
    integer,intent(in) :: length
    integer,intent(in) :: length
    character(len=*),intent(in) :: f
    character(len=*),intent(in) :: f
    character(len=length) :: ca
    character(len=length) :: ca
    character(len=length) :: cb
    character(len=length) :: cb
    write (ca,f) a
    write (ca,f) a
    write (cb,f) b
    write (cb,f) b
    if (ca /= cb) call abort
    if (ca /= cb) call abort
  end subroutine testoutput
  end subroutine testoutput
end module testmod
end module testmod
! Testing I/O of large integer kinds (larger than kind=8)
! Testing I/O of large integer kinds (larger than kind=8)
program test
program test
  use testmod
  use testmod
  implicit none
  implicit none
  integer(kind=k) :: x
  integer(kind=k) :: x
  character(len=50) :: c1, c2
  character(len=50) :: c1, c2
  call testoutput (0_k,0_8,50,'(I50)')
  call testoutput (0_k,0_8,50,'(I50)')
  call testoutput (1_k,1_8,50,'(I50)')
  call testoutput (1_k,1_8,50,'(I50)')
  call testoutput (-1_k,-1_8,50,'(I50)')
  call testoutput (-1_k,-1_8,50,'(I50)')
  x = huge(0_8)
  x = huge(0_8)
  call testoutput (x,huge(0_8),50,'(I50)')
  call testoutput (x,huge(0_8),50,'(I50)')
  x = -huge(0_8)
  x = -huge(0_8)
  call testoutput (x,-huge(0_8),50,'(I50)')
  call testoutput (x,-huge(0_8),50,'(I50)')
end program test
end program test
! { dg-final { cleanup-modules "testmod" } }
! { dg-final { cleanup-modules "testmod" } }
 
 

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.