Program g05pffe
! G05PFF Example Program Text
! Mark 29.2 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: g05kff, g05pff, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: lseed = 1, nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: gamma
Integer :: df, genid, i, ifail, ip, iq, lr, &
lstate, ltheta, nreal, num, rn, &
subid
Logical :: fcall
Character (1) :: dist
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: et(:), ht(:), r(:), theta(:)
Integer :: seed(lseed)
Integer, Allocatable :: state(:)
! .. Executable Statements ..
Write (nout,*) 'G05PFF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the base generator information and seed
Read (nin,*) genid, subid, seed(1)
! Initial call to initializer to get size of STATE array
lstate = 0
Allocate (state(lstate))
ifail = 0
Call g05kff(genid,subid,seed,lseed,state,lstate,ifail)
! Reallocate STATE
Deallocate (state)
Allocate (state(lstate))
! Initialize the generator to a repeatable sequence
ifail = 0
Call g05kff(genid,subid,seed,lseed,state,lstate,ifail)
! Read in sample size and number of realizations
Read (nin,*) num, nreal
! Read in number of coefficients
Read (nin,*) ip, iq
lr = 2*(ip+iq+2)
ltheta = ip + iq + 1
Allocate (theta(ltheta),ht(num),et(num),r(lr))
! Read in error distribution
Read (nin,*) dist
! Read in degrees of freedom if required
If (dist=='T' .Or. dist=='t') Then
Read (nin,*) df
End If
! Read in rest of series parameters
Read (nin,*) theta(1:ltheta)
Read (nin,*) gamma
! Set FCALL for first realization
fcall = .True.
! Generate NREAL realizations
Do rn = 1, nreal
ifail = 0
Call g05pff(dist,num,ip,iq,theta,gamma,df,ht,et,fcall,r,lr,state, &
ifail)
! Display the results
Write (nout,99998) 'Realization Number ', rn
Write (nout,*) ' I HT(I) ET(I)'
Write (nout,*) ' --------------------------------------'
Write (nout,99999)(i,ht(i),et(i),i=1,num)
Write (nout,*)
! Set FCALL flag for any further realizations
fcall = .False.
End Do
99999 Format (1X,I5,1X,F16.4,1X,F16.4)
99998 Format (1X,A,I0)
End Program g05pffe