Octopus
v_ks.F90
Go to the documentation of this file.
1!! Copyright (C) 2002-2006 M. Marques, A. Castro, A. Rubio, G. Bertsch
2!!
3!! This program is free software; you can redistribute it and/or modify
4!! it under the terms of the GNU General Public License as published by
5!! the Free Software Foundation; either version 2, or (at your option)
6!! any later version.
7!!
8!! This program is distributed in the hope that it will be useful,
9!! but WITHOUT ANY WARRANTY; without even the implied warranty of
10!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11!! GNU General Public License for more details.
12!!
13!! You should have received a copy of the GNU General Public License
14!! along with this program; if not, write to the Free Software
15!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
16!! 02110-1301, USA.
17!!
18
19#include "global.h"
20
21module v_ks_oct_m
22 use accel_oct_m
23 use comm_oct_m
25 use debug_oct_m
28 use energy_oct_m
32 use global_oct_m
33 use grid_oct_m
37 use ions_oct_m
38 use, intrinsic :: iso_fortran_env
41 use lda_u_oct_m
45 use mesh_oct_m
48 use mpi_oct_m
51 use parser_oct_m
56 use pseudo_oct_m
59 use sort_oct_m
60 use space_oct_m
68 use xc_oct_m
69 use xc_f03_lib_m
70 use xc_fbe_oct_m
74 use xc_oep_oct_m
75 use xc_sic_oct_m
77 use xc_vdw_oct_m
79
80 ! from the dftd3 library
81 use dftd3_api
82
83 implicit none
84
85 private
86 public :: &
87 v_ks_t, &
88 v_ks_init, &
89 v_ks_end, &
92 v_ks_calc, &
98
99 type v_ks_calc_t
100 private
101 logical :: calculating
102 logical :: time_present
103 real(real64) :: time
104 real(real64), allocatable :: density(:, :)
105 logical :: total_density_alloc
106 real(real64), pointer, contiguous :: total_density(:)
107 type(energy_t), allocatable :: energy
108 type(states_elec_t), pointer :: hf_st
109 real(real64), allocatable :: vxc(:, :)
110 real(real64), allocatable :: vtau(:, :)
111 real(real64), allocatable :: axc(:, :, :)
112 real(real64), allocatable :: a_ind(:, :)
113 real(real64), allocatable :: b_ind(:, :)
114 logical :: calc_energy
115 end type v_ks_calc_t
116
117 type v_ks_t
118 private
119 integer, public :: theory_level = -1
120
121 logical, public :: frozen_hxc = .false.
122
123 integer, public :: xc_family = 0
124 integer, public :: xc_flags = 0
125 integer, public :: xc_photon = 0
126 type(xc_t), public :: xc
127 type(xc_photons_t), public :: xc_photons
128 type(xc_oep_t), public :: oep
129 type(xc_oep_photon_t), public :: oep_photon
130 type(xc_ks_inversion_t), public :: ks_inversion
131 type(xc_sic_t), public :: sic
132 type(xc_vdw_t), public :: vdw
133 type(grid_t), pointer, public :: gr
134 type(v_ks_calc_t) :: calc
135 logical :: calculate_current = .false.
136 type(current_t) :: current_calculator
137 logical :: include_td_field = .false.
138 logical, public :: has_photons = .false.
139 logical :: xc_photon_include_hartree = .true.
140
141 real(real64), public :: stress_xc_gga(3, 3)
142 type(photon_mode_t), pointer, public :: pt => null()
143 type(mf_t), public :: pt_mx
144 end type v_ks_t
145
146contains
147
148 ! ---------------------------------------------------------
149 subroutine v_ks_init(ks, namespace, gr, st, ions, mc, space, kpoints)
150 type(v_ks_t), intent(inout) :: ks
151 type(namespace_t), intent(in) :: namespace
152 type(grid_t), target, intent(inout) :: gr
153 type(states_elec_t), intent(in) :: st
154 type(ions_t), intent(inout) :: ions
155 type(multicomm_t), intent(in) :: mc
156 class(space_t), intent(in) :: space
157 type(kpoints_t), intent(in) :: kpoints
158
159 integer :: x_id, c_id, xk_id, ck_id, default, val
160 logical :: parsed_theory_level, using_hartree_fock
161 integer :: pseudo_x_functional, pseudo_c_functional
162 integer :: oep_type
163
164 push_sub(v_ks_init)
165
166 ! We need to parse TheoryLevel and XCFunctional, this is
167 ! complicated because they are interdependent.
168
169 !%Variable TheoryLevel
170 !%Type integer
171 !%Section Hamiltonian
172 !%Description
173 !% The calculations can be run with different "theory levels" that
174 !% control how electrons are simulated. The default is
175 !% <tt>dft</tt>. When hybrid functionals are requested, through
176 !% the <tt>XCFunctional</tt> variable, the default is
177 !% <tt>hartree_fock</tt>.
178 !%Option independent_particles 2
179 !% Particles will be considered as independent, <i>i.e.</i> as non-interacting.
180 !% This mode is mainly used for testing purposes, as the code is usually
181 !% much faster with <tt>independent_particles</tt>.
182 !%Option hartree 1
183 !% Calculation within the Hartree method (experimental). Note that, contrary to popular
184 !% belief, the Hartree potential is self-interaction-free. Therefore, this run
185 !% mode will not yield the same result as <tt>kohn-sham</tt> without exchange-correlation.
186 !%Option hartree_fock 3
187 !% This is the traditional Hartree-Fock scheme. Like the Hartree scheme, it is fully
188 !% self-interaction-free.
189 !%Option kohn_sham 4
190 !% This is the default density-functional theory scheme. Note that you can also use
191 !% hybrid functionals in this scheme, but they will be handled the "DFT" way, <i>i.e.</i>,
192 !% solving the OEP equation.
193 !%Option generalized_kohn_sham 5
194 !% This is similar to the <tt>kohn-sham</tt> scheme, except that this allows for nonlocal operators.
195 !% This is the default mode to run hybrid functionals, meta-GGA functionals, or DFT+U.
196 !% It can be more convenient to use <tt>kohn-sham</tt> DFT within the OEP scheme to get similar (but not the same) results.
197 !% Note that within this scheme you can use a correlation functional, or a hybrid
198 !% functional (see <tt>XCFunctional</tt>). In the latter case, you will be following the
199 !% quantum-chemistry recipe to use hybrids.
200 !%Option rdmft 7
201 !% (Experimental) Reduced Density Matrix functional theory.
202 !%End
204 ks%xc_family = xc_family_none
205 ks%sic%level = sic_none
206 ks%oep%level = oep_level_none
207 ks%oep_photon%level = oep_level_none
208
209 ks%theory_level = kohn_sham_dft
210 parsed_theory_level = .false.
211
212 ! the user knows what he wants, give her that
213 if (parse_is_defined(namespace, 'TheoryLevel')) then
214 call parse_variable(namespace, 'TheoryLevel', kohn_sham_dft, ks%theory_level)
215 if (.not. varinfo_valid_option('TheoryLevel', ks%theory_level)) call messages_input_error(namespace, 'TheoryLevel')
217 parsed_theory_level = .true.
218 end if
220 ! parse the XC functional
222 call get_functional_from_pseudos(pseudo_x_functional, pseudo_c_functional)
224 default = 0
225 if (ks%theory_level == kohn_sham_dft .or. ks%theory_level == generalized_kohn_sham_dft) then
226 default = xc_get_default_functional(space%dim, pseudo_x_functional, pseudo_c_functional)
227 end if
229 if (.not. parse_is_defined(namespace, 'XCFunctional') &
230 .and. (pseudo_x_functional /= pseudo_exchange_any .or. pseudo_c_functional /= pseudo_correlation_any)) then
231 call messages_write('Info: the XCFunctional has been selected to match the pseudopotentials', new_line = .true.)
232 call messages_write(' used in the calculation.')
233 call messages_info()
234 end if
236 ! The description of this variable can be found in file src/xc/functionals_list.F90
237 call parse_variable(namespace, 'XCFunctional', default, val)
238
239 ! the first 3 digits of the number indicate the X functional and
240 ! the next 3 the C functional.
241 c_id = val / libxc_c_index
242 x_id = val - c_id * libxc_c_index
243
244 if ((x_id /= pseudo_x_functional .and. pseudo_x_functional /= pseudo_exchange_any) .or. &
245 (c_id /= pseudo_c_functional .and. pseudo_c_functional /= pseudo_exchange_any)) then
246 call messages_write('The XCFunctional that you selected does not match the one used', new_line = .true.)
247 call messages_write('to generate the pseudopotentials.')
248 call messages_warning(namespace=namespace)
249 end if
250
251 ! FIXME: we rarely need this. We should only parse when necessary.
252
253 !%Variable XCKernel
254 !%Type integer
255 !%Section Hamiltonian::XC
256 !%Description
257 !% Defines the exchange-correlation kernel. Only LDA kernels are available currently.
258 !% The options are the same as <tt>XCFunctional</tt>.
259 !% Note: the kernel is only needed for Casida, Sternheimer, or optimal-control calculations.
260 !% Defaults:
261 !% <br>1D: <tt>lda_x_1d + lda_c_1d_csc</tt>
262 !% <br>2D: <tt>lda_x_2d + lda_c_2d_amgb</tt>
263 !% <br>3D: <tt>lda_x + lda_c_pz_mod</tt>
264 !%Option xc_functional -1
265 !% The same functional defined by <tt>XCFunctional</tt>.
266 !%End
267 call parse_variable(namespace, 'XCKernel', default, val)
268 if (-1 == val) then
269 ck_id = c_id
270 xk_id = x_id
271 else
272 ck_id = val / libxc_c_index
273 xk_id = val - ck_id * libxc_c_index
274 end if
275
276 call messages_obsolete_variable(namespace, 'XFunctional', 'XCFunctional')
277 call messages_obsolete_variable(namespace, 'CFunctional', 'XCFunctional')
278
279 !%Variable XCPhotonFunctional
280 !%Type integer
281 !%Default 0
282 !%Section Hamiltonian::XC
283 !%Description
284 !% Defines the exchange and correlation functionals to be used for the QEDFT
285 !% description of the electron-photon system.
286 !%Option none 0
287 !% No functional is used
288 !%Option photon_x_lda 10
289 !% Exchange-only local density approcimation
290 !%Option photon_xc_lda 11
291 !% Exchange-correlation local density approcimation
292 !%Option photon_x_wfn 20
293 !% Exchange-only based on wave functions
294 !%Option photon_xc_wfn 21
295 !% Exchange-correlation based on wave functions
296 !%End
297
298 call parse_variable(namespace, 'XCPhotonFunctional', option__xcphotonfunctional__none, ks%xc_photon)
299
300 !%Variable XCPhotonIncludeHartree
301 !%Type logical
302 !%Default yes
303 !%Section Hamiltonian::XC
304 !%Description
305 !% Use the Hartree potential and energy in calculations
306 !%End
307
308 call parse_variable(namespace, 'XCPhotonIncludeHartree', .true., ks%xc_photon_include_hartree)
309
310 if (.not. ks%xc_photon_include_hartree) then
311 call messages_write('turn off hartree potential and energy')
312 call messages_warning(namespace=namespace)
313 end if
314
315 ! initialize XC modules
316
317 ! This is a bit ugly, theory_level might not be generalized KS or HF now
318 ! but it might become generalized KS or HF later. This is safe because it
319 ! becomes generalized KS in the cases where the functional is hybrid
320 ! and the ifs inside check for both conditions.
321 using_hartree_fock = (ks%theory_level == hartree_fock) &
322 .or. (ks%theory_level == generalized_kohn_sham_dft .and. family_is_hybrid(ks%xc))
323 call xc_init(ks%xc, namespace, space%dim, space%periodic_dim, st%qtot, &
324 x_id, c_id, xk_id, ck_id, hartree_fock = using_hartree_fock, ispin=st%d%ispin)
325
326 ks%xc_family = ks%xc%family
327 ks%xc_flags = ks%xc%flags
328
329 if (.not. parsed_theory_level) then
330 default = kohn_sham_dft
331
332 ! the functional is a hybrid, use Hartree-Fock as theory level by default
333 if (family_is_hybrid(ks%xc) .or. family_is_mgga_with_exc(ks%xc)) then
335 end if
336
337 ! In principle we do not need to parse. However we do it for consistency
338 call parse_variable(namespace, 'TheoryLevel', default, ks%theory_level)
339 if (.not. varinfo_valid_option('TheoryLevel', ks%theory_level)) call messages_input_error(namespace, 'TheoryLevel')
340
341 end if
342
343 ! In case we need OEP, we need to find which type of OEP it is
344 oep_type = -1
345 if (family_is_mgga_with_exc(ks%xc)) then
346 call messages_experimental('MGGA energy functionals')
347
348 if (accel_is_enabled() .and. (gr%parallel_in_domains .or. st%parallel_in_states .or. st%d%kpt%parallel)) then
349 !At the moment this combination produces wrong results
350 call messages_not_implemented("MGGA with energy functionals and CUDA+MPI")
351 end if
352
353 if (ks%theory_level == kohn_sham_dft) then
354 call messages_experimental("MGGA within the Kohn-Sham scheme")
355 ks%xc_family = ior(ks%xc_family, xc_family_oep)
356 oep_type = oep_type_mgga
357 end if
358 end if
359
360 call messages_obsolete_variable(namespace, 'NonInteractingElectrons', 'TheoryLevel')
361 call messages_obsolete_variable(namespace, 'HartreeFock', 'TheoryLevel')
362
363 ! Due to how the code is made, we need to set this to have theory level other than DFT
364 ! correct...
365 ks%sic%amaldi_factor = m_one
366
367 select case (ks%theory_level)
369
370 case (hartree)
371 call messages_experimental("Hartree theory level")
372 if (space%periodic_dim == space%dim) then
373 call messages_experimental("Hartree in fully periodic system")
374 end if
375 if (kpoints%full%npoints > 1) then
376 call messages_not_implemented("Hartree with k-points", namespace=namespace)
377 end if
378
379 case (hartree_fock)
380 if (kpoints%full%npoints > 1) then
381 call messages_experimental("Hartree-Fock with k-points")
382 end if
383
385 if (kpoints%full%npoints > 1 .and. family_is_hybrid(ks%xc)) then
386 call messages_experimental("Hybrid functionals with k-points")
387 end if
388
389 case (rdmft)
390 call messages_experimental('RDMFT theory level')
391
392 case (kohn_sham_dft)
393
394 ! check for SIC
395 if (bitand(ks%xc_family, xc_family_lda + xc_family_gga) /= 0) then
396 call xc_sic_init(ks%sic, namespace, gr, st, mc, space)
397 end if
398
399 if (bitand(ks%xc_family, xc_family_oep) /= 0) then
400 select case (ks%xc%functional(func_x,1)%id)
401 case (xc_oep_x_slater)
402 if (kpoints%reduced%npoints > 1) then
403 call messages_not_implemented("Slater with k-points", namespace=namespace)
404 end if
405 ks%oep%level = oep_level_none
406 case (xc_oep_x_fbe)
407 if (kpoints%reduced%npoints > 1) then
408 call messages_not_implemented("FBE functional with k-points", namespace=namespace)
409 end if
410 ks%oep%level = oep_level_none
411 case default
412 if((.not. ks%has_photons) .or. (ks%xc_photon /= 0)) then
413 if(oep_type == -1) then ! Else we have a MGGA
414 oep_type = oep_type_exx
415 end if
416 call xc_oep_init(ks%oep, namespace, gr, st, mc, space, oep_type)
417 end if
418 end select
419 else
420 ks%oep%level = oep_level_none
421 end if
422
423 if (bitand(ks%xc_family, xc_family_ks_inversion) /= 0) then
424 call xc_ks_inversion_init(ks%ks_inversion, namespace, gr, ions, st, ks%xc, mc, space, kpoints)
425 end if
426
427 end select
428
429 if (st%d%ispin == spinors) then
430 if (bitand(ks%xc_family, xc_family_mgga + xc_family_hyb_mgga) /= 0) then
431 call messages_not_implemented("MGGA with spinors", namespace=namespace)
432 end if
433 end if
434
435 ks%frozen_hxc = .false.
436
437 call v_ks_write_info(ks, namespace=namespace)
438
439 ks%gr => gr
440 ks%calc%calculating = .false.
441
442 !The value of ks%calculate_current is set to false or true by Output
443 call current_init(ks%current_calculator, namespace)
444
445 call ks%vdw%init(namespace, space, gr, ks%xc, ions, x_id, c_id)
446
447 if (ks%xc_photon /= 0) then
448 ! initilize the photon free variables
449 call ks%xc_photons%init(namespace, ks%xc_photon , space, gr, st)
450 ! remornalize the electron mass due to light-matter interaction; here we only deal with it in free space
451 ks%oep_photon%level = oep_level_none
452 end if
453
454
455 pop_sub(v_ks_init)
456
457 contains
458
459 subroutine get_functional_from_pseudos(x_functional, c_functional)
460 integer, intent(out) :: x_functional
461 integer, intent(out) :: c_functional
462
463 integer :: xf, cf, ispecies
464 logical :: warned_inconsistent
465
466 x_functional = pseudo_exchange_any
467 c_functional = pseudo_correlation_any
468
469 warned_inconsistent = .false.
470 do ispecies = 1, ions%nspecies
471 select type(spec=>ions%species(ispecies)%s)
472 class is(pseudopotential_t)
473 xf = spec%x_functional()
474 cf = spec%c_functional()
475 class default
478 end select
479
480 if (xf == pseudo_exchange_unknown .or. cf == pseudo_correlation_unknown) then
481 call messages_write("Unknown XC functional for species '"//trim(ions%species(ispecies)%s%get_label())//"'")
482 call messages_warning(namespace=namespace)
483 cycle
484 end if
485
486 if (x_functional == pseudo_exchange_any) then
487 x_functional = xf
488 else
489 if (xf /= x_functional .and. .not. warned_inconsistent) then
490 call messages_write('Inconsistent XC functional detected between species')
491 call messages_warning(namespace=namespace)
492 warned_inconsistent = .true.
493 end if
494 end if
495
496 if (c_functional == pseudo_correlation_any) then
497 c_functional = cf
498 else
499 if (cf /= c_functional .and. .not. warned_inconsistent) then
500 call messages_write('Inconsistent XC functional detected between species')
501 call messages_warning(namespace=namespace)
502 warned_inconsistent = .true.
503 end if
504 end if
505
506 end do
507
508 assert(x_functional /= pseudo_exchange_unknown)
509 assert(c_functional /= pseudo_correlation_unknown)
510
511 end subroutine get_functional_from_pseudos
512 end subroutine v_ks_init
513 ! ---------------------------------------------------------
514
515 ! ---------------------------------------------------------
516 subroutine v_ks_end(ks)
517 type(v_ks_t), intent(inout) :: ks
518
519 push_sub(v_ks_end)
520
521 call ks%vdw%end()
522
523 select case (ks%theory_level)
524 case (kohn_sham_dft)
525 if (bitand(ks%xc_family, xc_family_ks_inversion) /= 0) then
526 call xc_ks_inversion_end(ks%ks_inversion)
527 end if
528 if (bitand(ks%xc_family, xc_family_oep) /= 0) then
529 call xc_oep_end(ks%oep)
530 end if
531 call xc_end(ks%xc)
533 call xc_end(ks%xc)
534 end select
535
536 call xc_sic_end(ks%sic)
537
538 if (ks%xc_photon /= 0) then
539 call ks%xc_photons%end()
540 end if
541
542 pop_sub(v_ks_end)
543 end subroutine v_ks_end
544 ! ---------------------------------------------------------
545
546
547 ! ---------------------------------------------------------
548 subroutine v_ks_write_info(ks, iunit, namespace)
549 type(v_ks_t), intent(in) :: ks
550 integer, optional, intent(in) :: iunit
551 type(namespace_t), optional, intent(in) :: namespace
553 push_sub(v_ks_write_info)
554
555 call messages_print_with_emphasis(msg="Theory Level", iunit=iunit, namespace=namespace)
556 call messages_print_var_option("TheoryLevel", ks%theory_level, iunit=iunit, namespace=namespace)
557
558 select case (ks%theory_level)
560 call messages_info(iunit=iunit, namespace=namespace)
561 call xc_write_info(ks%xc, iunit, namespace)
562
563 case (kohn_sham_dft)
564 call messages_info(iunit=iunit, namespace=namespace)
565 call xc_write_info(ks%xc, iunit, namespace)
566
567 call messages_info(iunit=iunit, namespace=namespace)
568
569 call xc_sic_write_info(ks%sic, iunit, namespace)
570 call xc_oep_write_info(ks%oep, iunit, namespace)
571 call xc_ks_inversion_write_info(ks%ks_inversion, iunit, namespace)
572
573 end select
574
575 call messages_print_with_emphasis(iunit=iunit, namespace=namespace)
576
577 pop_sub(v_ks_write_info)
578 end subroutine v_ks_write_info
579 ! ---------------------------------------------------------
580
581
582 !----------------------------------------------------------
583 subroutine v_ks_h_setup(namespace, space, gr, ions, ext_partners, st, ks, hm, calc_eigenval, calc_current)
584 type(namespace_t), intent(in) :: namespace
585 type(electron_space_t), intent(in) :: space
586 type(grid_t), intent(in) :: gr
587 type(ions_t), intent(in) :: ions
588 type(partner_list_t), intent(in) :: ext_partners
589 type(states_elec_t), intent(inout) :: st
590 type(v_ks_t), intent(inout) :: ks
591 type(hamiltonian_elec_t), intent(inout) :: hm
592 logical, optional, intent(in) :: calc_eigenval
593 logical, optional, intent(in) :: calc_current
594
595 integer, allocatable :: ind(:)
596 integer :: ist, ik
597 real(real64), allocatable :: copy_occ(:)
598 logical :: calc_eigenval_
599 logical :: calc_current_
600
601 push_sub(v_ks_h_setup)
602
603 calc_eigenval_ = optional_default(calc_eigenval, .true.)
604 calc_current_ = optional_default(calc_current, .true.)
605 call states_elec_fermi(st, namespace, gr)
606 call density_calc(st, gr, st%rho)
607 call v_ks_calc(ks, namespace, space, hm, st, ions, ext_partners, calc_eigenval = calc_eigenval_, calc_current = calc_current_) ! get potentials
608
609 if (st%restart_reorder_occs .and. .not. st%fromScratch) then
610 message(1) = "Reordering occupations for restart."
611 call messages_info(1, namespace=namespace)
612
613 safe_allocate(ind(1:st%nst))
614 safe_allocate(copy_occ(1:st%nst))
615
616 do ik = 1, st%nik
617 call sort(st%eigenval(:, ik), ind)
618 copy_occ(1:st%nst) = st%occ(1:st%nst, ik)
619 do ist = 1, st%nst
620 st%occ(ist, ik) = copy_occ(ind(ist))
621 end do
622 end do
623
624 safe_deallocate_a(ind)
625 safe_deallocate_a(copy_occ)
626 end if
627
628 if (calc_eigenval_) call states_elec_fermi(st, namespace, gr) ! occupations
629 call energy_calc_total(namespace, space, hm, gr, st, ext_partners)
630
631 pop_sub(v_ks_h_setup)
632 end subroutine v_ks_h_setup
633
634 ! ---------------------------------------------------------
635 subroutine v_ks_calc(ks, namespace, space, hm, st, ions, ext_partners, &
636 calc_eigenval, time, calc_energy, calc_current, force_semilocal)
637 type(v_ks_t), intent(inout) :: ks
638 type(namespace_t), intent(in) :: namespace
639 type(electron_space_t), intent(in) :: space
640 type(hamiltonian_elec_t), intent(inout) :: hm
641 type(states_elec_t), intent(inout) :: st
642 type(ions_t), intent(in) :: ions
643 type(partner_list_t), intent(in) :: ext_partners
644 logical, optional, intent(in) :: calc_eigenval
645 real(real64), optional, intent(in) :: time
646 logical, optional, intent(in) :: calc_energy
647 logical, optional, intent(in) :: calc_current
648 logical, optional, intent(in) :: force_semilocal
649
650 logical :: calc_current_
651
652 push_sub(v_ks_calc)
653
654 calc_current_ = optional_default(calc_current, .true.)
655
656 call v_ks_calc_start(ks, namespace, space, hm, st, ions, hm%kpoints%latt, ext_partners, time, &
657 calc_energy, calc_current_, force_semilocal=force_semilocal)
658 call v_ks_calc_finish(ks, hm, namespace, space, hm%kpoints%latt, st, &
659 ext_partners, force_semilocal=force_semilocal)
660
661 if (optional_default(calc_eigenval, .false.)) then
662 call energy_calc_eigenvalues(namespace, hm, ks%gr%der, st)
663 end if
664
665 !Update the magnetic constrain
666 call magnetic_constrain_update(hm%magnetic_constrain, ks%gr, st%d, space, hm%kpoints%latt, ions%pos)
667
668 pop_sub(v_ks_calc)
669 end subroutine v_ks_calc
670
671 ! ---------------------------------------------------------
672
677 subroutine v_ks_calc_start(ks, namespace, space, hm, st, ions, latt, ext_partners, time, &
678 calc_energy, calc_current, force_semilocal)
679 type(v_ks_t), target, intent(inout) :: ks
680 type(namespace_t), intent(in) :: namespace
681 class(space_t), intent(in) :: space
682 type(hamiltonian_elec_t), target, intent(in) :: hm
683 type(states_elec_t), intent(inout) :: st
684 type(ions_t), intent(in) :: ions
685 type(lattice_vectors_t), intent(in) :: latt
686 type(partner_list_t), intent(in) :: ext_partners
687 real(real64), optional, intent(in) :: time
688 logical, optional, intent(in) :: calc_energy
689 logical, optional, intent(in) :: calc_current
690 logical, optional, intent(in) :: force_semilocal
691
692 logical :: calc_current_
693
694 push_sub(v_ks_calc_start)
695
696 calc_current_ = optional_default(calc_current, .true.) &
697 .and. ks%calculate_current &
698 .and. states_are_complex(st) &
700
701 call profiling_in("KOHN_SHAM_CALC")
702
703 assert(.not. ks%calc%calculating)
704 ks%calc%calculating = .true.
705
706 if (debug%info) then
707 write(message(1), '(a)') 'Debug: Calculating Kohn-Sham potential.'
708 call messages_info(1, namespace=namespace)
709 end if
710
711 ks%calc%time_present = present(time)
712 ks%calc%time = optional_default(time, m_zero)
713
714 ks%calc%calc_energy = optional_default(calc_energy, .true.)
715
716 ! If the Hxc term is frozen, there is nothing more to do (WARNING: MISSING ks%calc%energy%intnvxc)
717 if (ks%frozen_hxc) then
718 if (calc_current_) then
719 call states_elec_allocate_current(st, space, ks%gr)
720 call current_calculate(ks%current_calculator, namespace, ks%gr, hm, space, st)
721 end if
722
723 call profiling_out("KOHN_SHAM_CALC")
724 pop_sub(v_ks_calc_start)
725 return
726 end if
727
728 safe_allocate(ks%calc%energy)
729
730 call energy_copy(hm%energy, ks%calc%energy)
731
732 ks%calc%energy%intnvxc = m_zero
733
734 nullify(ks%calc%total_density)
735
736 if (ks%theory_level /= independent_particles .and. abs(ks%sic%amaldi_factor) > m_epsilon) then
737
738 call calculate_density()
739
740 if (poisson_is_async(hm%psolver)) then
741 call dpoisson_solve_start(hm%psolver, ks%calc%total_density)
742 end if
743
744 if (ks%theory_level /= hartree .and. ks%theory_level /= rdmft) call v_a_xc(hm, force_semilocal)
745 else
746 ks%calc%total_density_alloc = .false.
747 end if
748
749 if (calc_current_) then
750 call states_elec_allocate_current(st, space, ks%gr)
751 call current_calculate(ks%current_calculator, namespace, ks%gr, hm, space, st)
752 end if
753
754 nullify(ks%calc%hf_st)
755 if (ks%theory_level == hartree .or. ks%theory_level == hartree_fock &
756 .or. ks%theory_level == rdmft .or. (ks%theory_level == generalized_kohn_sham_dft &
757 .and. family_is_hybrid(ks%xc))) then
758 safe_allocate(ks%calc%hf_st)
759 call states_elec_copy(ks%calc%hf_st, st)
760
761 if (st%parallel_in_states) then
762 if (accel_is_enabled()) then
763 call messages_write('State parallelization of Hartree-Fock exchange is not supported')
764 call messages_new_line()
765 call messages_write('when running with OpenCL/CUDA. Please use domain parallelization')
766 call messages_new_line()
767 call messages_write("or disable acceleration using 'DisableAccel = yes'.")
768 call messages_fatal(namespace=namespace)
769 end if
771 end if
772 end if
773
774
775 ! Calculate the vector potential induced by the electronic current.
776 ! WARNING: calculating the self-induced magnetic field here only makes
777 ! sense if it is going to be used in the Hamiltonian, which does not happen
778 ! now. Otherwise one could just calculate it at the end of the calculation.
779 if (hm%self_induced_magnetic) then
780 safe_allocate(ks%calc%a_ind(1:ks%gr%np_part, 1:space%dim))
781 safe_allocate(ks%calc%b_ind(1:ks%gr%np_part, 1:space%dim))
782 call magnetic_induced(namespace, ks%gr, st, hm%psolver, hm%kpoints, ks%calc%a_ind, ks%calc%b_ind)
783 end if
784
785 if ((ks%has_photons) .and. (ks%calc%time_present) .and. (ks%xc_photon == 0) ) then
786 call mf_calc(ks%pt_mx, ks%gr, st, ions, ks%pt, time)
787 end if
788
789 ! if (ks%has_vibrations) then
790 ! call vibrations_eph_coup(ks%vib, ks%gr, hm, ions, st)
791 ! end if
792
793 call profiling_out("KOHN_SHAM_CALC")
794 pop_sub(v_ks_calc_start)
795
796 contains
797
798 subroutine calculate_density()
799 integer :: ip
800
802
803 ! get density taking into account non-linear core corrections
804 safe_allocate(ks%calc%density(1:ks%gr%np, 1:st%d%nspin))
805 call states_elec_total_density(st, ks%gr, ks%calc%density)
806
807 ! Amaldi correction
808 if (ks%sic%level == sic_amaldi) then
809 call lalg_scal(ks%gr%np, st%d%nspin, ks%sic%amaldi_factor, ks%calc%density)
810 end if
811
812 nullify(ks%calc%total_density)
813 if (allocated(st%rho_core) .or. hm%d%spin_channels > 1) then
814 ks%calc%total_density_alloc = .true.
815
816 safe_allocate(ks%calc%total_density(1:ks%gr%np))
817
818 do ip = 1, ks%gr%np
819 ks%calc%total_density(ip) = sum(ks%calc%density(ip, 1:hm%d%spin_channels))
820 end do
821
822 ! remove non-local core corrections
823 if (allocated(st%rho_core)) then
824 call lalg_axpy(ks%gr%np, -ks%sic%amaldi_factor, st%rho_core, ks%calc%total_density)
825 end if
826 else
827 ks%calc%total_density_alloc = .false.
828 ks%calc%total_density => ks%calc%density(:, 1)
829 end if
830
832 end subroutine calculate_density
833
834 ! ---------------------------------------------------------
835 subroutine v_a_xc(hm, force_semilocal)
836 type(hamiltonian_elec_t), intent(in) :: hm
837 logical, optional, intent(in) :: force_semilocal
838
839 integer :: ispin
840
841 push_sub(v_ks_calc_start.v_a_xc)
842 call profiling_in("XC")
843
844 ks%calc%energy%exchange = m_zero
845 ks%calc%energy%correlation = m_zero
846 ks%calc%energy%xc_j = m_zero
847 ks%calc%energy%vdw = m_zero
848
849 safe_allocate(ks%calc%vxc(1:ks%gr%np, 1:st%d%nspin))
850 ks%calc%vxc = m_zero
851
852 if (family_is_mgga_with_exc(hm%xc)) then
853 safe_allocate(ks%calc%vtau(1:ks%gr%np, 1:st%d%nspin))
854 ks%calc%vtau = m_zero
855 end if
856
857 ! Get the *local* XC term
858 if (ks%calc%calc_energy) then
859 if (family_is_mgga_with_exc(hm%xc)) then
860 call xc_get_vxc(ks%gr, ks%xc, st, hm%kpoints, hm%psolver, namespace, space, ks%calc%density, st%d%ispin, &
861 latt%rcell_volume, ks%calc%vxc, ex = ks%calc%energy%exchange, ec = ks%calc%energy%correlation, &
862 deltaxc = ks%calc%energy%delta_xc, vtau = ks%calc%vtau, force_orbitalfree=force_semilocal)
863 else
864 call xc_get_vxc(ks%gr, ks%xc, st, hm%kpoints, hm%psolver, namespace, space, ks%calc%density, st%d%ispin, &
865 latt%rcell_volume, ks%calc%vxc, ex = ks%calc%energy%exchange, ec = ks%calc%energy%correlation, &
866 deltaxc = ks%calc%energy%delta_xc, stress_xc=ks%stress_xc_gga, force_orbitalfree=force_semilocal)
867 end if
868 else
869 if (family_is_mgga_with_exc(hm%xc)) then
870 call xc_get_vxc(ks%gr, ks%xc, st, hm%kpoints, hm%psolver, namespace, space, ks%calc%density, &
871 st%d%ispin, latt%rcell_volume, ks%calc%vxc, vtau = ks%calc%vtau, force_orbitalfree=force_semilocal)
872 else
873 call xc_get_vxc(ks%gr, ks%xc, st, hm%kpoints, hm%psolver, namespace, space, ks%calc%density, &
874 st%d%ispin, latt%rcell_volume, ks%calc%vxc, stress_xc=ks%stress_xc_gga, force_orbitalfree=force_semilocal)
875 end if
876 end if
877
878 !Noncollinear functionals
879 if (bitand(hm%xc%family, xc_family_nc_lda + xc_family_nc_mgga) /= 0) then
880 if (st%d%ispin /= spinors) then
881 message(1) = "Noncollinear functionals can only be used with spinor wavefunctions."
882 call messages_fatal(1)
883 end if
884
885 if (optional_default(force_semilocal, .false.)) then
886 message(1) = "Cannot perform LCAO for noncollinear MGGAs."
887 message(2) = "Please perform a LDA calculation first."
888 call messages_fatal(2)
889 end if
890
891 if (ks%calc%calc_energy) then
892 if (family_is_mgga_with_exc(hm%xc)) then
893 call xc_get_nc_vxc(ks%gr, ks%xc, st, hm%kpoints, space, namespace, ks%calc%density, ks%calc%vxc, &
894 vtau = ks%calc%vtau, ex = ks%calc%energy%exchange, ec = ks%calc%energy%correlation)
895 else
896 call xc_get_nc_vxc(ks%gr, ks%xc, st, hm%kpoints, space, namespace, ks%calc%density, ks%calc%vxc, &
897 ex = ks%calc%energy%exchange, ec = ks%calc%energy%correlation)
898 end if
899 else
900 if (family_is_mgga_with_exc(hm%xc)) then
901 call xc_get_nc_vxc(ks%gr, ks%xc, st, hm%kpoints, space, namespace, ks%calc%density, &
902 ks%calc%vxc, vtau = ks%calc%vtau)
903 else
904 call xc_get_nc_vxc(ks%gr, ks%xc, st, hm%kpoints, space, namespace, ks%calc%density, ks%calc%vxc)
905 end if
906 end if
907 end if
908
909 if (optional_default(force_semilocal, .false.)) then
910 call profiling_out("XC")
911 pop_sub(v_ks_calc_start.v_a_xc)
912 return
913 end if
914
915 ! ADSIC correction
916 if (ks%sic%level == sic_adsic) then
917 if (family_is_mgga(hm%xc%family)) then
918 call messages_not_implemented('ADSIC with MGGAs', namespace=namespace)
919 end if
920 if (ks%calc%calc_energy) then
921 call xc_sic_calc_adsic(ks%sic, namespace, space, ks%gr, st, hm, ks%xc, ks%calc%density, &
922 ks%calc%vxc, ex = ks%calc%energy%exchange, ec = ks%calc%energy%correlation)
923 else
924 call xc_sic_calc_adsic(ks%sic, namespace, space, ks%gr, st, hm, ks%xc, ks%calc%density, &
925 ks%calc%vxc)
926 end if
927 end if
928 !PZ SIC is done in the finish routine as OEP full needs to update the Hamiltonian
929
930 if (ks%theory_level == kohn_sham_dft) then
931 ! The OEP family has to be handled specially
932 ! Note that OEP is done in the finish state, as it requires updating the Hamiltonian and needs the new Hartre and vxc term
933 if (bitand(ks%xc_family, xc_family_oep) /= 0 .or. family_is_mgga_with_exc(ks%xc)) then
934
935 if (ks%xc%functional(func_x,1)%id == xc_oep_x_slater) then
936 call x_slater_calc(namespace, ks%gr, space, hm%exxop, st, hm%kpoints, ks%calc%energy%exchange, &
937 vxc = ks%calc%vxc)
938 else if (ks%xc%functional(func_x,1)%id == xc_oep_x_fbe .or. ks%xc%functional(func_x,1)%id == xc_oep_x_fbe_sl) then
939 call x_fbe_calc(ks%xc%functional(func_x,1)%id, namespace, hm%psolver, ks%gr, st, space, &
940 ks%calc%energy%exchange, vxc = ks%calc%vxc)
941
942 else if (ks%xc%functional(func_c,1)%id == xc_lda_c_fbe_sl) then
943
944 call fbe_c_lda_sl(namespace, hm%psolver, ks%gr, st, space, &
945 ks%calc%energy%correlation, vxc = ks%calc%vxc)
946
947 else
948 if (ks%oep_photon%level /= oep_level_none) then
949 if (states_are_real(st)) then
950 call dxc_oep_photon_calc(ks%oep_photon, namespace, ks%xc, ks%gr, &
951 hm, st, space, ks%calc%energy%exchange, ks%calc%energy%correlation, vxc = ks%calc%vxc)
952 else
953 call zxc_oep_photon_calc(ks%oep_photon, namespace, ks%xc, ks%gr, &
954 hm, st, space, ks%calc%energy%exchange, ks%calc%energy%correlation, vxc = ks%calc%vxc)
955 end if
956 ks%calc%energy%photon_exchange = ks%oep_photon%pt%ex
957 end if
958 end if
959
960 end if
961
962 if (bitand(ks%xc_family, xc_family_ks_inversion) /= 0) then
963 ! Also treat KS inversion separately (not part of libxc)
964 call xc_ks_inversion_calc(ks%ks_inversion, namespace, space, ks%gr, hm, ext_partners, st, vxc = ks%calc%vxc, &
965 time = ks%calc%time)
966 end if
967
968 ! compute the photon-free photon exchange potential and energy
969 if (ks%xc_photon /= 0) then
970
971 call ks%xc_photons%v_ks(namespace, ks%calc%total_density, ks%calc%density, ks%gr, space, hm%psolver, hm%ep, st)
972
973 ! add the photon-free px potential into the xc potential
974 do ispin = 1, hm%d%spin_channels
975 call lalg_axpy(ks%gr%np, m_one, ks%xc_photons%vpx(1:ks%gr%np), ks%calc%vxc(1:ks%gr%np, ispin) )
976 end do
977
978 ! photon-exchange energy
979 ks%calc%energy%photon_exchange = ks%xc_photons%ex
980 end if
981
982 end if
983
984 call ks%vdw%calc(namespace, space, latt, ions%atom, ions%natoms, ions%pos, &
985 ks%gr, st, ks%calc%energy%vdw, ks%calc%vxc)
986
987 if (ks%calc%calc_energy) then
988 ! MGGA vtau contribution is done after copying vtau to hm%vtau
989
990 if (hm%lda_u_level /= dft_u_none) then
991 if (states_are_real(st)) then
992 ks%calc%energy%int_dft_u = denergy_calc_electronic(namespace, hm, ks%gr%der, st, terms = term_dft_u)
993 else
994 ks%calc%energy%int_dft_u = zenergy_calc_electronic(namespace, hm, ks%gr%der, st, terms = term_dft_u)
995 end if
996 end if
997 end if
998
999 call profiling_out("XC")
1000 pop_sub(v_ks_calc_start.v_a_xc)
1001 end subroutine v_a_xc
1002
1003 end subroutine v_ks_calc_start
1004 ! ---------------------------------------------------------
1005
1006 subroutine v_ks_calc_finish(ks, hm, namespace, space, latt, st, ext_partners, force_semilocal)
1007 type(v_ks_t), target, intent(inout) :: ks
1008 type(hamiltonian_elec_t), intent(inout) :: hm
1009 type(namespace_t), intent(in) :: namespace
1010 class(space_t), intent(in) :: space
1011 type(lattice_vectors_t), intent(in) :: latt
1012 type(states_elec_t), intent(inout) :: st
1013 type(partner_list_t), intent(in) :: ext_partners
1014 logical, optional, intent(in) :: force_semilocal
1015
1016 integer :: ip, ispin
1017 type(states_elec_t) :: xst
1019 real(real64) :: exx_energy
1020 real(real64) :: factor
1021
1022 push_sub(v_ks_calc_finish)
1023
1024 assert(ks%calc%calculating)
1025 ks%calc%calculating = .false.
1026
1027 if (ks%frozen_hxc) then
1028 pop_sub(v_ks_calc_finish)
1029 return
1030 end if
1031
1032 !change the pointer to the energy object
1033 safe_deallocate_a(hm%energy)
1034 call move_alloc(ks%calc%energy, hm%energy)
1035
1036 if (hm%self_induced_magnetic) then
1037 hm%a_ind(1:ks%gr%np, 1:space%dim) = ks%calc%a_ind(1:ks%gr%np, 1:space%dim)
1038 hm%b_ind(1:ks%gr%np, 1:space%dim) = ks%calc%b_ind(1:ks%gr%np, 1:space%dim)
1039
1040 safe_deallocate_a(ks%calc%a_ind)
1041 safe_deallocate_a(ks%calc%b_ind)
1042 end if
1043
1044 if (allocated(hm%v_static)) then
1045 hm%energy%intnvstatic = dmf_dotp(ks%gr, ks%calc%total_density, hm%v_static)
1046 else
1047 hm%energy%intnvstatic = m_zero
1048 end if
1049
1050 if (ks%theory_level == independent_particles .or. abs(ks%sic%amaldi_factor) <= m_epsilon) then
1051
1052 hm%vhxc = m_zero
1053 hm%energy%intnvxc = m_zero
1054 hm%energy%hartree = m_zero
1055 hm%energy%exchange = m_zero
1056 hm%energy%exchange_hf = m_zero
1057 hm%energy%correlation = m_zero
1058 else
1059
1060 hm%energy%hartree = m_zero
1061 call v_ks_hartree(namespace, ks, space, hm, ext_partners)
1062
1063 if (.not. optional_default(force_semilocal, .false.)) then
1064 !PZ-SIC
1065 if(ks%sic%level == sic_pz_oep) then
1066 if (states_are_real(st)) then
1067 call dxc_oep_calc(ks%sic%oep, namespace, ks%xc, ks%gr, hm, st, space, &
1068 latt%rcell_volume, hm%energy%exchange, hm%energy%correlation, vxc = ks%calc%vxc)
1069 else
1070 call zxc_oep_calc(ks%sic%oep, namespace, ks%xc, ks%gr, hm, st, space, &
1071 latt%rcell_volume, hm%energy%exchange, hm%energy%correlation, vxc = ks%calc%vxc)
1072 end if
1073 end if
1074
1075 ! OEP for exchange ad MGGAs (within Kohn-Sham DFT)
1076 if (ks%theory_level == kohn_sham_dft .and. ks%oep%level /= oep_level_none) then
1077 ! The OEP family has to be handled specially
1078 if (ks%xc%functional(func_x,1)%id == xc_oep_x .or. family_is_mgga_with_exc(ks%xc)) then
1079 if (states_are_real(st)) then
1080 call dxc_oep_calc(ks%oep, namespace, ks%xc, ks%gr, hm, st, space, &
1081 latt%rcell_volume, hm%energy%exchange, hm%energy%correlation, vxc = ks%calc%vxc)
1082 else
1083 call zxc_oep_calc(ks%oep, namespace, ks%xc, ks%gr, hm, st, space, &
1084 latt%rcell_volume, hm%energy%exchange, hm%energy%correlation, vxc = ks%calc%vxc)
1085 end if
1086 end if
1087 end if
1088 end if
1089
1090 if (ks%calc%calc_energy) then
1091 ! Now we calculate Int[n vxc] = energy%intnvxc
1092 hm%energy%intnvxc = m_zero
1093
1094 if (ks%theory_level /= independent_particles .and. ks%theory_level /= hartree .and. ks%theory_level /= rdmft) then
1095 do ispin = 1, hm%d%nspin
1096 if (ispin <= 2) then
1097 factor = m_one
1098 else
1099 factor = m_two
1100 end if
1101 hm%energy%intnvxc = hm%energy%intnvxc + &
1102 factor*dmf_dotp(ks%gr, st%rho(:, ispin), ks%calc%vxc(:, ispin), reduce = .false.)
1103 end do
1104 if (ks%gr%parallel_in_domains) call ks%gr%allreduce(hm%energy%intnvxc)
1105 end if
1106 end if
1107
1108
1109 if (ks%theory_level /= hartree .and. ks%theory_level /= rdmft) then
1110 ! move allocation of vxc from ks%calc to hm
1111 safe_deallocate_a(hm%vxc)
1112 call move_alloc(ks%calc%vxc, hm%vxc)
1113
1114 if (family_is_mgga_with_exc(hm%xc)) then
1115 call lalg_copy(ks%gr%np, hm%d%nspin, ks%calc%vtau, hm%vtau)
1116 call hm%hm_base%accel_copy_pot(ks%gr, hm%vtau)
1117 safe_deallocate_a(ks%calc%vtau)
1118
1119 ! We need to evaluate the energy after copying vtau to hm%vtau
1120 if (ks%theory_level == generalized_kohn_sham_dft .and. ks%calc%calc_energy) then
1121 ! MGGA vtau contribution
1122 if (states_are_real(st)) then
1123 hm%energy%intnvxc = hm%energy%intnvxc &
1124 + denergy_calc_electronic(namespace, hm, ks%gr%der, st, terms = term_mgga)
1125 else
1126 hm%energy%intnvxc = hm%energy%intnvxc &
1127 + zenergy_calc_electronic(namespace, hm, ks%gr%der, st, terms = term_mgga)
1128 end if
1129 end if
1130 end if
1131
1132 else
1133 hm%vxc = m_zero
1134 end if
1135
1136 if (.not. ks%xc_photon_include_hartree) then
1137 hm%energy%hartree = m_zero
1138 hm%vhartree = m_zero
1139 end if
1140
1141 ! Build Hartree + XC potential
1142
1143 do ip = 1, ks%gr%np
1144 hm%vhxc(ip, 1) = hm%vxc(ip, 1) + hm%vhartree(ip)
1145 end do
1146 if (allocated(hm%vberry)) then
1147 do ip = 1, ks%gr%np
1148 hm%vhxc(ip, 1) = hm%vhxc(ip, 1) + hm%vberry(ip, 1)
1149 end do
1150 end if
1151
1152 if (hm%d%ispin > unpolarized) then
1153 do ip = 1, ks%gr%np
1154 hm%vhxc(ip, 2) = hm%vxc(ip, 2) + hm%vhartree(ip)
1155 end do
1156 if (allocated(hm%vberry)) then
1157 do ip = 1, ks%gr%np
1158 hm%vhxc(ip, 2) = hm%vhxc(ip, 2) + hm%vberry(ip, 2)
1159 end do
1160 end if
1161 end if
1162
1163 if (hm%d%ispin == spinors) then
1164 do ispin=3, 4
1165 do ip = 1, ks%gr%np
1166 hm%vhxc(ip, ispin) = hm%vxc(ip, ispin)
1167 end do
1168 end do
1169 end if
1170
1171 ! Note: this includes hybrids calculated with the Fock operator instead of OEP
1172 hm%energy%exchange_hf = m_zero
1173 if ((ks%theory_level == hartree .or. ks%theory_level == hartree_fock &
1174 .or. ks%theory_level == rdmft .or. ks%theory_level == generalized_kohn_sham_dft)) then
1175
1176 ! swap the states object
1177 if (associated(hm%exxop%st)) then
1178 if (hm%exxop%st%parallel_in_states) call states_elec_parallel_remote_access_stop(hm%exxop%st)
1179 call states_elec_end(hm%exxop%st)
1180 safe_deallocate_p(hm%exxop%st)
1181 end if
1182 if (associated(ks%calc%hf_st) .and. hm%exxop%useACE) then
1183 if (ks%calc%hf_st%parallel_in_states) call states_elec_parallel_remote_access_stop(ks%calc%hf_st)
1184 end if
1185
1186 !At the moment this block is called before the reinit call. This way the LCAO does not call the
1187 !exchange operator.
1188 !This should be changed and the CAM parameters should also be obtained from the restart information
1189 !Maybe the parameters should be mixed too.
1190 exx_energy = m_zero
1191 if (.not. optional_default(force_semilocal, .false.)) then
1192 if ((ks%theory_level == hartree_fock .or. ks%theory_level == rdmft &
1193 .or. (ks%theory_level == generalized_kohn_sham_dft &
1194 .and. family_is_hybrid(ks%xc))) .and. hm%exxop%useACE) then
1195 call xst%nullify()
1196 if (states_are_real(ks%calc%hf_st)) then
1197 call dexchange_operator_compute_potentials(hm%exxop, namespace, space, ks%gr, &
1198 ks%calc%hf_st, xst, hm%kpoints, exx_energy)
1199 call dexchange_operator_ace(hm%exxop, namespace, ks%gr, ks%calc%hf_st, xst)
1200 else
1201 call zexchange_operator_compute_potentials(hm%exxop, namespace, space, ks%gr, &
1202 ks%calc%hf_st, xst, hm%kpoints, exx_energy)
1203 if (hm%phase%is_allocated()) then
1204 call zexchange_operator_ace(hm%exxop, namespace, ks%gr, ks%calc%hf_st, xst, hm%phase)
1205 else
1206 call zexchange_operator_ace(hm%exxop, namespace, ks%gr, ks%calc%hf_st, xst)
1207 end if
1208 end if
1209 call states_elec_end(xst)
1210 exx_energy = exx_energy + hm%exxop%singul%energy
1211 end if
1212 end if
1213
1214 select case (ks%theory_level)
1216 if (family_is_hybrid(ks%xc)) then
1217 ! Add the energy only the ACE case. In the non-ACE case, the exchange energy is not correct
1218 hm%energy%exchange_hf = hm%energy%exchange_hf + exx_energy
1219 call exchange_operator_reinit(hm%exxop, ks%xc%cam_omega, ks%xc%cam_alpha, ks%xc%cam_beta, ks%calc%hf_st)
1220 end if
1221 case (hartree_fock)
1222 ! Add the energy only the ACE case. In the non-ACE case, the exchange energy is not correct
1223 hm%energy%exchange_hf = hm%energy%exchange_hf + exx_energy
1224 call exchange_operator_reinit(hm%exxop, ks%xc%cam_omega, ks%xc%cam_alpha, ks%xc%cam_beta, ks%calc%hf_st)
1225 case (hartree)
1226 call exchange_operator_reinit(hm%exxop, m_zero, m_one, m_zero, ks%calc%hf_st)
1227 case (rdmft)
1228 call exchange_operator_reinit(hm%exxop, m_zero, m_one, m_zero, ks%calc%hf_st)
1229 end select
1230 end if
1231
1232 end if
1233
1234 ! Because of the intent(in) in v_ks_calc_start, we need to update the parameters of hybrids for OEP
1235 ! here
1236 if (ks%theory_level == kohn_sham_dft .and. bitand(ks%xc_family, xc_family_oep) /= 0) then
1237 if (ks%xc%functional(func_x,1)%id /= xc_oep_x_slater .and. ks%xc%functional(func_x,1)%id /= xc_oep_x_fbe) then
1238 call exchange_operator_reinit(hm%exxop, ks%xc%cam_omega, ks%xc%cam_alpha, ks%xc%cam_beta)
1239 end if
1240 end if
1241
1242 if (ks%has_photons .and. (ks%xc_photon == 0)) then
1243 if (associated(ks%pt_mx%vmf)) then
1244 forall(ip = 1:ks%gr%np) hm%vhxc(ip, 1) = hm%vhxc(ip, 1) + ks%pt_mx%vmf(ip)
1245 if (hm%d%ispin > unpolarized) then
1246 forall(ip = 1:ks%gr%np) hm%vhxc(ip, 2) = hm%vhxc(ip, 2) + ks%pt_mx%vmf(ip)
1247 end if
1248 end if
1249 hm%ep%photon_forces(1:space%dim) = ks%pt_mx%fmf(1:space%dim)
1250 end if
1251
1252 if (ks%vdw%vdw_correction /= option__vdwcorrection__none) then
1253 hm%ep%vdw_forces = ks%vdw%forces
1254 hm%ep%vdw_stress = ks%vdw%stress
1255 safe_deallocate_a(ks%vdw%forces)
1256 else
1257 hm%ep%vdw_forces = 0.0_real64
1258 end if
1259
1260 if (ks%calc%time_present .or. hm%time_zero) then
1261 call hm%update(ks%gr, namespace, space, ext_partners, time = ks%calc%time)
1262 else
1263 call hamiltonian_elec_update_pot(hm, ks%gr)
1264 end if
1265
1266
1267 safe_deallocate_a(ks%calc%density)
1268 if (ks%calc%total_density_alloc) then
1269 safe_deallocate_p(ks%calc%total_density)
1270 end if
1271 nullify(ks%calc%total_density)
1272
1273 pop_sub(v_ks_calc_finish)
1274 end subroutine v_ks_calc_finish
1275
1276 ! ---------------------------------------------------------
1277 !
1281 !
1282 subroutine v_ks_hartree(namespace, ks, space, hm, ext_partners)
1283 type(namespace_t), intent(in) :: namespace
1284 type(v_ks_t), intent(inout) :: ks
1285 class(space_t), intent(in) :: space
1286 type(hamiltonian_elec_t), intent(inout) :: hm
1287 type(partner_list_t), intent(in) :: ext_partners
1288
1289 push_sub(v_ks_hartree)
1290
1291 if (.not. poisson_is_async(hm%psolver)) then
1292 ! solve the Poisson equation
1293 call dpoisson_solve(hm%psolver, namespace, hm%vhartree, ks%calc%total_density)
1294 else
1295 ! The calculation was started by v_ks_calc_start.
1296 call dpoisson_solve_finish(hm%psolver, hm%vhartree)
1297 end if
1298
1299 if (ks%calc%calc_energy) then
1300 ! Get the Hartree energy
1301 hm%energy%hartree = m_half*dmf_dotp(ks%gr, ks%calc%total_density, hm%vhartree)
1302 end if
1303
1305 if(ks%calc%time_present) then
1306 if(hamiltonian_elec_has_kick(hm)) then
1307 call pcm_hartree_potential(hm%pcm, space, ks%gr, hm%psolver, ext_partners, hm%vhartree, &
1308 ks%calc%total_density, hm%energy%pcm_corr, kick=hm%kick, time=ks%calc%time)
1309 else
1310 call pcm_hartree_potential(hm%pcm, space, ks%gr, hm%psolver, ext_partners, hm%vhartree, &
1311 ks%calc%total_density, hm%energy%pcm_corr, time=ks%calc%time)
1312 end if
1313 else
1314 if(hamiltonian_elec_has_kick(hm)) then
1315 call pcm_hartree_potential(hm%pcm, space, ks%gr, hm%psolver, ext_partners, hm%vhartree, &
1316 ks%calc%total_density, hm%energy%pcm_corr, kick=hm%kick)
1317 else
1318 call pcm_hartree_potential(hm%pcm, space, ks%gr, hm%psolver, ext_partners, hm%vhartree, &
1319 ks%calc%total_density, hm%energy%pcm_corr)
1320 end if
1321 end if
1322
1323 pop_sub(v_ks_hartree)
1324 end subroutine v_ks_hartree
1325 ! ---------------------------------------------------------
1326
1327
1328 ! ---------------------------------------------------------
1329 subroutine v_ks_freeze_hxc(ks)
1330 type(v_ks_t), intent(inout) :: ks
1331
1332 push_sub(v_ks_freeze_hxc)
1333
1334 ks%frozen_hxc = .true.
1335
1336 pop_sub(v_ks_freeze_hxc)
1337 end subroutine v_ks_freeze_hxc
1338 ! ---------------------------------------------------------
1339
1340 subroutine v_ks_calculate_current(this, calc_cur)
1341 type(v_ks_t), intent(inout) :: this
1342 logical, intent(in) :: calc_cur
1343
1344 push_sub(v_ks_calculate_current)
1345
1346 this%calculate_current = calc_cur
1347
1348 pop_sub(v_ks_calculate_current)
1349 end subroutine v_ks_calculate_current
1350
1351end module v_ks_oct_m
1352
1353!! Local Variables:
1354!! mode: f90
1355!! coding: utf-8
1356!! End:
constant times a vector plus a vector
Definition: lalg_basic.F90:170
Copies a vector x, to a vector y.
Definition: lalg_basic.F90:185
scales a vector by a constant
Definition: lalg_basic.F90:156
This is the common interface to a sorting routine. It performs the shell algorithm,...
Definition: sort.F90:149
pure logical function, public accel_is_enabled()
Definition: accel.F90:400
subroutine, public current_calculate(this, namespace, gr, hm, space, st)
Compute total electronic current density.
Definition: current.F90:367
subroutine, public current_init(this, namespace)
Definition: current.F90:177
type(debug_t), save, public debug
Definition: debug.F90:151
This module implements a calculator for the density and defines related functions.
Definition: density.F90:120
subroutine, public states_elec_total_density(st, mesh, total_rho)
This routine calculates the total electronic density.
Definition: density.F90:849
subroutine, public density_calc(st, gr, density, istin)
Computes the density from the orbitals in st.
Definition: density.F90:608
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)
Definition: energy.F90:167
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
Definition: global.F90:189
real(real64), parameter, public m_zero
Definition: global.F90:187
real(real64), parameter, public m_epsilon
Definition: global.F90:203
real(real64), parameter, public m_half
Definition: global.F90:193
real(real64), parameter, public m_one
Definition: global.F90:188
This module implements the underlying real-space grid.
Definition: grid.F90:117
integer, parameter, public term_mgga
integer, parameter, public term_dft_u
integer, parameter, public generalized_kohn_sham_dft
integer, parameter, public rdmft
integer, parameter, public hartree
logical function, public hamiltonian_elec_has_kick(hm)
integer, parameter, public hartree_fock
integer, parameter, public independent_particles
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.
integer, parameter, public kohn_sham_dft
This module defines classes and functions for interaction partners.
integer, parameter, public dft_u_none
Definition: lda_u.F90:200
subroutine, public magnetic_constrain_update(this, mesh, std, space, latt, pos)
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...
Definition: magnetic.F90:381
This module defines various routines, operating on mesh functions.
This module defines the meshes, which are used in Octopus.
Definition: mesh.F90:118
subroutine, public messages_print_with_emphasis(msg, iunit, namespace)
Definition: messages.F90:930
subroutine, public messages_not_implemented(feature, namespace)
Definition: messages.F90:1125
character(len=512), private msg
Definition: messages.F90:165
subroutine, public messages_warning(no_lines, all_nodes, namespace)
Definition: messages.F90:543
subroutine, public messages_obsolete_variable(namespace, name, rep)
Definition: messages.F90:1057
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
Definition: messages.F90:624
subroutine, public messages_new_line()
Definition: messages.F90:1146
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
Definition: messages.F90:420
subroutine, public messages_input_error(namespace, var, details, row, column)
Definition: messages.F90:723
subroutine, public messages_experimental(name, namespace)
Definition: messages.F90:1097
This module handles the communicators for the various parallelization strategies.
Definition: multicomm.F90:145
logical function, public parse_is_defined(namespace, name)
Definition: parser.F90:502
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)
Definition: poisson.F90:2338
subroutine, public dpoisson_solve_finish(this, pot)
Definition: poisson.F90:2361
subroutine, public dpoisson_solve(this, namespace, pot, rho, all_nodes, kernel)
Calculates the Poisson equation. Given the density returns the corresponding potential.
Definition: poisson.F90:913
logical pure function, public poisson_is_async(this)
Definition: poisson.F90:1467
subroutine, public profiling_out(label)
Increment out counter and sum up difference between entry and exit time.
Definition: profiling.F90:623
subroutine, public profiling_in(label, exclude)
Increment in counter and save entry time.
Definition: profiling.F90:552
integer, parameter, public pseudo_exchange_unknown
Definition: pseudo.F90:188
integer, parameter, public pseudo_correlation_unknown
Definition: pseudo.F90:192
integer, parameter, public pseudo_correlation_any
Definition: pseudo.F90:192
integer, parameter, public pseudo_exchange_any
Definition: pseudo.F90:188
This module is intended to contain "only mathematical" functions and procedures.
Definition: sort.F90:117
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...
Definition: v_ks.F90:1376
subroutine, public v_ks_calc_finish(ks, hm, namespace, space, latt, st, ext_partners, force_semilocal)
Definition: v_ks.F90:1100
subroutine, public v_ks_freeze_hxc(ks)
Definition: v_ks.F90:1423
subroutine, public v_ks_end(ks)
Definition: v_ks.F90:610
subroutine, public v_ks_calculate_current(this, calc_cur)
Definition: v_ks.F90:1434
subroutine, public v_ks_write_info(ks, iunit, namespace)
Definition: v_ks.F90:642
subroutine, public v_ks_calc_start(ks, namespace, space, hm, st, ions, latt, ext_partners, time, calc_energy, calc_current, force_semilocal)
This routine starts the calculation of the Kohn-Sham potential. The routine v_ks_calc_finish must be ...
Definition: v_ks.F90:772
subroutine, public v_ks_calc(ks, namespace, space, hm, st, ions, ext_partners, calc_eigenval, time, calc_energy, calc_current, force_semilocal)
Definition: v_ks.F90:730
subroutine, public v_ks_h_setup(namespace, space, gr, ions, ext_partners, st, ks, hm, calc_eigenval, calc_current)
Definition: v_ks.F90:677
subroutine, public v_ks_init(ks, namespace, gr, st, ions, mc, space, kpoints)
Definition: v_ks.F90:243
subroutine, public x_slater_calc(namespace, gr, space, exxop, st, kpoints, ex, vxc)
Interface to X(slater_calc)
Definition: x_slater.F90:145
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....
Definition: xc_fbe.F90:165
subroutine, public fbe_c_lda_sl(namespace, psolver, gr, st, space, ec, vxc)
Sturm-Liouville version of the FBE local-density correlation functional.
Definition: xc_fbe.F90:431
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 libxc_c_index
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)
Definition: xc.F90:114
subroutine, public xc_write_info(xcs, iunit, namespace)
Definition: xc.F90:216
subroutine, public xc_init(xcs, namespace, ndim, periodic_dim, nel, x_id, c_id, xk_id, ck_id, hartree_fock, ispin)
Definition: xc.F90:246
pure logical function, public family_is_mgga(family, only_collinear)
Is the xc function part of the mGGA family.
Definition: xc.F90:563
logical pure function, public family_is_mgga_with_exc(xcs)
Is the xc function part of the mGGA family with an energy functional.
Definition: xc.F90:576
subroutine, public xc_end(xcs)
Definition: xc.F90:502
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)
Definition: xc.F90:737
logical pure function, public family_is_hybrid(xcs)
Returns true if the functional is an hybrid functional.
Definition: xc.F90:591
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...
Definition: xc.F90:2395
integer, parameter, public oep_type_mgga
Definition: xc_oep.F90:184
integer, parameter, public oep_level_none
the OEP levels
Definition: xc_oep.F90:172
subroutine, public xc_oep_end(oep)
Definition: xc_oep.F90:356
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....
Definition: xc_oep.F90:2263
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....
Definition: xc_oep.F90:1431
subroutine, public xc_oep_write_info(oep, iunit, namespace)
Definition: xc_oep.F90:378
integer, parameter, public oep_type_exx
The different types of OEP that we can work with.
Definition: xc_oep.F90:184
subroutine, public xc_oep_init(oep, namespace, gr, st, mc, space, oep_type)
Definition: xc_oep.F90:217
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.
Definition: xc_photons.F90:121
integer, parameter, public sic_none
no self-interaction correction
Definition: xc_sic.F90:148
subroutine, public xc_sic_write_info(sic, iunit, namespace)
Definition: xc_sic.F90:251
integer, parameter, public sic_adsic
Averaged density SIC.
Definition: xc_sic.F90:148
subroutine, public xc_sic_init(sic, namespace, gr, st, mc, space)
initialize the SIC object
Definition: xc_sic.F90:168
subroutine, public xc_sic_end(sic)
finalize the SIC and, if needed, the included OEP
Definition: xc_sic.F90:237
integer, parameter, public sic_pz_oep
Perdew-Zunger SIC (OEP way)
Definition: xc_sic.F90:148
integer, parameter, public sic_amaldi
Amaldi correction term.
Definition: xc_sic.F90:148
subroutine, public xc_sic_calc_adsic(sic, namespace, space, gr, st, hm, xc, density, vxc, ex, ec)
Computes the ADSIC potential and energy.
Definition: xc_sic.F90:282
A module that takes care of xc contribution from vdW interactions.
Definition: xc_vdw.F90:116
Extension of space that contains the knowledge of the spin dimension.
Description of the grid, containing information on derivatives, stencil, and symmetries.
Definition: grid.F90:168
The states_elec_t class contains all electronic wave functions.
int true(void)
subroutine get_functional_from_pseudos(x_functional, c_functional)
Definition: v_ks.F90:553
subroutine v_a_xc(hm, force_semilocal)
Definition: v_ks.F90:929
subroutine calculate_density()
Definition: v_ks.F90:892