typeeigensolver_tprivateinteger,public::es_type!< which eigensolver to use
real(real64),public::toleranceinteger,public::es_maxiterreal(real64)::imag_time!> Stores information about how well it performed.
real(real64),allocatable,public::diff(:,:)!< Diff in `nst` states, per k-point
integer,public::matvecinteger,allocatable,public::converged(:)!< Number of converged states, per k-point
!> Stores information about the preconditioning.
type(preconditioner_t),public::pre!> Store routine used for subspace diagonalisation
type(subspace_t)::sdiaginteger::rmmdiis_minimization_iterlogical,public::folded_spectrum! cg options
logical,public::orthogonalize_to_allinteger,public::conjugate_directionlogical,public::additional_termsreal(real64),public::energy_change_threshold! Chebyshev filtering options
type(eigen_chebyshev_t),public::cheby_paramstype(exponential_t)::exponential_operatorcontainsprocedure::run=>eigensolver_runendtypeeigensolver_t
subroutineeigensolver_run(eigens,namespace,gr,st,hm,iter,conv,nstconv)class(eigensolver_t),intent(inout)::eigenstype(namespace_t),intent(in)::namespacetype(grid_t),intent(in)::grtype(states_elec_t),intent(inout)::sttype(hamiltonian_elec_t),intent(inout)::hminteger,intent(in)::iterlogical,optional,intent(out)::convinteger,optional,intent(in)::nstconv!< Number of states considered for
! !< the convergence criteria
integer::ik,ist,nstconv_#ifdef HAVE_MPI
logical::conv_reducedinteger::outcount,lmatvecreal(real64),allocatable::ldiff(:),leigenval(:)real(real64),allocatable::ldiff_out(:),leigenval_out(:)integer,allocatable::lconv(:)#endif
callprofiling_in("EIGEN_SOLVER")PUSH_SUB(eigensolver_run)if(present(conv))conv=.false.if(present(nstconv))thennstconv_=nstconvelsenstconv_=st%nstendifeigens%matvec=0if(mpi_grp_is_root(mpi_world).and.eigensolver_has_progress_bar(eigens).and..not.debug%info)thencallloct_progress_bar(-1,st%lnst*st%d%kpt%nlocal)endifik_loop:doik=st%d%kpt%start,st%d%kpt%endif(states_are_real(st))thencalldeigensolver_run(eigens,namespace,gr,st,hm,iter,ik)elsecallzeigensolver_run(eigens,namespace,gr,st,hm,iter,ik)endifif(.not.eigens%folded_spectrum)then! recheck convergence after subspace diagonalization, since states may have reordered
eigens%converged(ik)=0doist=1,st%nstif(eigens%diff(ist,ik)<eigens%tolerance)theneigens%converged(ik)=istelseexitendifenddoendifenddoik_loopif(mpi_grp_is_root(mpi_world).and.eigensolver_has_progress_bar(eigens).and..not.debug%info)thenwrite(stdout,'(1x)')endifif(present(conv))conv=all(eigens%converged(st%d%kpt%start:st%d%kpt%end)>=nstconv_)#ifdef HAVE_MPI
if(st%d%kpt%parallel)thenif(present(conv))thencallst%d%kpt%mpi_grp%allreduce(conv,conv_reduced,1,MPI_LOGICAL,MPI_LAND)conv=conv_reducedendiflmatvec=eigens%matveccallst%d%kpt%mpi_grp%allreduce(lmatvec,eigens%matvec,1,MPI_INTEGER,MPI_SUM)SAFE_ALLOCATE(lconv(1:st%d%kpt%nlocal))lconv(1:st%d%kpt%nlocal)=eigens%converged(st%d%kpt%start:st%d%kpt%end)calllmpi_gen_allgatherv(st%d%kpt%nlocal,lconv,outcount,eigens%converged,st%d%kpt%mpi_grp)ASSERT(outcount==st%nik)SAFE_DEALLOCATE_A(lconv)! every node needs to know all eigenvalues (and diff)
SAFE_ALLOCATE(ldiff(1:st%d%kpt%nlocal))SAFE_ALLOCATE(leigenval(1:st%d%kpt%nlocal))SAFE_ALLOCATE(ldiff_out(1:st%nik))SAFE_ALLOCATE(leigenval_out(1:st%nik))doist=st%st_start,st%st_endldiff(1:st%d%kpt%nlocal)=eigens%diff(ist,st%d%kpt%start:st%d%kpt%end)leigenval(1:st%d%kpt%nlocal)=st%eigenval(ist,st%d%kpt%start:st%d%kpt%end)calllmpi_gen_allgatherv(st%d%kpt%nlocal,ldiff,outcount,ldiff_out,st%d%kpt%mpi_grp)eigens%diff(ist,:)=ldiff_outASSERT(outcount==st%nik)calllmpi_gen_allgatherv(st%d%kpt%nlocal,leigenval,outcount,leigenval_out,st%d%kpt%mpi_grp)st%eigenval(ist,:)=leigenval_outASSERT(outcount==st%nik)enddoSAFE_DEALLOCATE_A(ldiff)SAFE_DEALLOCATE_A(ldiff_out)SAFE_DEALLOCATE_A(leigenval)SAFE_DEALLOCATE_A(leigenval_out)endif#endif
POP_SUB(eigensolver_run)callprofiling_out("EIGEN_SOLVER")endsubroutineeigensolver_run