(git:34ef472)
xc_derivatives.F
Go to the documentation of this file.
1 !--------------------------------------------------------------------------------------------------!
2 ! CP2K: A general program to perform molecular dynamics simulations !
3 ! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4 ! !
5 ! SPDX-License-Identifier: GPL-2.0-or-later !
6 !--------------------------------------------------------------------------------------------------!
7 
8 ! **************************************************************************************************
10 
12  section_vals_type,&
14  USE kinds, ONLY: dp
15  USE xc_b97, ONLY: b97_lda_eval,&
16  b97_lda_info,&
17  b97_lsd_eval,&
19  USE xc_cs1, ONLY: cs1_lda_eval,&
20  cs1_lda_info,&
21  cs1_lsd_eval,&
23  USE xc_derivative_set_types, ONLY: xc_derivative_set_type
24  USE xc_exchange_gga, ONLY: xgga_eval,&
25  xgga_info
26  USE xc_hcth, ONLY: hcth_lda_eval,&
28  USE xc_ke_gga, ONLY: ke_gga_info,&
31  USE xc_libxc, ONLY: libxc_lda_eval,&
35  USE xc_lyp, ONLY: lyp_lda_eval,&
36  lyp_lda_info,&
37  lyp_lsd_eval,&
43  USE xc_optx, ONLY: optx_lda_eval,&
47  USE xc_pade, ONLY: pade_info,&
48  pade_init,&
51  USE xc_pbe, ONLY: pbe_lda_eval,&
52  pbe_lda_info,&
53  pbe_lsd_eval,&
55  USE xc_perdew86, ONLY: p86_lda_eval,&
57  USE xc_perdew_wang, ONLY: perdew_wang_info,&
60  USE xc_perdew_zunger, ONLY: pz_info,&
61  pz_lda_eval,&
64  xc_rho_cflags_type
65  USE xc_rho_set_types, ONLY: xc_rho_set_get,&
66  xc_rho_set_type
67  USE xc_tfw, ONLY: tfw_lda_eval,&
68  tfw_lda_info,&
69  tfw_lsd_eval,&
74  USE xc_tpss, ONLY: tpss_lda_eval,&
76  USE xc_vwn, ONLY: vwn_lda_eval,&
77  vwn_lda_info,&
78  vwn_lsd_eval,&
80  USE xc_xalpha, ONLY: xalpha_info,&
83  USE xc_xbecke88, ONLY: xb88_lda_eval,&
99  USE xc_xbeef, ONLY: xbeef_lda_eval,&
115  USE xc_xwpbe, ONLY: xwpbe_lda_eval,&
119 #include "../base/base_uses.f90"
120 
121  IMPLICIT NONE
122 
123  PRIVATE
124 
125  LOGICAL, PARAMETER :: debug_this_module = .false.
126  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'xc_derivatives'
127 
129 
130 CONTAINS
131 
132 ! **************************************************************************************************
133 !> \brief get the information about the given functional
134 !> \param functional the functional you want info about
135 !> \param lsd if you are using lsd or lda
136 !> \param reference the reference to the acticle where the functional is
137 !> explained
138 !> \param shortform the short definition of the functional
139 !> \param needs the flags corresponding to the inputs needed by this
140 !> functional are set to true (the flags not needed aren't touched)
141 !> \param max_deriv the maximal derivative available
142 !> \param print_warn whether to print warnings (mainly relevant for libxc)
143 !> \author fawzi
144 ! **************************************************************************************************
145  SUBROUTINE xc_functional_get_info(functional, lsd, reference, shortform, &
146  needs, max_deriv, print_warn)
147  TYPE(section_vals_type), POINTER :: functional
148  LOGICAL, INTENT(in) :: lsd
149  CHARACTER(LEN=*), INTENT(OUT), OPTIONAL :: reference, shortform
150  TYPE(xc_rho_cflags_type), INTENT(inout), OPTIONAL :: needs
151  INTEGER, INTENT(out), OPTIONAL :: max_deriv
152  LOGICAL, INTENT(IN), OPTIONAL :: print_warn
153 
154  INTEGER :: i_param
155  REAL(kind=dp) :: r_param
156 
157  cpassert(ASSOCIATED(functional))
158  SELECT CASE (functional%section%name)
159  CASE ("BECKE97")
160  IF (lsd) THEN
161  CALL b97_lsd_info(reference=reference, shortform=shortform, &
162  needs=needs, max_deriv=max_deriv, b97_params=functional)
163  ELSE
164  CALL b97_lda_info(reference=reference, shortform=shortform, &
165  needs=needs, max_deriv=max_deriv, b97_params=functional)
166  END IF
167  CASE ("BECKE88_LR_ADIABATIC")
168  IF (lsd) THEN
169  CALL xb88_lr_adiabatic_lsd_info(reference=reference, shortform=shortform, &
170  needs=needs, max_deriv=max_deriv)
171  ELSE
172  CALL xb88_lr_adiabatic_lda_info(reference=reference, shortform=shortform, &
173  needs=needs, max_deriv=max_deriv)
174  END IF
175  CASE ("LYP_ADIABATIC")
176  IF (lsd) THEN
177  CALL lyp_adiabatic_lsd_info(reference=reference, shortform=shortform, &
178  needs=needs, max_deriv=max_deriv)
179  ELSE
180  CALL lyp_adiabatic_lda_info(reference=reference, shortform=shortform, &
181  needs=needs, max_deriv=max_deriv)
182  END IF
183  CASE ("BEEF")
184  IF (lsd) THEN
185  CALL xbeef_lsd_info(reference=reference, shortform=shortform, &
186  needs=needs, max_deriv=max_deriv)
187  ELSE
188  CALL xbeef_lda_info(reference=reference, shortform=shortform, &
189  needs=needs, max_deriv=max_deriv)
190  END IF
191  CASE ("BECKE88")
192  IF (lsd) THEN
193  CALL xb88_lsd_info(reference=reference, shortform=shortform, &
194  needs=needs, max_deriv=max_deriv)
195  ELSE
196  CALL xb88_lda_info(reference=reference, shortform=shortform, &
197  needs=needs, max_deriv=max_deriv)
198  END IF
199  CASE ("BECKE88_LR")
200  IF (lsd) THEN
201  CALL xb88_lr_lsd_info(reference=reference, shortform=shortform, &
202  needs=needs, max_deriv=max_deriv)
203  ELSE
204  CALL xb88_lr_lda_info(reference=reference, shortform=shortform, &
205  needs=needs, max_deriv=max_deriv)
206  END IF
207  CASE ("LYP")
208  IF (lsd) THEN
209  CALL lyp_lsd_info(reference=reference, shortform=shortform, &
210  needs=needs, max_deriv=max_deriv)
211  ELSE
212  CALL lyp_lda_info(reference=reference, shortform=shortform, &
213  needs=needs, max_deriv=max_deriv)
214  END IF
215  CASE ("PADE")
216  CALL pade_info(reference, shortform, lsd=lsd, needs=needs)
217  CASE ("HCTH")
218  CALL section_vals_val_get(functional, "PARAMETER_SET", i_val=i_param)
219  cpassert(.NOT. lsd)
220  CALL hcth_lda_info(i_param, reference, shortform, needs, max_deriv)
221  CASE ("OPTX")
222  IF (lsd) THEN
223  CALL optx_lsd_info(reference, shortform, needs, max_deriv)
224  ELSE
225  CALL optx_lda_info(reference, shortform, needs, max_deriv)
226  END IF
227  CASE ("CS1")
228  IF (lsd) THEN
229  CALL cs1_lsd_info(reference, shortform, needs, max_deriv)
230  ELSE
231  CALL cs1_lda_info(reference, shortform, needs=needs, max_deriv=max_deriv)
232  END IF
233  CASE ("XGGA")
234  CALL section_vals_val_get(functional, "FUNCTIONAL", i_val=i_param)
235  CALL xgga_info(i_param, lsd, reference, shortform, needs, max_deriv)
236  CASE ("KE_GGA")
237  CALL section_vals_val_get(functional, "FUNCTIONAL", i_val=i_param)
238  CALL ke_gga_info(i_param, lsd, reference, shortform, needs, max_deriv)
239  CASE ("P86C")
240  IF (lsd) THEN
241  cpabort("BP functional not implemented with LSD")
242  END IF
243  CALL p86_lda_info(reference, shortform, needs, max_deriv)
244  CASE ("PW92")
245  CALL section_vals_val_get(functional, "PARAMETRIZATION", i_val=i_param)
246  CALL section_vals_val_get(functional, "SCALE", r_val=r_param)
247  CALL perdew_wang_info(i_param, lsd, reference, shortform, needs, max_deriv, &
248  r_param)
249  CASE ("PZ81")
250  CALL section_vals_val_get(functional, "PARAMETRIZATION", i_val=i_param)
251  CALL pz_info(i_param, lsd, reference, shortform, needs, max_deriv)
252  CASE ("TFW")
253  IF (lsd) THEN
254  CALL tfw_lsd_info(reference, shortform, needs, max_deriv)
255  ELSE
256  CALL tfw_lda_info(reference, shortform, needs, max_deriv)
257  END IF
258  CASE ("TF")
259  CALL thomas_fermi_info(lsd, reference, shortform, needs, max_deriv)
260  CASE ("VWN")
261  IF (lsd) THEN
262  CALL vwn_lsd_info(reference, shortform, needs, max_deriv)
263  ELSE
264  CALL vwn_lda_info(reference, shortform, needs, max_deriv)
265  END IF
266  CASE ("XALPHA")
267  CALL section_vals_val_get(functional, "XA", r_val=r_param)
268  CALL xalpha_info(lsd, reference, shortform, needs, max_deriv, &
269  xa_parameter=r_param)
270  CASE ("TPSS")
271  IF (lsd) THEN
272  cpabort("TPSS functional not implemented with LSD. Use the LIBXC version instead.")
273  ELSE
274  CALL tpss_lda_info(functional, reference, shortform, needs, max_deriv)
275  END IF
276  CASE ("PBE")
277  IF (lsd) THEN
278  CALL pbe_lsd_info(functional, reference, shortform, needs, max_deriv)
279  ELSE
280  CALL pbe_lda_info(functional, reference, shortform, needs, max_deriv)
281  END IF
282  CASE ("XWPBE")
283  IF (lsd) THEN
284  CALL xwpbe_lsd_info(reference, shortform, needs, max_deriv)
285  ELSE
286  CALL xwpbe_lda_info(reference, shortform, needs, max_deriv)
287  END IF
288  CASE ("BECKE_ROUSSEL")
289  IF (lsd) THEN
290  CALL xbecke_roussel_lsd_info(reference, shortform, needs, max_deriv)
291  ELSE
292  CALL xbecke_roussel_lda_info(reference, shortform, needs, max_deriv)
293  END IF
294  CASE ("LDA_HOLE_T_C_LR")
295  IF (lsd) THEN
296  CALL xlda_hole_t_c_lr_lsd_info(reference, shortform, needs, max_deriv)
297  ELSE
298  CALL xlda_hole_t_c_lr_lda_info(reference, shortform, needs, max_deriv)
299  END IF
300  CASE ("PBE_HOLE_T_C_LR")
301  IF (lsd) THEN
302  CALL xpbe_hole_t_c_lr_lsd_info(reference, shortform, needs, max_deriv)
303  ELSE
304  CALL xpbe_hole_t_c_lr_lda_info(reference, shortform, needs, max_deriv)
305  END IF
306  CASE ("GV09")
307  IF (lsd) THEN
308  CALL xbr_pbe_lda_hole_tc_lr_lsd_info(reference, shortform, needs, max_deriv)
309  ELSE
310  CALL xbr_pbe_lda_hole_tc_lr_lda_info(reference, shortform, needs, max_deriv)
311  END IF
312  CASE default
313  ! If the functional has not been implemented internally, it's from LibXC
314  IF (lsd) THEN
315  CALL libxc_lsd_info(functional, reference, shortform, needs, max_deriv, print_warn)
316  ELSE
317  CALL libxc_lda_info(functional, reference, shortform, needs, max_deriv, print_warn)
318  END IF
319  END SELECT
320  END SUBROUTINE xc_functional_get_info
321 
322 ! **************************************************************************************************
323 !> \brief evaluate a functional (and its derivatives)
324 !> \param functional a section that describes the functional to be added
325 !> \param lsd if a local spin desnity is performed
326 !> \param rho_set a rho set where all the arguments needed by this functional
327 !> should be valid (which argument are needed can be found with
328 !> xc_functional_get_info)
329 !> \param deriv_set place where to store the functional derivatives (they are
330 !> added to the derivatives)
331 !> \param deriv_order degree of the derivative that should be evaluated,
332 !> if positive all the derivatives up to the given degree are evaluated,
333 !> if negative only the given degree is requested (but to simplify
334 !> the code all the derivatives might be calculated, you should ignore
335 !> them when adding derivatives of various functionals they might contain
336 !> the derivative of just one functional)
337 !> \par History
338 !> 11.2003 created [fawzi]
339 !> \author fawzi
340 ! **************************************************************************************************
341  SUBROUTINE xc_functional_eval(functional, lsd, rho_set, deriv_set, deriv_order)
342 
343  TYPE(section_vals_type), POINTER :: functional
344  LOGICAL, INTENT(in) :: lsd
345  TYPE(xc_rho_set_type), INTENT(IN) :: rho_set
346  TYPE(xc_derivative_set_type), INTENT(IN) :: deriv_set
347  INTEGER, INTENT(IN) :: deriv_order
348 
349  CHARACTER(len=*), PARAMETER :: routinen = 'xc_functional_eval'
350 
351  INTEGER :: handle, i_param
352  LOGICAL :: fun_active
353  REAL(kind=dp) :: density_cut, gradient_cut, r_param
354 
355  CALL timeset(routinen, handle)
356 
357  CALL xc_rho_set_get(rho_set, rho_cutoff=density_cut, &
358  drho_cutoff=gradient_cut)
359  CALL section_vals_val_get(functional, "_SECTION_PARAMETERS_", &
360  l_val=fun_active)
361  IF (.NOT. fun_active) THEN
362  CALL timestop(handle)
363  RETURN
364  END IF
365 
366  SELECT CASE (functional%section%name)
367  CASE ("BECKE97")
368  IF (lsd) THEN
369  CALL b97_lsd_eval(rho_set, deriv_set, deriv_order, functional)
370  ELSE
371  CALL b97_lda_eval(rho_set, deriv_set, deriv_order, functional)
372  END IF
373  CASE ("BECKE88_LR_ADIABATIC")
374  IF (lsd) THEN
375  CALL xb88_lr_adiabatic_lsd_eval(rho_set, deriv_set, deriv_order, functional)
376  ELSE
377  CALL xb88_lr_adiabatic_lda_eval(rho_set, deriv_set, deriv_order, functional)
378  END IF
379  CASE ("LYP_ADIABATIC")
380  IF (lsd) THEN
381  CALL lyp_adiabatic_lsd_eval(rho_set, deriv_set, deriv_order, functional)
382  ELSE
383  CALL lyp_adiabatic_lda_eval(rho_set, deriv_set, deriv_order, functional)
384  END IF
385  CASE ("BECKE88")
386  IF (lsd) THEN
387  CALL xb88_lsd_eval(rho_set, deriv_set, deriv_order, functional)
388  ELSE
389  CALL xb88_lda_eval(rho_set, deriv_set, deriv_order, functional)
390  END IF
391  CASE ("BEEF")
392  IF (lsd) THEN
393  CALL xbeef_lsd_eval(rho_set, deriv_set, deriv_order, functional)
394  ELSE
395  CALL xbeef_lda_eval(rho_set, deriv_set, deriv_order, functional)
396  END IF
397  CASE ("BECKE88_LR")
398  IF (lsd) THEN
399  CALL xb88_lr_lsd_eval(rho_set, deriv_set, deriv_order, functional)
400  ELSE
401  CALL xb88_lr_lda_eval(rho_set, deriv_set, deriv_order, functional)
402  END IF
403  CASE ("LYP")
404  IF (lsd) THEN
405  CALL lyp_lsd_eval(rho_set, deriv_set, deriv_order, functional)
406  ELSE
407  CALL lyp_lda_eval(rho_set, deriv_set, deriv_order, functional)
408  END IF
409  CASE ("PADE")
410  CALL pade_init(density_cut)
411  IF (lsd) THEN
412  CALL pade_lsd_pw_eval(deriv_set, rho_set, deriv_order)
413  ELSE
414  CALL pade_lda_pw_eval(deriv_set, rho_set, deriv_order)
415  END IF
416  CASE ("HCTH")
417  cpassert(.NOT. lsd)
418  CALL section_vals_val_get(functional, "PARAMETER_SET", i_val=i_param)
419  CALL hcth_lda_eval(i_param, rho_set, deriv_set, deriv_order)
420  CASE ("OPTX")
421  IF (lsd) THEN
422  CALL optx_lsd_eval(rho_set, deriv_set, deriv_order, functional)
423  ELSE
424  CALL optx_lda_eval(rho_set, deriv_set, deriv_order, functional)
425  END IF
426  CASE ("CS1")
427  IF (lsd) THEN
428  CALL cs1_lsd_eval(rho_set, deriv_set, deriv_order)
429  ELSE
430  CALL cs1_lda_eval(rho_set, deriv_set, deriv_order)
431  END IF
432  CASE ("XGGA")
433  CALL section_vals_val_get(functional, "FUNCTIONAL", i_val=i_param)
434  CALL xgga_eval(i_param, lsd, rho_set, deriv_set, deriv_order)
435  CASE ("KE_GGA")
436  CALL section_vals_val_get(functional, "FUNCTIONAL", i_val=i_param)
437  IF (lsd) THEN
438  CALL ke_gga_lsd_eval(i_param, rho_set, deriv_set, deriv_order)
439  ELSE
440  CALL ke_gga_lda_eval(i_param, rho_set, deriv_set, deriv_order)
441  END IF
442  CASE ("P86C")
443  cpassert(.NOT. lsd)
444  CALL p86_lda_eval(rho_set, deriv_set, deriv_order, functional)
445  CASE ("PW92")
446  CALL section_vals_val_get(functional, "PARAMETRIZATION", i_val=i_param)
447  CALL section_vals_val_get(functional, "SCALE", r_val=r_param)
448  IF (lsd) THEN
449  CALL perdew_wang_lsd_eval(i_param, rho_set, deriv_set, deriv_order, &
450  r_param)
451  ELSE
452  CALL perdew_wang_lda_eval(i_param, rho_set, deriv_set, deriv_order, &
453  r_param)
454  END IF
455  CASE ("PZ81")
456  CALL section_vals_val_get(functional, "PARAMETRIZATION", i_val=i_param)
457  IF (lsd) THEN
458  CALL pz_lsd_eval(i_param, rho_set, deriv_set, deriv_order, functional)
459  ELSE
460  CALL pz_lda_eval(i_param, rho_set, deriv_set, deriv_order, functional)
461  END IF
462  CASE ("TFW")
463  IF (lsd) THEN
464  CALL tfw_lsd_eval(rho_set, deriv_set, deriv_order)
465  ELSE
466  CALL tfw_lda_eval(rho_set, deriv_set, deriv_order)
467  END IF
468  CASE ("TF")
469  IF (lsd) THEN
470  CALL thomas_fermi_lsd_eval(rho_set, deriv_set, deriv_order)
471  ELSE
472  CALL thomas_fermi_lda_eval(rho_set, deriv_set, deriv_order)
473  END IF
474  CASE ("VWN")
475  IF (lsd) THEN
476  CALL vwn_lsd_eval(rho_set, deriv_set, deriv_order, functional)
477  ELSE
478  CALL vwn_lda_eval(rho_set, deriv_set, deriv_order, functional)
479  END IF
480  CASE ("XALPHA")
481  CALL section_vals_val_get(functional, "XA", r_val=r_param)
482  IF (lsd) THEN
483  CALL xalpha_lsd_eval(rho_set, deriv_set, deriv_order, &
484  xa_parameter=r_param, xa_params=functional)
485  ELSE
486  CALL xalpha_lda_eval(rho_set, deriv_set, deriv_order, &
487  xa_parameter=r_param, xa_params=functional)
488  END IF
489  CASE ("TPSS")
490  IF (lsd) THEN
491  cpabort("TPSS functional not implemented with LSD. Use the LIBXC version instead.")
492  ELSE
493  CALL tpss_lda_eval(rho_set, deriv_set, deriv_order, functional)
494  END IF
495  CASE ("PBE")
496  IF (lsd) THEN
497  CALL pbe_lsd_eval(rho_set, deriv_set, deriv_order, functional)
498  ELSE
499  CALL pbe_lda_eval(rho_set, deriv_set, deriv_order, functional)
500  END IF
501  CASE ("XWPBE")
502  IF (lsd) THEN
503  CALL xwpbe_lsd_eval(rho_set, deriv_set, deriv_order, functional)
504  ELSE
505  CALL xwpbe_lda_eval(rho_set, deriv_set, deriv_order, functional)
506  END IF
507  CASE ("BECKE_ROUSSEL")
508  IF (lsd) THEN
509  CALL xbecke_roussel_lsd_eval(rho_set, deriv_set, deriv_order, functional)
510  ELSE
511  CALL xbecke_roussel_lda_eval(rho_set, deriv_set, deriv_order, functional)
512  END IF
513  CASE ("LDA_HOLE_T_C_LR")
514  IF (lsd) THEN
515  CALL xlda_hole_t_c_lr_lsd_eval(rho_set, deriv_set, deriv_order, functional)
516  ELSE
517  CALL xlda_hole_t_c_lr_lda_eval(rho_set, deriv_set, deriv_order, functional)
518  END IF
519  CASE ("PBE_HOLE_T_C_LR")
520  IF (lsd) THEN
521  CALL xpbe_hole_t_c_lr_lsd_eval(rho_set, deriv_set, deriv_order, functional)
522  ELSE
523  CALL xpbe_hole_t_c_lr_lda_eval(rho_set, deriv_set, deriv_order, functional)
524  END IF
525  CASE ("GV09")
526  IF (lsd) THEN
527  CALL xbr_pbe_lda_hole_tc_lr_lsd_eval(rho_set, deriv_set, deriv_order, &
528  functional)
529  ELSE
530  CALL xbr_pbe_lda_hole_tc_lr_lda_eval(rho_set, deriv_set, deriv_order, &
531  functional)
532  END IF
533  CASE default
534  ! If functional not natively supported, ask LibXC
535  IF (lsd) THEN
536  CALL libxc_lsd_eval(rho_set, deriv_set, deriv_order, functional)
537  ELSE
538  CALL libxc_lda_eval(rho_set, deriv_set, deriv_order, functional)
539  END IF
540  END SELECT
541 
542  CALL timestop(handle)
543  END SUBROUTINE xc_functional_eval
544 
545 ! **************************************************************************************************
546 !> \brief ...
547 !> \param functionals a section containing the functional combination to be
548 !> applied
549 !> \param lsd if a local spin desnity is performed
550 !> \param rho_set a rho set where all the arguments needed by this functional
551 !> should be valid (which argument are needed can be found with
552 !> xc_functional_get_info)
553 !> \param deriv_set place where to store the functional derivatives (they are
554 !> added to the derivatives)
555 !> \param deriv_order degree of the derivative that should be evaluated,
556 !> if positive all the derivatives up to the given degree are evaluated,
557 !> if negative only the given degree is requested (but to simplify
558 !> the code all the derivatives might be calculated, you should ignore
559 !> them when adding derivatives of various functionals they might contain
560 !> the derivative of just one functional)
561 !> \author fawzi
562 ! **************************************************************************************************
563  SUBROUTINE xc_functionals_eval(functionals, lsd, rho_set, deriv_set, &
564  deriv_order)
565  TYPE(section_vals_type), POINTER :: functionals
566  LOGICAL, INTENT(in) :: lsd
567  TYPE(xc_rho_set_type), INTENT(IN) :: rho_set
568  TYPE(xc_derivative_set_type), INTENT(IN) :: deriv_set
569  INTEGER, INTENT(in) :: deriv_order
570 
571  INTEGER :: ifun
572  TYPE(section_vals_type), POINTER :: xc_fun
573 
574  cpassert(ASSOCIATED(functionals))
575  ifun = 0
576  DO
577  ifun = ifun + 1
578  xc_fun => section_vals_get_subs_vals2(functionals, i_section=ifun)
579  IF (.NOT. ASSOCIATED(xc_fun)) EXIT
580  CALL xc_functional_eval(xc_fun, &
581  lsd=lsd, &
582  rho_set=rho_set, &
583  deriv_set=deriv_set, &
584  deriv_order=deriv_order)
585  END DO
586  END SUBROUTINE xc_functionals_eval
587 
588 ! **************************************************************************************************
589 !> \brief ...
590 !> \param functionals a section containing the functional combination to be
591 !> applied
592 !> \param lsd if a local spin desnity is performed
593 !> \param calc_potential set, if potential calculation will be carried out later.
594 !> helps to save memory and flops. defaults to false.
595 !> \return ...
596 !> \author fawzi
597 ! **************************************************************************************************
598  FUNCTION xc_functionals_get_needs(functionals, lsd, calc_potential) &
599  result(needs)
600  TYPE(section_vals_type), POINTER :: functionals
601  LOGICAL, INTENT(in) :: lsd
602  LOGICAL, INTENT(in), OPTIONAL :: calc_potential
603  TYPE(xc_rho_cflags_type) :: needs
604 
605  INTEGER :: ifun
606  LOGICAL :: my_calc_potential
607  TYPE(section_vals_type), POINTER :: xc_fun
608 
609  my_calc_potential = .false.
610  IF (PRESENT(calc_potential)) my_calc_potential = calc_potential
611 
612  cpassert(ASSOCIATED(functionals))
613  CALL xc_rho_cflags_setall(needs, .false.)
614 
615  ifun = 0
616  DO
617  ifun = ifun + 1
618  xc_fun => section_vals_get_subs_vals2(functionals, i_section=ifun)
619  IF (.NOT. ASSOCIATED(xc_fun)) EXIT
620  CALL xc_functional_get_info(xc_fun, lsd=lsd, needs=needs)
621  END DO
622 
623  IF (my_calc_potential) THEN
624  IF (lsd) THEN
625  needs%rho_spin = .true.
626  needs%tau_spin = needs%tau_spin .OR. needs%tau
627  ELSE
628  needs%rho = .true.
629  END IF
630  IF (needs%norm_drho .OR. needs%norm_drho_spin) THEN
631  IF (lsd) THEN
632  needs%drho_spin = .true.
633  ELSE
634  needs%drho = .true.
635  END IF
636  END IF
637  END IF
638  END FUNCTION xc_functionals_get_needs
639 
640 END MODULE xc_derivatives
objects that represent the structure of input sections and the data contained in an input section
type(section_vals_type) function, pointer, public section_vals_get_subs_vals2(section_vals, i_section, i_rep_section)
returns the values of the n-th non default subsection (null if no such section exists (not so many no...
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
calculates the b97 correlation functional
Definition: xc_b97.F:24
subroutine, public b97_lda_info(b97_params, reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_b97.F:187
subroutine, public b97_lda_eval(rho_set, deriv_set, grad_deriv, b97_params)
evaluates the b97 correlation functional for lda
Definition: xc_b97.F:252
subroutine, public b97_lsd_info(b97_params, reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_b97.F:219
subroutine, public b97_lsd_eval(rho_set, deriv_set, grad_deriv, b97_params)
evaluates the b 97 xc functional for lsd
Definition: xc_b97.F:364
Calculate the CS1 Functional (Handy s improved LYP functional)
Definition: xc_cs1.F:15
subroutine, public cs1_lda_eval(rho_set, deriv_set, order)
...
Definition: xc_cs1.F:149
subroutine, public cs1_lsd_eval(rho_set, deriv_set, order)
...
Definition: xc_cs1.F:238
subroutine, public cs1_lsd_info(reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_cs1.F:100
subroutine, public cs1_lda_info(reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_cs1.F:72
represent a group ofunctional derivatives
type(xc_rho_cflags_type) function, public xc_functionals_get_needs(functionals, lsd, calc_potential)
...
subroutine, public xc_functional_get_info(functional, lsd, reference, shortform, needs, max_deriv, print_warn)
get the information about the given functional
subroutine, public xc_functionals_eval(functionals, lsd, rho_set, deriv_set, deriv_order)
...
Calculate several different exchange energy functionals with a GGA form.
subroutine, public xgga_eval(functional, lsd, rho_set, deriv_set, order)
evaluates different exchange gga
subroutine, public xgga_info(functional, lsd, reference, shortform, needs, max_deriv)
return various information on the xgga functionals
calculate the Hamprecht, Cohen, Tozer, and Handy (HCTH) exchange functional
Definition: xc_hcth.F:13
subroutine, public hcth_lda_info(iparset, reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_hcth.F:49
subroutine, public hcth_lda_eval(iparset, rho_set, deriv_set, grad_deriv)
evaluates the hcth functional for lda
Definition: xc_hcth.F:118
Calculate the several different kinetic energy functionals with a GGA form.
Definition: xc_ke_gga.F:16
subroutine, public ke_gga_lsd_eval(functional, rho_set, deriv_set, order)
...
Definition: xc_ke_gga.F:313
subroutine, public ke_gga_info(functional, lsd, reference, shortform, needs, max_deriv)
...
Definition: xc_ke_gga.F:97
subroutine, public ke_gga_lda_eval(functional, rho_set, deriv_set, order)
...
Definition: xc_ke_gga.F:178
calculates a functional from libxc and its derivatives
Definition: xc_libxc.F:28
subroutine, public libxc_lda_eval(rho_set, deriv_set, grad_deriv, libxc_params)
evaluates the functional from libxc
Definition: xc_libxc.F:543
subroutine, public libxc_lsd_eval(rho_set, deriv_set, grad_deriv, libxc_params)
evaluates the functional from libxc
Definition: xc_libxc.F:778
subroutine, public libxc_lsd_info(libxc_params, reference, shortform, needs, max_deriv, print_warn)
info about the functional from libxc
Definition: xc_libxc.F:416
subroutine, public libxc_lda_info(libxc_params, reference, shortform, needs, max_deriv, print_warn)
info about the functional from libxc
Definition: xc_libxc.F:308
Calculates the density_scaled Lyp functional when used in adiabatic hybrids. The energy is given as.
subroutine, public lyp_adiabatic_lda_info(reference, shortform, needs, max_deriv)
return various information on the functional
subroutine, public lyp_adiabatic_lsd_info(reference, shortform, needs, max_deriv)
return various information on the functional
subroutine, public lyp_adiabatic_lda_eval(rho_set, deriv_set, grad_deriv, lyp_adiabatic_params)
...
subroutine, public lyp_adiabatic_lsd_eval(rho_set, deriv_set, grad_deriv, lyp_adiabatic_params)
...
calculates the lyp correlation functional
Definition: xc_lyp.F:14
subroutine, public lyp_lda_info(reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_lyp.F:59
subroutine, public lyp_lsd_eval(rho_set, deriv_set, grad_deriv, lyp_params)
evaluates the becke 88 exchange functional for lsd
Definition: xc_lyp.F:727
subroutine, public lyp_lsd_info(reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_lyp.F:90
subroutine, public lyp_lda_eval(rho_set, deriv_set, grad_deriv, lyp_params)
evaluates the lyp correlation functional for lda
Definition: xc_lyp.F:124
calculate optx
Definition: xc_optx.F:14
subroutine, public optx_lda_info(reference, shortform, needs, max_deriv)
info about the optx functional
Definition: xc_optx.F:52
subroutine, public optx_lsd_eval(rho_set, deriv_set, grad_deriv, optx_params)
evaluates the optx functional for lsd
Definition: xc_optx.F:169
subroutine, public optx_lda_eval(rho_set, deriv_set, grad_deriv, optx_params)
evaluates the optx functional for lda
Definition: xc_optx.F:110
subroutine, public optx_lsd_info(reference, shortform, needs, max_deriv)
info about the optx functional (LSD)
Definition: xc_optx.F:79
Calculate the LDA functional in the Pade approximation Literature: S. Goedecker, M....
Definition: xc_pade.F:19
subroutine, public pade_init(cutoff, debug)
...
Definition: xc_pade.F:80
subroutine, public pade_lsd_pw_eval(deriv_set, rho_set, order)
...
Definition: xc_pade.F:204
subroutine, public pade_info(reference, shortform, lsd, needs, max_deriv)
...
Definition: xc_pade.F:106
subroutine, public pade_lda_pw_eval(deriv_set, rho_set, order)
...
Definition: xc_pade.F:141
calculates the pbe correlation functional
Definition: xc_pbe.F:21
subroutine, public pbe_lda_eval(rho_set, deriv_set, grad_deriv, pbe_params)
evaluates the pbe correlation functional for lda
Definition: xc_pbe.F:280
subroutine, public pbe_lsd_info(pbe_params, reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_pbe.F:174
subroutine, public pbe_lsd_eval(rho_set, deriv_set, grad_deriv, pbe_params)
evaluates the becke 88 exchange functional for lsd
Definition: xc_pbe.F:1326
subroutine, public pbe_lda_info(pbe_params, reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_pbe.F:70
Calculate the Perdew Correlation from 1986.
Definition: xc_perdew86.F:15
subroutine, public p86_lda_info(reference, shortform, needs, max_deriv)
...
Definition: xc_perdew86.F:94
subroutine, public p86_lda_eval(rho_set, deriv_set, order, p86_params)
...
Definition: xc_perdew86.F:120
Calculate the Perdew-Wang correlation potential and energy density and ist derivatives with respect t...
subroutine, public perdew_wang_lda_eval(method, rho_set, deriv_set, order, scale)
Calculate the correlation energy and its derivatives wrt to rho (the electron density) up to 3rd orde...
subroutine, public perdew_wang_info(method, lsd, reference, shortform, needs, max_deriv, scale)
Return some info on the functionals.
subroutine, public perdew_wang_lsd_eval(method, rho_set, deriv_set, order, scale)
Calculate the correlation energy and its derivatives wrt to rho (the electron density) up to 3rd orde...
Calculate the Perdew-Zunger correlation potential and energy density and ist derivatives with respect...
subroutine, public pz_lda_eval(method, rho_set, deriv_set, order, pz_params)
Calculate the correlation energy and its derivatives wrt to rho (the electron density) up to 3rd orde...
subroutine, public pz_lsd_eval(method, rho_set, deriv_set, order, pz_params)
Calculate the correlation energy and its derivatives wrt to rho (the electron density) up to 3rd orde...
subroutine, public pz_info(method, lsd, reference, shortform, needs, max_deriv)
Return some info on the functionals.
contains the structure
elemental subroutine, public xc_rho_cflags_setall(cflags, value)
sets all the flags to the given value
contains the structure
subroutine, public xc_rho_set_get(rho_set, can_return_null, rho, drho, norm_drho, rhoa, rhob, norm_drhoa, norm_drhob, rho_1_3, rhoa_1_3, rhob_1_3, laplace_rho, laplace_rhoa, laplace_rhob, drhoa, drhob, rho_cutoff, drho_cutoff, tau_cutoff, tau, tau_a, tau_b, local_bounds)
returns the various attributes of rho_set
Calculate the Thomas-Fermi kinetic energy functional plus the von Weizsaecker term.
Definition: xc_tfw.F:16
subroutine, public tfw_lda_info(reference, shortform, needs, max_deriv)
...
Definition: xc_tfw.F:81
subroutine, public tfw_lda_eval(rho_set, deriv_set, order)
...
Definition: xc_tfw.F:134
subroutine, public tfw_lsd_info(reference, shortform, needs, max_deriv)
...
Definition: xc_tfw.F:108
subroutine, public tfw_lsd_eval(rho_set, deriv_set, order)
...
Definition: xc_tfw.F:244
Calculate the Thomas-Fermi kinetic energy functional.
subroutine, public thomas_fermi_lsd_eval(rho_set, deriv_set, order)
...
subroutine, public thomas_fermi_lda_eval(rho_set, deriv_set, order)
...
subroutine, public thomas_fermi_info(lsd, reference, shortform, needs, max_deriv)
...
Calculates the tpss functional.
Definition: xc_tpss.F:17
subroutine, public tpss_lda_eval(rho_set, deriv_set, grad_deriv, tpss_params)
evaluates the tpss functional in the spin unpolarized (lda) case
Definition: xc_tpss.F:109
subroutine, public tpss_lda_info(tpss_params, reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_tpss.F:60
Calculate the LDA functional according to Vosk, Wilk and Nusair Literature: S. H. Vosko,...
Definition: xc_vwn.F:21
subroutine, public vwn_lda_info(reference, shortform, needs, max_deriv)
...
Definition: xc_vwn.F:115
subroutine, public vwn_lda_eval(rho_set, deriv_set, order, vwn_params)
...
Definition: xc_vwn.F:167
subroutine, public vwn_lsd_eval(rho_set, deriv_set, order, vwn_params)
...
Definition: xc_vwn.F:525
subroutine, public vwn_lsd_info(reference, shortform, needs, max_deriv)
...
Definition: xc_vwn.F:141
Calculate the local exchange functional.
Definition: xc_xalpha.F:19
subroutine, public xalpha_lda_eval(rho_set, deriv_set, order, xa_params, xa_parameter)
...
Definition: xc_xalpha.F:153
subroutine, public xalpha_info(lsd, reference, shortform, needs, max_deriv, xa_parameter, scaling)
...
Definition: xc_xalpha.F:92
subroutine, public xalpha_lsd_eval(rho_set, deriv_set, order, xa_params, xa_parameter)
...
Definition: xc_xalpha.F:223
calculates the longrange part of Becke 88 exchange functional
subroutine, public xb88_lr_lda_eval(rho_set, deriv_set, grad_deriv, xb88_lr_params)
evaluates the becke 88 longrange exchange functional for lda
subroutine, public xb88_lr_lsd_info(reference, shortform, needs, max_deriv)
return various information on the functional
subroutine, public xb88_lr_lda_info(reference, shortform, needs, max_deriv)
return various information on the functional
subroutine, public xb88_lr_lsd_eval(rho_set, deriv_set, grad_deriv, xb88_lr_params)
evaluates the becke 88 longrange exchange functional for lsd
Calculates the density_scaled BECKE88 long-range functional when used in adiabatic hybrids....
subroutine, public xb88_lr_adiabatic_lda_eval(rho_set, deriv_set, grad_deriv, xb88_lr_ad_params)
evaluates the becke 88 longrange exchange functional for lda
subroutine, public xb88_lr_adiabatic_lda_info(reference, shortform, needs, max_deriv)
return various information on the functional
subroutine, public xb88_lr_adiabatic_lsd_eval(rho_set, deriv_set, grad_deriv, xb88_lr_ad_params)
evaluates the becke 88 longrange exchange functional for lsd
subroutine, public xb88_lr_adiabatic_lsd_info(reference, shortform, needs, max_deriv)
return various information on the functional
calculates the Becke 88 exchange functional
Definition: xc_xbecke88.F:14
subroutine, public xb88_lsd_info(reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_xbecke88.F:90
subroutine, public xb88_lda_eval(rho_set, deriv_set, grad_deriv, xb88_params)
evaluates the becke 88 exchange functional for lda
Definition: xc_xbecke88.F:124
subroutine, public xb88_lsd_eval(rho_set, deriv_set, grad_deriv, xb88_params)
evaluates the becke 88 exchange functional for lsd
Definition: xc_xbecke88.F:637
subroutine, public xb88_lda_info(reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_xbecke88.F:59
Calculates the exchange energy based on the Becke-Roussel exchange hole. Takes advantage of an analyt...
subroutine, public xbecke_roussel_lsd_eval(rho_set, deriv_set, grad_deriv, br_params)
evaluates the Becke Roussel exchange functional for lda
subroutine, public xbecke_roussel_lda_info(reference, shortform, needs, max_deriv)
return various information on the functional
subroutine, public xbecke_roussel_lda_eval(rho_set, deriv_set, grad_deriv, br_params)
evaluates the Becke Roussel exchange functional for lda
subroutine, public xbecke_roussel_lsd_info(reference, shortform, needs, max_deriv)
return various information on the functional
calculates the Exchange contribution in the BEEF-vdW functional
Definition: xc_xbeef.F:15
subroutine, public xbeef_lda_eval(rho_set, deriv_set, grad_deriv, xbeef_params)
evaluates the beef exchange functional for lda
Definition: xc_xbeef.F:137
subroutine, public xbeef_lsd_info(reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_xbeef.F:104
subroutine, public xbeef_lda_info(reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_xbeef.F:73
subroutine, public xbeef_lsd_eval(rho_set, deriv_set, grad_deriv, xbeef_params)
evaluates the beef 88 exchange functional for lsd
Definition: xc_xbeef.F:311
This functional is a combination of three different exchange hole models. The ingredients are:
subroutine, public xbr_pbe_lda_hole_tc_lr_lsd_eval(rho_set, deriv_set, grad_deriv, params)
Intermediate routine that gets grids, derivatives and some params.
subroutine, public xbr_pbe_lda_hole_tc_lr_lda_eval(rho_set, deriv_set, grad_deriv, params)
Intermediate routine that gets grids, derivatives and some params.
subroutine, public xbr_pbe_lda_hole_tc_lr_lda_info(reference, shortform, needs, max_deriv)
return various information on the functional
subroutine, public xbr_pbe_lda_hole_tc_lr_lsd_info(reference, shortform, needs, max_deriv)
return various information on the functional
Calculates the lda exchange hole in a truncated coulomb potential. Can be used as longrange correctio...
subroutine, public xlda_hole_t_c_lr_lda_eval(rho_set, deriv_set, order, params)
evaluates the truncated lda exchange hole
subroutine, public xlda_hole_t_c_lr_lda_info(reference, shortform, needs, max_deriv)
returns various information on the functional
subroutine, public xlda_hole_t_c_lr_lsd_eval(rho_set, deriv_set, order, params)
evaluates the truncated lsd exchange hole. Calls the lda routine and applies spin scaling relation
subroutine, public xlda_hole_t_c_lr_lsd_info(reference, shortform, needs, max_deriv)
returns various information on the functional
Calculates the exchange energy for the pbe hole model in a truncated coulomb potential,...
subroutine, public xpbe_hole_t_c_lr_lda_info(reference, shortform, needs, max_deriv)
returns various information on the functional
subroutine, public xpbe_hole_t_c_lr_lda_eval(rho_set, deriv_set, order, params)
evaluates the pbe-hole exchange in a truncated coulomb potential
subroutine, public xpbe_hole_t_c_lr_lsd_eval(rho_set, deriv_set, order, params)
evaluates the pbe-hole exchange in a truncated coulomb potential
subroutine, public xpbe_hole_t_c_lr_lsd_info(reference, shortform, needs, max_deriv)
returns various information on the functional
Calculates short range exchange part for wPBE functional and averaged PBE exchange-hole functional (o...
Definition: xc_xwpbe.F:15
subroutine, public xwpbe_lda_eval(rho_set, deriv_set, order, xwpbe_params)
evaluates the screened hole averaged PBE exchange functional for lda
Definition: xc_xwpbe.F:150
subroutine, public xwpbe_lsd_eval(rho_set, deriv_set, order, xwpbe_params)
evaluates the screened hole averaged PBE exchange functional for lsd
Definition: xc_xwpbe.F:5255
subroutine, public xwpbe_lda_info(reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_xwpbe.F:113
subroutine, public xwpbe_lsd_info(reference, shortform, needs, max_deriv)
return various information on the functional
Definition: xc_xwpbe.F:5220