Octopus
xc_functional.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
22 use debug_oct_m
23 use global_oct_m
27 use parser_oct_m
28 use pseudo_oct_m
29 use xc_f03_lib_m
30
31 implicit none
32
33 ! Although the following file only contain comments, we include it here to make sure it exists.
34 ! Otherwise the code might compile, but not run properly, as the variables documentations
35 ! will be incomplete.
36#include "functionals_list.F90"
37
38 private
39 public :: &
45
46
49 integer, public, parameter :: &
50 XC_OEP_X = 901, & !< Exact exchange
51 xc_oep_x_slater = 902, &
52 xc_oep_x_fbe = 903, &
53 xc_ks_inversion = 904, &
54 xc_rdmft_xc_m = 905, &
55 xc_oep_x_fbe_sl = 906, &
56 xc_lda_c_fbe = 907, &
57 xc_lda_c_fbe_sl = 908, &
58 xc_half_hartree = 917, &
59 xc_vdw_c_vdwdf = 918, &
60 xc_vdw_c_vdwdf2 = 919, &
61 xc_vdw_c_vdwdfcx = 920, &
64 xc_mgga_x_nc_br = 923, &
65 xc_mgga_x_nc_br_1 = 924, &
66 xc_mgga_c_nc_cs = 925
67
70 integer, public, parameter :: &
71 XC_FAMILY_KS_INVERSION = 1024, &
72 xc_family_rdmft = 2048, &
73 xc_family_libvdwxc = 4096, &
74 xc_family_nc_lda = 8192, &
75 xc_family_nc_mgga = 16384
76
78 ! Components are public by default
79 integer :: family = 0
80 integer :: type = 0
81 integer :: id = 0
82
83 integer :: spin_channels = 0
84 integer :: flags = 0
85
86 type(xc_f03_func_t) :: conf
87 type(xc_f03_func_info_t), private :: info
88 type(libvdwxc_t) :: libvdwxc
89 end type xc_functional_t
90
91 integer, public, parameter :: LIBXC_C_INDEX = 1000
92
93contains
94
95 ! ---------------------------------------------------------
96 subroutine xc_functional_init(functl, namespace, id, ndim, nel, spin_channels)
97 type(xc_functional_t), intent(inout) :: functl
98 type(namespace_t), intent(in) :: namespace
99 integer, intent(in) :: id
100 integer, intent(in) :: ndim
101 real(real64), intent(in) :: nel
102 integer, intent(in) :: spin_channels
103
104 integer :: interact_1d
105 real(real64) :: alpha, parameters(2)
106 logical :: ok
107
108 push_sub(xc_functional_init)
109
110 ! initialize structure
111 functl%id = id
112 functl%spin_channels = spin_channels
113
114 if (functl%id == 0) then
115 functl%family = xc_family_none
116 else
117 ! get the family of the functional
118 functl%family = xc_f03_family_from_id(functl%id)
119 ! this also ensures it is actually a functional defined by the linked version of libxc
120
121 if (functl%family == xc_family_unknown) then
122
123 select case (functl%id)
125 functl%family = xc_family_oep
126
127 case (xc_lda_c_fbe)
128 functl%family = xc_family_lda
129
130 case (xc_ks_inversion)
131 functl%family = xc_family_ks_inversion
132
133 case (xc_half_hartree)
134 call messages_experimental("half-Hartree exchange", namespace=namespace)
135 functl%family = xc_family_lda ! XXX not really
136
138 functl%family = xc_family_libvdwxc
139 !functl%flags = functl%flags + XC_FLAGS_HAVE_VXC + XC_FLAGS_HAVE_EXC
140
141 case (xc_rdmft_xc_m)
142 functl%family = xc_family_rdmft
143
145 functl%family = xc_family_hyb_gga
146
148 functl%family = xc_family_nc_mgga
149
150 case default
151 call messages_input_error(namespace, 'XCFunctional', 'Unknown functional')
152
153 end select
154 end if
155 end if
156
157 if (functl%family == xc_family_oep) then
158 functl%type = xc_exchange
159
160 else if (functl%family == xc_family_ks_inversion .or. functl%family == xc_family_rdmft) then
161 functl%type = xc_exchange_correlation
162
163 else if (functl%family == xc_family_libvdwxc) then
164 call xc_f03_func_init(functl%conf, xc_lda_c_pw, spin_channels)
165 functl%info = xc_f03_func_get_info(functl%conf)
166 functl%type = xc_f03_func_info_get_kind(functl%info)
167 functl%flags = xc_f03_func_info_get_flags(functl%info)
168 ! Convert Octopus code for functional into corresponding libvdwxc code:
169 call libvdwxc_init(functl%libvdwxc, namespace, functl%id - xc_vdw_c_vdwdf + 1)
170
171 else if (functl%id == xc_half_hartree) then
172 functl%type = xc_exchange_correlation
173
174 else if(functl%id == xc_lda_c_fbe) then
175 functl%type = xc_correlation
176 functl%flags = xc_flags_have_exc + xc_flags_have_vxc
177
178 else if (functl%id == xc_mgga_x_nc_br .or. functl%id == xc_mgga_x_nc_br_1) then
179 functl%type = xc_exchange
180 functl%flags = xc_flags_have_vxc + xc_flags_have_exc
181
182 else if(functl%id == xc_mgga_c_nc_cs) then
183 functl%type = xc_correlation
184 functl%flags = xc_flags_have_vxc + xc_flags_have_exc
185
186 else if (functl%family == xc_family_none) then
187 functl%type = -1
188 functl%flags = 0
189
190 else ! handled by libxc
191 ! initialize
192
193 !For the two MVORB functionals, we initialize libxc with the non-MVORB functionals
194 select case (functl%id)
196 call xc_f03_func_init(functl%conf, xc_hyb_gga_xc_hse06, spin_channels)
197
199 call xc_f03_func_init(functl%conf, xc_hyb_gga_xc_pbeh, spin_channels)
200
201 case default
202 call xc_f03_func_init(functl%conf, functl%id, spin_channels)
203 end select
204 functl%info = xc_f03_func_get_info(functl%conf)
205 functl%type = xc_f03_func_info_get_kind(functl%info)
206 functl%flags = xc_f03_func_info_get_flags(functl%info)
207
208 ! FIXME: no need to say this for kernel
209 if (bitand(functl%flags, xc_flags_have_exc) == 0) then
210 message(1) = 'Specified functional does not have total energy available.'
211 message(2) = 'Corresponding component of energy will just be left as zero.'
212 call messages_warning(2, namespace=namespace)
213 end if
214
215 if (bitand(functl%flags, xc_flags_have_vxc) == 0) then
216 message(1) = 'Specified functional does not have XC potential available.'
217 message(2) = 'Cannot run calculations. Choose another XCFunctional.'
218 call messages_fatal(2, namespace=namespace)
219 end if
220
221 ok = bitand(functl%flags, xc_flags_1d) /= 0
222 if ((ndim /= 1) .and. ok) then
223 message(1) = 'Specified functional is only allowed in 1D.'
224 call messages_fatal(1, namespace=namespace)
225 end if
226 if (ndim == 1 .and. (.not. ok)) then
227 message(1) = 'Cannot use the specified functionals in 1D.'
228 call messages_fatal(1, namespace=namespace)
229 end if
230
231 ok = bitand(functl%flags, xc_flags_2d) /= 0
232 if ((ndim /= 2) .and. ok) then
233 message(1) = 'Specified functional is only allowed in 2D.'
234 call messages_fatal(1, namespace=namespace)
235 end if
236 if (ndim == 2 .and. (.not. ok)) then
237 message(1) = 'Cannot use the specified functionals in 2D.'
238 call messages_fatal(1, namespace=namespace)
239 end if
240
241 ok = bitand(functl%flags, xc_flags_3d) /= 0
242 if ((ndim /= 3) .and. ok) then
243 message(1) = 'Specified functional is only allowed in 3D.'
244 call messages_fatal(1, namespace=namespace)
245 end if
246 if (ndim == 3 .and. (.not. ok)) then
247 message(1) = 'Cannot use the specified functionals in 3D.'
248 call messages_fatal(1, namespace=namespace)
249 end if
250 end if
251
252! XC_NON_RELATIVISTIC = 0
253! XC_RELATIVISTIC = 1
254
255 ! FIXME: aren`t there other parameters that can or should be set?
256 ! special parameters that have to be configured
257 select case (functl%id)
258 ! FIXME: aren`t there other Xalpha functionals?
259 case (xc_lda_c_xalpha)
260
261 !%Variable Xalpha
262 !%Type float
263 !%Default 1.0
264 !%Section Hamiltonian::XC
265 !%Description
266 !% The parameter of the Slater X<math>\alpha</math> functional. Applies only for
267 !% <tt>XCFunctional = xc_lda_c_xalpha</tt>.
268 !%End
269 call parse_variable(namespace, 'Xalpha', m_one, parameters(1))
270
271 call xc_f03_func_set_ext_params(functl%conf, parameters(1))
272
273 ! FIXME: doesn`t this apply to other 1D functionals?
274 case (xc_lda_x_1d_soft, xc_lda_c_1d_csc)
275 !%Variable Interaction1D
276 !%Type integer
277 !%Default interaction_soft_coulomb
278 !%Section Hamiltonian::XC
279 !%Description
280 !% When running in 1D, one has to soften the Coulomb interaction. This softening
281 !% is not unique, and several possibilities exist in the literature.
282 !%Option interaction_exp_screened 0
283 !% Exponentially screened Coulomb interaction.
284 !% See, <i>e.g.</i>, M Casula, S Sorella, and G Senatore, <i>Phys. Rev. B</i> <b>74</b>, 245427 (2006).
285 !%Option interaction_soft_coulomb 1
286 !% Soft Coulomb interaction of the form <math>1/\sqrt{x^2 + \alpha^2}</math>.
287 !%End
288 call messages_obsolete_variable(namespace, 'SoftInteraction1D_alpha', 'Interaction1D')
289 call parse_variable(namespace, 'Interaction1D', option__interaction1d__interaction_soft_coulomb, interact_1d)
290
291 !%Variable Interaction1DScreening
292 !%Type float
293 !%Default 1.0
294 !%Section Hamiltonian::XC
295 !%Description
296 !% Defines the screening parameter <math>\alpha</math> of the softened Coulomb interaction
297 !% when running in 1D.
298 !%End
299 call messages_obsolete_variable(namespace, 'SoftInteraction1D_alpha', 'Interaction1DScreening')
300 call parse_variable(namespace, 'Interaction1DScreening', m_one, alpha)
301 parameters(1) = real(interact_1d, real64)
302 parameters(2) = alpha
303 call xc_f03_func_set_ext_params(functl%conf, parameters(1))
304
305 case (xc_lda_c_2d_prm)
306 parameters(1) = nel
307 call xc_f03_func_set_ext_params(functl%conf, parameters(1))
308
309 case (xc_gga_x_lb)
310 if (parse_is_defined(namespace, 'LB94_modified')) then
311 call messages_obsolete_variable(namespace, 'LB94_modified')
312 end if
313
314 if (parse_is_defined(namespace, 'LB94_threshold')) then
315 call messages_obsolete_variable(namespace, 'LB94_threshold')
316 end if
317 end select
318
319 pop_sub(xc_functional_init)
320 end subroutine xc_functional_init
321
322
323 ! ---------------------------------------------------------
324 subroutine xc_functional_end(functl)
325 type(xc_functional_t), intent(inout) :: functl
326
327 push_sub(xc_functional_end)
328
329 if (functl%family /= xc_family_none .and. functl%family /= xc_family_oep .and. &
330 functl%family /= xc_family_ks_inversion .and. functl%id /= xc_half_hartree &
331 .and. functl%id /= xc_lda_c_fbe &
332 .and. functl%family /= xc_family_nc_lda .and. functl%family /= xc_family_nc_mgga) then
333 call xc_f03_func_end(functl%conf)
334 end if
335
336 if (functl%family == xc_family_libvdwxc) then
337 call libvdwxc_end(functl%libvdwxc)
338 end if
339
340 pop_sub(xc_functional_end)
341 end subroutine xc_functional_end
342
343
344 ! ---------------------------------------------------------
345 subroutine xc_functional_write_info(functl, iunit, namespace)
346 type(xc_functional_t), intent(in) :: functl
347 integer, optional, intent(in) :: iunit
348 type(namespace_t), optional, intent(in) :: namespace
349
350 character(len=120) :: family
351 integer :: ii
352
354
355 if (functl%family == xc_family_oep) then
356 ! this is handled separately
357
358 select case (functl%id)
359 case (xc_oep_x)
360 write(message(1), '(2x,a)') 'Exchange'
361 write(message(2), '(4x,a)') 'Exact exchange'
362 call messages_info(2, iunit=iunit, namespace=namespace)
363
364 case(xc_oep_x_slater)
365 write(message(1), '(2x,a)') 'Exchange'
366 write(message(2), '(4x,a)') 'Slater exchange'
367 call messages_info(2, iunit=iunit, namespace=namespace)
368
369 case (xc_oep_x_fbe)
370 write(message(1), '(2x,a)') 'Exchange'
371 write(message(2), '(4x,a)') 'Force-based local exchange'
372 write(message(3), '(4x,a)') '[1] Tancogne-Dejean et al., J. Chem. Phys. 160, 024103 (2024)'
373 call messages_info(3, iunit=iunit, namespace=namespace)
374
375 case (xc_oep_x_fbe_sl)
376 write(message(1), '(2x,a)') 'Exchange'
377 write(message(2), '(4x,a)') 'Force-based local exchange - Sturm-Liouville'
378 call messages_info(2, iunit=iunit, namespace=namespace)
379
380 case (xc_lda_c_fbe_sl)
381 write(message(1), '(2x,a)') 'Correlation'
382 write(message(2), '(4x,a)') 'Force-based local-density correlation - Sturm-Liouville'
383 call messages_info(2, iunit=iunit, namespace=namespace)
384
385 case default
386 assert(.false.)
387 end select
388
389 else if (functl%family == xc_family_ks_inversion) then
390 ! this is handled separately
391 select case (functl%id)
392 case (xc_ks_inversion)
393 write(message(1), '(2x,a)') 'Exchange-Correlation:'
394 write(message(2), '(4x,a)') ' KS Inversion'
395 call messages_info(2, iunit=iunit, namespace=namespace)
396 end select
397
398 else if (functl%family == xc_family_libvdwxc) then
399 call libvdwxc_write_info(functl%libvdwxc, iunit=iunit)
400
401 else if (functl%id == xc_mgga_x_nc_br) then
402 write(message(1), '(2x,a)') 'Exchange'
403 write(message(2), '(4x,a)') 'Noncollinear Becke-Roussel (MGGA)'
404 write(message(3), '(4x,a)') '[1] N. Tancogne-Dejean, A. Rubio, and C. A. Ullrich, Phys. Rev. B 107, 165111 (2023)'
405 call messages_info(3, iunit)
406
407 else if (functl%id == xc_mgga_x_nc_br_1) then
408 write(message(1), '(2x,a)') 'Exchange'
409 write(message(2), '(4x,a)') 'Noncollinear Becke-Roussel, gamma = 1.0 (MGGA)'
410 write(message(3), '(4x,a)') '[1] N. Tancogne-Dejean, A. Rubio, and C. A. Ullrich, Phys. Rev. B 107, 165111 (2023)'
411 call messages_info(3, iunit)
412
413 else if (functl%id == xc_mgga_c_nc_cs) then
414 write(message(1), '(2x,a)') 'Correlation'
415 write(message(2), '(4x,a)') 'Noncollinear Colle-Salvetti (MGGA)'
416 write(message(3), '(4x,a)') '[1] N. Tancogne-Dejean, A. Rubio, and C. A. Ullrich, Phys. Rev. B 107, 165111 (2023)'
417 call messages_info(3, iunit)
418
419
420 else if (functl%id == xc_half_hartree) then
421 write(message(1), '(2x,a)') 'Exchange-Correlation:'
422 write(message(2), '(4x,a)') 'Half-Hartree two-electron exchange'
423 call messages_info(2, iunit=iunit, namespace=namespace)
424
425 else if(functl%id == xc_lda_c_fbe) then
426 write(message(1), '(2x,a)') 'Correlation'
427 write(message(2), '(4x,a)') 'Force-based LDA correlation'
428 call messages_info(2, iunit=iunit, namespace=namespace)
429
430 else if (functl%family /= xc_family_none) then ! all the other families
431 select case (functl%type)
432 case (xc_exchange)
433 write(message(1), '(2x,a)') 'Exchange'
434 case (xc_correlation)
435 write(message(1), '(2x,a)') 'Correlation'
436 case (xc_exchange_correlation)
437 write(message(1), '(2x,a)') 'Exchange-correlation'
438 case (xc_kinetic)
439 call messages_not_implemented("kinetic-energy functionals", namespace=namespace)
440 case default
441 write(message(1), '(a,i6,a,i6)') "Unknown functional type ", functl%type, ' for functional ', functl%id
442 call messages_fatal(1, namespace=namespace)
443 end select
444
445 select case (functl%family)
446 case (xc_family_lda)
447 write(family,'(a)') "LDA"
448 case (xc_family_gga)
449 write(family,'(a)') "GGA"
450 case (xc_family_mgga)
451 write(family,'(a)') "MGGA"
452 case (xc_family_hyb_lda)
453 write(family,'(a)') "Hybrid LDA"
454 case (xc_family_hyb_gga)
455 write(family,'(a)') "Hybrid GGA"
456 case (xc_family_hyb_mgga)
457 write(family,'(a)') "Hybrid MGGA"
458 end select
459 write(message(2), '(4x,4a)') trim(xc_f03_func_info_get_name(functl%info)), ' (', trim(family), ')'
460 call messages_info(2, iunit=iunit, namespace=namespace)
461
462 ii = 0
463 do while(ii >= 0)
464 write(message(1), '(4x,a,i1,2a)') '[', ii + 1, '] ', &
465 trim(xc_f03_func_reference_get_ref(xc_f03_func_info_get_references(functl%info, ii)))
466 call messages_info(1, iunit=iunit, namespace=namespace)
467 end do
468 end if
469
471 end subroutine xc_functional_write_info
472
473
475 integer function xc_get_default_functional(dim, pseudo_x_functional, pseudo_c_functional) result(default)
476 integer, intent(in) :: dim
477 integer, intent(in) :: pseudo_x_functional, pseudo_c_functional
478
480
481 default = 0
482
483 if (pseudo_x_functional /= pseudo_exchange_any) then
484 default = pseudo_x_functional
485 else
486 select case (dim)
487 case (3)
488 default = xc_lda_x
489 case (2)
490 default = xc_lda_x_2d
491 case (1)
492 default = xc_lda_x_1d_soft
493 end select
494 end if
495
496 assert(default >= 0)
497
498 if (pseudo_c_functional /= pseudo_correlation_any) then
499 default = default + libxc_c_index*pseudo_c_functional
500 else
501 select case (dim)
502 case (3)
503 default = default + libxc_c_index * xc_lda_c_pz_mod
504 case (2)
505 default = default + libxc_c_index * xc_lda_c_2d_amgb
506 case (1)
507 default = default + libxc_c_index * xc_lda_c_1d_csc
508 end select
509 end if
510
511 assert(default >= 0)
512
514 end function xc_get_default_functional
515
516end module xc_functional_oct_m
517
518!! Local Variables:
519!! mode: f90
520!! coding: utf-8
521!! End:
real(real64), parameter, public m_one
Definition: global.F90:188
subroutine, public libvdwxc_end(this)
Definition: libvdwxc.F90:481
subroutine, public libvdwxc_init(libvdwxc, namespace, functional)
Definition: libvdwxc.F90:161
subroutine, public libvdwxc_write_info(this, iunit, namespace)
Definition: libvdwxc.F90:207
subroutine, public messages_not_implemented(feature, namespace)
Definition: messages.F90:1125
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
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
logical function, public parse_is_defined(namespace, name)
Definition: parser.F90:502
integer, parameter, public pseudo_correlation_any
Definition: pseudo.F90:192
integer, parameter, public pseudo_exchange_any
Definition: pseudo.F90:188
integer, parameter, public xc_ks_inversion
inversion of Kohn-Sham potential
integer, parameter, public xc_vdw_c_vdwdf
vdw-df correlation from libvdwxc
integer, parameter, public xc_family_rdmft
subroutine, public xc_functional_write_info(functl, iunit, namespace)
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_mgga_c_nc_cs
Noncollinear version of the Colle-Salvetti correlation functional.
integer, parameter, public xc_hyb_gga_xc_mvorb_pbeh
Density-based mixing parameter of PBE0.
integer, parameter, public xc_mgga_x_nc_br
Noncollinear version of the Becke-Roussel functional.
integer, parameter, public xc_vdw_c_vdwdfcx
vdw-df-cx correlation from libvdwxc
subroutine, public xc_functional_init(functl, namespace, id, ndim, nel, spin_channels)
integer, parameter, public xc_lda_c_fbe
LDA correlation based ib the force-balance equation.
integer, parameter, public xc_family_nc_mgga
integer, parameter, public xc_half_hartree
half-Hartree exchange for two electrons (supports complex scaling)
integer, parameter, public xc_vdw_c_vdwdf2
vdw-df2 correlation from libvdwxc
integer, parameter, public xc_family_libvdwxc
integer, parameter, public xc_hyb_gga_xc_mvorb_hse06
Density-based mixing parameter of HSE06.
subroutine, public xc_functional_end(functl)
integer, parameter, public xc_lda_c_fbe_sl
LDA correlation based ib the force-balance equation - Sturm-Liouville version.
integer, parameter, public xc_rdmft_xc_m
RDMFT Mueller functional.
integer, parameter, public xc_mgga_x_nc_br_1
Noncollinear version of the Becke-Roussel functional, gamma=1.
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.