NAG Library Manual, Mark 28.4
Interfaces:  FL   CL   CPP   AD 

NAG FL Interface Introduction
Example description
    Program g01atfe
!     G01ATF Example Program Text

!     Mark 28.4 Release. NAG Copyright 2022.

!     .. Use Statements ..
      Use nag_library, Only: g01atf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: xkurt, xmax, xmean, xmin, xsd, xskew
      Integer                          :: b, i, ierr, ifail, iwt, nb, pn
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: rcomm(20)
      Real (Kind=nag_wp), Allocatable  :: wt(:), x(:)
!     .. Executable Statements ..
      Write (nout,*) 'G01ATF Example Program Results'
      Write (nout,*)

!     Skip heading in data file
      Read (nin,*)

!     Initialize the number of valid observations processed so far
      pn = 0

!     Loop over each block of data
      b = 0
      Do
!       Read in the number of observations in this block and the weight flag
        Read (nin,*,Iostat=ierr) nb, iwt
        If (ierr/=0) Then
          Exit
        End If

!       Keep a running total of the number of blocks of data
        b = b + 1

!       Allocate X to the required size
        Allocate (x(nb))

!       Read in the data for this block
        If (iwt==0) Then
          Allocate (wt(0))
          Read (nin,*) x(1:nb)
        Else
          Allocate (wt(nb))
          Read (nin,*)(x(i),wt(i),i=1,nb)
        End If

!       IFAIL = 53, 71 or 72 are warnings and return valid information in some
!       fields, so we don't want to terminate on any nonzero IFAIL. Therefore
!       we set the flag for a quiet exit
        ifail = 1

!       Update the summaries for this block of data
        Call g01atf(nb,x,iwt,wt,pn,xmean,xsd,xskew,xkurt,xmin,xmax,rcomm,      &
          ifail)
        If (ifail/=0 .And. ifail/=71 .And. ifail/=72 .And. ifail/=53) Then
          Write (nout,*) 'G01ATF failed with IFAIL = ', ifail
          Exit
        End If

        Deallocate (x,wt)
      End Do

      If (ifail==0 .Or. ifail==71 .Or. ifail==72 .Or. ifail==53) Then
!       Display the results
        Write (nout,99999) 'Data supplied in ', b, ' blocks'
        If (ifail==53) Then
          Write (nout,*)                                                       &
            'No valid observations supplied. All weights are zero.'
        Else
          Write (nout,99997) pn, 'valid observations'
          Write (nout,99998) 'Mean          ', xmean
          If (ifail==72) Then
            Write (nout,*)                                                     &
              '  Unable to calculate the standard deviation, skewness or ',    &
              'kurtosis'
          Else
            Write (nout,99998) 'Std devn      ', xsd
            If (ifail==71) Then
              Write (nout,*) '  Unable to calculate the skewness or kurtosis'
            Else
              Write (nout,99998) 'Skewness      ', xskew
              Write (nout,99998) 'Kurtosis      ', xkurt
            End If
          End If
          Write (nout,99998) 'Minimum       ', xmin
          Write (nout,99998) 'Maximum       ', xmax
        End If
      End If

99999 Format (1X,A,I0,A)
99998 Format (1X,A,F13.2)
99997 Format (1X,I0,1X,A)
    End Program g01atfe