PROGRAM f08fcfe ! F08FCF Example Program Text ! Mark 23 Release. NAG Copyright 2011. ! .. Use Statements .. USE nag_library, ONLY : dsyevd, nag_wp, x04caf ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: nin = 5, nout = 6 ! .. Local Scalars .. INTEGER :: i, ifail, info, lda, liwork, lwork, n CHARACTER (1) :: job, uplo ! .. Local Arrays .. REAL (KIND=nag_wp), ALLOCATABLE :: a(:,:), w(:), work(:) INTEGER, ALLOCATABLE :: iwork(:) ! .. Executable Statements .. WRITE (nout,*) 'F08FCF Example Program Results' ! Skip heading in data file READ (nin,*) READ (nin,*) n lda = n liwork = 5*n + 3 lwork = 2*n*n + 6*n + 1 ALLOCATE (a(lda,n),w(n),work(lwork),iwork(liwork)) ! Read A from data file READ (nin,*) uplo IF (uplo=='U') THEN READ (nin,*) (a(i,i:n),i=1,n) ELSE IF (uplo=='L') THEN READ (nin,*) (a(i,1:i),i=1,n) END IF READ (nin,*) job ! Calculate all the eigenvalues and eigenvectors of A ! The NAG name equivalent of dsyevd is f08fcf CALL dsyevd(job,uplo,n,a,lda,w,work,lwork,iwork,liwork,info) WRITE (nout,*) IF (info>0) THEN WRITE (nout,*) 'Failure to converge.' ELSE ! Print eigenvalues and eigenvectors WRITE (nout,*) 'Eigenvalues' WRITE (nout,99999) w(1:n) WRITE (nout,*) FLUSH (nout) ! ifail: behaviour on error exit ! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft ifail = 0 CALL x04caf('General',' ',n,n,a,lda,'Eigenvectors',ifail) END IF 99999 FORMAT (3X,(8F8.4)) END PROGRAM f08fcfe