Skip to content

Commit

Permalink
XAS_TDP| Added SOC based on quasi-degenerate-perturbation-theory (QDPT)
Browse files Browse the repository at this point in the history
  • Loading branch information
abussy authored and pseewald committed Oct 9, 2019
1 parent e6dc58b commit 4cee207
Show file tree
Hide file tree
Showing 11 changed files with 1,420 additions and 498 deletions.
1 change: 1 addition & 0 deletions src/atom_operators.F
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,7 @@ MODULE atom_operators

PUBLIC :: atom_int_setup, atom_ppint_setup, atom_int_release, atom_ppint_release
PUBLIC :: atom_relint_setup, atom_relint_release, atom_basis_projection_overlap
PUBLIC :: calculate_model_potential

CONTAINS

Expand Down
4 changes: 4 additions & 0 deletions src/cp_control_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -463,6 +463,7 @@ MODULE cp_control_types
TYPE(tddfpt_control_type), POINTER :: tddfpt_control
TYPE(tddfpt2_control_type), POINTER :: tddfpt2_control
TYPE(xas_control_type), POINTER :: xas_control
TYPE(xas_tdp_control_type), POINTER :: xas_tdp_control
TYPE(efield_p_type), POINTER, &
DIMENSION(:) :: efield_fields
INTEGER :: nspins, &
Expand All @@ -485,6 +486,7 @@ MODULE cp_control_types
sic_scaling_b
LOGICAL :: do_tddfpt_calculation, &
do_xas_calculation, &
do_xas_tdp_calculation, &
drho_by_collocation, &
use_kinetic_energy_density, &
restricted, &
Expand Down Expand Up @@ -762,6 +764,7 @@ SUBROUTINE dft_control_create(dft_control)
last_dft_control_id = last_dft_control_id+1
dft_control%id_nr = last_dft_control_id
NULLIFY (dft_control%xas_control)
NULLIFY (dft_control%xas_tdp_control)
NULLIFY (dft_control%qs_control)
NULLIFY (dft_control%tddfpt_control)
NULLIFY (dft_control%tddfpt2_control)
Expand Down Expand Up @@ -816,6 +819,7 @@ SUBROUTINE dft_control_release(dft_control)
CALL tddfpt_control_release(dft_control%tddfpt_control)
CALL tddfpt2_control_release(dft_control%tddfpt2_control)
CALL xas_control_release(dft_control%xas_control)
CALL xas_tdp_control_release(dft_control%xas_tdp_control)
CALL admm_control_release(dft_control%admm_control)
CALL efield_fields_release(dft_control%efield_fields)
CALL sccs_control_release(dft_control%sccs_control)
Expand Down
10 changes: 8 additions & 2 deletions src/cp_control_utils.F
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
!TEMP COMMENT
!--------------------------------------------------------------------------------------------------!
! CP2K: A general program to perform molecular dynamics simulations !
! Copyright (C) 2000 - 2019 CP2K developers group !
Expand Down Expand Up @@ -364,6 +363,14 @@ SUBROUTINE read_dft_control(dft_control, dft_section)
l_val=dft_control%do_xas_calculation)
END IF

tmp_section => section_vals_get_subs_vals(dft_section, "XAS_TDP")
CALL section_vals_get(tmp_section, explicit=dft_control%do_xas_tdp_calculation)
IF (dft_control%do_xas_tdp_calculation) THEN
! Override with section parameter
CALL section_vals_val_get(tmp_section, "_SECTION_PARAMETERS_", &
l_val=dft_control%do_xas_tdp_calculation)
END IF

