Skip to content

Commit

Permalink
Add default initializers to qs_linres_types.F
Browse files Browse the repository at this point in the history
  • Loading branch information
oschuett committed Feb 12, 2023
1 parent 685d0db commit e9823b4
Show file tree
Hide file tree
Showing 11 changed files with 218 additions and 408 deletions.
4 changes: 1 addition & 3 deletions src/mp2_cphf.F
Original file line number Diff line number Diff line change
Expand Up @@ -111,8 +111,7 @@ MODULE mp2_cphf
USE qs_ks_reference, ONLY: ks_ref_potential
USE qs_ks_types, ONLY: qs_ks_env_type,&
set_ks_env
USE qs_linres_types, ONLY: linres_control_create,&
linres_control_type
USE qs_linres_types, ONLY: linres_control_type
USE qs_mo_types, ONLY: mo_set_type
USE qs_neighbor_list_types, ONLY: neighbor_list_set_p_type
USE qs_overlap, ONLY: build_overlap_matrix
Expand Down Expand Up @@ -349,7 +348,6 @@ SUBROUTINE solve_z_vector_eq(qs_env, mp2_env, para_env, dft_control, &
! Prepare arrays for linres code
NULLIFY (linres_control)
ALLOCATE (linres_control)
CALL linres_control_create(linres_control)
linres_control%do_kernel = .TRUE.
linres_control%lr_triplet = .FALSE.
linres_control%linres_restart = .FALSE.
Expand Down
8 changes: 2 additions & 6 deletions src/qs_linres_current_utils.F
Original file line number Diff line number Diff line change
Expand Up @@ -89,8 +89,7 @@ MODULE qs_linres_current_utils
linres_solver,&
linres_write_restart
USE qs_linres_op, ONLY: set_vecp
USE qs_linres_types, ONLY: current_env_create,&
current_env_type,&
USE qs_linres_types, ONLY: current_env_type,&
deallocate_jrho_atom_set,&
get_current_env,&
init_jrho_atom_set,&
Expand Down Expand Up @@ -680,10 +679,7 @@ SUBROUTINE current_env_init(current_env, qs_env)
END IF

CALL current_env_cleanup(current_env)

CALL current_env_create(current_env)
!
!
current_env%gauge_init = .FALSE.
current_env%chi_tensor(:, :, :) = 0.0_dp
current_env%chi_tensor_loc(:, :, :) = 0.0_dp
current_env%nao = nao
Expand Down
3 changes: 0 additions & 3 deletions src/qs_linres_epr_utils.F
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,6 @@ MODULE qs_linres_epr_utils
qs_environment_type
USE qs_kind_types, ONLY: qs_kind_type
USE qs_linres_types, ONLY: deallocate_nablavks_atom_set,&
epr_env_create,&
epr_env_type,&
init_nablavks_atom_set,&
linres_control_type,&
Expand Down Expand Up @@ -132,8 +131,6 @@ SUBROUTINE epr_env_init(epr_env, qs_env)
WRITE (output_unit, "(T10,A,/)") "Initialization of the EPR environment"
END IF

CALL epr_env_create(epr_env)

CALL get_qs_env(qs_env=qs_env, &
atomic_kind_set=atomic_kind_set, &
qs_kind_set=qs_kind_set, &
Expand Down
3 changes: 0 additions & 3 deletions src/qs_linres_issc_utils.F
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,6 @@ MODULE qs_linres_issc_utils
USE qs_kind_types, ONLY: qs_kind_type
USE qs_linres_methods, ONLY: linres_solver
USE qs_linres_types, ONLY: get_issc_env,&
issc_env_create,&
issc_env_type,&
linres_control_type
USE qs_matrix_pools, ONLY: qs_matrix_pools_type
Expand Down Expand Up @@ -824,8 +823,6 @@ SUBROUTINE issc_env_init(issc_env, qs_env)
WRITE (output_unit, "(T10,A,/)") "Inizialization of the ISSC environment"
END IF

CALL issc_env_create(issc_env)
!
issc_section => section_vals_get_subs_vals(qs_env%input, &
& "PROPERTIES%LINRES%SPINSPIN")
!CALL section_vals_val_get(nmr_section,"INTERPOLATE_SHIFT",l_val=nmr_env%interpolate_shift)
Expand Down
6 changes: 1 addition & 5 deletions src/qs_linres_module.F
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,6 @@ MODULE qs_linres_module
dcdr_env_type,&
epr_env_type,&
issc_env_type,&
linres_control_create,&
linres_control_type,&
nmr_env_type,&
vcd_env_type
Expand Down Expand Up @@ -122,8 +121,6 @@ MODULE qs_linres_module

CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_linres_module'

! **************************************************************************************************

CONTAINS

! *****************************************************************************
Expand Down Expand Up @@ -218,7 +215,7 @@ SUBROUTINE vcd_linres(qs_env, p_env)

END SUBROUTINE vcd_linres

! *****************************************************************************
! **************************************************************************************************
!> \brief Calculates the derivatives of the MO coefficients dC/dR^lambda_beta
!> wrt to nuclear coordinates. The derivative is index by `beta`, the
!> electric dipole operator by `alpha`.
Expand Down Expand Up @@ -451,7 +448,6 @@ SUBROUTINE linres_init(lr_section, p_env, qs_env)
NULLIFY (dft_control, linres_control, loc_section, rho, mos, matrix_ks, rho_ao)

ALLOCATE (linres_control)
CALL linres_control_create(linres_control)
CALL set_qs_env(qs_env=qs_env, linres_control=linres_control)
CALL get_qs_env(qs_env=qs_env, &
dft_control=dft_control, matrix_ks=matrix_ks, mos=mos, rho=rho)
Expand Down
3 changes: 0 additions & 3 deletions src/qs_linres_nmr_utils.F
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,6 @@ MODULE qs_linres_nmr_utils
USE qs_environment_types, ONLY: get_qs_env,&
qs_environment_type
USE qs_linres_types, ONLY: linres_control_type,&
nmr_env_create,&
nmr_env_type
USE qs_matrix_pools, ONLY: qs_matrix_pools_type
USE scf_control_types, ONLY: scf_control_type
Expand Down Expand Up @@ -120,8 +119,6 @@ SUBROUTINE nmr_env_init(nmr_env, qs_env)
WRITE (output_unit, "(T10,A,/)") "Inizialization of the NMR environment"
END IF

CALL nmr_env_create(nmr_env)
!
! If current_density or full_nmr different allocations are required
nmr_section => section_vals_get_subs_vals(qs_env%input, &
& "PROPERTIES%LINRES%NMR")
Expand Down
3 changes: 1 addition & 2 deletions src/qs_linres_polar_utils.F
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,6 @@ MODULE qs_linres_polar_utils
linres_write_restart
USE qs_linres_types, ONLY: get_polar_env,&
linres_control_type,&
polar_env_create,&
polar_env_type,&
set_polar_env
USE qs_matrix_pools, ONLY: qs_matrix_pools_type
Expand Down Expand Up @@ -135,7 +134,7 @@ SUBROUTINE polar_env_init(qs_env)

! Create polar environment if needed
IF (.NOT. ASSOCIATED(polar_env)) THEN
CALL polar_env_create(polar_env)
ALLOCATE (polar_env)
CALL set_qs_env(qs_env=qs_env, polar_env=polar_env)
END IF

Expand Down

0 comments on commit e9823b4

Please sign in to comment.