38 use,
intrinsic :: iso_fortran_env
103 logical :: calculating
104 logical :: time_present
106 real(real64),
allocatable :: density(:, :)
107 logical :: total_density_alloc
108 real(real64),
pointer,
contiguous :: total_density(:)
109 type(energy_t),
allocatable :: energy
111 type(states_elec_t),
pointer :: hf_st
116 real(real64),
allocatable :: vxc(:, :)
117 real(real64),
allocatable :: vtau(:, :)
118 real(real64),
allocatable :: axc(:, :, :)
119 real(real64),
allocatable :: a_ind(:, :)
120 real(real64),
allocatable :: b_ind(:, :)
121 logical :: calc_energy
126 integer,
public :: theory_level = -1
128 logical,
public :: frozen_hxc = .false.
130 integer,
public :: xc_family = 0
131 integer,
public :: xc_flags = 0
132 integer,
public :: xc_photon = 0
133 type(xc_t),
public :: xc
134 type(xc_photons_t),
public :: xc_photons
135 type(xc_oep_t),
public :: oep
136 type(xc_oep_photon_t),
public :: oep_photon
137 type(xc_ks_inversion_t),
public :: ks_inversion
138 type(xc_sic_t),
public :: sic
139 type(xc_vdw_t),
public :: vdw
140 type(grid_t),
pointer,
public :: gr
141 type(v_ks_calc_t) :: calc
142 logical :: calculate_current = .false.
143 type(current_t) :: current_calculator
144 logical :: include_td_field = .false.
145 logical,
public :: has_photons = .false.
146 logical :: xc_photon_include_hartree = .
true.
148 real(real64),
public :: stress_xc_gga(3, 3)
149 type(photon_mode_t),
pointer,
public :: pt => null()
150 type(mf_t),
public :: pt_mx
156 subroutine v_ks_init(ks, namespace, gr, st, ions, mc, space, kpoints)
157 type(v_ks_t),
intent(inout) :: ks
158 type(namespace_t),
intent(in) :: namespace
159 type(grid_t),
target,
intent(inout) :: gr
160 type(states_elec_t),
intent(in) :: st
161 type(ions_t),
intent(inout) :: ions
162 type(multicomm_t),
intent(in) :: mc
163 class(space_t),
intent(in) :: space
164 type(kpoints_t),
intent(in) :: kpoints
166 integer :: x_id, c_id, xk_id, ck_id, default, val
167 logical :: parsed_theory_level, using_hartree_fock
168 integer :: pseudo_x_functional, pseudo_c_functional
211 ks%xc_family = xc_family_none
217 parsed_theory_level = .false.
238 call messages_write(
'Info: the XCFunctional has been selected to match the pseudopotentials', new_line = .
true.)
253 call messages_write(
'The XCFunctional that you selected does not match the one used', new_line = .
true.)
302 call parse_variable(namespace,
'XCPhotonFunctional', option__xcphotonfunctional__none, ks%xc_photon)
312 call parse_variable(namespace,
'XCPhotonIncludeHartree', .
true., ks%xc_photon_include_hartree)
314 if (.not. ks%xc_photon_include_hartree)
then
325 using_hartree_fock = (ks%theory_level ==
hartree_fock) &
327 call xc_init(ks%xc, namespace, space%dim, space%periodic_dim, st%qtot, &
328 x_id, c_id, xk_id, ck_id,
hartree_fock = using_hartree_fock, ispin=st%d%ispin)
330 ks%xc_family = ks%xc%family
331 ks%xc_flags = ks%xc%flags
333 if (.not. parsed_theory_level)
then
342 call parse_variable(namespace,
'TheoryLevel', default, ks%theory_level)
354 ks%xc_family = ior(ks%xc_family, xc_family_oep)
364 ks%sic%amaldi_factor =
m_one
366 select case (ks%theory_level)
371 if (space%periodic_dim == space%dim)
then
374 if (kpoints%full%npoints > 1)
then
379 if (kpoints%full%npoints > 1)
then
394 if (
bitand(ks%xc_family, xc_family_lda + xc_family_gga) /= 0)
then
395 call xc_sic_init(ks%sic, namespace, gr, st, mc, space)
398 if (
bitand(ks%xc_family, xc_family_oep) /= 0)
then
399 select case (ks%xc%functional(
func_x,1)%id)
401 if (kpoints%reduced%npoints > 1)
then
406 if (kpoints%reduced%npoints > 1)
then
411 if((.not. ks%has_photons) .or. (ks%xc_photon /= 0))
then
412 if(oep_type == -1)
then
415 call xc_oep_init(ks%oep, namespace, gr, st, mc, space, oep_type)
429 message(1) =
"SICCorrection can only be used with Kohn-Sham DFT"
433 if (st%d%ispin ==
spinors)
then
434 if (
bitand(ks%xc_family, xc_family_mgga + xc_family_hyb_mgga) /= 0)
then
439 ks%frozen_hxc = .false.
444 ks%calc%calculating = .false.
449 call ks%vdw%init(namespace, space, gr, ks%xc, ions, x_id, c_id)
450 if (ks%vdw%vdw_correction /= option__vdwcorrection__none .and. ks%theory_level ==
rdmft)
then
451 message(1) =
"VDWCorrection and RDMFT are not compatible"
454 if (ks%vdw%vdw_correction /= option__vdwcorrection__none .and. ks%theory_level ==
independent_particles)
then
455 message(1) =
"VDWCorrection and independent particles are not compatible"
459 if (ks%xc_photon /= 0)
then
461 call ks%xc_photons%init(namespace, ks%xc_photon , space, gr, st)
473 integer,
intent(out) :: x_functional
474 integer,
intent(out) :: c_functional
476 integer :: xf, cf, ispecies
477 logical :: warned_inconsistent
482 warned_inconsistent = .false.
483 do ispecies = 1, ions%nspecies
484 select type(spec=>ions%species(ispecies)%s)
486 xf = spec%x_functional()
487 cf = spec%c_functional()
490 call messages_write(
"Unknown XC functional for species '"//trim(ions%species(ispecies)%s%get_label())//
"'")
498 if (xf /= x_functional .and. .not. warned_inconsistent)
then
499 call messages_write(
'Inconsistent XC functional detected between species')
501 warned_inconsistent = .
true.
508 if (cf /= c_functional .and. .not. warned_inconsistent)
then
509 call messages_write(
'Inconsistent XC functional detected between species')
511 warned_inconsistent = .
true.
531 type(
v_ks_t),
intent(inout) :: ks
537 select case (ks%theory_level)
542 if (
bitand(ks%xc_family, xc_family_oep) /= 0)
then
552 if (ks%xc_photon /= 0)
then
553 call ks%xc_photons%end()
563 type(
v_ks_t),
intent(in) :: ks
564 integer,
optional,
intent(in) :: iunit
572 select case (ks%theory_level)
597 subroutine v_ks_h_setup(namespace, space, gr, ions, ext_partners, st, ks, hm, calc_eigenval, calc_current)
600 type(
grid_t),
intent(in) :: gr
601 type(
ions_t),
intent(in) :: ions
604 type(
v_ks_t),
intent(inout) :: ks
606 logical,
optional,
intent(in) :: calc_eigenval
607 logical,
optional,
intent(in) :: calc_current
609 integer,
allocatable :: ind(:)
611 real(real64),
allocatable :: copy_occ(:)
612 logical :: calc_eigenval_
613 logical :: calc_current_
621 call v_ks_calc(ks, namespace, space, hm, st, ions, ext_partners, calc_eigenval = calc_eigenval_, calc_current = calc_current_)
623 if (st%restart_reorder_occs .and. .not. st%fromScratch)
then
624 message(1) =
"Reordering occupations for restart."
627 safe_allocate(ind(1:st%nst))
628 safe_allocate(copy_occ(1:st%nst))
631 call sort(st%eigenval(:, ik), ind)
632 copy_occ(1:st%nst) = st%occ(1:st%nst, ik)
634 st%occ(ist, ik) = copy_occ(ind(ist))
638 safe_deallocate_a(ind)
639 safe_deallocate_a(copy_occ)
649 subroutine v_ks_calc(ks, namespace, space, hm, st, ions, ext_partners, &
650 calc_eigenval, time, calc_energy, calc_current, force_semilocal)
651 type(
v_ks_t),
intent(inout) :: ks
656 type(
ions_t),
intent(in) :: ions
658 logical,
optional,
intent(in) :: calc_eigenval
659 real(real64),
optional,
intent(in) :: time
660 logical,
optional,
intent(in) :: calc_energy
661 logical,
optional,
intent(in) :: calc_current
662 logical,
optional,
intent(in) :: force_semilocal
664 logical :: calc_current_
669 .and. ks%calculate_current &
673 if (calc_current_)
then
678 call v_ks_calc_start(ks, namespace, space, hm, st, ions, hm%kpoints%latt, ext_partners, time, &
679 calc_energy, force_semilocal=force_semilocal)
681 ext_partners, force_semilocal=force_semilocal)
692 call lalg_axpy(ks%gr%np, st%d%nspin,
m_one, hm%magnetic_constrain%pot, hm%ks_pot%vhxc)
704 subroutine v_ks_calc_start(ks, namespace, space, hm, st, ions, latt, ext_partners, time, &
705 calc_energy, force_semilocal)
706 type(
v_ks_t),
target,
intent(inout) :: ks
708 class(
space_t),
intent(in) :: space
711 type(
ions_t),
intent(in) :: ions
714 real(real64),
optional,
intent(in) :: time
715 logical,
optional,
intent(in) :: calc_energy
716 logical,
optional,
intent(in) :: force_semilocal
722 assert(.not. ks%calc%calculating)
723 ks%calc%calculating = .
true.
725 write(
message(1),
'(a)')
'Debug: Calculating Kohn-Sham potential.'
728 ks%calc%time_present =
present(time)
734 if (ks%frozen_hxc)
then
740 allocate(ks%calc%energy)
744 ks%calc%energy%intnvxc =
m_zero
746 nullify(ks%calc%total_density)
756 if (ks%theory_level /=
hartree .and. ks%theory_level /=
rdmft)
call v_a_xc(hm, force_semilocal)
758 ks%calc%total_density_alloc = .false.
765 nullify(ks%calc%hf_st)
770 if (st%parallel_in_states)
then
772 call messages_write(
'State parallelization of Hartree-Fock exchange is not supported')
774 call messages_write(
'when running with OpenCL/CUDA. Please use domain parallelization')
776 call messages_write(
"or disable acceleration using 'DisableAccel = yes'.")
781 if (hm%exxop%useACE)
then
784 safe_allocate(ks%calc%hf_st)
794 if (hm%self_induced_magnetic)
then
795 safe_allocate(ks%calc%a_ind(1:ks%gr%np_part, 1:space%dim))
796 safe_allocate(ks%calc%b_ind(1:ks%gr%np_part, 1:space%dim))
797 call magnetic_induced(namespace, ks%gr, st, hm%psolver, hm%kpoints, ks%calc%a_ind, ks%calc%b_ind)
800 if ((ks%has_photons) .and. (ks%calc%time_present) .and. (ks%xc_photon == 0) )
then
801 call mf_calc(ks%pt_mx, ks%gr, st, ions, ks%pt, time)
819 safe_allocate(ks%calc%density(1:ks%gr%np, 1:st%d%nspin))
824 call lalg_scal(ks%gr%np, st%d%nspin, ks%sic%amaldi_factor, ks%calc%density)
827 nullify(ks%calc%total_density)
828 if (
allocated(st%rho_core) .or. hm%d%spin_channels > 1)
then
829 ks%calc%total_density_alloc = .
true.
831 safe_allocate(ks%calc%total_density(1:ks%gr%np))
834 ks%calc%total_density(ip) = sum(ks%calc%density(ip, 1:hm%d%spin_channels))
838 if (
allocated(st%rho_core))
then
839 call lalg_axpy(ks%gr%np, -ks%sic%amaldi_factor, st%rho_core, ks%calc%total_density)
842 ks%calc%total_density_alloc = .false.
843 ks%calc%total_density => ks%calc%density(:, 1)
850 subroutine v_a_xc(hm, force_semilocal)
852 logical,
optional,
intent(in) :: force_semilocal
859 ks%calc%energy%exchange =
m_zero
860 ks%calc%energy%correlation =
m_zero
861 ks%calc%energy%xc_j =
m_zero
862 ks%calc%energy%vdw =
m_zero
864 allocate(ks%calc%vxc(1:ks%gr%np, 1:st%d%nspin))
868 safe_allocate(ks%calc%vtau(1:ks%gr%np, 1:st%d%nspin))
873 if (ks%calc%calc_energy)
then
875 call xc_get_vxc(ks%gr, ks%xc, st, hm%kpoints, hm%psolver, namespace, space, ks%calc%density, st%d%ispin, &
876 latt%rcell_volume, ks%calc%vxc, ex = ks%calc%energy%exchange, ec = ks%calc%energy%correlation, &
877 deltaxc = ks%calc%energy%delta_xc, vtau = ks%calc%vtau, force_orbitalfree=force_semilocal)
879 call xc_get_vxc(ks%gr, ks%xc, st, hm%kpoints, hm%psolver, namespace, space, ks%calc%density, st%d%ispin, &
880 latt%rcell_volume, ks%calc%vxc, ex = ks%calc%energy%exchange, ec = ks%calc%energy%correlation, &
881 deltaxc = ks%calc%energy%delta_xc, stress_xc=ks%stress_xc_gga, force_orbitalfree=force_semilocal)
885 call xc_get_vxc(ks%gr, ks%xc, st, hm%kpoints, hm%psolver, namespace, space, ks%calc%density, &
886 st%d%ispin, latt%rcell_volume, ks%calc%vxc, vtau = ks%calc%vtau, force_orbitalfree=force_semilocal)
888 call xc_get_vxc(ks%gr, ks%xc, st, hm%kpoints, hm%psolver, namespace, space, ks%calc%density, &
889 st%d%ispin, latt%rcell_volume, ks%calc%vxc, stress_xc=ks%stress_xc_gga, force_orbitalfree=force_semilocal)
895 if (st%d%ispin /=
spinors)
then
896 message(1) =
"Noncollinear functionals can only be used with spinor wavefunctions."
901 message(1) =
"Cannot perform LCAO for noncollinear MGGAs."
902 message(2) =
"Please perform a LDA calculation first."
906 if (ks%calc%calc_energy)
then
908 call xc_get_nc_vxc(ks%gr, ks%xc, st, hm%kpoints, space, namespace, ks%calc%density, ks%calc%vxc, &
909 vtau = ks%calc%vtau, ex = ks%calc%energy%exchange, ec = ks%calc%energy%correlation)
911 call xc_get_nc_vxc(ks%gr, ks%xc, st, hm%kpoints, space, namespace, ks%calc%density, ks%calc%vxc, &
912 ex = ks%calc%energy%exchange, ec = ks%calc%energy%correlation)
916 call xc_get_nc_vxc(ks%gr, ks%xc, st, hm%kpoints, space, namespace, ks%calc%density, &
917 ks%calc%vxc, vtau = ks%calc%vtau)
919 call xc_get_nc_vxc(ks%gr, ks%xc, st, hm%kpoints, space, namespace, ks%calc%density, ks%calc%vxc)
924 call ks%vdw%calc(namespace, space, latt, ions%atom, ions%natoms, ions%pos, &
925 ks%gr, st, ks%calc%energy%vdw, ks%calc%vxc)
938 if (ks%calc%calc_energy)
then
939 call xc_sic_calc_adsic(ks%sic, namespace, space, ks%gr, st, hm, ks%xc, ks%calc%density, &
940 ks%calc%vxc, ex = ks%calc%energy%exchange, ec = ks%calc%energy%correlation)
942 call xc_sic_calc_adsic(ks%sic, namespace, space, ks%gr, st, hm, ks%xc, ks%calc%density, &
954 call x_slater_calc(namespace, ks%gr, space, hm%exxop, st, hm%kpoints, ks%calc%energy%exchange, &
957 call x_fbe_calc(ks%xc%functional(
func_x,1)%id, namespace, hm%psolver, ks%gr, st, space, &
958 ks%calc%energy%exchange, vxc = ks%calc%vxc)
962 call fbe_c_lda_sl(namespace, hm%psolver, ks%gr, st, space, &
963 ks%calc%energy%correlation, vxc = ks%calc%vxc)
971 call xc_ks_inversion_calc(ks%ks_inversion, namespace, space, ks%gr, hm, ext_partners, st, vxc = ks%calc%vxc, &
976 if (ks%xc_photon /= 0)
then
978 call ks%xc_photons%v_ks(namespace, ks%calc%total_density, ks%gr, space, hm%psolver, hm%ep, st)
981 do ispin = 1, hm%d%spin_channels
982 call lalg_axpy(ks%gr%np,
m_one, ks%xc_photons%vpx(1:ks%gr%np), ks%calc%vxc(1:ks%gr%np, ispin) )
986 ks%calc%energy%photon_exchange = ks%xc_photons%ex
991 if (ks%calc%calc_energy)
then
1004 subroutine v_ks_calc_finish(ks, hm, namespace, space, latt, st, ext_partners, force_semilocal)
1005 type(
v_ks_t),
target,
intent(inout) :: ks
1008 class(
space_t),
intent(in) :: space
1012 logical,
optional,
intent(in) :: force_semilocal
1014 integer :: ip, ispin
1017 real(real64) :: exx_energy
1018 real(real64) :: factor
1022 assert(ks%calc%calculating)
1023 ks%calc%calculating = .false.
1025 if (ks%frozen_hxc)
then
1031 safe_deallocate_a(hm%energy)
1032 call move_alloc(ks%calc%energy, hm%energy)
1034 if (hm%self_induced_magnetic)
then
1035 hm%a_ind(1:ks%gr%np, 1:space%dim) = ks%calc%a_ind(1:ks%gr%np, 1:space%dim)
1036 hm%b_ind(1:ks%gr%np, 1:space%dim) = ks%calc%b_ind(1:ks%gr%np, 1:space%dim)
1038 safe_deallocate_a(ks%calc%a_ind)
1039 safe_deallocate_a(ks%calc%b_ind)
1042 if (
allocated(hm%v_static))
then
1043 hm%energy%intnvstatic =
dmf_dotp(ks%gr, ks%calc%total_density, hm%v_static)
1045 hm%energy%intnvstatic =
m_zero
1051 hm%energy%intnvxc =
m_zero
1052 hm%energy%hartree =
m_zero
1053 hm%energy%exchange =
m_zero
1054 hm%energy%exchange_hf =
m_zero
1055 hm%energy%correlation =
m_zero
1058 hm%energy%hartree =
m_zero
1059 call v_ks_hartree(namespace, ks, space, hm, ext_partners)
1065 call dxc_oep_calc(ks%sic%oep, namespace, ks%xc, ks%gr, hm, st, space, &
1066 latt%rcell_volume, hm%energy%exchange, hm%energy%correlation, vxc = ks%calc%vxc)
1068 call zxc_oep_calc(ks%sic%oep, namespace, ks%xc, ks%gr, hm, st, space, &
1069 latt%rcell_volume, hm%energy%exchange, hm%energy%correlation, vxc = ks%calc%vxc)
1078 call dxc_oep_calc(ks%oep, namespace, ks%xc, ks%gr, hm, st, space, &
1079 latt%rcell_volume, hm%energy%exchange, hm%energy%correlation, vxc = ks%calc%vxc)
1081 call zxc_oep_calc(ks%oep, namespace, ks%xc, ks%gr, hm, st, space, &
1082 latt%rcell_volume, hm%energy%exchange, hm%energy%correlation, vxc = ks%calc%vxc)
1091 hm, st, space, hm%energy%exchange, hm%energy%correlation, vxc = ks%calc%vxc)
1094 hm, st, space, hm%energy%exchange, hm%energy%correlation, vxc = ks%calc%vxc)
1096 hm%energy%photon_exchange = ks%oep_photon%pt%ex
1100 if (ks%calc%calc_energy)
then
1102 hm%energy%intnvxc =
m_zero
1105 do ispin = 1, hm%d%nspin
1106 if (ispin <= 2)
then
1111 hm%energy%intnvxc = hm%energy%intnvxc + &
1112 factor*
dmf_dotp(ks%gr, st%rho(:, ispin), ks%calc%vxc(:, ispin), reduce = .false.)
1114 call ks%gr%allreduce(hm%energy%intnvxc)
1119 if (ks%theory_level /=
hartree .and. ks%theory_level /=
rdmft)
then
1121 safe_deallocate_a(hm%ks_pot%vxc)
1122 call move_alloc(ks%calc%vxc, hm%ks_pot%vxc)
1125 call hm%ks_pot%set_vtau(ks%calc%vtau)
1126 safe_deallocate_a(ks%calc%vtau)
1132 hm%energy%intnvxc = hm%energy%intnvxc &
1135 hm%energy%intnvxc = hm%energy%intnvxc &
1145 if (.not. ks%xc_photon_include_hartree)
then
1146 hm%energy%hartree =
m_zero
1147 hm%ks_pot%vhartree =
m_zero
1153 hm%ks_pot%vhxc(ip, 1) = hm%ks_pot%vxc(ip, 1) + hm%ks_pot%vhartree(ip)
1155 if (
allocated(hm%vberry))
then
1157 hm%ks_pot%vhxc(ip, 1) = hm%ks_pot%vhxc(ip, 1) + hm%vberry(ip, 1)
1163 hm%ks_pot%vhxc(ip, 2) = hm%ks_pot%vxc(ip, 2) + hm%ks_pot%vhartree(ip)
1165 if (
allocated(hm%vberry))
then
1167 hm%ks_pot%vhxc(ip, 2) = hm%ks_pot%vhxc(ip, 2) + hm%vberry(ip, 2)
1172 if (hm%d%ispin ==
spinors)
then
1175 hm%ks_pot%vhxc(ip, ispin) = hm%ks_pot%vxc(ip, ispin)
1181 hm%energy%exchange_hf =
m_zero
1183 .or. ks%theory_level ==
rdmft &
1187 if (.not. hm%exxop%useACE)
then
1189 if (
associated(hm%exxop%st))
then
1192 safe_deallocate_p(hm%exxop%st)
1203 select case (ks%theory_level)
1217 if (hm%exxop%useACE)
then
1221 ks%calc%hf_st, xst, hm%kpoints, exx_energy)
1225 ks%calc%hf_st, xst, hm%kpoints, exx_energy)
1226 if (hm%phase%is_allocated())
then
1233 exx_energy = exx_energy + hm%exxop%singul%energy
1237 select case (ks%theory_level)
1240 hm%energy%exchange_hf = hm%energy%exchange_hf + exx_energy
1243 hm%energy%exchange_hf = hm%energy%exchange_hf + exx_energy
1261 if (ks%has_photons .and. (ks%xc_photon == 0))
then
1262 if (
associated(ks%pt_mx%vmf))
then
1263 forall(ip = 1:ks%gr%np) hm%ks_pot%vhxc(ip, 1) = hm%ks_pot%vhxc(ip, 1) + ks%pt_mx%vmf(ip)
1265 forall(ip = 1:ks%gr%np) hm%ks_pot%vhxc(ip, 2) = hm%ks_pot%vhxc(ip, 2) + ks%pt_mx%vmf(ip)
1268 hm%ep%photon_forces(1:space%dim) = ks%pt_mx%fmf(1:space%dim)
1271 if (ks%vdw%vdw_correction /= option__vdwcorrection__none)
then
1272 assert(
allocated(ks%vdw%forces))
1273 hm%ep%vdw_forces(:, :) = ks%vdw%forces(:, :)
1274 hm%ep%vdw_stress = ks%vdw%stress
1275 safe_deallocate_a(ks%vdw%forces)
1277 hm%ep%vdw_forces = 0.0_real64
1280 if (ks%calc%time_present .or. hm%time_zero)
then
1281 call hm%update(ks%gr, namespace, space, ext_partners, time = ks%calc%time)
1287 safe_deallocate_a(ks%calc%density)
1288 if (ks%calc%total_density_alloc)
then
1289 safe_deallocate_p(ks%calc%total_density)
1291 nullify(ks%calc%total_density)
1302 subroutine v_ks_hartree(namespace, ks, space, hm, ext_partners)
1304 type(
v_ks_t),
intent(inout) :: ks
1305 class(
space_t),
intent(in) :: space
1313 call dpoisson_solve(hm%psolver, namespace, hm%ks_pot%vhartree, ks%calc%total_density, reset=.false.)
1319 if (ks%calc%calc_energy)
then
1321 hm%energy%hartree =
m_half*
dmf_dotp(ks%gr, ks%calc%total_density, hm%ks_pot%vhartree)
1325 if(ks%calc%time_present)
then
1328 ks%calc%total_density, hm%energy%pcm_corr, kick=hm%kick, time=ks%calc%time)
1331 ks%calc%total_density, hm%energy%pcm_corr, time=ks%calc%time)
1336 ks%calc%total_density, hm%energy%pcm_corr, kick=hm%kick)
1339 ks%calc%total_density, hm%energy%pcm_corr)
1350 type(
v_ks_t),
intent(inout) :: ks
1354 ks%frozen_hxc = .
true.
1361 type(
v_ks_t),
intent(inout) :: this
1362 logical,
intent(in) :: calc_cur
1366 this%calculate_current = calc_cur
1373 type(
v_ks_t),
intent(inout) :: ks
1377 real(real64),
intent(out) :: int_dft_u
constant times a vector plus a vector
scales a vector by a constant
This is the common interface to a sorting routine. It performs the shell algorithm,...
pure logical function, public accel_is_enabled()
subroutine, public current_calculate(this, namespace, gr, hm, space, st)
Compute total electronic current density.
subroutine, public current_init(this, namespace)
This module implements a calculator for the density and defines related functions.
subroutine, public states_elec_total_density(st, mesh, total_rho)
This routine calculates the total electronic density.
subroutine, public density_calc(st, gr, density, istin)
Computes the density from the orbitals in st.
This module calculates the derivatives (gradients, Laplacians, etc.) of a function.
integer, parameter, public unpolarized
Parameters...
integer, parameter, public spinors
subroutine, public energy_calc_total(namespace, space, hm, gr, st, ext_partners, iunit, full)
This subroutine calculates the total energy of the system. Basically, it adds up the KS eigenvalues,...
real(real64) function, public zenergy_calc_electronic(namespace, hm, der, st, terms)
real(real64) function, public denergy_calc_electronic(namespace, hm, der, st, terms)
subroutine, public energy_calc_eigenvalues(namespace, hm, der, st)
subroutine, public energy_copy(ein, eout)
subroutine, public dexchange_operator_ace(this, namespace, mesh, st, xst, phase)
subroutine, public zexchange_operator_compute_potentials(this, namespace, space, gr, st, xst, kpoints, ex, F_out)
subroutine, public dexchange_operator_compute_potentials(this, namespace, space, gr, st, xst, kpoints, ex, F_out)
subroutine, public zexchange_operator_ace(this, namespace, mesh, st, xst, phase)
subroutine, public exchange_operator_reinit(this, omega, alpha, beta, st)
real(real64), parameter, public m_two
real(real64), parameter, public m_zero
real(real64), parameter, public m_epsilon
real(real64), parameter, public m_half
real(real64), parameter, public m_one
This module implements the underlying real-space grid.
integer, parameter, public term_mgga
integer, parameter, public term_dft_u
logical function, public hamiltonian_elec_has_kick(hm)
logical function, public hamiltonian_elec_needs_current(hm, states_are_real)
subroutine, public hamiltonian_elec_update_pot(this, mesh, accumulate)
Update the KS potential of the electronic Hamiltonian.
This module defines classes and functions for interaction partners.
A module to handle KS potential, without the external potential.
integer, parameter, public rdmft
integer, parameter, public hartree
integer, parameter, public hartree_fock
integer, parameter, public independent_particles
integer, parameter, public generalized_kohn_sham_dft
integer, parameter, public kohn_sham_dft
integer, parameter, public dft_u_none
This modules implements the routines for doing constrain DFT for noncollinear magnetism.
integer, parameter, public constrain_none
subroutine, public magnetic_constrain_update(this, mesh, std, space, latt, pos, rho)
Recomputes the magnetic contraining potential.
subroutine, public magnetic_induced(namespace, gr, st, psolver, kpoints, a_ind, b_ind)
This subroutine receives as input a current, and produces as an output the vector potential that it i...
This module defines various routines, operating on mesh functions.
This module defines the meshes, which are used in Octopus.
subroutine, public messages_print_with_emphasis(msg, iunit, namespace)
subroutine, public messages_not_implemented(feature, namespace)
character(len=512), private msg
subroutine, public messages_warning(no_lines, all_nodes, namespace)
subroutine, public messages_obsolete_variable(namespace, name, rep)
subroutine, public messages_new_line()
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
subroutine, public messages_input_error(namespace, var, details, row, column)
subroutine, public messages_experimental(name, namespace)
subroutine, public messages_info(no_lines, iunit, debug_only, stress, all_nodes, namespace)
This module handles the communicators for the various parallelization strategies.
logical function, public parse_is_defined(namespace, name)
subroutine, public pcm_hartree_potential(pcm, space, mesh, psolver, ext_partners, vhartree, density, pcm_corr, kick, time)
PCM reaction field due to the electronic density.
subroutine, public mf_calc(this, gr, st, ions, pt_mode, time)
subroutine, public dpoisson_solve_start(this, rho)
subroutine, public dpoisson_solve(this, namespace, pot, rho, all_nodes, kernel, reset)
Calculates the Poisson equation. Given the density returns the corresponding potential.
subroutine, public dpoisson_solve_finish(this, pot)
logical pure function, public poisson_is_async(this)
subroutine, public profiling_out(label)
Increment out counter and sum up difference between entry and exit time.
subroutine, public profiling_in(label, exclude)
Increment in counter and save entry time.
integer, parameter, public pseudo_exchange_unknown
integer, parameter, public pseudo_correlation_unknown
integer, parameter, public pseudo_correlation_any
integer, parameter, public pseudo_exchange_any
This module is intended to contain "only mathematical" functions and procedures.
integer, parameter, private libxc_c_index
pure logical function, public states_are_complex(st)
pure logical function, public states_are_real(st)
This module handles spin dimensions of the states and the k-point distribution.
subroutine, public states_elec_fermi(st, namespace, mesh, compute_spin)
calculate the Fermi level for the states in this object
subroutine, public states_elec_end(st)
finalize the states_elec_t object
subroutine, public states_elec_copy(stout, stin, exclude_wfns, exclude_eigenval, special)
make a (selective) copy of a states_elec_t object
subroutine, public states_elec_allocate_current(st, space, mesh)
This module provides routines for communicating states when using states parallelization.
subroutine, public states_elec_parallel_remote_access_stop(this)
stop remote memory access for states on other processors
subroutine, public states_elec_parallel_remote_access_start(this)
start remote memory access for states on other processors
subroutine v_ks_hartree(namespace, ks, space, hm, ext_partners)
Hartree contribution to the KS potential. This function is designed to be used by v_ks_calc_finish an...
subroutine, public v_ks_calc_finish(ks, hm, namespace, space, latt, st, ext_partners, force_semilocal)
subroutine, public v_ks_freeze_hxc(ks)
subroutine, public v_ks_end(ks)
subroutine, public v_ks_calculate_current(this, calc_cur)
subroutine, public v_ks_write_info(ks, iunit, namespace)
subroutine, public v_ks_update_dftu_energy(ks, namespace, hm, st, int_dft_u)
Update the value of <\psi | V_U | \psi>, where V_U is the DFT+U potential.
subroutine, public v_ks_calc_start(ks, namespace, space, hm, st, ions, latt, ext_partners, time, calc_energy, force_semilocal)
This routine starts the calculation of the Kohn-Sham potential. The routine v_ks_calc_finish must be ...
subroutine, public v_ks_calc(ks, namespace, space, hm, st, ions, ext_partners, calc_eigenval, time, calc_energy, calc_current, force_semilocal)
subroutine, public v_ks_h_setup(namespace, space, gr, ions, ext_partners, st, ks, hm, calc_eigenval, calc_current)
subroutine, public v_ks_init(ks, namespace, gr, st, ions, mc, space, kpoints)
subroutine, public x_slater_calc(namespace, gr, space, exxop, st, kpoints, ex, vxc)
Interface to X(slater_calc)
subroutine, public x_fbe_calc(id, namespace, psolver, gr, st, space, ex, vxc)
Interface to X(x_fbe_calc) Two possible run modes possible: adiabatic and Sturm-Liouville....
subroutine, public fbe_c_lda_sl(namespace, psolver, gr, st, space, ec, vxc)
Sturm-Liouville version of the FBE local-density correlation functional.
integer, parameter, public xc_family_ks_inversion
declaring 'family' constants for 'functionals' not handled by libxc careful not to use a value define...
integer function, public xc_get_default_functional(dim, pseudo_x_functional, pseudo_c_functional)
Returns the default functional given the one parsed from the pseudopotentials and the space dimension...
integer, parameter, public xc_family_nc_mgga
integer, parameter, public xc_oep_x
Exact exchange.
integer, parameter, public xc_lda_c_fbe_sl
LDA correlation based ib the force-balance equation - Sturm-Liouville version.
integer, parameter, public xc_family_nc_lda
integer, parameter, public xc_oep_x_fbe_sl
Exchange approximation based on the force balance equation - Sturn-Liouville version.
integer, parameter, public xc_oep_x_fbe
Exchange approximation based on the force balance equation.
integer, parameter, public xc_oep_x_slater
Slater approximation to the exact exchange.
integer, parameter, public func_c
integer, parameter, public func_x
subroutine, public xc_ks_inversion_end(ks_inv)
subroutine, public xc_ks_inversion_write_info(ks_inversion, iunit, namespace)
subroutine, public xc_ks_inversion_init(ks_inv, namespace, gr, ions, st, xc, mc, space, kpoints)
subroutine, public xc_ks_inversion_calc(ks_inversion, namespace, space, gr, hm, ext_partners, st, vxc, time)
subroutine, public xc_write_info(xcs, iunit, namespace)
subroutine, public xc_init(xcs, namespace, ndim, periodic_dim, nel, x_id, c_id, xk_id, ck_id, hartree_fock, ispin)
pure logical function, public family_is_mgga(family, only_collinear)
Is the xc function part of the mGGA family.
logical pure function, public family_is_mgga_with_exc(xcs)
Is the xc function part of the mGGA family with an energy functional.
subroutine, public xc_end(xcs)
subroutine, public xc_get_vxc(gr, xcs, st, kpoints, psolver, namespace, space, rho, ispin, rcell_volume, vxc, ex, ec, deltaxc, vtau, ex_density, ec_density, stress_xc, force_orbitalfree)
logical pure function, public family_is_hybrid(xcs)
Returns true if the functional is an hybrid functional.
subroutine, public xc_get_nc_vxc(gr, xcs, st, kpoints, space, namespace, rho, vxc, ex, ec, vtau, ex_density, ec_density)
This routines is similar to xc_get_vxc but for noncollinear functionals, which are not implemented in...
integer, parameter, public oep_type_mgga
integer, parameter, public oep_level_none
the OEP levels
subroutine, public xc_oep_end(oep)
subroutine, public zxc_oep_calc(oep, namespace, xcs, gr, hm, st, space, rcell_volume, ex, ec, vxc)
This file handles the evaluation of the OEP potential, in the KLI or full OEP as described in S....
subroutine, public dxc_oep_calc(oep, namespace, xcs, gr, hm, st, space, rcell_volume, ex, ec, vxc)
This file handles the evaluation of the OEP potential, in the KLI or full OEP as described in S....
subroutine, public xc_oep_write_info(oep, iunit, namespace)
integer, parameter, public oep_type_exx
The different types of OEP that we can work with.
subroutine, public xc_oep_init(oep, namespace, gr, st, mc, space, oep_type)
subroutine, public zxc_oep_photon_calc(oep, namespace, xcs, gr, hm, st, space, ex, ec, vxc)
This file handles the evaluation of the OEP potential, in the KLI or full OEP as described in S....
subroutine, public dxc_oep_photon_calc(oep, namespace, xcs, gr, hm, st, space, ex, ec, vxc)
This file handles the evaluation of the OEP potential, in the KLI or full OEP as described in S....
This module implements the "photon-free" electron-photon exchange-correlation functional.
integer, parameter, public sic_none
no self-interaction correction
subroutine, public xc_sic_write_info(sic, iunit, namespace)
integer, parameter, public sic_adsic
Averaged density SIC.
subroutine, public xc_sic_init(sic, namespace, gr, st, mc, space)
initialize the SIC object
subroutine, public xc_sic_end(sic)
finalize the SIC and, if needed, the included OEP
integer, parameter, public sic_pz_oep
Perdew-Zunger SIC (OEP way)
integer, parameter, public sic_amaldi
Amaldi correction term.
subroutine, public xc_sic_calc_adsic(sic, namespace, space, gr, st, hm, xc, density, vxc, ex, ec)
Computes the ADSIC potential and energy.
A module that takes care of xc contribution from vdW interactions.
Extension of space that contains the knowledge of the spin dimension.
Description of the grid, containing information on derivatives, stencil, and symmetries.
The states_elec_t class contains all electronic wave functions.
subroutine get_functional_from_pseudos(x_functional, c_functional)
Tries to find out the functional from the pseudopotential.
subroutine v_a_xc(hm, force_semilocal)
subroutine calculate_density()