Skip to content

Commit

Permalink
Refactoring mixing methods
Browse files Browse the repository at this point in the history
  • Loading branch information
juerghutter committed Mar 19, 2019
1 parent 83d6fe5 commit 6e8ba42
Show file tree
Hide file tree
Showing 8 changed files with 377 additions and 253 deletions.
11 changes: 8 additions & 3 deletions src/dm_ls_scf_qs.F
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,8 @@ MODULE dm_ls_scf_qs
USE qs_ks_types, ONLY: qs_ks_did_change,&
qs_ks_env_type,&
set_ks_env
USE qs_mixing_utils, ONLY: mixing_allocate,&
USE qs_mixing_utils, ONLY: charge_mixing_init,&
mixing_allocate,&
mixing_init
USE qs_neighbor_list_types, ONLY: neighbor_list_set_p_type
USE qs_rho_atom_types, ONLY: rho_atom_type
Expand Down Expand Up @@ -761,8 +762,7 @@ SUBROUTINE rho_mixing_ls_init(qs_env, ls_scf_env)

CALL timeset(routineN, handle)

CALL get_qs_env(qs_env, dft_control=dft_control, &
rho=rho)
CALL get_qs_env(qs_env, dft_control=dft_control, rho=rho)

CALL mixing_allocate(qs_env, ls_scf_env%density_mixing_method, nspins=ls_scf_env%nspins, &
mixing_store=ls_scf_env%mixing_store)
Expand All @@ -771,6 +771,11 @@ SUBROUTINE rho_mixing_ls_init(qs_env, ls_scf_env)
CALL get_qs_env(qs_env, rho_atom_set=rho_atom)
CALL mixing_init(ls_scf_env%density_mixing_method, rho, ls_scf_env%mixing_store, &
ls_scf_env%para_env, rho_atom=rho_atom)
ELSEIF (dft_control%qs_control%dftb .OR. dft_control%qs_control%xtb) THEN
CALL charge_mixing_init(ls_scf_env%density_mixing_method, ls_scf_env%mixing_store, &
ls_scf_env%para_env)
ELSEIF (dft_control%qs_control%semi_empirical) THEN
CPABORT('SE Code not possible')
ELSE
CALL mixing_init(ls_scf_env%density_mixing_method, rho, ls_scf_env%mixing_store, &
ls_scf_env%para_env)
Expand Down
8 changes: 7 additions & 1 deletion src/negf_methods.F
Original file line number Diff line number Diff line change
Expand Up @@ -1010,7 +1010,13 @@ SUBROUTINE converge_density(negf_env, negf_control, sub_env, qs_env, v_shift, ba
! mixing storage allocation
IF (negf_env%mixing_method >= gspace_mixing_nr) THEN
CALL mixing_allocate(qs_env, negf_env%mixing_method, nspins=nspins, mixing_store=negf_env%mixing_storage)
CALL mixing_init(negf_env%mixing_method, rho_struct, negf_env%mixing_storage, para_env)
IF (dft_control%qs_control%dftb .OR. dft_control%qs_control%xtb) THEN
CPABORT('TB Code not available')
ELSE IF (dft_control%qs_control%semi_empirical) THEN
CPABORT('SE Code not possible')
ELSE
CALL mixing_init(negf_env%mixing_method, rho_struct, negf_env%mixing_storage, para_env)
END IF
END IF

IF (log_unit > 0) THEN
Expand Down
67 changes: 43 additions & 24 deletions src/qs_density_mixing_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -57,30 +57,39 @@ MODULE qs_density_mixing_types
END TYPE cp_1d_z_p_type

TYPE mixing_storage_type
INTEGER :: ref_count, ig_max, ncall, nbuffer, n_simple_mix, nskip_mixing, p_metric_method
INTEGER, POINTER, DIMENSION(:) :: ig_global_index
LOGICAL :: gmix_p
LOGICAL, POINTER, DIMENSION(:) :: paw
CHARACTER(len=15) :: iter_method
REAL(dp) :: alpha, bconst, beta, broy_w0, max_g2, max_gvec_exp, pulay_alpha, pulay_beta, r_step, &
reg_par, sigma_max, wc, wmax
REAL(dp), DIMENSION(:), POINTER :: p_metric
REAL(KIND=dp), DIMENSION(:), POINTER :: kerker_factor
REAL(KIND=dp), DIMENSION(:), POINTER :: special_metric
REAL(dp), DIMENSION(:, :), POINTER :: weight
REAL(KIND=dp), DIMENSION(:, :), POINTER :: norm_res_buffer, pulay_matrix
REAL(dp), DIMENSION(:, :, :), POINTER :: fmat, gmat, smat
TYPE(cp_1d_z_p_type), DIMENSION(:), POINTER :: last_res, rhoin, rhoin_old
TYPE(cp_1d_z_p_type), DIMENSION(:, :), POINTER :: delta_res, u_vec, z_vec
TYPE(cp_1d_z_p_type), DIMENSION(:, :), POINTER ::drho_buffer, rhoin_buffer, &
res_buffer
TYPE(dbcsr_p_type), DIMENSION(:, :), POINTER :: rho_ao_in, rho_ao_in_old, rho_ao_lastres
TYPE(dbcsr_p_type), DIMENSION(:, :, :), POINTER :: rho_ao_in_buffer
TYPE(dbcsr_p_type), DIMENSION(:, :, :), POINTER :: rho_ao_res_buffer
TYPE(dbcsr_type), POINTER :: rho_ao_mix, rho_ao_res
TYPE(rho_atom_coeff), DIMENSION(:, :), POINTER :: cpc_h_lastres, cpc_s_lastres
TYPE(rho_atom_coeff), DIMENSION(:, :), POINTER :: cpc_h_in, cpc_s_in
TYPE(rho_atom_coeff), DIMENSION(:, :), POINTER :: cpc_h_old, cpc_s_old
INTEGER :: ref_count
INTEGER :: ig_max, ncall, nbuffer, n_simple_mix, &
nskip_mixing, p_metric_method
INTEGER, POINTER, DIMENSION(:) :: ig_global_index
LOGICAL :: gmix_p
LOGICAL, POINTER, DIMENSION(:) :: paw
CHARACTER(len=15) :: iter_method
REAL(KIND=dp) :: alpha, bconst, beta, broy_w0, &
max_g2, max_gvec_exp, pulay_alpha, &
pulay_beta, r_step, reg_par, &
sigma_max, wc, wmax
REAL(KIND=dp), DIMENSION(:), POINTER :: p_metric
REAL(KIND=dp), DIMENSION(:), POINTER :: kerker_factor
REAL(KIND=dp), DIMENSION(:), POINTER :: special_metric
REAL(KIND=dp), DIMENSION(:, :), POINTER :: weight
REAL(KIND=dp), DIMENSION(:, :), POINTER :: norm_res_buffer, pulay_matrix
REAL(KIND=dp), DIMENSION(:, :, :), POINTER :: fmat, gmat, smat
!
REAL(KIND=dp) :: nat_local, max_shell
REAL(KIND=dp), DIMENSION(:, :, :, :), POINTER :: acharge
REAL(KIND=dp), DIMENSION(:), POINTER :: atlist
!
TYPE(cp_1d_z_p_type), DIMENSION(:), POINTER :: last_res, rhoin, rhoin_old
TYPE(cp_1d_z_p_type), DIMENSION(:, :), POINTER :: delta_res, u_vec, z_vec
TYPE(cp_1d_z_p_type), DIMENSION(:, :), POINTER :: drho_buffer, rhoin_buffer, res_buffer
TYPE(dbcsr_p_type), DIMENSION(:, :), POINTER :: rho_ao_in, rho_ao_in_old, rho_ao_lastres
TYPE(dbcsr_p_type), DIMENSION(:, :, :), POINTER :: rho_ao_in_buffer
TYPE(dbcsr_p_type), DIMENSION(:, :, :), POINTER :: rho_ao_res_buffer
TYPE(dbcsr_type), POINTER :: rho_ao_mix, rho_ao_res
!
TYPE(rho_atom_coeff), DIMENSION(:, :), POINTER :: cpc_h_lastres, cpc_s_lastres
TYPE(rho_atom_coeff), DIMENSION(:, :), POINTER :: cpc_h_in, cpc_s_in
TYPE(rho_atom_coeff), DIMENSION(:, :), POINTER :: cpc_h_old, cpc_s_old
TYPE(rho_atom_coeff), DIMENSION(:, :, :), POINTER :: cpc_h_in_buffer, cpc_s_in_buffer
TYPE(rho_atom_coeff), DIMENSION(:, :, :), POINTER :: cpc_h_res_buffer, cpc_s_res_buffer
TYPE(rho_atom_coeff), DIMENSION(:, :, :), POINTER :: dcpc_h_in, dcpc_s_in
Expand Down Expand Up @@ -131,6 +140,8 @@ SUBROUTINE mixing_storage_create(mixing_store, mixing_section, mixing_method, ec
NULLIFY (mixing_store%fmat)
NULLIFY (mixing_store%gmat)
NULLIFY (mixing_store%smat)
NULLIFY (mixing_store%acharge)
NULLIFY (mixing_store%atlist)
NULLIFY (mixing_store%last_res)
NULLIFY (mixing_store%rhoin)
NULLIFY (mixing_store%rhoin_old)
Expand Down Expand Up @@ -383,6 +394,13 @@ SUBROUTINE mixing_storage_release(mixing_store)
DEALLOCATE (mixing_store%fmat)
END IF

IF (ASSOCIATED(mixing_store%acharge)) THEN
DEALLOCATE (mixing_store%acharge)
END IF
IF (ASSOCIATED(mixing_store%atlist)) THEN
DEALLOCATE (mixing_store%atlist)
END IF

IF (ASSOCIATED(mixing_store%delta_res)) THEN
DO i = 1, SIZE(mixing_store%delta_res, 2)
DO j = 1, SIZE(mixing_store%delta_res, 1)
Expand Down Expand Up @@ -706,4 +724,5 @@ SUBROUTINE create_mixing_section(section, ls_scf)
CALL keyword_release(keyword)

END SUBROUTINE create_mixing_section

END MODULE qs_density_mixing_types

0 comments on commit 6e8ba42

Please sign in to comment.