Getting random integers from /dev/urandom

The following code reads random integers from /dev/urandom and runs with gfortran, flang, and Intel Fortran on WSL2 . With gfortran it works for calls to random_int(iran) for N = size(iran) = 2^22 but not 2^23, but for ifort it works for larger N. For flang it works for at least 2^22. I wonder if there are compilers for Unix-like operating systems for which the program fails for N = 2^22. If this generally works, one can write a subroutine to get random integers in chunks of this size or smaller.

module random_mod
implicit none
contains
subroutine random_int(iran)
integer, intent(out) :: iran(:)
integer :: iu
open(newunit=iu, file='/dev/urandom', access='stream', form='UNFORMATTED')
read (iu) iran
close (iu)
end subroutine random_int
end module random_mod
!
program test_random_int
use random_mod, only: random_int
implicit none
integer, parameter :: niter = 5, nmin = 2**22, nexit = 4*10**6
integer :: iter, n
integer, allocatable :: v(:)
print "(*(a12))","#","min","max"
do iter=1,niter
   n = nmin
   do
      allocate (v(n))
      call random_int(v)
      print "(*(i12))",n,minval(v),maxval(v)
      deallocate (v)
      if (n > nexit) exit
      n = n*2
   end do
end do
print "('huge = ',i0)",huge(v)
end program test_random_int

Sample output:

           #         min         max
     4194304 -2147483533  2147483524
     4194304 -2147482033  2147483355
     4194304 -2147481522  2147482836
     4194304 -2147483486  2147482049
     4194304 -2147483578  2147483202
huge = 2147483647

Perhaps, it is better to just read /dev/urandom to seed the PRNG? In most cases, random floats from a PRNG seem to be more useful that random bytes.

From man urandom on Linux (Ubuntu 20.04):

Since Linux 3.16, a read(2) from /dev/urandom will return at most 32 MB.

Actually, it reads 33554431 bytes which is 1 byte short of full 32MB, ie. 8M 4B integers. It is consistent with your observation. Intel ifort apparently reads the /dev/urandom device in some smarter way.

1 Like