Program g01arfe
! G01ARF Example Program Text
! Mark 29.3 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: g01arf, nag_wp, x04abf
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: iset = 1, nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: unit, unit1, unit2
Integer :: i, ifail, ldplot, lines, n, nstepx, &
nstepy, outchn
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: sorty(:), y(:)
Integer, Allocatable :: iwork(:)
Character (1), Allocatable :: plot(:,:)
! .. Intrinsic Procedures ..
Intrinsic :: max
! .. Executable Statements ..
Write (nout,*) 'G01ARF Example Program Results'
Write (nout,*)
Flush (nout)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) n, unit, nstepx, nstepy
! Make sure there is more than the minimum number of lines available
! for the plot
ldplot = max(100,nstepy)
Allocate (y(n),iwork(n),sorty(n),plot(ldplot,nstepx))
! Read in data
Read (nin,*) y(1:n)
! Set advisory channel
outchn = nout
Call x04abf(iset,outchn)
! Produce and display the plot
unit1 = unit
ifail = 0
Call g01arf('Fences','Print',n,y,nstepx,nstepy,unit1,plot,ldplot,lines, &
sorty,iwork,ifail)
Write (nout,*)
Flush (nout)
! Produce the plot, without printing it
unit2 = unit
ifail = 0
Call g01arf('Extremes','Noprint',n,y,nstepx,nstepy,unit2,plot,ldplot, &
lines,sorty,iwork,ifail)
! Display the plot
Do i = 1, lines
Write (nout,99999) plot(i,1:nstepx)
End Do
99999 Format (1X,132A)
End Program g01arfe