Skip to content

Commit

Permalink
Set defaults method dependent for sTDA MN exponents (#1946)
Browse files Browse the repository at this point in the history
* Set defaults method dependent for sTDA MN exponents
Allow for input of parameters
Adjust regtests

* sTDA input, correct release of keyword

* Correctly set parameters from input
  • Loading branch information
juerghutter committed Feb 15, 2022
1 parent 2f1076a commit 903cfe9
Show file tree
Hide file tree
Showing 9 changed files with 231 additions and 14 deletions.
2 changes: 2 additions & 0 deletions src/cp_control_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -424,6 +424,8 @@ MODULE cp_control_types
LOGICAL :: do_exchange
REAL(KIND=dp) :: hfx_fraction
REAL(KIND=dp) :: eps_td_filter
REAL(KIND=dp) :: mn_alpha
REAL(KIND=dp) :: mn_beta
END TYPE stda_control_type

! **************************************************************************************************
Expand Down
8 changes: 7 additions & 1 deletion src/cp_control_utils.F
Original file line number Diff line number Diff line change
Expand Up @@ -1259,7 +1259,7 @@ SUBROUTINE read_tddfpt2_control(t_control, t_section, qs_control)
INTEGER, ALLOCATABLE, DIMENSION(:) :: inds
LOGICAL :: do_ewald, do_exchange, expl, explicit, &
multigrid_set
REAL(KIND=dp) :: filter, hfx
REAL(KIND=dp) :: filter, fval, hfx
TYPE(section_vals_type), POINTER :: dipole_section, mgrid_section, &
stda_section, xc_func, xc_section
Expand Down Expand Up @@ -1415,6 +1415,8 @@ SUBROUTINE read_tddfpt2_control(t_control, t_section, qs_control)
t_control%stda_control%hfx_fraction = 0.0_dp
t_control%stda_control%do_exchange = .TRUE.
t_control%stda_control%eps_td_filter = 1.e-10_dp
t_control%stda_control%mn_alpha = -99.0_dp
t_control%stda_control%mn_beta = -99.0_dp
! set default for Ewald method (on/off) dependent on periodicity
SELECT CASE (qs_control%periodicity)
CASE (0)
Expand All @@ -1439,6 +1441,10 @@ SUBROUTINE read_tddfpt2_control(t_control, t_section, qs_control)
IF (expl) t_control%stda_control%do_ewald = do_ewald
CALL section_vals_val_get(stda_section, "DO_EXCHANGE", l_val=do_exchange, explicit=expl)
IF (expl) t_control%stda_control%do_exchange = do_exchange
CALL section_vals_val_get(stda_section, "MATAGA_NISHIMOTO_CEXP", r_val=fval)
t_control%stda_control%mn_alpha = fval
CALL section_vals_val_get(stda_section, "MATAGA_NISHIMOTO_XEXP", r_val=fval)
t_control%stda_control%mn_beta = fval
END IF
CALL timestop(handle)
Expand Down
14 changes: 14 additions & 0 deletions src/input_cp2k_properties_dft.F
Original file line number Diff line number Diff line change
Expand Up @@ -1646,6 +1646,20 @@ SUBROUTINE create_stda_section(section)
CALL section_add_keyword(section, keyword)
CALL keyword_release(keyword)

CALL keyword_create(keyword, __LOCATION__, name="MATAGA_NISHIMOTO_CEXP", &
description="Exponent used in Mataga-Nishimoto formula for Coulomb (alpha). "// &
"Default value is method dependent!", &
usage="MATAGA_NISHIMOTO_CEXP", default_r_val=-99.0_dp)
CALL section_add_keyword(section, keyword)
CALL keyword_release(keyword)

CALL keyword_create(keyword, __LOCATION__, name="MATAGA_NISHIMOTO_XEXP", &
description="Exponent used in Mataga-Nishimoto formula for Exchange (beta). "// &
"Default value is method dependent!", &
usage="MATAGA_NISHIMOTO_XEXP", default_r_val=-99.0_dp)
CALL section_add_keyword(section, keyword)
CALL keyword_release(keyword)

END SUBROUTINE create_stda_section

! **************************************************************************************************
Expand Down
55 changes: 50 additions & 5 deletions src/qs_tddfpt2_stda_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,14 @@ MODULE qs_tddfpt2_stda_types
get_atomic_kind
USE basis_set_types, ONLY: get_gto_basis_set,&
gto_basis_set_type
USE cp_control_types, ONLY: stda_control_type
USE cp_control_types, ONLY: dft_control_type,&
stda_control_type
USE cp_log_handling, ONLY: cp_get_default_logger,&
cp_logger_type
USE cp_output_handling, ONLY: cp_print_key_finished_output,&
cp_print_key_unit_nr
USE input_section_types, ONLY: section_vals_get_subs_vals,&
section_vals_type
USE kinds, ONLY: dp
USE physcon, ONLY: evolt
USE qs_environment_types, ONLY: get_qs_env,&
Expand Down Expand Up @@ -117,20 +124,31 @@ SUBROUTINE stda_init_param(qs_env, stda_kernel, stda_control)
TYPE(stda_env_type) :: stda_kernel
TYPE(stda_control_type) :: stda_control

INTEGER :: ikind, nkind
INTEGER :: ikind, log_unit, nkind
TYPE(atomic_kind_type), DIMENSION(:), POINTER :: atomic_kind_set
TYPE(atomic_kind_type), POINTER :: atomic_kind
TYPE(cp_logger_type), POINTER :: logger
TYPE(dft_control_type), POINTER :: dft_control
TYPE(gto_basis_set_type), POINTER :: tmp_basis_set
TYPE(qs_kind_type), DIMENSION(:), POINTER :: qs_kind_set
TYPE(qs_kind_type), POINTER :: qs_kind
TYPE(section_vals_type), POINTER :: tddfpt_print_section
TYPE(stda_kind_type), POINTER :: kind_param

NULLIFY (logger)
logger => cp_get_default_logger()

CPASSERT(ASSOCIATED(stda_kernel%kind_param_set))

NULLIFY (atomic_kind_set, qs_kind_set) !get element symbol and atomic number
CALL get_qs_env(qs_env, atomic_kind_set=atomic_kind_set, qs_kind_set=qs_kind_set)
CALL get_qs_env(qs_env, dft_control=dft_control, &
atomic_kind_set=atomic_kind_set, qs_kind_set=qs_kind_set)
nkind = SIZE(qs_kind_set)

NULLIFY (tddfpt_print_section)
tddfpt_print_section => section_vals_get_subs_vals(qs_env%input, "PROPERTIES%TDDFPT%PRINT")
log_unit = cp_print_key_unit_nr(logger, tddfpt_print_section, "PROGRAM_BANNER", extension=".tddfptLog")

DO ikind = 1, nkind
atomic_kind => atomic_kind_set(ikind)
kind_param => stda_kernel%kind_param_set(ikind)%kind_param
Expand All @@ -151,8 +169,24 @@ SUBROUTINE stda_init_param(qs_env, stda_kernel, stda_control)
END IF

! alpha and beta parameter
stda_kernel%alpha_param = alpha(1) + stda_kernel%hfx_fraction*alpha(2)
stda_kernel%beta_param = beta(1) + stda_kernel%hfx_fraction*beta(2)
IF (stda_control%mn_alpha < -98.0_dp) THEN
IF (dft_control%qs_control%xtb) THEN
stda_kernel%alpha_param = 2.0_dp
ELSE
stda_kernel%alpha_param = alpha(1) + stda_kernel%hfx_fraction*alpha(2)
END IF
ELSE
stda_kernel%alpha_param = stda_control%mn_alpha
END IF
IF (stda_control%mn_beta < -98.0_dp) THEN
IF (dft_control%qs_control%xtb) THEN
stda_kernel%beta_param = 4.0_dp
ELSE
stda_kernel%beta_param = beta(1) + stda_kernel%hfx_fraction*beta(2)
END IF
ELSE
stda_kernel%beta_param = stda_control%mn_beta
END IF

! TD Filter
stda_kernel%eps_td_filter = stda_control%eps_td_filter
Expand All @@ -168,6 +202,17 @@ SUBROUTINE stda_init_param(qs_env, stda_kernel, stda_control)
kind_radius=stda_kernel%kind_param_set(ikind)%kind_param%rcut)
END DO

