! M01DAF Example Program Text
! Mark 29.3 Release. NAG Copyright 2023.
Module m01dafe_mod
! M01DAF Example Program Module:
! Parameters and User-defined Routines
! .. Use Statements ..
Use nag_library, Only: nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Accessibility Statements ..
Private
Public :: ex1, ex2
! .. Parameters ..
Integer, Parameter, Public :: nin = 5, nout = 6
Contains
Subroutine ex1
! Example 1: rank data in ascending order
! .. Use Statements ..
Use nag_library, Only: m01daf
! .. Implicit None Statement ..
Implicit None
! .. Local Scalars ..
Integer :: i, ifail, m1, m2
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: rv(:)
Integer, Allocatable :: irank(:)
! .. Executable Statements ..
! Skip header
Read (nin,*)
Write (nout,*)
Write (nout,*)
Write (nout,*) 'Example 1'
! Read in problem size
Read (nin,*) m2
m1 = 1
Allocate (rv(m2),irank(m2))
! Read vector to be ranked
Read (nin,*)(rv(i),i=m1,m2)
ifail = 0
Call m01daf(rv,m1,m2,'Ascending',irank,ifail)
Write (nout,*) ' Data Ranks'
Write (nout,*)
Do i = m1, m2
Write (nout,99999) rv(i), irank(i)
End Do
Deallocate (rv,irank)
99999 Format (1X,F7.1,I7)
End Subroutine ex1
Subroutine ex2
! Example 2: rank data, invert the rank permutation and calculate
! weighted quantiles
! .. Use Statements ..
Use nag_library, Only: m01daf, m01naf, m01zaf
! .. Local Scalars ..
Real (Kind=nag_wp) :: aq
Integer :: i, ifail, iv, n, nq
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: cwt(:), q(:), qv(:), rv(:), wt(:)
Integer, Allocatable :: irank(:)
! .. Executable Statements ..
! Skip header in file
Read (nin,*)
Write (nout,*)
Write (nout,*)
Write (nout,*) 'Example 2'
! Read problem size
Read (nin,*) n, nq
Allocate (q(nq),rv(n),wt(n),qv(nq),irank(n),cwt(n))
! Read in data
Read (nin,*) rv(1:n)
! Rank the data
ifail = 0
Call m01daf(rv,1,n,'Ascending',irank,ifail)
! Convert ranks into indices
ifail = 0
Call m01zaf(irank,1,n,ifail)
! Read in weights
Read (nin,*) wt(1:n)
! Obtain the cumulative sum of the weights of the sorted data
cwt(1) = wt(irank(1))
Do i = 2, n
cwt(i) = cwt(i-1) + wt(irank(i))
End Do
! Read in the required quantiles
Read (nin,*) q(1:nq)
! Find the quantiles
Do i = 1, nq
! scale the quantiles w.r.t the total cumulative sum
aq = q(i)*cwt(n)
ifail = 0
iv = m01naf(.False.,cwt,1,n,aq,ifail)
iv = iv + 1
If (iv>n) Then
iv = n
End If
! convert the index returned by M01NAF into a value
! from the (sorted) original data
qv(i) = rv(irank(iv))
End Do
! Display results
Write (nout,*) 'Quantile Result'
Write (nout,*)
Write (nout,99999)(q(i),qv(i),i=1,nq)
99999 Format (1X,F7.2,4X,F7.2)
Deallocate (q,rv,wt,qv,irank,cwt)
End Subroutine ex2
End Module m01dafe_mod
Program m01dafe
! Mark 29.3 Release. NAG Copyright 2023.
! M01NDF Example Main Program
! .. Use Statements ..
Use m01dafe_mod, Only: ex1, ex2, nin, nout
! .. Implicit None Statement ..
Implicit None
! .. Executable Statements ..
Write (nout,*) 'M01DAF Example Program Results'
! Skip heading in data file
Read (nin,*)
! Example of ranking data
Call ex1
! Example using sorted data to calculate weighted quantiles
Call ex2
End Program m01dafe