- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi i wrote the following program
PROGRAM DELAYTIMEFINAL
IMPLICIT NONE
!DECLARE LOCAL VARIABLES
INTEGER ::TMAX=48
INTEGER ::TINCR=1
INTEGER ::T,IERROR,bINT,REL_INT,i,N=10000
REAL::DTE,CU1,b,U1,H1,T01
REAL::KF1=0.0223
REAL::TM=2.4028235E13
!BODY OF CODE
CALL RANDOM_SEED
HISTORIES:DO T=1,TMAX,TINCR
T01=0.0
DTE=0.0
CU1=0.0
INNER:DO
!CALL RANDOM U AND H VALUE
CALL EXP_RND_NO(U1,KF1,T01,CU1)
CALL NORM_RANDOM_NUMBER(H1)
!IF CUMULATIVE U VALUE IS BIGGER THAN TM MISSION FINISHES
IF(CU1.GE.TM)EXIT INNER
!CALCULATION OF INSPECTION INTERVAL
b=CU1/T
bINT=INT(b)
REL_INT=(bINT*T)+T
IF(CU1.GE.(REL_INT-H1))THEN
!INSPECTION
T01=T01+U1
ELSE !(U.LT.(REL_INT-H))
!BREAKDOWN
T01=T01+U1
DTE=DTE+1.0
END IF
END DO INNER
!WRITE RESULTS
WRITE(*,*) T,DTE
!WRITE RESULTS IN OUTPUT TXT FILE
OPEN(30,FILE='RESULTS.txt',STATUS='REPLACE',ACTION='WRITE',IOSTAT=IERROR)
WRITE(30,*) T,DTE
END DO HISTORIES
END PROGRAM DELAYTIMEFINAL
!=================================================================================
SUBROUTINE EXP_RND_NO(U,KF,T0,CU)
IMPLICIT NONE
REAL, INTENT(OUT) ::U,CU
REAL, INTENT(IN) ::KF
REAL, INTENT(INOUT) ::T0
REAL ::RT
CALL RANDOM_NUMBER(RT)
U=-(1./KF)*LOG(1-(RT))
CU=CU+T0
END SUBROUTINE
!================================================================================
SUBROUTINE NORM_RANDOM_NUMBER(H)
IMPLICIT NONE
REAL,INTENT(OUT) ::H
REAL ::U2,U3,V2,V3,S
REAL,SAVE ::G
LOGICAL, SAVE ::GAUS_STORED=.FALSE.
DO
IF(GAUS_STORED)THEN
H=G
GAUS_STORED=.FALSE.
ELSE
DO
CALL RANDOM_NUMBER(U2)
CALL RANDOM_NUMBER(U3)
V2=(2.0*U2)-1.0
V3=(2.0*U3)-1.0
S=V2**2.0+V3**2.0
IF(S>0.0.AND.S<1.0)EXIT
END DO
S=SQRT((-2.0*LOG(S))/S)
H=V2*S
G=V3*S
GAUS_STORED=.TRUE.
END IF
IF(H>0.0.AND.H<1.0)EXIT
END DO
END SUBROUTINE
!===================================================================================
It is a simulation program which calculates an expected number of failures (DTE), for a certain inspection interval T. The problem i have is that i need to run this program say 10000 and produce an average value of DTE for each inspection interval T. I have tried inserting a counting DO loop which executes the main body 10000 times but the random number generators have the same seed values between each iteration of the counting loop so the same value of DTE is produced making the average solution pointless. Ideally it would run wih a different seed value for each iteration which would produce different values of DTE, the average of DTE would then approach the true analytical value. I know im asking alot but i have very basic programming skills and i am approaching a deadline for which i need to make this program work.
For anybody who can spare the time to read through this gargantuan post and make a suggestion, thanks alot.
PROGRAM DELAYTIMEFINAL
IMPLICIT NONE
!DECLARE LOCAL VARIABLES
INTEGER ::TMAX=48
INTEGER ::TINCR=1
INTEGER ::T,IERROR,bINT,REL_INT,i,N=10000
REAL::DTE,CU1,b,U1,H1,T01
REAL::KF1=0.0223
REAL::TM=2.4028235E13
!BODY OF CODE
CALL RANDOM_SEED
HISTORIES:DO T=1,TMAX,TINCR
T01=0.0
DTE=0.0
CU1=0.0
INNER:DO
!CALL RANDOM U AND H VALUE
CALL EXP_RND_NO(U1,KF1,T01,CU1)
CALL NORM_RANDOM_NUMBER(H1)
!IF CUMULATIVE U VALUE IS BIGGER THAN TM MISSION FINISHES
IF(CU1.GE.TM)EXIT INNER
!CALCULATION OF INSPECTION INTERVAL
b=CU1/T
bINT=INT(b)
REL_INT=(bINT*T)+T
IF(CU1.GE.(REL_INT-H1))THEN
!INSPECTION
T01=T01+U1
ELSE !(U.LT.(REL_INT-H))
!BREAKDOWN
T01=T01+U1
DTE=DTE+1.0
END IF
END DO INNER
!WRITE RESULTS
WRITE(*,*) T,DTE
!WRITE RESULTS IN OUTPUT TXT FILE
OPEN(30,FILE='RESULTS.txt',STATUS='REPLACE',ACTION='WRITE',IOSTAT=IERROR)
WRITE(30,*) T,DTE
END DO HISTORIES
END PROGRAM DELAYTIMEFINAL
!=================================================================================
SUBROUTINE EXP_RND_NO(U,KF,T0,CU)
IMPLICIT NONE
REAL, INTENT(OUT) ::U,CU
REAL, INTENT(IN) ::KF
REAL, INTENT(INOUT) ::T0
REAL ::RT
CALL RANDOM_NUMBER(RT)
U=-(1./KF)*LOG(1-(RT))
CU=CU+T0
END SUBROUTINE
!================================================================================
SUBROUTINE NORM_RANDOM_NUMBER(H)
IMPLICIT NONE
REAL,INTENT(OUT) ::H
REAL ::U2,U3,V2,V3,S
REAL,SAVE ::G
LOGICAL, SAVE ::GAUS_STORED=.FALSE.
DO
IF(GAUS_STORED)THEN
H=G
GAUS_STORED=.FALSE.
ELSE
DO
CALL RANDOM_NUMBER(U2)
CALL RANDOM_NUMBER(U3)
V2=(2.0*U2)-1.0
V3=(2.0*U3)-1.0
S=V2**2.0+V3**2.0
IF(S>0.0.AND.S<1.0)EXIT
END DO
S=SQRT((-2.0*LOG(S))/S)
H=V2*S
G=V3*S
GAUS_STORED=.TRUE.
END IF
IF(H>0.0.AND.H<1.0)EXIT
END DO
END SUBROUTINE
!===================================================================================
It is a simulation program which calculates an expected number of failures (DTE), for a certain inspection interval T. The problem i have is that i need to run this program say 10000 and produce an average value of DTE for each inspection interval T. I have tried inserting a counting DO loop which executes the main body 10000 times but the random number generators have the same seed values between each iteration of the counting loop so the same value of DTE is produced making the average solution pointless. Ideally it would run wih a different seed value for each iteration which would produce different values of DTE, the average of DTE would then approach the true analytical value. I know im asking alot but i have very basic programming skills and i am approaching a deadline for which i need to make this program work.
For anybody who can spare the time to read through this gargantuan post and make a suggestion, thanks alot.
Link Copied
6 Replies
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Are you saying that you put all the code from the main program in a loop, including the call to RANDOM_SEED, and get the same numbers each time? You should move the call to RANDOM_SEED outside the loop - execute that only once per program.
Unless you're using a VERY old version of Digital Visual Fortran, calling RANDOM_SEED with no arguments will give you a seed based on the current time of day, so it should be different each time. Old versions used a fixed seed in this case. But either way, you don't want to call RANDOM_SEED more than once unless you want to reproduce a set of random numbers.
Unless you're using a VERY old version of Digital Visual Fortran, calling RANDOM_SEED with no arguments will give you a seed based on the current time of day, so it should be different each time. Old versions used a fixed seed in this case. But either way, you don't want to call RANDOM_SEED more than once unless you want to reproduce a set of random numbers.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Quoting - Steve Lionel (Intel)
Are you saying that you put all the code from the main program in a loop, including the call to RANDOM_SEED, and get the same numbers each time? You should move the call to RANDOM_SEED outside the loop - execute that only once per program.
Unless you're using a VERY old version of Digital Visual Fortran, calling RANDOM_SEED with no arguments will give you a seed based on the current time of day, so it should be different each time. Old versions used a fixed seed in this case. But either way, you don't want to call RANDOM_SEED more than once unless you want to reproduce a set of random numbers.
Unless you're using a VERY old version of Digital Visual Fortran, calling RANDOM_SEED with no arguments will give you a seed based on the current time of day, so it should be different each time. Old versions used a fixed seed in this case. But either way, you don't want to call RANDOM_SEED more than once unless you want to reproduce a set of random numbers.
i leave the random seed outside the loop, when i run this program shut it down and then run it again it produces different results. I think i understand this to mean that the random seed is working the way it should however i need the program to effectivley do the same thing within a single execution of the code. I dont know if i am explaining this very well but ideally i want the random number generators to use a different seed value every single time the subroutines are accessed, this should in my opinion generate diferent results from one iteration of a counting loop to the next, with each result being in the range of the true value. The idea is that if i perform enough iterations then the average should approach the true value.
Does this make sense?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Assuming that you call RANDOM_SEED only once, each call to RANDOM_NUMBER should get you the next value in the pseudo-random sequence. If you are seeing repeats across loop iterations, there's something wrong with your program that shows that result. I'm confident that if you displayed the result from RANDOM_NUMBER each time that you would not see the sequence repeat.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Quoting - Steve Lionel (Intel)
Assuming that you call RANDOM_SEED only once, each call to RANDOM_NUMBER should get you the next value in the pseudo-random sequence. If you are seeing repeats across loop iterations, there's something wrong with your program that shows that result. I'm confident that if you displayed the result from RANDOM_NUMBER each time that you would not see the sequence repeat.
I usually call random_seed at the start of the body of code, the counting do loop is inserted after the HISTORIES:DO, when i tell the program to right the result for that particular T value i get repetition of the same result. If i run the code as it is quoted in this post, close the comand prompt and run it again i get a different results. Is there a way in which i could write a code which could execute code this in a similar way to closing the command prompt and re-runing the code?
Sorry but i am grateful of your help.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I still don't see why you think that the random numbers are the same in each iteration, but you have not showed the code you used to demonstrate that.
I have modified the program to do what I think you want - I just set the count to 10 but you can change it. At the end it just prints the average DTE values. I am a little concerned with routine NORM_RANDOM_NUMBER which saves a value G from past iterations but I don't understand exactly what it is doing.
I have highlighted changes I made. Does this help?
PROGRAM DELAYTIMEFINAL
IMPLICIT NONE
!DECLARE LOCAL VARIABLES
INTEGER,PARAMETER ::TMAX=48
INTEGER, PARAMETER ::TINCR=1
INTEGER ::T,IERROR,bINT,REL_INT,i,J
INTEGER, PARAMETER :: N = 10 !N=10000
REAL::DTE,CU1,b,U1,H1,T01
REAL::KF1=0.0223
REAL::TM=2.4028235E13
REAL, DIMENSION(TMAX) :: DTE_AVERAGES
DTE_AVERAGES = 0.0
!BODY OF CODE
CALL RANDOM_SEED
AVG_LOOP: DO J=1,N
HISTORIES:DO T=1,TMAX,TINCR
T01=0.0
DTE=0.0
CU1=0.0
INNER:DO
!CALL RANDOM U AND H VALUE
CALL EXP_RND_NO(U1,KF1,T01,CU1)
CALL NORM_RANDOM_NUMBER(H1)
!IF CUMULATIVE U VALUE IS BIGGER THAN TM MISSION FINISHES
IF(CU1.GE.TM)EXIT INNER
!CALCULATION OF INSPECTION INTERVAL
b=CU1/T
bINT=INT(b)
REL_INT=(bINT*T)+T
IF(CU1.GE.(REL_INT-H1))THEN
!INSPECTION
T01=T01+U1
ELSE !(U.LT.(REL_INT-H))
!BREAKDOWN
T01=T01+U1
DTE=DTE+1.0
END IF
END DO INNER
!WRITE RESULTS
WRITE(*,*) T,DTE
!WRITE RESULTS IN OUTPUT TXT FILE
OPEN(30,FILE='RESULTS.txt',STATUS='REPLACE',ACTION='WRITE',IOSTAT=IERROR)
WRITE(30,*) T,DTE
DTE_AVERAGES(T) = DTE_AVERAGES(T) + DTE
END DO HISTORIES
END DO AVG_LOOP
DTE_AVERAGES = DTE_AVERAGES / REAL(N)
WRITE (*,*) DTE_AVERAGES
END PROGRAM DELAYTIMEFINAL
I have modified the program to do what I think you want - I just set the count to 10 but you can change it. At the end it just prints the average DTE values. I am a little concerned with routine NORM_RANDOM_NUMBER which saves a value G from past iterations but I don't understand exactly what it is doing.
I have highlighted changes I made. Does this help?
PROGRAM DELAYTIMEFINAL
IMPLICIT NONE
!DECLARE LOCAL VARIABLES
INTEGER,PARAMETER ::TMAX=48
INTEGER, PARAMETER ::TINCR=1
INTEGER ::T,IERROR,bINT,REL_INT,i,J
INTEGER, PARAMETER :: N = 10 !N=10000
REAL::DTE,CU1,b,U1,H1,T01
REAL::KF1=0.0223
REAL::TM=2.4028235E13
REAL, DIMENSION(TMAX) :: DTE_AVERAGES
DTE_AVERAGES = 0.0
!BODY OF CODE
CALL RANDOM_SEED
AVG_LOOP: DO J=1,N
HISTORIES:DO T=1,TMAX,TINCR
T01=0.0
DTE=0.0
CU1=0.0
INNER:DO
!CALL RANDOM U AND H VALUE
CALL EXP_RND_NO(U1,KF1,T01,CU1)
CALL NORM_RANDOM_NUMBER(H1)
!IF CUMULATIVE U VALUE IS BIGGER THAN TM MISSION FINISHES
IF(CU1.GE.TM)EXIT INNER
!CALCULATION OF INSPECTION INTERVAL
b=CU1/T
bINT=INT(b)
REL_INT=(bINT*T)+T
IF(CU1.GE.(REL_INT-H1))THEN
!INSPECTION
T01=T01+U1
ELSE !(U.LT.(REL_INT-H))
!BREAKDOWN
T01=T01+U1
DTE=DTE+1.0
END IF
END DO INNER
!WRITE RESULTS
WRITE(*,*) T,DTE
!WRITE RESULTS IN OUTPUT TXT FILE
OPEN(30,FILE='RESULTS.txt',STATUS='REPLACE',ACTION='WRITE',IOSTAT=IERROR)
WRITE(30,*) T,DTE
DTE_AVERAGES(T) = DTE_AVERAGES(T) + DTE
END DO HISTORIES
END DO AVG_LOOP
DTE_AVERAGES = DTE_AVERAGES / REAL(N)
WRITE (*,*) DTE_AVERAGES
END PROGRAM DELAYTIMEFINAL
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
steve,
as we say in liverpool you are an absolute legend! this works fine, cheers for all your help.
andi

Reply
Topic Options
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page