Program g03bcfe

!     G03BCF Example Program Text

!     Mark 25 Release. NAG Copyright 2014.

!     .. Use Statements ..
      Use nag_library, Only: g03bcf, nag_wp, x04caf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: alpha, rss
      Integer                          :: i, ifail, ldr, ldx, ldy, lwk, m, n
      Character (1)                    :: pscale, stand
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: r(:,:), res(:), wk(:), x(:,:),       &
                                          y(:,:), yhat(:,:)
!     .. Executable Statements ..
      Write (nout,*) 'G03BCF Example Program Results'
      Write (nout,*)
      Flush (nout)

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

!     Read in problem size
      Read (nin,*) n, m, stand, pscale

      ldx = n
      ldy = n
      ldr = m
      lwk = m*m + 7*m
      Allocate (x(ldx,m),y(ldy,m),yhat(ldy,m),r(ldr,m),res(n),wk(lwk))

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

!     Calculate rotations
      ifail = 0
      Call g03bcf(stand,pscale,n,m,x,ldx,y,ldy,yhat,r,ldr,alpha,rss,res,wk, &
        ifail)

!     Display results
      ifail = 0
      Call x04caf('General',' ',m,m,r,ldr,'Rotation Matrix',ifail)
      If (pscale=='S' .Or. pscale=='s') Then
        Write (nout,*)
        Write (nout,99999) ' Scale factor = ', alpha
      End If
      Write (nout,*)
      Flush (nout)
      ifail = 0
      Call x04caf('General',' ',n,m,y,ldy,'Target Matrix',ifail)
      Write (nout,*)
      Flush (nout)
      ifail = 0
      Call x04caf('General',' ',n,m,yhat,ldy,'Fitted Matrix',ifail)
      Write (nout,*)
      Write (nout,99999) 'RSS = ', rss

99999 Format (1X,A,F10.3)
    End Program g03bcfe