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

NAG FL Interface Introduction
Example description
    Program m01ecfe

!     M01ECF Example Program Text

!     Mark 29.3 Release. NAG Copyright 2023.

!     .. Use Statements ..
      Use nag_library, Only: m01dbf, m01ecf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Integer                          :: i, ifail, m1, m2
!     .. Local Arrays ..
      Integer, Allocatable             :: ifreq(:), irank(:)
      Character (6), Allocatable       :: ch(:)
!     .. Executable Statements ..
      Write (nout,*) 'M01ECF Example Program Results'

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

      Read (nin,*) m2
      Allocate (ifreq(m2),irank(m2),ch(m2))

      m1 = 1

      Do i = m1, m2
        Read (nin,99999,End=100) ch(i), ifreq(i)
      End Do

      ifail = 0
      Call m01dbf(ifreq,m1,m2,'Descending',irank,ifail)

      ifail = 0
      Call m01ecf(ch,m1,m2,irank,ifail)

      Write (nout,*)
      Write (nout,*) 'Names in order of frequency'
      Write (nout,*)
      Write (nout,99998)(ch(i),i=m1,m2)

100   Continue

99999 Format (A6,I6)
99998 Format (1X,A)
    End Program m01ecfe