!   D03MAF Example Program Text
!   Mark 25 Release. NAG Copyright 2014.

    Module d03mafe_mod

!     D03MAF 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                               :: isin
!     .. Parameters ..
      Real (Kind=nag_wp), Parameter        :: rad = 6.0_nag_wp
      Real (Kind=nag_wp), Parameter        :: xmid = 7.0_nag_wp
      Real (Kind=nag_wp), Parameter        :: ymid = 7.0_nag_wp
      Integer, Parameter, Public           :: nin = 5, nout = 6
    Contains
      Function isin(x,y)
!       Circular domain

!       .. Function Return Value ..
        Integer                              :: isin
!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (In)      :: x, y
!       .. Executable Statements ..
        If ((x-xmid)**2+(y-ymid)**2<=rad**2) Then
          isin = 1
        Else
          isin = 0
        End If
        Return
      End Function isin
    End Module d03mafe_mod

    Program d03mafe

!     D03MAF Example Main Program

!     .. Use Statements ..
      Use nag_library, Only: d03maf, nag_wp
      Use d03mafe_mod, Only: isin, nin, nout
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)                   :: h
      Integer                              :: i, ifail, m, n, nb, npts,        &
                                              sddist, sdindx
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable      :: dist(:,:), places(:,:)
      Integer, Allocatable                 :: indx(:,:)
!     .. Executable Statements ..
      Write (nout,*) 'D03MAF Example Program Results'
      Write (nout,*)
!     Skip heading in data file
      Read (nin,*)
      Read (nin,*) sddist, sdindx
      Allocate (dist(4,sddist),places(2,sdindx),indx(4,sdindx))

      Read (nin,*) h
      Read (nin,*) m, n, nb

!     ifail: behaviour on error exit   
!            =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft  
      ifail = 0
      Call d03maf(h,m,n,nb,npts,places,indx,sdindx,isin,dist,sddist,ifail)

      Write (nout,*) '  I    X(I)      Y(I)'
      Do i = 1, npts
        Write (nout,99999) i, places(1,i), places(2,i)
      End Do
      Write (nout,*)
      Write (nout,*) 'INDX'
      Write (nout,99998)(indx(1:4,i),i=1,npts)

99999 Format (1X,I3,2F10.6)
99998 Format (1X,4I5)
    End Program d03mafe