PROGRAM g02fcfe ! G02FCF Example Program Text ! Mark 23 Release. NAG Copyright 2011. ! .. Use Statements .. USE nag_library, ONLY : g02fcf, nag_wp ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: nin = 5, nout = 6 ! .. Local Scalars .. REAL (KIND=nag_wp) :: d, pdl, pdu INTEGER :: i, ifail, ip, n ! .. Local Arrays .. REAL (KIND=nag_wp), ALLOCATABLE :: res(:), work(:) ! .. Executable Statements .. WRITE (nout,*) 'G02FCF Example Program Results' WRITE (nout,*) ! Skip heading in data file READ (nin,*) ! Read in the problem size READ (nin,*) n, ip ALLOCATE (res(n),work(n)) ! Read in the data READ (nin,*) (res(i),i=1,n) ! Calculate the statistic ifail = 0 CALL g02fcf(n,ip,res,d,pdl,pdu,work,ifail) ! Display the results WRITE (nout,99999) ' Durbin-Watson statistic ', d WRITE (nout,*) WRITE (nout,99998) ' Lower and upper bound ', pdl, pdu 99999 FORMAT (1X,A,F10.4) 99998 FORMAT (1X,A,2F10.4) END PROGRAM g02fcfe