fixing selection of rmm diagonalization mode

This commit is contained in:
Pietro Delugas 2021-07-15 19:34:02 +02:00
parent 3c1b5dae41
commit 2345a7fa99
4 changed files with 19 additions and 19 deletions

View File

@ -151,15 +151,7 @@ CONTAINS
CALL get_command_argument ( narg, arg )
ENDIF
READ ( arg, *, ERR = 15, END = 15) nmany_
narg = narg + 1
CASE ( '-rmmparo', '-rmm_with_paro', '-rmm_use_paro' )
IF (read_string) THEN
CALL my_getarg ( input_command_line, narg, arg )
ELSE
CALL get_command_argument ( narg, arg )
ENDIF
READ ( arg, *, ERR = 15, END = 15) rmm_with_paro_
narg = narg + 1
narg = narg + 1
CASE DEFAULT
command_line = TRIM(command_line) // ' ' // TRIM(arg)
END SELECT
@ -182,7 +174,6 @@ CONTAINS
CALL mp_bcast( nband_ , root, world_comm )
CALL mp_bcast( ndiag_ , root, world_comm )
CALL mp_bcast( pencil_decomposition_ , root, world_comm )
CALL mp_bcast( rmm_with_paro_, root, world_comm)
END SUBROUTINE get_command_line
!

View File

@ -208,9 +208,10 @@ MODULE control_flags
rmm_ndim, &! max dimension of subspace in RMM-DIIS diagonalization
gs_nblock ! blocking size in Gram-Schmidt orthogonalization
LOGICAL, PUBLIC :: &
rmm_conv, &! if true, RMM-DIIS is performed up to converge
diago_full_acc = .FALSE. ! if true, empty eigenvalues have the same
! accuracy of the occupied ones
rmm_conv, &! if true, RMM-DIIS is performed up to converge
rmm_with_davidson = .TRUE., &! if true RMM-DIIS in alternance with davidson
diago_full_acc = .FALSE. ! if true, empty eigenvalues have the same
! accuracy of the occupied ones
!
! ... ionic dynamics
!

View File

@ -1300,17 +1300,17 @@ SUBROUTINE c_bands_nscf( )
END SUBROUTINE c_bands_nscf
FUNCTION rmm_use_davidson(iter_) RESULT (res)
USE command_line_options, ONLY: rmm_with_paro_
USE control_flags, ONLY: rmm_with_davidson
IMPLICIT NONE
INTEGER,INTENT(IN) :: iter_
LOGICAL :: res
res = (.NOT. rmm_with_paro_) .AND. ( iter_ < 3 .OR. MOD(iter_,5) == 0)
res = (rmm_with_davidson) .AND. ( iter_ < 3 .OR. MOD(iter_,5) == 0)
END FUNCTION rmm_use_davidson
FUNCTION rmm_use_paro(iter_) RESULT (res)
USE command_line_options, ONLY: rmm_with_paro_
USE control_flags, ONLY: rmm_with_davidson
IMPLICIT NONE
INTEGER, INTENT(IN) :: iter_
LOGICAL :: res
res = (rmm_with_paro_) .AND. (MOD(iter_,8) == 0)
res = (.NOT. rmm_with_davidson) .AND. (MOD(iter_,5) == 1)
END FUNCTION rmm_use_paro

View File

@ -144,7 +144,7 @@ SUBROUTINE iosys()
!
USE extrapolation, ONLY : pot_order, wfc_order
USE control_flags, ONLY : isolve, max_cg_iter, max_ppcg_iter, david, &
rmm_ndim, rmm_conv, gs_nblock, &
rmm_ndim, rmm_conv, gs_nblock, rmm_with_davidson, &
tr2, imix, gamma_only, &
nmix, iverbosity, smallmem, niter, &
io_level, ethr, lscf, lbfgs, lmd, &
@ -981,13 +981,21 @@ SUBROUTINE iosys()
!
isolve = 3
!
CASE ( 'rmm', 'rmm-diis' )
CASE ( 'rmm', 'rmm-diis', 'rmm-davidson' )
!
isolve = 4
rmm_ndim = diago_rmm_ndim
rmm_conv = diago_rmm_conv
gs_nblock = diago_gs_nblock
rmm_with_davidson = .TRUE.
!
CASE ( 'rmm-paro')
!
isolve = 4
rmm_ndim = diago_rmm_ndim
rmm_conv = diago_rmm_conv
gs_nblock = diago_gs_nblock
rmm_with_davidson = .FALSE.
CASE DEFAULT
!
CALL errore( 'iosys', 'diagonalization ' // &