eig_sym(a, m, w, z, info)
implicit none
real(8), intent(in) :: a(:,:)
integer, intent(out) :: m
real(8), intent(out) :: w(:)
real(8), intent(out) :: z(:,:)
integer, intent(out) :: info
integer, parameter :: nb = 64
character(1), parameter :: jobz = 'V'
character(1), parameter :: range = 'I'
character(1), parameter :: uplo = 'U'
real(8), allocatable :: a_(:,:)
real(8) :: abstol
integer :: n, lda, ldz
integer :: liwork, lwork
integer :: il, iu
real(8) :: vl, vu
real(8), allocatable :: work(:)
integer, allocatable :: iwork(:)
integer, allocatable :: isuppz(:)
real(8) :: dummy(1)
integer :: idum(1)
n = size(a,1)
allocate(a_(n,n))
a_ = a
il = 1
iu = n
lda = n
ldz = n
m = n
allocate(isuppz(2*m))
lwork = -1
liwork = -1
call DSYEVR(jobz, range, uplo, &
n, a_, lda, vl, vu, il, iu, abstol, &
m, w, z, ldz, isuppz, &
dummy, lwork, idum, liwork, info)
lwork = max((nb+6)*n, nint(dummy(1)))
liwork = max(10*n, idum(1))
allocate(work(lwork), iwork(liwork))
abstol = 0.d0
call DSYEVR(jobz, range, uplo, &
n, a_, lda, vl, vu, il, iu, abstol, &
m, w, z, ldz, isuppz, &
work, lwork, iwork, liwork, info)
if( m < n )then
w(m+1:n) = 0.d0
z(:,m+1:n) = 0.d0
endif
eig_sym