IF (log_unit > 0) THEN
IF (.NOT. stda_kernel%do_exchange) THEN
WRITE (log_unit, "(T2,A,T78,A3)") "sTDA| Exchange term is not used!"
END IF
WRITE (log_unit, "(T2,A,T71,F10.4)") "sTDA| HFX Fraction", stda_kernel%hfx_fraction
WRITE (log_unit, "(T2,A,T71,F10.4)") "sTDA| Mataga-Nishimoto exponent (C)", stda_kernel%alpha_param
WRITE (log_unit, "(T2,A,T71,F10.4)") "sTDA| Mataga-Nishimoto exponent (X)", stda_kernel%beta_param
WRITE (log_unit, "(T2,A,T61,E20.8)") "sTDA| TD matrix filter", stda_kernel%eps_td_filter
END IF
CALL cp_print_key_finished_output(log_unit, logger, tddfpt_print_section, "PROGRAM_BANNER")

END SUBROUTINE stda_init_param
! **************************************************************************************************
!> \brief Allocate the sTDA environment
Expand Down
4 changes: 2 additions & 2 deletions tests/QS/regtest-stda-force/TEST_FILES
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,6 @@ h2o_f06.inp 1 1.0E-12
h2o_f07.inp 1 1.0E-12 -17.23463662845554
h2o_f08a.inp 1 1.0E-12 -17.23033252463928
h2o_f08b.inp 1 1.0E-12 -17.23207360292983
CH2O_stda-xtb-s_virtual_shift.inp 37 1.0E-06 0.256889E-01
water_xTB_virtual_shift.inp 37 1.0E-06 0.295621E+00
CH2O_stda-xtb-s_virtual_shift.inp 37 1.0E-06 0.779158E-01
water_xTB_virtual_shift.inp 37 1.0E-06 0.236248E+00
#EOF
6 changes: 3 additions & 3 deletions tests/QS/regtest-tddfpt-stda/TEST_FILES
Original file line number Diff line number Diff line change
Expand Up @@ -8,14 +8,14 @@ CH2Oplus_tddfpt_stda-lsd.inp 37 1.0E-05
CH2O_tddfpt_stda-pbe-s.inp 37 1.0E-05 0.125452E+00
CH2O_tddfpt_stda-pbe-s_doexchange.inp 37 1.0E-05 0.155105E+00
CH2O_tddfpt_stda-xtb-s.inp 37 1.0E-05 0.150482E+00
CH2O_stda-xtb-s.inp 37 1.0E-05 0.256889E-01
CH2O_stda-xtb-s.inp 37 1.0E-05 0.779158E-01
H2O_tddfpt_stda-pbe-s.inp 37 1.0E-05 0.599658E+00
H2Oplus_tddfpt_stda-pbe-lsd.inp 37 1.0E-05 0.463329E+00
H2O_tddfpt_stda-pbe-t.inp 37 1.0E-05 0.595565E+00
H2O_tddfpt_stda-pbe0-s.inp 37 1.0E-05 0.637391E+00
H2O_tddfpt_stda-pbe0-t.inp 37 1.0E-05 0.633489E+00
H2O_tddfpt_stda-s-1.inp 37 1.0E-05 0.173021E+00
NO_tddfpt_stda-s-1.inp 37 1.0E-05 0.375613E+00
water_xTB.inp 37 2.0E-05 0.185374E+00
water_xTBi_NTO.inp 37 2.0E-05 0.185374E+00
water_xTB.inp 37 2.0E-05 0.126001E+00
water_xTBi_NTO.inp 37 2.0E-05 0.126001E+00
#EOF
4 changes: 2 additions & 2 deletions tests/xTB/regtest-debug/TEST_FILES
Original file line number Diff line number Diff line change
Expand Up @@ -9,8 +9,8 @@ ch2o_t03.inp 86 1.0E-12 0.11459198
ch2o_t04.inp 86 1.0E-12 0.109829662200E+01
ch2o_t05.inp 87 1.0E-12 0.226843652140E+02
ch2o_t06.inp 87 1.0E-12 0.230117849452E+02
ch2o_t07.inp 86 1.0E-12 0.914433972994E+00
ch2o_t08.inp 86 1.0E-12 0.924084786637E+00
ch2o_t07.inp 86 1.0E-12 0.954101834865E+00
ch2o_t08.inp 86 1.0E-12 0.963128388956E+00
ch3br_nonbond_2.inp 1 1.0E-12 -11.78062819229165
ch3br_nonbond.inp 1 1.0E-12 -11.78062802267188
ch3br_atprop_nonbond.inp 1 1.0E-10 -11.78112949522890
Expand Down
3 changes: 2 additions & 1 deletion tests/xTB/regtest-stda/TEST_FILES
Original file line number Diff line number Diff line change
Expand Up @@ -4,5 +4,6 @@
# 1 compares the last total energy in the file
# for details see cp2k/tools/do_regtest
#
water_xTB.inp 37 2.0E-05 0.185374E+00
water_xTB.inp 37 2.0E-05 0.126001E+00
water_xTB_2.inp 37 2.0E-05 0.186902E+00
#EOF
149 changes: 149 additions & 0 deletions tests/xTB/regtest-stda/water_xTB_2.inp
Original file line number Diff line number Diff line change
@@ -0,0 +1,149 @@
&GLOBAL
PROJECT water_xTB
RUN_TYPE ENERGY
PRINT_LEVEL LOW
PREFERRED_DIAG_LIBRARY SL
&END GLOBAL
&FORCE_EVAL
METHOD Quickstep
&PROPERTIES
&TDDFPT
KERNEL sTDA
&sTDA
FRACTION 0.5
DO_EWALD T
MATAGA_NISHIMOTO_CEXP 2.50
MATAGA_NISHIMOTO_XEXP 3.00
&END sTDA
OE_CORR SHIFT
EV_SHIFT [eV] 2.0
NSTATES 1
MAX_ITER 50
CONVERGENCE [eV] 1.0e-5
&END TDDFPT
&END PROPERTIES
&DFT
&QS
METHOD xTB
&xTB
DO_EWALD T
&END
&END QS
&SCF
SCF_GUESS atomic
MAX_SCF 10
EPS_SCF 1.E-5
&OUTER_SCF
MAX_SCF 10
EPS_SCF 1.E-5
&END
&OT ON
MINIMIZER DIIS
PRECONDITIONER FULL_SINGLE_INVERSE
&END OT
&END SCF
&END DFT
&SUBSYS
&CELL
ABC 9.8528 9.8528 9.8528
&END CELL
&COORD
O 2.280398 9.146539 5.088696
O 1.251703 2.406261 7.769908
O 1.596302 6.920128 0.656695
O 2.957518 3.771868 1.877387
O 0.228972 5.884026 6.532308
O 9.023431 6.119654 0.092451
O 7.256289 8.493641 5.772041
O 5.090422 9.467016 0.743177
O 6.330888 7.363471 3.747750
O 7.763819 8.349367 9.279457
O 8.280798 3.837153 5.799282
O 8.878250 2.025797 1.664102
O 9.160372 0.285100 6.871004
O 4.962043 4.134437 0.173376
O 2.802896 8.690383 2.435952
O 9.123223 3.549232 8.876721
O 1.453702 1.402538 2.358278
O 6.536550 1.146790 7.609732
O 2.766709 0.881503 9.544263
O 0.856426 2.075964 5.010625
O 6.386036 1.918950 0.242690
O 2.733023 4.452756 5.850203
O 4.600039 9.254314 6.575944
O 3.665373 6.210561 3.158420
O 3.371648 6.925594 7.476036
O 5.287920 3.270653 6.155080
O 5.225237 6.959594 9.582991
O 0.846293 5.595877 3.820630
O 9.785620 8.164617 3.657879
O 8.509982 4.430362 2.679946
O 1.337625 8.580920 8.272484
O 8.054437 9.221335 1.991376
H 1.762019 9.820429 5.528454
H 3.095987 9.107088 5.588186
H 0.554129 2.982634 8.082024
H 1.771257 2.954779 7.182181
H 2.112148 6.126321 0.798136
H 1.776389 7.463264 1.424030
H 3.754249 3.824017 1.349436
H 3.010580 4.524142 2.466878
H 0.939475 5.243834 6.571945
H 0.515723 6.520548 5.877445
H 9.852960 6.490366 0.393593
H 8.556008 6.860063 -0.294256
H 7.886607 7.941321 6.234506
H 7.793855 9.141028 5.315813
H 4.467366 9.971162 0.219851
H 5.758685 10.102795 0.998994
H 6.652693 7.917443 3.036562
H 6.711966 7.743594 4.539279
H 7.751955 8.745180 10.150905
H 7.829208 9.092212 8.679343
H 8.312540 3.218330 6.528858
H 8.508855 4.680699 6.189990
H 9.742249 1.704975 1.922581
H 8.799060 2.876412 2.095861
H 9.505360 1.161677 6.701213
H 9.920117 -0.219794 7.161006
H 4.749903 4.186003 -0.758595
H 5.248010 5.018415 0.403676
H 3.576065 9.078451 2.026264
H 2.720238 9.146974 3.273164
H 9.085561 4.493058 9.031660
H 9.215391 3.166305 9.749133
H 1.999705 2.060411 1.927796
H 1.824184 0.564565 2.081195
H 7.430334 0.849764 7.438978
H 6.576029 1.537017 8.482885
H 2.415851 1.576460 8.987338
H 2.276957 0.099537 9.289499
H 1.160987 1.818023 4.140602
H 0.350256 2.874437 4.860741
H 5.768804 2.638450 0.375264
H 7.221823 2.257514 0.563730
H 3.260797 5.243390 5.962382
H 3.347848 3.732214 5.988196
H 5.328688 9.073059 5.982269
H 5.007063 9.672150 7.334875
H 4.566850 6.413356 3.408312
H 3.273115 7.061666 2.963521
H 3.878372 7.435003 6.843607
H 3.884673 6.966316 8.283117
H 5.918240 3.116802 5.451335
H 5.355924 2.495093 6.711958
H 5.071858 7.687254 10.185667
H 6.106394 7.112302 9.241707
H 1.637363 5.184910 4.169264
H 0.427645 4.908936 3.301903
H 9.971698 7.227076 3.709104
H 10.647901 8.579244 3.629806
H 8.046808 5.126383 2.213838
H 7.995317 4.290074 3.474723
H 1.872601 7.864672 7.930401
H 0.837635 8.186808 8.987268
H 8.314696 10.115534 2.212519
H 8.687134 8.667252 2.448452
&END COORD
&END SUBSYS
&END FORCE_EVAL

0 comments on commit 903cfe9

Please sign in to comment.