! Read the finite field input section
dft_control%apply_efield = .FALSE.
dft_control%apply_efield_field = .FALSE. !this is for RTP
Expand Down Expand Up @@ -707,7 +714,6 @@ SUBROUTINE read_qs_section(qs_control, qs_section)
CALL section_vals_val_get(qs_section, "CLUSTER_EMBED_SUBSYS", l_val=qs_control%cluster_embed_subsys)
CALL section_vals_val_get(qs_section, "HIGH_LEVEL_EMBED_SUBSYS", l_val=qs_control%high_level_embed_subsys)
CALL section_vals_val_get(qs_section, "DFET_EMBEDDED", l_val=qs_control%dfet_embedded)
CALL section_vals_val_get(qs_section, "DMFET_EMBEDDED", l_val=qs_control%dmfet_embedded)
! Integers gapw
CALL section_vals_val_get(qs_section, "LMAXN1", i_val=qs_control%gapw_control%lmax_sphere)
Expand Down
11 changes: 4 additions & 7 deletions src/input_constants.F
Original file line number Diff line number Diff line change
Expand Up @@ -543,7 +543,8 @@ MODULE input_constants
INTEGER, PARAMETER, PUBLIC :: sic_list_all = 1, &
sic_list_unpaired = 2
INTEGER, PARAMETER, PUBLIC :: tddfpt_singlet = 0, &
tddfpt_triplet = 1
tddfpt_triplet = 1, &
tddfpt_both = 2
INTEGER, PARAMETER, PUBLIC :: tddfpt_lanczos = 0, &
tddfpt_davidson = 1
INTEGER, PARAMETER, PUBLIC :: oe_none = 0, &
Expand Down Expand Up @@ -611,7 +612,8 @@ MODULE input_constants
xas_tp_xfh = 5, &
xas_dscf = 6, &
xas_tp_flex = 7
INTEGER, PARAMETER, PUBLIC :: xas_1s_type = 1, &
INTEGER, PARAMETER, PUBLIC :: xas_not_excited = 0, &
xas_1s_type = 1, &
xas_2s_type = 2, &
xas_2p_type = 3, &
xas_3s_type = 4, &
Expand All @@ -637,11 +639,6 @@ MODULE input_constants
tddfpt_dipole_length = 2, &
tddfpt_dipole_velocity = 3

! Time-dependent XAS
INTEGER, PARAMETER, PUBLIC :: xas_tdp_by_index = 1, &
xas_tdp_by_kind = 2, &
xas_tdp_exop_coulomb = 1

! Linear Response for properties
INTEGER, PARAMETER, PUBLIC :: lr_none = 0, &
lr_chemshift = 1, &
Expand Down
80 changes: 41 additions & 39 deletions src/input_cp2k_dft.F
Original file line number Diff line number Diff line change
Expand Up @@ -96,7 +96,7 @@ MODULE input_cp2k_dft
xas_2s_type, xas_3d_type, xas_3p_type, xas_3s_type, xas_4d_type, xas_4f_type, xas_4p_type, &
xas_4s_type, xas_dip_len, xas_dip_vel, xas_dscf, xas_none, xas_tp_fh, xas_tp_flex, &
xas_tp_hh, xas_tp_xfh, xas_tp_xhh, xes_tp_val, xas_not_excited, xas_tdp_by_kind, &
xas_tdp_by_index, xas_tdp_hfx, xas_tdp_pade
xas_tdp_by_index, xas_tdp_hfx, xas_tdp_pade, tddfpt_both
USE input_cp2k_almo, ONLY: create_almo_scf_section
USE input_cp2k_distribution, ONLY: create_distribution_section
USE input_cp2k_field, ONLY: create_efield_section,&
Expand Down Expand Up @@ -419,6 +419,10 @@ SUBROUTINE create_dft_section(section)
CALL section_add_subsection(section, subsection)
CALL section_release(subsection)

CALL create_xas_tdp_section(subsection)
CALL section_add_subsection(section, subsection)
CALL section_release(subsection)

CALL create_localize_section(subsection)
CALL section_add_subsection(section, subsection)
CALL section_release(subsection)
Expand Down Expand Up @@ -3257,15 +3261,11 @@ SUBROUTINE create_qs_section(section)
CALL section_add_subsection(section, subsection)
CALL section_release(subsection)

