view gcc/testsuite/gfortran.dg/random_7.f90 @ 128:fe568345ddd5

fix CbC-example
author mir3636
date Wed, 11 Apr 2018 19:32:28 +0900
parents 04ced10e8804
children 84e7813d76e9
line wrap: on
line source

! { dg-do run }
! { dg-options "-fdefault-integer-8" }
!
program trs
  implicit none
  integer :: size, ierr
  integer, allocatable, dimension(:) :: seed, check
  call test_random_seed(size)
  allocate(seed(size),check(size))
  seed(:) = huge(seed) / 17
  call test_random_seed(put=seed)
  call test_random_seed(get=check)
  ! In the current xorshift1024* implementation the last seed value is
  ! special
  seed(size) = check(size)
  if (any (seed /= check)) call abort
contains
  subroutine test_random_seed(size, put, get)
    integer, optional :: size
    integer, dimension(:), optional :: put
    integer, dimension(:), optional :: get
    call random_seed(size, put, get)
  end subroutine test_random_seed
end program trs