Example description
    Program a00adfe

!     A00ADF Example Program Text

!     Mark 26.2 Release. NAG Copyright 2017.

!     .. Use Statements ..
      Use nag_library, Only: a00adf, x05aaf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: msglen = 15, nout = 6
!     .. Local Scalars ..
      Integer                          :: i, mkmaj, mkmin
      Logical                          :: licval
      Character (80)                   :: fcomp, hdware, impl, opsys, pcode,   &
                                          prec, vend
!     .. Local Arrays ..
      Integer                          :: itime(7)
      Character (102)                  :: msg(msglen)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: trim
!     .. Executable Statements ..
      Write (nout,*) 'A00ADF Example Program Results'

      Call a00adf(impl,prec,pcode,mkmaj,mkmin,hdware,opsys,fcomp,vend,licval)

!     Print implementation details.

      Write (nout,*)

      msg(1) = '*** Start of NAG Library implementation details ***'
      msg(2) = ''
      msg(3) = 'Implementation title: ' // impl
      msg(4) = '           Precision: ' // prec
      msg(5) = '        Product Code: ' // pcode

      If (mkmin<10) Then
        Write (msg(6),99999) mkmaj, mkmin
      Else
        Write (msg(6),99998) mkmaj, mkmin
      End If

      If (vend=='(self-contained)') Then
        msg(7) = '      Vendor Library: None'
      Else
        msg(7) = '      Vendor Library: ' // vend
      End If

      msg(8) = 'Applicable to:'
      msg(9) = '            hardware: ' // hdware
      msg(10) = '    operating system: ' // opsys
      msg(11) = '    Fortran compiler: ' // fcomp
      msg(12) = 'and compatible systems.'

      If (.Not. licval) Then
        msg(13) = '       Licence query: Unsuccessful'
      Else
        msg(13) = '       Licence query: Successful'
      End If

      msg(14) = ''
      msg(15) = '*** End of NAG Library implementation details ***'

      Do i = 1, msglen
        Write (nout,'(A)') trim(msg(i))
      End Do

!     Print the date.

      Write (nout,*)
      Write (nout,*) 'This program was run on the following date:'

      Call x05aaf(itime)

      Write (nout,99997) itime

      Write (nout,*) '*** ----------------------------------------- ***'

99999 Format ('                Mark: ',I2,'.',I1,1X,A)
99998 Format ('                Mark: ',I2,'.',I2,1X,A)
99997 Format (3X,I4.4,2I2.2,'-',3(I2.2,':'),I3.3)
    End Program a00adfe