! Embedding subsections: DFET and DMFET
! Embedding subsections
CALL create_optimize_embed(subsection)
CALL section_add_subsection(section, subsection)
CALL section_release(subsection)

CALL create_optimize_dmfet(subsection)
CALL section_add_subsection(section, subsection)
CALL section_release(subsection)

END SUBROUTINE create_qs_section

! **************************************************************************************************
Expand Down Expand Up @@ -6190,7 +6190,7 @@ SUBROUTINE create_print_embed_pot_cube(section)
description="The stride (X,Y,Z) used to write the cube file "// &
"(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
" 1 number valid for all components.", &
usage="STRIDE 1 1 1", n_var=-1, default_i_vals=(/1, 1, 1/), type_of_var=integer_t)
usage="STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
CALL section_add_keyword(print_key, keyword)
CALL keyword_release(keyword)

Expand Down Expand Up @@ -6244,7 +6244,7 @@ SUBROUTINE create_print_simple_grid(section)
description="The stride (X,Y,Z) used to write the cube file "// &
"(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
" 1 number valid for all components.", &
usage="STRIDE 1 1 1", n_var=-1, default_i_vals=(/1, 1, 1/), type_of_var=integer_t)
usage="STRIDE 1 1 1", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
CALL section_add_keyword(print_key, keyword)
CALL keyword_release(keyword)

Expand Down Expand Up @@ -7668,7 +7668,7 @@ SUBROUTINE create_xas_section(section)

CALL keyword_create(keyword, __LOCATION__, name="STATE_TYPE", &
variants=(/"TYPE"/), &
description="Type of the orbitas that are excited for the xas spectra calculation", &
description="Type of the orbitals that are excited for the xas spectra calculation", &
usage="STATE_TYPE 1S", &
default_i_val=xas_1s_type, &
enum_c_vals=s2a("1S", "2S", "2P", "3S", "3P", "3D", "4S", "4P", "4D", "4F"), &
Expand Down Expand Up @@ -7880,7 +7880,7 @@ SUBROUTINE create_xas_tdp_section(section)
description="XAS simulations using TDDFPT. Excitation from specified "// &
"core orbitals are considered one at a time. In case of high symmetry "// &
"structures, donor core orbitals should be localized.", &
n_keywords=11, n_subsections=4, repeats=.FALSE.)
n_keywords=14, n_subsections=3, repeats=.FALSE.)

NULLIFY (keyword, subsection, print_key)

Expand Down Expand Up @@ -7983,14 +7983,27 @@ SUBROUTINE create_xas_tdp_section(section)
CALL keyword_create(keyword, name="EXCITATIONS", &
variants=(/"EXCITATION"/), &
description="Whether singlet or triplet excitations should be "// &
"considered (starting from the spin-restricted ground state)",&
"considered (starting from the spin-restricted ground state)."//&
"BOTH is needed for spin-orbit coupling calculations.",&
usage="EXCITATIONS {string}", &
default_i_val=tddfpt_singlet, &
enum_c_vals=s2a("SINGLET", "TRIPLET"), &
enum_i_vals=(/tddfpt_singlet, tddfpt_triplet/))
enum_c_vals=s2a("SINGLET", "TRIPLET", "BOTH"), &
enum_i_vals=(/tddfpt_singlet, tddfpt_triplet, tddfpt_both/))
CALL section_add_keyword(section, keyword)
CALL keyword_release(keyword)

CALL keyword_create(keyword, name="SPIN_ORBIT_COUPLING", &
variants=(/"SOC"/), &
description="The number of excited states to include in spin-orbit "// &
"coupling calculations. The N lowest energy excited states, "// &
"regardless of their spin multiplicity, are taken. "// &
"If zero, SOC is not treated. If -1, all available "// &
"excited states are taken.", &
usage="SOC {integer}", &
default_i_val=0)
CALL section_add_keyword(section, keyword)
CALL keyword_release(keyword)

