Merge branch 'develop-qe' into 'develop'

Reduce memory for Sternheimer algorithm

See merge request QEF/q-e!1399
This commit is contained in:
giannozz 2021-04-27 19:19:08 +00:00
commit 826f8d9b57
4 changed files with 12 additions and 9 deletions

View File

@ -21,7 +21,7 @@ SUBROUTINE lr_init_nfo()
USE klist, ONLY : nks,xk,ngk,igk_k
USE wvfct, ONLY : nbnd
USE lr_variables, ONLY : lr_verbosity, eels, size_evc, calculator, &
& lrdrho, nwordd0psi, iund0psi, iudwf, iu1dwf,&
& iund0psi, iudwf, iu1dwf,&
& iundvpsi
USE io_global, ONLY : stdout
USE constants, ONLY : tpi, eps8
@ -99,11 +99,9 @@ SUBROUTINE lr_init_nfo()
size_evc = nbnd * npwx * npol * nksq
nwordwfc = nbnd * npwx * npol
IF (trim(calculator)=='sternheimer') THEN
lrdrho = 2 * dfftp%nr1x * dfftp%nr2x * dfftp%nr3x * nspin_mag
nwordd0psi = nbnd * npwx * npol * nksq
CALL open_buffer ( iundvpsi, 'dvpsi.', nwordd0psi, io_level, exst_mem, exst)
CALL open_buffer ( iudwf, 'dwf', nwordd0psi, io_level, exst_mem, exst)
CALL open_buffer ( iu1dwf, 'mwf', nwordd0psi, io_level, exst_mem, exst)
CALL open_buffer ( iundvpsi, 'dvpsi.', nwordwfc, io_level, exst_mem, exst)
CALL open_buffer ( iudwf, 'dwf', nwordwfc, io_level, exst_mem, exst)
CALL open_buffer ( iu1dwf, 'mwf', nwordwfc, io_level, exst_mem, exst)
!
ENDIF
!

View File

@ -69,7 +69,7 @@ SUBROUTINE one_sternheimer_step(iu, flag)
USE mp, ONLY : mp_sum
USE fft_helper_subroutines, ONLY : fftx_ntgrp
USE lr_variables, ONLY : fru, fiu, iundvpsi, iudwf, &
lrdrho, iudrho, n_ipol, lr_verbosity, &
iudrho, n_ipol, lr_verbosity, &
chirr, chirz, chizr, chizz, epsm1, &
current_w, lr1dwf, iu1dwf, itermax!, &
!intq, intq_nc

View File

@ -60,7 +60,6 @@ MODULE lr_variables
INTEGER :: iudwf = 24
INTEGER :: iudrho = 23
INTEGER :: iu1dwf = 25
INTEGER :: lrdrho
REAL(kind=dp) :: increment
INTEGER :: units
REAL(kind=dp) :: end

View File

@ -16,7 +16,8 @@ SUBROUTINE stop_lr( full_run )
USE lr_variables, ONLY : n_ipol, LR_polarization, beta_store, &
& gamma_store, zeta_store, norm0, code1,code2, &
& lr_verbosity, itermax, bgz_suffix, &
eels, q1, q2, q3
& eels, q1, q2, q3, calculator, iundvpsi, iudwf,&
& iu1dwf
USE io_global, ONLY : ionode, stdout
USE io_files, ONLY : tmp_dir, prefix, iunwfc
USE environment, ONLY : environment_end
@ -144,6 +145,11 @@ SUBROUTINE stop_lr( full_run )
! EELS: Close the file where it read the wavefunctions at k and k+q.
!
IF (eels) CALL close_buffer(iunwfc, 'keep')
IF ( trim(calculator)=='sternheimer' ) THEN
CALL close_buffer ( iundvpsi,'delete' )
CALL close_buffer ( iudwf,'delete' )
CALL close_buffer ( iu1dwf,'delete' )
ENDIF
!
STOP
!