Program g13nafe
!     G13NAF Example Program Text

!     Mark 26.1 Release. NAG Copyright 2016.

!     .. Use Statements ..
      Use nag_library, Only: g13naf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: beta
      Integer                          :: ctype, i, ifail, iparam, minss, n,   &
                                          ntau
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: param(1)
      Real (Kind=nag_wp), Allocatable  :: sparam(:), y(:)
      Integer, Allocatable             :: tau(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: repeat
!     .. Executable Statements ..
      Continue
      Write (nout,*) 'G13NAF Example Program Results'
      Write (nout,*)

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

!     Read in the problem size
      Read (nin,*) n

!     Allocate memory to hold the input series
      Allocate (y(n))

!     Read in the input series
      Read (nin,*) y(1:n)

!     Read in the type of change point, penalty and minimum segment size
      Read (nin,*) ctype, iparam, beta, minss

!     Read in the distribution parameter (if required)
      If (iparam==1) Then
        Read (nin,*) param(1)
      End If

!     Allocate output arrays
      Allocate (tau(n),sparam(2*n+2))

!     Call routine to detect change points
      ifail = -1
      Call g13naf(ctype,n,y,beta,minss,iparam,param,ntau,tau,sparam,ifail)

      If (ifail==0 .Or. ifail==200 .Or. ifail==201) Then
!       Display the results
        If (ctype==5 .Or. ctype==6) Then
!         Exponential or Poisson distribution
          Write (nout,99999) ' -- Change Points --      Distribution'
          Write (nout,99999) '  Number     Position      Parameter'
          Write (nout,99999) repeat('=',38)
          Do i = 1, ntau
            Write (nout,99998) i, tau(i), sparam(i)
          End Do
        Else
!         Normal or Gamma distribution
          Write (nout,99999)                                                   &
            ' -- Change Points --         --- Distribution ---'
          Write (nout,99999) ' Number     Position              Parameters'
          Write (nout,99999) repeat('=',50)
          Do i = 1, ntau
            Write (nout,99997) i, tau(i), sparam(2*i-1), sparam(2*i)
          End Do
        End If
        If (ifail==200 .Or. ifail==201) Then
          Write (nout,99999)                                                   &
            'Some truncation occurred internally to avoid overflow'
        End If
      End If

99999 Format (1X,A)
99998 Format (1X,I4,7X,I6,4X,F12.2)
99997 Format (1X,I4,7X,I6,2(4X,F12.2))
    End Program g13nafe