SUBROUTINE tdiagrw ( v, e, t, subd,n,nmax,nvmax ) USE Numeric_Kinds_Module USE FileUnits_Module IMPLICIT NONE !============================================================================== ! --calls tred3, tql2, and trbak3 to diagonalize a matrix ! v(n*(n+1)/2) -- matrix to be diagonalized, must be symmetric ! e(n) -- output, the eigenvalues of ! t(n,n) -- output, the eigenvectors of ! n -- appropriate dimension variables (INTEGER*4) ! subd(n) -- scratch array used by tred2 and tql2 !============================================================================== INTEGER :: n, nmax, nvmax INTEGER :: nv, i, j, ierr REAL(dp) :: e(nmax), t(nmax,nmax), subd(nmax), v(nvmax) !============================================================================== nv=(n*(n+1))/2 CALL tred3rw(n,nv,v,e,subd,subd,nmax,nvmax) DO i=1,n DO j=1,n t(j,i)=0.d0 ENDDO t(i,i)=1.d0 ENDDO CALL tql2rw(n,n,e,subd,t,ierr,nmax,nvmax) IF(ierr.ne.0) WRITE(Output_Unit,10) ierr CALL trbak3rw(n,n,nv,v,n,t,nmax,nvmax) IF ( ierr .ne. 0 ) WRITE(Output_Unit,10) ierr 10 FORMAT ( ' diagonalization error #', i3, ' returned by tql2' ) RETURN ! --------------***END-tdiag***--------------------------------------- END