Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations strongm on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Creating a Random Number Generator

Status
Not open for further replies.

gjw1684

Vendor
May 26, 2007
9
US
Good Afternoon,

I would like to know if there is a standard procedure to create a random number generator. In my program, I have a text file that looks something like this:

10012.3 343 23 193 EP 32 49 PO 32 ...
...
...

where this has at most 20 columns and an indefinite number of rows. What I would like to do is to pick a particular column entry, say the 10th column (which is a real number), of each row, copy that entry three times, add a random number to it between 0 and 1, and print it to another text file. Here is an idea of how my code is written up:

program check

INTEGER :: i
INTEGER :: iseed
REAL :: ran
REAL :: sum
REAL :: V1
REAL :: V2
REAL :: V3
REAL :: V4
character(len=256) :: s
character(len=256) a(256)
integer n,m

WRITE(*,*) 'Enter seed'
READ(*,*) iseed
CALL SEED( iseed)

open(unit=4, file='text1.txt ', status='old')
open(unit=5, file='text2.txt', status='replace')

do while(.true.)
read(4,fmt='(A)',end=777) s
read(s,*,end=555,err=666) (a(n),n=1,256)
555 n = n - 1
if (n .lt. 20) then
continue
end if

READ (a(10), '(I10)') V1

DO i = 1,3
CALL random0(ran)
WRITE(5,'(A)') V1 + ran
END DO
end if
end do


666 continue
777 continue

end program check

MODULE ran001
IMPLICIT NONE
SAVE
INTEGER :: m=9876
END MODULE ran001

SUBROUTINE random0(ran)
USE ran001
IMPLICIT NONE
REAL, INTENT(OUT) :: ran
m = MOD(8121 * m + 28411 , 134456)
ran = REAL(m) / 134456.
END SUBROUTINE random0

SUBROUTINE seed (iseed)
USE ran001
IMPLICIT NONE
INTEGER, INTENT(IN) :: iseed
n = ABS (iseed)
END SUBROUTINE seed




When I do this code, this code produces a lot of nonsensical characters in the output text file. Any suggestions?
 
You're writing V1+ran in A format. V1+ran produces a real number so it should be written in D, E, F or G format. Yes, there is a standard procedure for producing random numbers. Here is an example from a Fast Fourier Transform package from some university (no idea which - it is just called PSC). The standard routines of interest are

a) random_seed
b) random_number

The rest of it is just a way of initializing the random seed based on current date and time.
Code:
! [URL unfurl="true"]http://www.psc.edu/~burkardt/src/fftpack/fftpack.f90[/URL]
subroutine random_initialize ( )
  integer date_time(8), i, seed, seed_size
  integer, allocatable :: seed_vec(:)
  real t
!
!  Get the seed size
   call random_seed (size = seed_size)
!
!  Allocate space for the seed
   allocate (seed_vec(seed_size))
!
!  Get the current date and time.
   call date_and_time (values = date_time)
!
!  Construct a seed from the date/time
   seed = 0
   do i = 1, 8
      seed = ieor (seed, date_time(i))
   end do
!
!  Create a seed
   do i = 1, seed_size
      seed_vec(i) = ieor (seed, i)
   end do
!
!  Set the random number seed value.
   call random_seed (size = seed_size, put = seed_vec(1:seed_size))
!
!  Free up the seed space.
   deallocate (seed_vec)
   return
end subroutine random_initialize
!
! Test it
program main
   real t
   integer i
   call random_initialize ()
   do i = 1, 10
      call random_number (harvest = t)
      write (*,*) t
   end do
end program main
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top