CALL keyword_create(keyword, name="TAMM_DANCOFF", &
variants=(/"TDA"/), &
description="Whether the Tamm-Dancoff approximation should be used.", &
Expand All @@ -8007,39 +8020,28 @@ SUBROUTINE create_xas_tdp_section(section)
CALL section_add_keyword(section, keyword)
CALL keyword_release(keyword)

!*** XC_KERNEL subsection ***!
CALL section_create(subsection, "XC_KERNEL", &
description="This subsection sets parameter for the xc kernel "//&
"evaluation such as the functional to use and the atomic "//&
"grids specification", &
n_keywords=2, n_subsections=0, repeats=.FALSE.)

CALL keyword_create(keyword, name="FUNCTIONAL", &
CALL keyword_create(keyword, name="XC_KERNEL", &
description="This keyword is used to chose the functional with which "//&
"the XC kernel should be evaluated. Currently only exact "//&
"exchange and the PADE(LDA) are available.", &
usage="FUNCTIONAL string", &
default_i_val=xas_tdp_hfx, &
enum_c_vals=s2a("HFX", "PADE"), &
enum_i_vals=(/xas_tdp_hfx, xas_tdp_pade/))
CALL section_add_keyword(subsection, keyword)
CALL keyword_release(keyword)
"exchange (HFX) and the LDA (PADE) are available.", &
usage="XC_KERNEL string", &
default_i_val=xas_tdp_hfx, &
enum_c_vals=s2a("HFX", "PADE"), &
enum_i_vals=(/xas_tdp_hfx, xas_tdp_pade/))
CALL section_add_keyword(section, keyword)
CALL keyword_release(keyword)

CALL keyword_create(keyword, name="GRID", &
description="Specification of the atomic grids for the excited kinds."//&
"This keyword can/should be repeated for each excited kind. "//&
description="Specification of the atomic grids for a given atomic kind."//&
"This keyword can/should be repeated for each kind. "//&
"The default grid dimensions are those set for the GAPW "// &
"ground state calculation.", &
"ground state calculation. These grids are used for PADE "// &
"xc-kernel calculations and/or for spin-orbit coupling.", &
usage="GRID kind na nr", &
n_var=3, type_of_var=char_t, repeats=.TRUE.)
CALL section_add_keyword(subsection, keyword)
CALL section_add_keyword(section, keyword)
CALL keyword_release(keyword)

CALL section_add_subsection(section, subsection)
CALL section_release(subsection)

!*** END of XC_KERNEL subsection ***!

CALL create_localize_section(subsection)
CALL section_add_subsection(section, subsection)
CALL section_release(subsection)
Expand All @@ -8066,8 +8068,8 @@ SUBROUTINE create_xas_tdp_section(section)
CALL section_add_subsection(section, subsection)
CALL section_release(subsection)

END SUBROUTINE create_xas_tdp_section

END SUBROUTINE create_xas_tdp_section
! **************************************************************************************************
!> \brief Create CP2K input section for the smearing of occupation numbers
!> \param section ...
Expand Down
1 change: 1 addition & 0 deletions src/qs_energy_utils.F
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,7 @@ MODULE qs_energy_utils
USE qs_tddfpt2_methods, ONLY: tddfpt
USE scf_control_types, ONLY: scf_control_type
USE xas_methods, ONLY: xas
USE xas_tdp_methods, ONLY: xas_tdp
#include "./base/base_uses.f90"

IMPLICIT NONE
Expand Down
2 changes: 1 addition & 1 deletion src/xas_methods.F
Original file line number Diff line number Diff line change
Expand Up @@ -130,7 +130,7 @@ MODULE xas_methods

! *** Public subroutines ***

PUBLIC :: xas
PUBLIC :: xas, calc_stogto_overlap

CONTAINS

Expand Down

0 comments on commit 4cee207

Please sign in to comment.