Program g07bbfe
! G07BBF Example Program Text
! Mark 26.1 Release. NAG Copyright 2016.
! .. Use Statements ..
Use nag_library, Only: g07bbf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: corr, dev, sexmu, sexsig, tol, xmu, &
xsig
Integer :: i, ifail, maxit, n, nit
Character (1) :: method
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: wk(:), x(:), xc(:)
Integer, Allocatable :: ic(:)
Integer :: nobs(4)
! .. Executable Statements ..
Write (nout,*) 'G07BBF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in problem size and control parameters
Read (nin,*) n, method, xmu, xsig, tol, maxit
Allocate (x(n),xc(n),ic(n),wk(2*n))
! Read in data
Read (nin,*)(x(i),xc(i),ic(i),i=1,n)
! Calculate estimates
ifail = 0
Call g07bbf(method,n,x,xc,ic,xmu,xsig,tol,maxit,sexmu,sexsig,corr,dev, &
nobs,nit,wk,ifail)
! Display results
Write (nout,99999) ' Mean = ', xmu
Write (nout,99999) ' Standard deviation = ', xsig
Write (nout,99999) ' Standard error of mean = ', sexmu
Write (nout,99999) ' Standard error of sigma = ', sexsig
Write (nout,99999) ' Correlation coefficient = ', corr
Write (nout,99998) ' Number of right censored observations = ', nobs(1)
Write (nout,99998) ' Number of left censored observations = ', nobs(2)
Write (nout,99998) ' Number of interval censored observations = ', &
nobs(3)
Write (nout,99998) ' Number of exactly specified observations = ', &
nobs(4)
Write (nout,99998) ' Number of iterations = ', nit
Write (nout,99999) ' Log-likelihood = ', dev
99999 Format (1X,A,F8.4)
99998 Format (1X,A,I2)
End Program g07bbfe