Program f02xufe ! F02XUF Example Program Text ! Mark 24 Release. NAG Copyright 2012. ! .. Use Statements .. Use nag_library, Only: f02xuf, nag_wp, x04dbf ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: nin = 5, nout = 6 ! .. Local Scalars .. Integer :: i, ifail, lcwork, lda, ldb, ldq, & lrwork, n, ncolb Logical :: wantp, wantq ! .. Local Arrays .. Complex (Kind=nag_wp), Allocatable :: a(:,:), b(:), cwork(:), q(:,:) Real (Kind=nag_wp), Allocatable :: rwork(:), sv(:) Character (1) :: clabs(1), rlabs(1) ! .. Intrinsic Procedures .. Intrinsic :: conjg ! .. Executable Statements .. Write (nout,*) 'F02XUF Example Program Results' Write (nout,*) Flush (nout) ! Skip heading in data file Read (nin,*) Read (nin,*) n, ncolb lcwork = n - 1 lda = n ldb = n ldq = n lrwork = 5*(n-1) Allocate (a(lda,n),b(ldb),cwork(lcwork),q(ldq,n),rwork(lrwork),sv(n)) Read (nin,*)(a(i,i:n),i=1,n) Read (nin,*) b(1:n) ! Find the SVD of A. wantq = .True. wantp = .True. ! ifail: behaviour on error exit ! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft ifail = 0 Call f02xuf(n,a,lda,ncolb,b,ldb,wantq,q,ldq,sv,wantp,rwork,cwork,ifail) Write (nout,*) 'Singular value decomposition of A' Write (nout,*) Write (nout,*) 'Singular values' Write (nout,99999) sv(1:n) Write (nout,*) Flush (nout) ifail = 0 Call x04dbf('General',' ',n,n,q,ldq,'Bracketed','F7.4', & 'Left-hand singular vectors, by column','N',rlabs,'N',clabs,80,0, & ifail) Write (nout,*) Write (nout,*) 'Right-hand singular vectors, by column' Do i = 1, n Write (nout,99998) conjg(a(1:n,i)) End Do Write (nout,*) Write (nout,*) 'Vector conjg( Q'' )*B' Write (nout,99998) b(1:n) 99999 Format (1X,3F9.4) 99998 Format (3X,3('(',F7.4,',',F8.4,') ':)) End Program f02xufe