PROGRAM g02lafe

!      G02LAF Example Program Text

!      Mark 23 Release. NAG Copyright 2011.

!      .. Use Statements ..
       USE nag_library, ONLY : g02laf, nag_wp, x04caf
!      .. Implicit None Statement ..
       IMPLICIT NONE
!      .. Parameters ..
       INTEGER, PARAMETER              :: nin = 5, nout = 6
!      .. Local Scalars ..
       INTEGER                         :: i, ifail, ip, iscale, j, ldc, ldp,   &
                                          ldt, ldu, ldw, ldx, ldxres, ldy,     &
                                          ldycv, ldyres, maxfac, mx, my, n
       CHARACTER (80)                  :: fmt
!      .. Local Arrays ..
       REAL (KIND=nag_wp), ALLOCATABLE :: c(:,:), p(:,:), t(:,:), u(:,:),      &
                                          w(:,:), x(:,:), xbar(:), xcv(:),     &
                                          xres(:,:), xstd(:), y(:,:), ybar(:), &
                                          ycv(:,:), yres(:,:), ystd(:)
       INTEGER, ALLOCATABLE            :: isx(:)
!      .. Intrinsic Functions ..
       INTRINSIC                          count
!      .. Executable Statements ..
       WRITE (nout,*) 'G02LAF Example Program Results'
       WRITE (nout,*)
       FLUSH (nout)

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

!      Read in the problem size
       READ (nin,*) n, mx, my, iscale, maxfac

       ldx = n
       ldy = n
       ALLOCATE (x(ldx,mx),isx(mx),y(ldy,my))

!      Read in data
       READ (nin,*) (x(i,1:mx),y(i,1:my),i=1,n)

!      Read in variable inclusion flags
       READ (nin,*) (isx(j),j=1,mx)

!      Calculate IP
       ip = count(isx(1:mx)==1)

       ldxres = n
       ldyres = n
       ldw = ip
       ldp = ip
       ldt = n
       ldc = my
       ldu = n
       ldycv = maxfac
       ALLOCATE (xbar(ip),ybar(my),xstd(ip),ystd(my),xres(ldxres,ip), &
          yres(ldyres,my),w(ldw,maxfac),p(ldp,maxfac),t(ldt,maxfac), &
          c(ldc,maxfac),u(ldu,maxfac),xcv(maxfac),ycv(ldycv,my))

!      Fit a PLS model
       ifail = 0
       CALL g02laf(n,mx,x,ldx,isx,ip,my,y,ldy,xbar,ybar,iscale,xstd,ystd, &
          maxfac,xres,ldxres,yres,ldyres,w,ldw,p,ldp,t,ldt,c,ldc,u,ldu,xcv, &
          ycv,ldycv,ifail)

!      Display results
       ifail = 0
       CALL x04caf('General',' ',ip,maxfac,p,ldp,'x-loadings, P',ifail)
       WRITE (nout,*)
       FLUSH (nout)
       ifail = 0
       CALL x04caf('General',' ',n,maxfac,t,ldt,'x-scores, T',ifail)
       WRITE (nout,*)
       FLUSH (nout)
       ifail = 0
       CALL x04caf('General',' ',my,maxfac,c,ldc,'y-loadings, C',ifail)
       WRITE (nout,*)
       FLUSH (nout)
       ifail = 0
       CALL x04caf('General',' ',n,maxfac,u,ldu,'y-scores, U',ifail)
       WRITE (nout,*)
       WRITE (nout,*) 'Explained Variance'
       WRITE (nout,*) ' Model effects   Dependent variable(s)'
       WRITE (fmt,99999) '(', my + 1, '(F12.6,3X))'
       WRITE (nout,fmt) (xcv(i),ycv(i,1:my),i=1,maxfac)

99999  FORMAT (A,I0,A)
    END PROGRAM g02lafe