Skip to content

Commit

Permalink
Remove the 'method' component of the derived type 'qs_control_type'
Browse files Browse the repository at this point in the history
  • Loading branch information
schulkov committed Jan 18, 2020
1 parent 7bf9092 commit 89607a6
Show file tree
Hide file tree
Showing 3 changed files with 33 additions and 34 deletions.
1 change: 0 additions & 1 deletion src/cp_control_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -264,7 +264,6 @@ MODULE cp_control_types
! Gaussian-type functions (primitive basis functions).
! **************************************************************************************************
TYPE qs_control_type
CHARACTER(LEN=10) :: method
INTEGER :: method_id
REAL(KIND=dp) :: eps_core_charge, &
eps_kg_orb, &
Expand Down
48 changes: 24 additions & 24 deletions src/cp_control_utils.F
Original file line number Diff line number Diff line change
Expand Up @@ -41,8 +41,7 @@ MODULE cp_control_utils
sic_list_all, sic_list_unpaired, sic_mauri_spz, sic_mauri_us, sic_none, slater, &
tddfpt_excitations, use_mom_ref_user, xas_dip_len
USE input_cp2k_check, ONLY: xc_functionals_expand
USE input_cp2k_dft, ONLY: create_dft_section,&
create_qs_section
USE input_cp2k_dft, ONLY: create_dft_section
USE input_enumeration_types, ONLY: enum_i2c,&
enumeration_type
USE input_keyword_types, ONLY: keyword_get,&
Expand Down Expand Up @@ -602,9 +601,6 @@ SUBROUTINE read_qs_section(qs_control, qs_section)
LOGICAL :: explicit, was_present
REAL(dp) :: tmp, tmpsqrt, value
REAL(dp), POINTER :: scal(:)
TYPE(enumeration_type), POINTER :: enum
TYPE(keyword_type), POINTER :: keyword
TYPE(section_type), POINTER :: section
TYPE(section_vals_type), POINTER :: cdft_control_section, ddapc_restraint_section, &
dftb_parameter, dftb_section, lri_optbas_section, mull_section, s2_restraint_section, &
se_section, xtb_parameter, xtb_section
Expand Down Expand Up @@ -754,12 +750,6 @@ SUBROUTINE read_qs_section(qs_control, qs_section)
!Method
CALL section_vals_val_get(qs_section, "METHOD", i_val=qs_control%method_id)
NULLIFY (section, keyword, enum)
CALL create_qs_section(section)
keyword => section_get_keyword(section, "METHOD")
CALL keyword_get(keyword, enum=enum)
qs_control%method = enum_i2c(enum, qs_control%method_id)
CALL section_release(section)
qs_control%gapw = .FALSE.
qs_control%gapw_xc = .FALSE.
qs_control%gpw = .FALSE.
Expand Down Expand Up @@ -1588,31 +1578,42 @@ SUBROUTINE write_qs_control(qs_control, dft_section)
CHARACTER(len=*), PARAMETER :: routineN = 'write_qs_control', &
routineP = moduleN//':'//routineN
CHARACTER(len=20) :: method, quadrature
INTEGER :: handle, i, igrid_level, ngrid_level, &
output_unit
TYPE(cp_logger_type), POINTER :: logger
TYPE(ddapc_restraint_type), POINTER :: ddapc_restraint_control
TYPE(enumeration_type), POINTER :: enum
TYPE(keyword_type), POINTER :: keyword
TYPE(section_type), POINTER :: section
TYPE(section_type), POINTER :: qs_section
TYPE(section_vals_type), POINTER :: print_section_vals, qs_section_vals
IF (qs_control%semi_empirical) RETURN
IF (qs_control%dftb) RETURN
IF (qs_control%xtb) RETURN
CALL timeset(routineN, handle)
NULLIFY (logger, enum, keyword, section)
NULLIFY (logger, print_section_vals, qs_section, qs_section_vals)
logger => cp_get_default_logger()
print_section_vals => section_vals_get_subs_vals(dft_section, "PRINT")
qs_section_vals => section_vals_get_subs_vals(dft_section, "QS")
CALL section_vals_get(qs_section_vals, section=qs_section)
CALL create_qs_section(section)
keyword => section_get_keyword(section, "QUADRATURE")
NULLIFY (enum, keyword)
keyword => section_get_keyword(qs_section, "METHOD")
CALL keyword_get(keyword, enum=enum)
method = enum_i2c(enum, qs_control%method_id)
output_unit = cp_print_key_unit_nr(logger, dft_section, &
"PRINT%DFT_CONTROL_PARAMETERS", extension=".Log")
NULLIFY (enum, keyword)
keyword => section_get_keyword(qs_section, "QUADRATURE")
CALL keyword_get(keyword, enum=enum)
quadrature = enum_i2c(enum, qs_control%gapw_control%quadrature)
output_unit = cp_print_key_unit_nr(logger, print_section_vals, &
"DFT_CONTROL_PARAMETERS", extension=".Log")
IF (output_unit > 0) THEN
ngrid_level = SIZE(qs_control%e_cutoff)
WRITE (UNIT=output_unit, FMT="(/,T2,A,T71,A)") &
"QS| Method:", ADJUSTR(qs_control%method)
WRITE (UNIT=output_unit, FMT="(/,T2,A,T61,A20)") &
"QS| Method:", ADJUSTR(method)
IF (qs_control%pw_grid_opt%spherical) THEN
WRITE (UNIT=output_unit, FMT="(T2,A,T61,A)") &
"QS| Density plane wave grid type", " SPHERICAL HALFSPACE"
Expand Down Expand Up @@ -1678,9 +1679,9 @@ SUBROUTINE write_qs_control(qs_control, dft_section)
qs_control%gapw_control%eps_svd, &
"QS| GAPW| eps_cpc:", &
qs_control%gapw_control%eps_cpc
WRITE (UNIT=output_unit, FMT="(T2,A,T55,A30)") &
WRITE (UNIT=output_unit, FMT="(T2,A,T61,A20)") &
"QS| GAPW| atom-r-grid: quadrature:", &
enum_i2c(enum, qs_control%gapw_control%quadrature)
ADJUSTR(quadrature)
WRITE (UNIT=output_unit, FMT="(T2,A,T71,I10)") &
"QS| GAPW| atom-s-grid: max l :", &
qs_control%gapw_control%lmax_sphere, &
Expand Down Expand Up @@ -1764,9 +1765,8 @@ SUBROUTINE write_qs_control(qs_control, dft_section)
END SELECT
END IF
END IF
CALL cp_print_key_finished_output(output_unit, logger, dft_section, &
"PRINT%DFT_CONTROL_PARAMETERS")
CALL section_release(section)
CALL cp_print_key_finished_output(output_unit, logger, print_section_vals, &
"DFT_CONTROL_PARAMETERS")
CALL timestop(handle)
Expand Down
18 changes: 9 additions & 9 deletions src/qs_environment.F
Original file line number Diff line number Diff line change
Expand Up @@ -729,11 +729,11 @@ SUBROUTINE qs_init_subsys(qs_env, para_env, subsys, cell, cell_ref, use_ref_cell

! *** Check that no all-electron potential is present if GPW or GAPW_XC
CALL get_qs_kind_set(qs_kind_set, all_potential_present=all_potential_present)
IF ((dft_control%qs_control%method == "GPW") .OR. &
(dft_control%qs_control%method == "GAPW_XC") .OR. &
(dft_control%qs_control%method == "OFGPW")) THEN
IF ((dft_control%qs_control%method_id == do_method_gpw) .OR. &
(dft_control%qs_control%method_id == do_method_gapw_xc) .OR. &
(dft_control%qs_control%method_id == do_method_ofgpw)) THEN
IF (all_potential_present) THEN
CPABORT("All-el calculations with GPW, GAPW_XC, and OFGPW are not implemented ")
CPABORT("All-electron calculations with GPW, GAPW_XC, and OFGPW are not implemented")
END IF
END IF

Expand Down Expand Up @@ -831,11 +831,11 @@ SUBROUTINE qs_init_subsys(qs_env, para_env, subsys, cell, cell_ref, use_ref_cell
lmax_sphere = 2*maxlgto
dft_control%qs_control%gapw_control%lmax_sphere = lmax_sphere
END IF
IF (dft_control%qs_control%method == "LRIGPW" .OR. dft_control%qs_control%lri_optbas) THEN
IF (dft_control%qs_control%method_id == do_method_lrigpw .OR. dft_control%qs_control%lri_optbas) THEN
CALL get_qs_kind_set(qs_kind_set, maxlgto=maxlgto_lri, basis_type="LRI_AUX")
!take maxlgto from lri basis if larger (usually)
maxlgto = MAX(maxlgto, maxlgto_lri)
ELSE IF (dft_control%qs_control%method == "RIGPW") THEN
ELSE IF (dft_control%qs_control%method_id == do_method_rigpw) THEN
CALL get_qs_kind_set(qs_kind_set, maxlgto=maxlgto_lri, basis_type="RI_HXC")
maxlgto = MAX(maxlgto, maxlgto_lri)
END IF
Expand All @@ -854,8 +854,8 @@ SUBROUTINE qs_init_subsys(qs_env, para_env, subsys, cell, cell_ref, use_ref_cell
CALL init_qs_kind_set(qs_kind_set)

! *** Initialise GAPW soft basis and projectors
IF (dft_control%qs_control%method == "GAPW" .OR. &
dft_control%qs_control%method == "GAPW_XC") THEN
IF (dft_control%qs_control%method_id == do_method_gapw .OR. &
dft_control%qs_control%method_id == do_method_gapw_xc) THEN
qs_control => dft_control%qs_control
CALL init_gapw_basis_set(qs_kind_set, qs_control, qs_env%input)
ENDIF
Expand Down Expand Up @@ -1492,7 +1492,7 @@ SUBROUTINE qs_init_subsys(qs_env, para_env, subsys, cell, cell_ref, use_ref_cell
CALL qs_env_setup(qs_env)
! Allocate and Initialie rho0 soft on the global grid
IF (dft_control%qs_control%method == "GAPW") THEN
IF (dft_control%qs_control%method_id == do_method_gapw) THEN
CALL get_qs_env(qs_env=qs_env, rho0_mpole=rho0_mpole)
CALL rho0_s_grid_create(qs_env, rho0_mpole)
END IF
Expand Down

0 comments on commit 89607a6

Please sign in to comment.