PROGRAM g05phfe ! G05PHF Example Program Text ! Mark 23 Release. NAG Copyright 2011. ! .. Use Statements .. USE nag_library, ONLY : g05kff, g05phf, nag_wp ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: lseed = 1, nin = 5, nout = 6 ! .. Local Scalars .. REAL (KIND=nag_wp) :: avar, var, xmean INTEGER :: genid, ifail, ip, iq, lr, lstate, & mode, n, subid ! .. Local Arrays .. REAL (KIND=nag_wp), ALLOCATABLE :: phi(:), r(:), theta(:), x(:) INTEGER :: seed(lseed) INTEGER, ALLOCATABLE :: state(:) ! .. Intrinsic Functions .. INTRINSIC max ! .. Executable Statements .. WRITE (nout,*) 'G05PHF 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 initialiser 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 READ (nin,*) n ! Read in number of coefficients READ (nin,*) ip, iq lr = ip + iq + 6 + max(ip,iq+1) ALLOCATE (phi(ip),theta(iq),x(n),r(lr)) ! Read in mean READ (nin,*) xmean ! Read in autoregressive coefficients IF (ip>0) THEN READ (nin,*) phi(1:ip) END IF ! Read in moving average coefficients IF (iq>0) THEN READ (nin,*) theta(1:iq) END IF ! Read in variance READ (nin,*) avar ! Using a single call to G05PHF, so set up reference vector ! and generate values in one go mode = 2 ifail = 0 CALL g05phf(mode,n,xmean,ip,phi,iq,theta,avar,r,lr,state,var,x,ifail) ! Display the variates WRITE (nout,99999) x(1:n) 99999 FORMAT (1X,F12.4) END PROGRAM g05phfe