TABLE OF CONTENTS


ABINIT/m_libpaw_libxc [ Modules ]

[ Top ] [ Modules ]

NAME

  m_libpaw_libxc

FUNCTION

  Module used to interface libPAW with host code.
  At present, two cases are implemented:
   - Use of ABINIT m_libxc_functional module
   - Use of embedded m_libpaw_libxc_funcs module

COPYRIGHT

 Copyright (C) 2014-2024 ABINIT group (MT)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .

SOURCE

2501 module m_libpaw_libxc
2502 
2503 #if defined HAVE_LIBPAW_ABINIT
2504  use libxc_functionals
2505 
2506 #else
2507  use m_libpaw_libxc_funcs, only : &
2508 & libxc_functionals_check             => libpaw_libxc_check, &
2509 & libxc_functionals_init              => libpaw_libxc_init, &
2510 & libxc_functionals_end               => libpaw_libxc_end, &
2511 & libxc_functionals_fullname          => libpaw_libxc_fullname, &
2512 & libxc_functionals_getid             => libpaw_libxc_getid, &
2513 & libxc_functionals_family_from_id    => libpaw_libxc_family_from_id, &
2514 & libxc_functionals_ixc               => libpaw_libxc_ixc, &
2515 & libxc_functionals_isgga             => libpaw_libxc_isgga, &
2516 & libxc_functionals_ismgga            => libpaw_libxc_ismgga, &
2517 & libxc_functionals_is_tb09           => libpaw_libxc_is_tb09, &
2518 & libxc_functionals_needs_laplacian   => libpaw_libxc_needs_laplacian, &
2519 & libxc_functionals_needs_temperature => libpaw_libxc_needs_temperature, &
2520 & libxc_functionals_set_temperature   => libpaw_libxc_set_temperature, &
2521 & libxc_functionals_has_kxc           => libpaw_libxc_has_kxc, &
2522 & libxc_functionals_has_k3xc          => libpaw_libxc_has_k3xc, &
2523 & libxc_functionals_nspin             => libpaw_libxc_nspin, &
2524 & libxc_functionals_is_hybrid         => libpaw_libxc_is_hybrid, &
2525 & libxc_functionals_is_hybrid_from_id => libpaw_libxc_is_hybrid_from_id, &
2526 & libxc_functionals_get_hybridparams  => libpaw_libxc_get_hybridparams, &
2527 & libxc_functionals_set_hybridparams  => libpaw_libxc_set_hybridparams, &
2528 & libxc_functionals_gga_from_hybrid   => libpaw_libxc_gga_from_hybrid, &
2529 & libxc_functionals_getvxc            => libpaw_libxc_getvxc
2530 #endif
2531 
2532  implicit none
2533 
2534 end module m_libpaw_libxc

ABINIT/m_libpaw_libxc_funcs [ Modules ]

[ Top ] [ Modules ]

NAME

  m_libpaw_libxc_funcs

FUNCTION

  Module containing interfaces to the LibXC library, for exchange
  correlation potentials and energies.

COPYRIGHT

 Copyright (C) 2015-2024 ABINIT group (MO, MT)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .

NOTES

  This file comes directly from m_libpaw_libxc.F90 module delivered with ABINIT.
  It defines a structured datatype (libpaw_libxc_type) and associated methods
  to initialize/finalize it and get properties from it.
  * It uses by default a global variable (paw_xc_global, libpaw_libxc_type) which has
    to be initialized/finalized with the libpaw_libxc_init and libpaw_libxc_end methods.
  * It is also possible to define a local (private) variable of type libpaw_libxc_type.
    For that, the different methods have to be called with an extra optional
    argument (called xc_funcs in this example):
    !!!!! call libpaw_libxc_init(ixc,nspden,xc_funcs)
    !!!!! call libpaw_libxc_end(xc_funcs)

SOURCE

 30 !Need iso C bindings provided by the compiler
 31 #define LIBPAW_ISO_C_BINDING 1
 32 
 33 #include "libpaw.h"
 34 
 35 module m_libpaw_libxc_funcs
 36 
 37  USE_DEFS
 38  USE_MSG_HANDLING
 39  USE_MEMORY_PROFILING
 40 
 41 !ISO C bindings are mandatory
 42 #ifdef LIBPAW_ISO_C_BINDING
 43  use, intrinsic :: iso_c_binding
 44 #endif
 45 
 46  implicit none
 47  private
 48 
 49 !Public functions
 50  public :: libpaw_libxc_check              ! Check if the code has been compiled with libXC
 51  public :: libpaw_libxc_init               ! Initialize a set of XC functional(s), from libXC
 52  public :: libpaw_libxc_end                ! End usage of a set of libXC functional(s)
 53  public :: libpaw_libxc_fullname           ! Return full name of a set of XC functional(s)
 54  public :: libpaw_libxc_getid              ! Return identifer of a XC functional, from its name
 55  public :: libpaw_libxc_family_from_id     ! Retrieve family of a XC functional, from its id
 56  public :: libpaw_libxc_ixc                ! The value of ixc used to initialize the XC functional(s)
 57  public :: libpaw_libxc_islda              ! Return TRUE if the set of XC functional(s) is LDA
 58  public :: libpaw_libxc_isgga              ! Return TRUE if the set of XC functional(s) is GGA or meta-GGA
 59  public :: libpaw_libxc_ismgga             ! Return TRUE if the set of XC functional(s) is meta-GGA
 60  public :: libpaw_libxc_is_tb09            ! Return TRUE if the XC functional is Tran-Blaha 2009.
 61  public :: libpaw_libxc_set_c_tb09         ! Set c parameter for Tran-Blaha 2009 functional
 62  public :: libpaw_libxc_needs_laplacian    ! Return TRUE if the set of XC functional uses LAPLACIAN
 63  public :: libpaw_libxc_needs_temperature  ! Return TRUE if the set of XC functional(s) uses the elec. temperature
 64  public :: libpaw_libxc_set_temperature    ! Set electronic temperature in a set of XC functional(s)
 65  public :: libpaw_libxc_has_kxc            ! Return TRUE if Kxc (3rd der) is available for a set of XC functional(s)
 66  public :: libpaw_libxc_has_k3xc           ! Return TRUE if K3xc (4th der) is available for a set of XC functional(s)
 67  public :: libpaw_libxc_nspin              ! The number of spin components for a set of XC functional(s)
 68  public :: libpaw_libxc_is_hybrid          ! Return TRUE if a set of XC functional(s) is hybrid
 69  public :: libpaw_libxc_is_hybrid_from_id  ! Return TRUE if a XC functional is hybrid, from its id
 70  public :: libpaw_libxc_get_hybridparams   ! Retrieve parameter(s) hybrid functional(s)
 71  public :: libpaw_libxc_set_hybridparams   ! Change parameter(s) of hybrid functional(s)
 72  public :: libpaw_libxc_gga_from_hybrid    ! Return the id of the XC-GGA used for the hybrid
 73  public :: libpaw_libxc_getvxc             ! Return XC potential and energy, from input density
 74 
 75 !Private functions
 76  private :: libpaw_libxc_compute_tb09      ! Compute c parameter for Tran-Blaha 2009 functional
 77  private :: libpaw_libxc_getrefs           ! Get references of a single XC functional
 78  private :: libpaw_libxc_depends_on_temp   ! TRUE if a single functional depends on elec. temperature
 79  private :: libpaw_libxc_set_temp          ! Set electronic temperature in a single XC functional
 80  private :: libpaw_libxc_constants_load    ! Load libXC constants from C headers
 81 #ifdef LIBPAW_ISO_C_BINDING
 82  private :: char_f_to_c                    ! Convert a string from Fortran to C
 83  private :: char_c_to_f                    ! Convert a string from C to Fortran
 84 #endif
 85 
 86 !Public constants (use libpaw_libxc_constants_load to init them)
 87  integer,public,save :: LIBPAW_XC_FAMILY_UNKNOWN       = -1
 88  integer,public,save :: LIBPAW_XC_FAMILY_LDA           =  1
 89  integer,public,save :: LIBPAW_XC_FAMILY_GGA           =  2
 90  integer,public,save :: LIBPAW_XC_FAMILY_MGGA          =  4
 91  integer,public,save :: LIBPAW_XC_FAMILY_LCA           =  8
 92  integer,public,save :: LIBPAW_XC_FAMILY_OEP           = 16
 93  integer,public,save :: LIBPAW_XC_FAMILY_HYB_GGA       = 32
 94  integer,public,save :: LIBPAW_XC_FAMILY_HYB_MGGA      = 64
 95  integer,public,save :: LIBPAW_XC_FAMILY_HYB_LDA       =128
 96  integer,public,save :: LIBPAW_XC_FLAGS_HAVE_EXC       =  1
 97  integer,public,save :: LIBPAW_XC_FLAGS_HAVE_VXC       =  2
 98  integer,public,save :: LIBPAW_XC_FLAGS_HAVE_FXC       =  4
 99  integer,public,save :: LIBPAW_XC_FLAGS_HAVE_KXC       =  8
100  integer,public,save :: LIBPAW_XC_FLAGS_HAVE_LXC       = 16
101  integer,public,save :: LIBPAW_XC_FLAGS_NEEDS_LAPLACIAN= 32768
102  integer,public,save :: LIBPAW_XC_EXCHANGE             =  0
103  integer,public,save :: LIBPAW_XC_CORRELATION          =  1
104  integer,public,save :: LIBPAW_XC_EXCHANGE_CORRELATION =  2
105  integer,public,save :: LIBPAW_XC_KINETIC              =  3
106  integer,public,save :: LIBPAW_XC_SINGLE_PRECISION     =  0
107  logical,private,save :: libpaw_xc_constants_initialized=.false.
108 
109 !XC functional public type
110  type,public :: libpaw_libxc_type
111    integer  :: id              ! identifier
112    integer  :: family          ! LDA, GGA, etc.
113    integer  :: kind            ! EXCHANGE, CORRELATION, etc.
114    integer  :: nspin           ! # of spin components
115    integer  :: abi_ixc         ! Abinit IXC id for this functional
116    logical  :: has_exc         ! TRUE is exc is available for the functional
117    logical  :: has_vxc         ! TRUE is vxc is available for the functional
118    logical  :: has_fxc         ! TRUE is fxc is available for the functional
119    logical  :: has_kxc         ! TRUE is kxc is available for the functional
120    logical  :: needs_laplacian ! TRUE is functional needs laplacian of density
121    logical  :: is_hybrid       ! TRUE is functional is a hybrid functional
122    real(dp) :: hyb_mixing      ! Hybrid functional: mixing factor of Fock contribution (default=0)
123    real(dp) :: hyb_mixing_sr   ! Hybrid functional: mixing factor of SR Fock contribution (default=0)
124    real(dp) :: hyb_range       ! Range (for separation) for a hybrid functional (default=0)
125    real(dp) :: temperature     ! Electronic temperature; if <=0, the functional doesnt depend on it
126    real(dp) :: xc_tb09_c       ! Special TB09 functional parameter
127    real(dp) :: sigma_threshold ! Value of a threshold to be applied on density gradient (sigma)
128                                ! (temporary dur to a libxc bug) - If <0, apply no filter
129 #ifdef LIBPAW_ISO_C_BINDING
130    type(C_PTR),pointer :: conf => null() ! C pointer to the functional itself
131 #endif
132  end type libpaw_libxc_type
133 
134 !List of functionals on which a filter has to be applied on sigma (density gradient)
135 !  This should be done by libXC via _set_sigma_threshold but this is not (libXC 6)
136  real(dp),parameter :: libpaw_sigma_threshold_def = 1.0e-25_dp
137  integer,parameter :: libpaw_n_sigma_filtered = 17
138  character(len=28) :: libpaw_sigma_filtered(libpaw_n_sigma_filtered) = &
139 &  ['XC_HYB_GGA_XC_HSE03         ','XC_HYB_GGA_XC_HSE06         ','XC_HYB_GGA_XC_HJS_PBE       ',&
140 &   'XC_HYB_GGA_XC_HJS_PBE_SOL   ','XC_HYB_GGA_XC_HJS_B88       ','XC_HYB_GGA_XC_HJS_B97X      ',&
141 &   'XC_HYB_GGA_XC_LRC_WPBEH     ','XC_HYB_GGA_XC_LRC_WPBE      ','XC_HYB_GGA_XC_LC_WPBE       ',&
142 &   'XC_HYB_GGA_XC_HSE12         ','XC_HYB_GGA_XC_HSE12S        ','XC_HYB_GGA_XC_HSE_SOL       ',&
143 &   'XC_HYB_GGA_XC_LC_WPBE_WHS   ','XC_HYB_GGA_XC_LC_WPBEH_WHS  ','XC_HYB_GGA_XC_LC_WPBE08_WHS ',&
144 &   'XC_HYB_GGA_XC_LC_WPBESOL_WHS','XC_HYB_GGA_XC_WHPBE0        ']
145 
146 !----------------------------------------------------------------------
147 
148 !Private global XC functional
149  type(libpaw_libxc_type),target,save :: paw_xc_global(2)
150 
151 !----------------------------------------------------------------------
152 
153 !Interfaces for C bindings
154 #ifdef LIBPAW_ISO_C_BINDING
155  interface
156    integer(C_INT) function xc_func_init(xc_func,functional,nspin) bind(C,name="xc_func_init")
157      use, intrinsic :: iso_c_binding, only : C_INT,C_PTR
158      integer(C_INT),value :: functional,nspin
159      type(C_PTR) :: xc_func
160    end function xc_func_init
161  end interface
162 !
163  interface
164    subroutine xc_func_end(xc_func) bind(C,name="xc_func_end")
165      use, intrinsic :: iso_c_binding, only : C_PTR
166      type(C_PTR) :: xc_func
167    end subroutine xc_func_end
168  end interface
169 !
170  interface
171    integer(C_INT) function xc_functional_get_number(name) &
172 &                          bind(C,name="xc_functional_get_number")
173      use, intrinsic :: iso_c_binding, only : C_INT,C_PTR
174      type(C_PTR),value :: name
175    end function xc_functional_get_number
176  end interface
177 !
178  interface
179    type(C_PTR) function xc_functional_get_name(number) &
180 &                       bind(C,name="xc_functional_get_name")
181      use, intrinsic :: iso_c_binding, only : C_INT,C_PTR
182      integer(C_INT),value :: number
183    end function xc_functional_get_name
184  end interface
185 !
186  interface
187    integer(C_INT) function xc_family_from_id(id,family,number) &
188 &                          bind(C,name="xc_family_from_id")
189      use, intrinsic :: iso_c_binding, only : C_INT,C_PTR
190      integer(C_INT),value :: id
191      type(C_PTR),value :: family,number
192    end function xc_family_from_id
193  end interface
194 !
195  interface
196    subroutine xc_hyb_cam_coef(xc_func,omega,alpha,beta) &
197 &             bind(C,name="xc_hyb_cam_coef")
198      use, intrinsic :: iso_c_binding, only : C_DOUBLE,C_PTR
199      real(C_DOUBLE) :: omega,alpha,beta
200      type(C_PTR) :: xc_func
201    end subroutine xc_hyb_cam_coef
202  end interface
203 !
204  interface
205    subroutine libpaw_xc_get_lda(xc_func,np,rho,zk,vrho,v2rho2,v3rho3) &
206 &             bind(C,name="libpaw_xc_get_lda")
207      use, intrinsic :: iso_c_binding, only : C_INT,C_PTR
208      integer(C_INT),value :: np
209      type(C_PTR),value :: rho,zk,vrho,v2rho2,v3rho3
210      type(C_PTR) :: xc_func
211    end subroutine libpaw_xc_get_lda
212  end interface
213 !
214  interface
215    subroutine libpaw_xc_get_gga(xc_func,np,rho,sigma,zk,vrho,vsigma, &
216 &             v2rho2,v2rhosigma,v2sigma2,v3rho3,v3rho2sigma,v3rhosigma2,v3sigma3) &
217 &             bind(C,name="libpaw_xc_get_gga")
218      use, intrinsic :: iso_c_binding, only : C_INT,C_PTR
219      integer(C_INT),value :: np
220      type(C_PTR),value :: rho,sigma,zk,vrho,vsigma,v2rho2,v2rhosigma,v2sigma2, &
221 &                         v3rho3,v3rho2sigma,v3rhosigma2,v3sigma3
222      type(C_PTR) :: xc_func
223    end subroutine libpaw_xc_get_gga
224  end interface
225 !
226  interface
227    subroutine libpaw_xc_get_mgga(xc_func,np,rho,sigma,lapl,tau,zk,vrho,vsigma,vlapl,vtau, &
228 &             v2rho2,v2rhosigma,v2rholapl,v2rhotau,v2sigma2,v2sigmalapl, &
229 &             v2sigmatau,v2lapl2,v2lapltau,v2tau2) &
230 &             bind(C,name="libpaw_xc_get_mgga")
231      use, intrinsic :: iso_c_binding, only : C_INT,C_PTR
232      integer(C_INT),value :: np
233      type(C_PTR),value :: rho,sigma,lapl,tau,zk,vrho,vsigma,vlapl,vtau, &
234 &                         v2rho2,v2sigma2,v2lapl2,v2tau2,v2rhosigma,v2rholapl,v2rhotau, &
235 &                         v2sigmalapl,v2sigmatau,v2lapltau
236      type(C_PTR) :: xc_func
237    end subroutine libpaw_xc_get_mgga
238  end interface
239 !
240  interface
241    subroutine libpaw_xc_func_set_params(xc_func,params,n_params) bind(C)
242      use, intrinsic :: iso_c_binding, only : C_INT,C_DOUBLE,C_PTR
243      integer(C_INT),value :: n_params
244      real(C_DOUBLE) :: params(*)
245      type(C_PTR) :: xc_func
246    end subroutine libpaw_xc_func_set_params
247  end interface
248 !
249  interface
250    integer(C_INT) function libpaw_xc_func_set_params_name(xc_func,name,param) bind(C)
251      use, intrinsic :: iso_c_binding, only : C_INT,C_DOUBLE,C_PTR
252      real(C_DOUBLE) :: param
253      type(C_PTR) :: xc_func
254      type(C_PTR),value :: name
255    end function libpaw_xc_func_set_params_name
256  end interface
257 !
258  interface
259    type(C_PTR) function libpaw_xc_func_get_params_name(xc_func,ipar) bind(C)
260      use, intrinsic :: iso_c_binding, only : C_INT,C_PTR
261      type(C_PTR) :: xc_func
262      integer(C_INT) :: ipar
263    end function libpaw_xc_func_get_params_name
264  end interface
265 !
266  interface
267    type(C_PTR) function libpaw_xc_func_get_params_description(xc_func,ipar) bind(C)
268      use, intrinsic :: iso_c_binding, only : C_INT,C_PTR
269      type(C_PTR) :: xc_func
270      integer(C_INT) :: ipar
271    end function libpaw_xc_func_get_params_description
272  end interface
273 !
274  interface
275    subroutine libpaw_xc_func_set_density_threshold(xc_func,dens_threshold) bind(C)
276      use, intrinsic :: iso_c_binding, only : C_DOUBLE,C_PTR
277      real(C_DOUBLE) :: dens_threshold
278      type(C_PTR) :: xc_func
279    end subroutine libpaw_xc_func_set_density_threshold
280  end interface
281 !
282  interface
283    subroutine libpaw_xc_func_set_sig_threshold(xc_func,sigma_threshold) bind(C)
284      use, intrinsic :: iso_c_binding, only : C_DOUBLE,C_PTR
285      real(C_DOUBLE) :: sigma_threshold
286      type(C_PTR) :: xc_func
287    end subroutine libpaw_xc_func_set_sig_threshold
288  end interface
289 !
290  interface
291    integer(C_INT) function libpaw_xc_func_is_hybrid_from_id(func_id) bind(C)
292      use, intrinsic :: iso_c_binding, only : C_INT
293      integer(C_INT),value :: func_id
294    end function libpaw_xc_func_is_hybrid_from_id
295  end interface
296 !
297  interface
298    subroutine libpaw_xc_get_singleprecision_constant(xc_cst_singleprecision) &
299 &             bind(C,name="libpaw_xc_get_singleprecision_constant")
300      use, intrinsic :: iso_c_binding, only : C_INT
301      integer(C_INT) :: xc_cst_singleprecision
302    end subroutine libpaw_xc_get_singleprecision_constant
303  end interface
304 !
305  interface
306    subroutine libpaw_xc_get_family_constants(xc_cst_unknown,xc_cst_lda,xc_cst_gga, &
307 &             xc_cst_mgga,xc_cst_lca,xc_cst_oep,xc_cst_hyb_gga,xc_cst_hyb_mgga, &
308 &             xc_cst_hyb_lda) &
309 &             bind(C,name="libpaw_xc_get_family_constants")
310      use, intrinsic :: iso_c_binding, only : C_INT
311      integer(C_INT) :: xc_cst_unknown,xc_cst_lda,xc_cst_gga,xc_cst_mgga, &
312 &                      xc_cst_lca,xc_cst_oep,xc_cst_hyb_gga,xc_cst_hyb_mgga, &
313 &                      xc_cst_hyb_lda
314    end subroutine libpaw_xc_get_family_constants
315  end interface
316 !
317  interface
318    subroutine libpaw_xc_get_flags_constants(xc_cst_flags_have_exc,xc_cst_flags_have_vxc, &
319               xc_cst_flags_have_fxc,xc_cst_flags_have_kxc,xc_cst_flags_have_lxc, &
320 &             xc_cst_flags_needs_lapl) &
321 &             bind(C,name="libpaw_xc_get_flags_constants")
322      use, intrinsic :: iso_c_binding, only : C_INT
323      integer(C_INT) :: xc_cst_flags_have_exc,xc_cst_flags_have_vxc,xc_cst_flags_have_fxc, &
324 &                      xc_cst_flags_have_kxc,xc_cst_flags_have_lxc,xc_cst_flags_needs_lapl
325    end subroutine libpaw_xc_get_flags_constants
326  end interface
327 !
328  interface
329    subroutine libpaw_xc_get_kind_constants(xc_cst_exchange,xc_cst_correlation, &
330 &             xc_cst_exchange_correlation,xc_cst_kinetic) &
331 &             bind(C,name="libpaw_xc_get_kind_constants")
332      use, intrinsic :: iso_c_binding, only : C_INT
333      integer(C_INT) :: xc_cst_exchange,xc_cst_correlation, &
334 &                      xc_cst_exchange_correlation,xc_cst_kinetic
335    end subroutine libpaw_xc_get_kind_constants
336  end interface
337 !
338  interface
339    type(C_PTR) function libpaw_xc_func_type_malloc() &
340 &                       bind(C,name="libpaw_xc_func_type_malloc")
341      use, intrinsic :: iso_c_binding, only : C_PTR
342    end function libpaw_xc_func_type_malloc
343  end interface
344 !
345  interface
346    subroutine libpaw_xc_func_type_free(xc_func) &
347 &             bind(C,name="libpaw_xc_func_type_free")
348      use, intrinsic :: iso_c_binding, only : C_PTR
349      type(C_PTR) :: xc_func
350    end subroutine libpaw_xc_func_type_free
351  end interface
352 !
353  interface
354    type(C_PTR) function libpaw_xc_get_info_name(xc_func) &
355 &                       bind(C,name="libpaw_xc_get_info_name")
356      use, intrinsic :: iso_c_binding, only : C_PTR
357      type(C_PTR) :: xc_func
358    end function libpaw_xc_get_info_name
359  end interface
360 !
361  interface
362    type(C_PTR) function libpaw_xc_get_info_refs(xc_func,iref) &
363 &                       bind(C,name="libpaw_xc_get_info_refs")
364      use, intrinsic :: iso_c_binding, only : C_INT,C_PTR
365      type(C_PTR) :: xc_func
366      integer(C_INT) :: iref
367    end function libpaw_xc_get_info_refs
368  end interface
369 !
370  interface
371    integer(C_INT) function libpaw_xc_get_info_flags(xc_func) &
372 &                          bind(C,name="libpaw_xc_get_info_flags")
373      use, intrinsic :: iso_c_binding, only : C_INT,C_PTR
374      type(C_PTR) :: xc_func
375    end function libpaw_xc_get_info_flags
376  end interface
377 !
378  interface
379    integer(C_INT) function libpaw_xc_get_info_kind(xc_func) &
380 &                          bind(C,name="libpaw_xc_get_info_kind")
381      use, intrinsic :: iso_c_binding, only : C_INT,C_PTR
382      type(C_PTR) :: xc_func
383    end function libpaw_xc_get_info_kind
384  end interface
385 #endif
386 
387 contains

libpaw_libxc_funcs/libpaw_libxc_is_tb09 [ Functions ]

[ Top ] [ Functions ]

NAME

  libpaw_libxc_is_tb09

FUNCTION

  Test function to identify whether the presently used functional
  is Tran-Blaha 2009 or not

INPUTS

 [xc_functionals(2)]=<type(libxc_functional_type)>, optional argument
                     Handle for XC functionals

SOURCE

1023 logical function libpaw_libxc_is_tb09(xc_functionals) result(ans)
1024 
1025 !Arguments ------------------------------------
1026  type(libpaw_libxc_type),intent(in),optional :: xc_functionals(2)
1027 
1028 ! *************************************************************************
1029 
1030  ans  = .false.
1031  if (.not.libpaw_xc_constants_initialized) call libpaw_libxc_constants_load()
1032 
1033  if (present(xc_functionals)) then
1034    ans = any(xc_functionals%id == libpaw_libxc_getid('XC_MGGA_X_TB09'))
1035  else
1036    ans = any(paw_xc_global%id == libpaw_libxc_getid('XC_MGGA_X_TB09'))
1037  end if
1038 
1039 end function libpaw_libxc_is_tb09

libpaw_libxc_funcs/libpaw_libxc_set_hybridparams [ Functions ]

[ Top ] [ Functions ]

NAME

  libpaw_libxc_set_hybridparams

FUNCTION

  Set the parameters of an hybrid functional (mixing coefficient(s) and range separation)
  Applies on a (set of) functional(s)

INPUTS

 [hyb_mixing]       = mixing factor of Fock contribution
 [hyb_mixing_sr]    = mixing factor of short-range Fock contribution
 [hyb_range]        = Range (for separation)
 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals to initialize

OUTPUT

SOURCE

1497 subroutine libpaw_libxc_set_hybridparams(hyb_mixing,hyb_mixing_sr,hyb_range,xc_functionals)
1498 
1499 !Arguments ------------------------------------
1500  real(dp),intent(in),optional :: hyb_mixing,hyb_mixing_sr,hyb_range
1501  type(libpaw_libxc_type),intent(in),optional,target :: xc_functionals(2)
1502 !Local variables -------------------------------
1503  integer :: ii,id_pbe0,id_hse03,id_hse06
1504  logical :: is_pbe0,is_hse
1505  character(len=500) :: msg
1506  type(libpaw_libxc_type),pointer :: xc_func
1507 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
1508  integer(C_INT) :: npar_c
1509  real(C_DOUBLE) :: alpha_c,beta_c,omega_c,param_c(3)
1510 #endif
1511 
1512 ! *************************************************************************
1513 
1514  is_pbe0=.false.
1515  is_hse =.false.
1516  id_pbe0=libpaw_libxc_getid('HYB_GGA_XC_PBEH')
1517  id_hse03=libpaw_libxc_getid('HYB_GGA_XC_HSE03')
1518  id_hse06=libpaw_libxc_getid('HYB_GGA_XC_HSE06')
1519 
1520  do ii = 1, 2
1521 
1522 !  Select XC functional
1523    if (present(xc_functionals)) then
1524      xc_func => xc_functionals(ii)
1525    else
1526      xc_func => paw_xc_global(ii)
1527    end if
1528 
1529 !  Doesnt work with all hybrid functionals
1530    if (is_pbe0.or.is_hse) then
1531      msg='Invalid XC functional: contains 2 hybrid exchange functionals!'
1532      LIBPAW_ERROR(msg)
1533    end if
1534    is_pbe0=(xc_func%id==id_pbe0)
1535    is_hse=((xc_func%id==id_hse03).or.(xc_func%id==id_hse06))
1536    if ((.not.is_pbe0).and.(.not.is_hse)) cycle
1537 
1538 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
1539 !  First retrieve current values of parameters
1540    call xc_hyb_cam_coef(xc_func%conf,omega_c,alpha_c,beta_c)
1541 
1542 !  New values for parameters
1543    if (present(hyb_mixing)) alpha_c=real(hyb_mixing,kind=C_DOUBLE)
1544    if (present(hyb_mixing_sr)) beta_c=real(hyb_mixing_sr,kind=C_DOUBLE)
1545    if (present(hyb_range)) omega_c=real(hyb_range,kind=C_DOUBLE)
1546 
1547 !  PBE0: set parameters
1548    if (is_pbe0) then
1549      npar_c=int(1,kind=C_INT) ; param_c(1)=alpha_c
1550      call libpaw_xc_func_set_params(xc_func%conf,param_c,npar_c)
1551    end if
1552 
1553 !  HSE: set parameters
1554    if (is_hse) then
1555      npar_c=int(3,kind=C_INT)
1556      param_c(1)=beta_c;param_c(2:3)=omega_c
1557      call libpaw_xc_func_set_params(xc_func%conf,param_c,npar_c)
1558    end if
1559 
1560 #else
1561 !  This is to avoid unused arguments
1562    if(.false. .and. present(hyb_mixing) .and. present(hyb_mixing_sr) .and. present(hyb_range))then
1563      msg='One should not be here'
1564    endif
1565 #endif
1566 
1567  end do
1568 
1569  if ((.not.is_pbe0).and.(.not.is_hse)) then
1570    msg='Invalid XC functional: not able to change parameters for this functional!'
1571    LIBPAW_WARNING(msg)
1572  end if
1573 
1574 end subroutine libpaw_libxc_set_hybridparams

libpaw_libxc_funcs/libpaw_libxcset_c_tb09 [ Functions ]

[ Top ] [ Functions ]

NAME

  libpaw_libxc_set_c_tb09

FUNCTION

  Set c parameter for the Tran-Blaha 2009 functional

INPUTS

 xc_c_tb09= value of the c parameter to set for the TB09 functional
 [xc_functionals(2)]=<type(libxc_functional_type)>, optional argument
                     Handle for XC functionals

SOURCE

1058 subroutine libpaw_libxc_set_c_tb09(xc_tb09_c,xc_functionals)
1059 
1060 !Arguments ------------------------------------
1061  real(dp),intent(in) :: xc_tb09_c
1062  type(libpaw_libxc_type),intent(inout),optional :: xc_functionals(2)
1063 !Local variables -------------------------------
1064  integer :: ii
1065 
1066 ! *************************************************************************
1067 
1068  if (present(xc_functionals)) then
1069    do ii=1,2
1070      if (xc_functionals(ii)%id == libpaw_libxc_getid('XC_MGGA_X_TB09')) then
1071        xc_functionals(ii)%xc_tb09_c = xc_tb09_c
1072      end if
1073    end do
1074  else
1075    do ii=1,2
1076      if (paw_xc_global(ii)%id == libpaw_libxc_getid('XC_MGGA_X_TB09')) then
1077        paw_xc_global(ii)%xc_tb09_c = xc_tb09_c
1078      end if
1079    end do
1080  end if
1081 
1082 end subroutine libpaw_libxc_set_c_tb09

m_libpaw_libxc_funcs/char_c_to_f [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  char_c_to_f

FUNCTION

 Helper function to convert a C string to a Fortran string
 Based on a routine by Joseph M. Krahn

INPUTS

  c_string=C string

OUTPUT

  f_string=Fortran string

SOURCE

2458 #if defined LIBPAW_ISO_C_BINDING
2459 subroutine char_c_to_f(c_string,f_string)
2460 !Arguments ------------------------------------
2461  character(kind=C_CHAR,len=1),intent(in) :: c_string(*)
2462  character(len=*),intent(out) :: f_string
2463 !Local variables -------------------------------
2464  integer :: ii
2465 !! *************************************************************************
2466  ii=1
2467  do while(c_string(ii)/=C_NULL_CHAR.and.ii<=len(f_string))
2468    f_string(ii:ii)=c_string(ii) ; ii=ii+1
2469  end do
2470  if (ii<len(f_string)) f_string(ii:)=' '
2471  end subroutine char_c_to_f
2472 #endif

m_libpaw_libxc_funcs/char_f_to_c [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  char_f_to_c

FUNCTION

 Helper function to convert a Fortran string to a C string
 Based on a routine by Joseph M. Krahn

INPUTS

  f_string=Fortran string

OUTPUT

  c_string=C string

SOURCE

2423 #if defined LIBPAW_ISO_C_BINDING
2424 function char_f_to_c(f_string) result(c_string)
2425 !Arguments ------------------------------------
2426  character(len=*),intent(in) :: f_string
2427  character(kind=C_CHAR,len=1) :: c_string(len_trim(f_string)+1)
2428 !Local variables -------------------------------
2429  integer :: ii,strlen
2430 !! *************************************************************************
2431  strlen=len_trim(f_string)
2432  forall(ii=1:strlen)
2433    c_string(ii)=f_string(ii:ii)
2434  end forall
2435  c_string(strlen+1)=C_NULL_CHAR
2436  end function char_f_to_c
2437 #endif

m_libpaw_libxc_funcs/libpaw_libxc_check [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_check

FUNCTION

  Check if the code has been compiled with an usable version of libXC

INPUTS

 [stop_if_error]=optional flag; if TRUE the code stops if libXC is not correctly used

SOURCE

404  function libpaw_libxc_check(stop_if_error)
405 
406 !Arguments ------------------------------------
407  logical :: libpaw_libxc_check
408  logical,intent(in),optional :: stop_if_error
409 !Local variables-------------------------------
410  character(len=100) :: msg
411 
412 ! *************************************************************************
413 
414 #if defined LIBPAW_HAVE_LIBXC
415 #if defined LIBPAW_ISO_C_BINDING
416  if (.not.libpaw_xc_constants_initialized) call libpaw_libxc_constants_load()
417  if (LIBPAW_XC_SINGLE_PRECISION==1) then
418    libpaw_libxc_check=.false.
419    msg='LibXC should be compiled with double precision!'
420  end if
421 #else
422  libpaw_libxc_check=.false.
423  msg='LibXC cannot be used without ISO_C_BINDING support by the Fortran compiler!'
424 #endif
425 #else
426  libpaw_libxc_check=.false.
427  msg='LibPAW was not compiled with LibXC support.'
428 #endif
429 
430  if (present(stop_if_error)) then
431    if (stop_if_error.and.trim(msg)/="") then
432      LIBPAW_ERROR(msg)
433    end if
434  end if
435 
436  end function libpaw_libxc_check

m_libpaw_libxc_funcs/libpaw_libxc_compute_tb09 [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_compute_tb09

FUNCTION

  Compute c parameter for Tran-Blaha 2009 functional and set it

INPUTS

 npts=number of of points for the density
 nspden=number of spin-density components
 rho(npts,nspden)=electronic density
 grho2(npts,nspden)=squared gradient of the density

OUTPUT

SIDE EFFECTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals to initialize

SOURCE

2108  subroutine libpaw_libxc_compute_tb09(npts,nspden,rho,grho2,xc_functionals)
2109 
2110 !Arguments ------------------------------------
2111  integer, intent(in) :: npts,nspden
2112  real(dp),intent(in)  :: rho(npts,nspden),grho2(npts,2*min(nspden,2)-1)
2113  type(libpaw_libxc_type),intent(inout),optional,target :: xc_functionals(2)
2114 !Local variables -------------------------------
2115 !scalars
2116  integer  :: ii,ipts
2117  logical :: fixed_c_tb09,is_mgga_tb09
2118  real(dp) :: cc
2119 !arrays
2120  type(libpaw_libxc_type),pointer :: xc_funcs(:)
2121  real(dp),allocatable :: gnon(:)
2122 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
2123  integer(C_INT) :: npar_c=int(2,kind=C_INT)
2124  real(C_DOUBLE) :: param_c(2)
2125 #endif
2126 
2127 ! *************************************************************************
2128 
2129  if (.not.libpaw_xc_constants_initialized) call libpaw_libxc_constants_load()
2130 
2131 !Select XC functional(s)
2132  if (present(xc_functionals)) then
2133    xc_funcs => xc_functionals
2134  else
2135    xc_funcs => paw_xc_global
2136  end if
2137 
2138  is_mgga_tb09=(any(xc_funcs%id==libpaw_libxc_getid('XC_MGGA_X_TB09')))
2139  fixed_c_tb09=(any(abs(xc_funcs%xc_tb09_c-99.99_dp)>tol12))
2140 
2141  if (is_mgga_tb09) then
2142 
2143 !  C is fixed by the user
2144    if (fixed_c_tb09) then
2145      cc=zero
2146      do ii=1,2
2147        if (abs(xc_funcs(ii)%xc_tb09_c-99.99_dp)>tol12) cc=xc_funcs(ii)%xc_tb09_c
2148      end do
2149      !write(msg,'(2a,f9.6)' ) ch10,&
2150      !& 'In the mGGA functional TB09, c is fixed by the user and is equal to ',cc
2151      !call wrtout(std_out,msg,'COLL')
2152 !  C is computed
2153    else
2154      LIBPAW_ALLOCATE(gnon,(npts))
2155      do ipts=1,npts
2156        if (sum(rho(ipts,:))<=1e-7_dp) then
2157          gnon(ipts)=zero
2158        else
2159          if (nspden==1) then
2160            gnon(ipts)=sqrt(grho2(ipts,1))/rho(ipts,1)
2161          else
2162            gnon(ipts)=sqrt(grho2(ipts,3))/sum(rho(ipts,:))
2163          end if
2164        end if
2165      end do
2166      cc= -0.012_dp + 1.023_dp*sqrt(sum(gnon)/npts)
2167      LIBPAW_DEALLOCATE(gnon)
2168      !write(msg,'(2a,f9.6)' ) ch10,'In the mGGA functional TB09, c = ',cc
2169      !call wrtout(std_out,msg,'COLL')
2170    end if
2171 
2172 !  Set c in XC data structure
2173    do ii=1,2
2174      if (xc_funcs(ii)%id==libpaw_libxc_getid('XC_MGGA_X_TB09')) then
2175 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
2176      param_c(1)=real(cc,kind=C_DOUBLE) ; param_c(2)=real(0._dp,kind=C_DOUBLE)
2177      call libpaw_xc_func_set_params(xc_funcs(ii)%conf,param_c,npar_c)
2178 #endif
2179      end if
2180    end do
2181  end if
2182 
2183 end subroutine libpaw_libxc_compute_tb09

m_libpaw_libxc_funcs/libpaw_libxc_constants_load [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_constants_load

FUNCTION

  Load libXC constants from C headers

SOURCE

2365  subroutine libpaw_libxc_constants_load()
2366 
2367 !Local variables-------------------------------
2368 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
2369  integer(C_INT) :: i1,i2,i3,i4,i5,i6,i7,i8,i9
2370 #endif
2371 
2372 ! *************************************************************************
2373 
2374 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
2375   call libpaw_xc_get_singleprecision_constant(i1)
2376   LIBPAW_XC_SINGLE_PRECISION     = int(i1)
2377   call libpaw_xc_get_family_constants(i1,i2,i3,i4,i5,i6,i7,i8,i9)
2378   LIBPAW_XC_FAMILY_UNKNOWN       = int(i1)
2379   LIBPAW_XC_FAMILY_LDA           = int(i2)
2380   LIBPAW_XC_FAMILY_GGA           = int(i3)
2381   LIBPAW_XC_FAMILY_MGGA          = int(i4)
2382   LIBPAW_XC_FAMILY_LCA           = int(i5)
2383   LIBPAW_XC_FAMILY_OEP           = int(i6)
2384   LIBPAW_XC_FAMILY_HYB_GGA       = int(i7)
2385   LIBPAW_XC_FAMILY_HYB_MGGA      = int(i8)
2386   LIBPAW_XC_FAMILY_HYB_LDA       = int(i9)
2387   call libpaw_xc_get_flags_constants(i1,i2,i3,i4,i5,i6)
2388   LIBPAW_XC_FLAGS_HAVE_EXC       = int(i1)
2389   LIBPAW_XC_FLAGS_HAVE_VXC       = int(i2)
2390   LIBPAW_XC_FLAGS_HAVE_FXC       = int(i3)
2391   LIBPAW_XC_FLAGS_HAVE_KXC       = int(i4)
2392   LIBPAW_XC_FLAGS_HAVE_LXC       = int(i5)
2393   LIBPAW_XC_FLAGS_NEEDS_LAPLACIAN= int(i6)
2394   call libpaw_xc_get_kind_constants(i1,i2,i3,i4)
2395   LIBPAW_XC_EXCHANGE             = int(i1)
2396   LIBPAW_XC_CORRELATION          = int(i2)
2397   LIBPAW_XC_EXCHANGE_CORRELATION = int(i3)
2398   LIBPAW_XC_KINETIC              = int(i4)
2399   libpaw_xc_constants_initialized=.true.
2400 #endif
2401 
2402  end subroutine libpaw_libxc_constants_load

m_libpaw_libxc_funcs/libpaw_libxc_depends_on_temp [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_depends_on_temp

FUNCTION

  Test function to identify whether a single XC functional
  depends on the electronic temperature or not

INPUTS

 xc_functional=<type(libpaw_libxc_type)>, handle for XC functional

SOURCE

2252 function libpaw_libxc_depends_on_temp(xc_functional)
2253 
2254 !Arguments ------------------------------------
2255  logical :: libpaw_libxc_depends_on_temp
2256  type(libpaw_libxc_type),intent(in) :: xc_functional
2257 !Local variables-------------------------------
2258 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
2259  integer(C_INT) :: ipar_c
2260  character(len=50) :: par_name
2261  character(kind=C_CHAR,len=1),pointer :: strg_c
2262 #endif
2263 
2264 ! *************************************************************************
2265 
2266  libpaw_libxc_depends_on_temp = .false.
2267 
2268 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
2269  ipar_c=0
2270  do while (ipar_c>=0)
2271    call c_f_pointer(libpaw_xc_func_get_params_name(xc_functional%conf,ipar_c),strg_c)
2272    if (associated(strg_c)) then
2273      call char_c_to_f(strg_c,par_name)
2274      if (trim(par_name)=="T") then
2275        libpaw_libxc_depends_on_temp=.true. ; exit
2276      end if
2277      ipar_c=ipar_c+1
2278    else
2279      ipar_c=-1
2280    end if
2281  end do
2282 
2283  if (.not.libpaw_libxc_depends_on_temp) then
2284 !  For libXC_version<5, these three functional were T-dependent
2285    libpaw_libxc_depends_on_temp = &
2286 &     (xc_functional%id==libpaw_libxc_getid('XC_LDA_XC_KSDT') .or. &
2287 &      xc_functional%id==libpaw_libxc_getid('XC_LDA_XC_GDSMFB') .or. &
2288 &      xc_functional%id==libpaw_libxc_getid('XC_LDA_XC_CORRKSDT'))
2289  end if
2290 
2291 #else
2292  if (.False.) write(std_out,*) xc_functional%id
2293 #endif
2294 
2295 end function libpaw_libxc_depends_on_temp

m_libpaw_libxc_funcs/libpaw_libxc_end [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_end

FUNCTION

  End usage of a (set of) XC functional(s).
  Call LibXC end function and deallocate module contents.

SIDE EFFECTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals to initialize

SOURCE

659  subroutine libpaw_libxc_end(xc_functionals)
660 
661 !Arguments ------------------------------------
662  type(libpaw_libxc_type),intent(inout),optional,target :: xc_functionals(2)
663 !Local variables-------------------------------
664  integer :: ii
665  type(libpaw_libxc_type),pointer :: xc_func
666 
667 ! *************************************************************************
668 
669  do ii = 1,2
670 
671 !  Select XC functional
672    if (present(xc_functionals)) then
673      xc_func => xc_functionals(ii)
674    else
675      xc_func => paw_xc_global(ii)
676    end if
677 
678    if (xc_func%id <= 0) cycle
679    xc_func%id=-1
680    xc_func%family=-1
681    xc_func%kind=-1
682    xc_func%nspin=1
683    xc_func%abi_ixc=huge(0)
684    xc_func%has_exc=.false.
685    xc_func%has_vxc=.false.
686    xc_func%has_fxc=.false.
687    xc_func%has_kxc=.false.
688    xc_func%needs_laplacian=.false.
689    xc_func%is_hybrid=.false.
690    xc_func%hyb_mixing_sr=zero
691    xc_func%hyb_range=zero
692    xc_func%xc_tb09_c=99.99_dp
693    xc_func%sigma_threshold=-one
694 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
695    if (associated(xc_func%conf)) then
696      call xc_func_end(xc_func%conf)
697      call libpaw_xc_func_type_free(c_loc(xc_func%conf))
698    end if
699 #endif
700 
701  end do
702 
703  end subroutine libpaw_libxc_end

m_libpaw_libxc_funcs/libpaw_libxc_family_from_id [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_family_from_id

FUNCTION

  Return family of a XC functional from its id

INPUTS

  xcid= id of a LibXC functional

SOURCE

838  function libpaw_libxc_family_from_id(xcid)
839 
840 !Arguments ------------------------------------
841  integer :: libpaw_libxc_family_from_id
842  integer,intent(in) :: xcid
843 !Local variables-------------------------------
844 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
845  integer(C_INT) :: xcid_c
846 #endif
847 
848 ! *************************************************************************
849 
850 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
851  xcid_c=int(xcid,kind=C_INT)
852  libpaw_libxc_family_from_id=int(xc_family_from_id(xcid_c,C_NULL_PTR,C_NULL_PTR))
853 #else
854  libpaw_libxc_family_from_id=-1
855  if (.false.) write(std_out,*) xcid
856 #endif
857 
858 end function libpaw_libxc_family_from_id

m_libpaw_libxc_funcs/libpaw_libxc_fullname [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_fullname

FUNCTION

  Return full name of a (set of) XC functional(s)

INPUTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals to initialize

SOURCE

721  function libpaw_libxc_fullname(xc_functionals)
722 
723 !Arguments ------------------------------------
724  character(len=100) :: libpaw_libxc_fullname
725  type(libpaw_libxc_type),intent(in),optional,target :: xc_functionals(2)
726 !Local variables-------------------------------
727  integer :: nxc
728  type(libpaw_libxc_type),pointer :: xc_funcs(:)
729 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
730  character(len=100) :: xcname
731  character(kind=C_CHAR,len=1),pointer :: strg_c
732 #endif
733 
734 ! *************************************************************************
735 
736  libpaw_libxc_fullname='No XC functional'
737 
738  if (present(xc_functionals)) then
739    xc_funcs => xc_functionals
740  else
741    xc_funcs => paw_xc_global
742  end if
743 
744  nxc=size(xc_funcs)
745  if (nxc<1) return
746 
747 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
748  if (nxc<2) then
749    if (xc_funcs(1)%id /= 0) then
750      call c_f_pointer(xc_functional_get_name(xc_funcs(1)%id),strg_c)
751      call char_c_to_f(strg_c,libpaw_libxc_fullname)
752    end if
753  else if (xc_funcs(1)%id <= 0) then
754    if (xc_funcs(2)%id /= 0) then
755      call c_f_pointer(xc_functional_get_name(xc_funcs(2)%id),strg_c)
756      call char_c_to_f(strg_c,libpaw_libxc_fullname)
757    end if
758  else if (xc_funcs(2)%id <= 0) then
759    if (xc_funcs(1)%id /= 0) then
760      call c_f_pointer(xc_functional_get_name(xc_funcs(1)%id),strg_c)
761      call char_c_to_f(strg_c,libpaw_libxc_fullname)
762    end if
763  else
764    call c_f_pointer(xc_functional_get_name(xc_funcs(1)%id),strg_c)
765    call char_c_to_f(strg_c,libpaw_libxc_fullname)
766    call c_f_pointer(xc_functional_get_name(xc_funcs(2)%id),strg_c)
767    call char_c_to_f(strg_c,xcname)
768    libpaw_libxc_fullname=trim(libpaw_libxc_fullname)//'+'//trim(xcname)
769  end if
770  libpaw_libxc_fullname=trim(libpaw_libxc_fullname)
771 #endif
772 
773 end function libpaw_libxc_fullname

m_libpaw_libxc_funcs/libpaw_libxc_get_hybridparams [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_get_hybridparams

FUNCTION

  Returns the parameters of an hybrid functional (mixing coefficient(s) and range separation)
  Applies on a (set of) functional(s)

INPUTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals to initialize

OUTPUT

  [hyb_mixing]  = mixing factor of Fock contribution
  [hyb_mixing_sr]= mixing factor of short-range Fock contribution
  [hyb_range]    = Range (for separation)

SOURCE

1410 subroutine libpaw_libxc_get_hybridparams(hyb_mixing,hyb_mixing_sr,hyb_range,xc_functionals)
1411 
1412 !Arguments ------------------------------------
1413  real(dp),intent(out),optional :: hyb_mixing,hyb_mixing_sr,hyb_range
1414  type(libpaw_libxc_type),intent(in),optional,target :: xc_functionals(2)
1415 !Local variables -------------------------------
1416  integer :: ii
1417  character(len=500) :: msg
1418  type(libpaw_libxc_type),pointer :: xc_func
1419 
1420 ! *************************************************************************
1421 
1422  if (present(hyb_mixing   )) hyb_mixing   =zero
1423  if (present(hyb_mixing_sr)) hyb_mixing_sr=zero
1424  if (present(hyb_range    )) hyb_range    =zero
1425 
1426  do ii = 1, 2
1427 
1428 !  Select XC functional
1429    if (present(xc_functionals)) then
1430      xc_func => xc_functionals(ii)
1431    else
1432      xc_func => paw_xc_global(ii)
1433    end if
1434 
1435 !  Mixing coefficient for the Fock contribution
1436    if (present(hyb_mixing)) then
1437      if (abs(xc_func%hyb_mixing) > tol8) then
1438        if (abs(hyb_mixing) <= tol8) then
1439          hyb_mixing=xc_func%hyb_mixing
1440        else
1441          msg='Invalid XC functional: contains 2 hybrid exchange functionals!'
1442          LIBPAW_ERROR(msg)
1443        end if
1444      end if
1445    end if
1446 
1447 !  Mixing coefficient for the short-range Fock contribution
1448    if (present(hyb_mixing_sr)) then
1449      if (abs(xc_func%hyb_mixing_sr) > tol8) then
1450        if (abs(hyb_mixing_sr) <= tol8) then
1451          hyb_mixing_sr=xc_func%hyb_mixing_sr
1452        else
1453          msg='Invalid XC functional: contains 2 hybrid exchange functionals!'
1454          LIBPAW_ERROR(msg)
1455        end if
1456      end if
1457    end if
1458 
1459 !  Range separation
1460    if (present(hyb_range)) then
1461      if (abs(xc_func%hyb_range) > tol8) then
1462        if (abs(hyb_range) <= tol8) then
1463          hyb_range=xc_func%hyb_range
1464        else
1465          msg='Invalid XC functional: contains 2 hybrid exchange functionals!'
1466          LIBPAW_ERROR(msg)
1467        end if
1468      end if
1469    end if
1470 
1471  end do
1472 
1473 end subroutine libpaw_libxc_get_hybridparams

m_libpaw_libxc_funcs/libpaw_libxc_getid [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_getid

FUNCTION

  Return identifer of a XC functional from its name
  Return -1 if undefined

INPUTS

  xcname= string containing the name of a XC functional

SOURCE

791  function libpaw_libxc_getid(xcname)
792 
793 !Arguments ------------------------------------
794  integer :: libpaw_libxc_getid
795  character(len=*),intent(in) :: xcname
796 !Local variables-------------------------------
797 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
798  character(len=256) :: str
799  character(kind=C_CHAR,len=1),target :: name_c(len_trim(xcname)+1)
800  character(kind=C_CHAR,len=1),target :: name_c_xc(len_trim(xcname)-2)
801  type(C_PTR) :: name_c_ptr
802 #endif
803 
804 ! *************************************************************************
805 
806 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
807  str=trim(xcname)
808  if (xcname(1:3)=="XC_".or.xcname(1:3)=="xc_") then
809    str=xcname(4:);name_c_xc=char_f_to_c(str)
810    name_c_ptr=c_loc(name_c_xc)
811  else
812    name_c=char_f_to_c(str)
813    name_c_ptr=c_loc(name_c)
814  end if
815  libpaw_libxc_getid=int(xc_functional_get_number(name_c_ptr))
816 #else
817  libpaw_libxc_getid=-1
818  if (.false.) write(std_out,*) xcname
819 #endif
820 
821 end function libpaw_libxc_getid

m_libpaw_libxc_funcs/libpaw_libxc_getrefs [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_getrefs

FUNCTION

  Return the reference(s) of a single XC functional

INPUTS

  xc_functional=<type(libpaw_libxc_type)>, handle for XC functional

OUTPUT

  xcrefs(:)= references(s) of the functional

SOURCE

2203 subroutine libpaw_libxc_getrefs(xcrefs,xc_functional)
2204 
2205 !Arguments ------------------------------------
2206  character(len=*),intent(out) :: xcrefs(:)
2207  type(libpaw_libxc_type),intent(in) :: xc_functional
2208 
2209 !Local variables-------------------------------
2210 #if defined LIBPAW_HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
2211  integer(C_INT) :: iref_c
2212  character(kind=C_CHAR,len=1),pointer :: strg_c
2213 #endif
2214 
2215 ! *************************************************************************
2216 
2217  xcrefs(:)=''
2218 
2219 #if defined LIBPAW_HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
2220  iref_c=0
2221  do while (iref_c>=0.and.iref_c<size(xcrefs))
2222    call c_f_pointer(libpaw_xc_get_info_refs(xc_functional%conf,iref_c),strg_c)
2223    if (associated(strg_c)) then
2224      call char_c_to_f(strg_c,xcrefs(iref_c+1))
2225      iref_c=iref_c+1
2226    else
2227      iref_c=-1
2228    end if
2229  end do
2230 #else
2231  if (.False.) write(std_out,*)xc_functional%id
2232 #endif
2233 
2234 end subroutine libpaw_libxc_getrefs

m_libpaw_libxc_funcs/libpaw_libxc_getvxc [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_getvxc

FUNCTION

  Return XC potential and energy, from input density (gradient etc...)

INPUTS

 ndvxc=size of dvxc
 nd2vxc=size of d2vxc
 npts=number of of points for the density
 nspden=number of spin-density components
 order=requested order of derivation
 rho(npts,nspden)=electronic density
 [grho2(npts,nspden)]=squared gradient of the density
 [lrho(npts,nspden)]=laplacian of the density
 [tau(npts,nspden)]= kinetic energy density

OUTPUT

 exc(npts)=XC energy density
 vxc(npts,nspden)=derivative of the energy density wrt to the density
 [vxclrho(npts,nspden)]=derivative of the energy density wrt to the density laplacian
 [vxctau(npts,nspden)]=derivative of the energy density wrt to the kinetic energy density
 [dvxc(npts,ndvxc)]=2nd derivative of the energy density wrt to the density
 [vxcgr(npts,3)]=2nd derivative of the energy density wrt to the gradient
                 2nd derivative of the energy density wrt to the density and the gradient
 [d2vxc(npts,nd2vxc)]=3rd derivative of the energy density wrt to the density

SIDE EFFECTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals to initialize

SOURCE

1747  subroutine libpaw_libxc_getvxc(ndvxc,nd2vxc,npts,nspden,order,rho,exc,vxc,&
1748 &           grho2,vxcgr,lrho,vxclrho,tau,vxctau,dvxc,d2vxc,xc_functionals) ! Optional arguments
1749 
1750 !Arguments ------------------------------------
1751  integer, intent(in) :: ndvxc,nd2vxc,npts,nspden,order
1752  real(dp),intent(in)  :: rho(npts,nspden)
1753  real(dp),intent(out) :: vxc(npts,nspden),exc(npts)
1754  real(dp),intent(in),optional :: grho2(npts,2*min(nspden,2)-1)
1755  real(dp),intent(out),optional :: vxcgr(npts,3)
1756  real(dp),intent(in),optional :: lrho(npts,nspden)
1757  real(dp),intent(out),optional :: vxclrho(npts,nspden)
1758  real(dp),intent(in),optional :: tau(npts,nspden)
1759  real(dp),intent(out),optional :: vxctau(npts,nspden)
1760  real(dp),intent(out),optional :: dvxc(npts,ndvxc)
1761  real(dp),intent(out),optional :: d2vxc(npts,nd2vxc)
1762  type(libpaw_libxc_type),intent(inout),optional,target :: xc_functionals(2)
1763 !Local variables -------------------------------
1764 !scalars
1765  integer  :: ii,ipts
1766  logical :: is_gga,is_mgga,needs_laplacian,has_sigma_threshold
1767  character(len=500) :: msg
1768  real(dp) :: sigma_threshold_max
1769 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
1770  type(C_PTR) :: rho_c,sigma_c,lrho_c,tau_c
1771 #endif
1772 !arrays
1773  real(dp),target :: rhotmp(nspden),sigma(3),exctmp,vxctmp(nspden),vsigma(3)
1774  real(dp),target :: v2rho2(3),v2rhosigma(6),v2sigma2(6)
1775  real(dp),target :: v2rholapl(3),v2sigmalapl(6),v2lapl2(3)
1776  real(dp),target :: v2rhotau(3),v2sigmatau(6),v2lapltau(3),v2tau2(3)
1777  real(dp),target :: v3rho3(4),v3rho2sigma(9),v3rhosigma2(12),v3sigma3(10)
1778  real(dp),target :: lrhotmp(nspden),tautmp(nspden),vlrho(nspden),vtau(nspden)
1779  type(libpaw_libxc_type),pointer :: xc_funcs(:)
1780 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
1781  type(C_PTR) :: exc_c(2),vxc_c(2),vsigma_c(2),vlrho_c(2),vtau_c(2)
1782  type(C_PTR) :: v2rho2_c(2),v2rhosigma_c(2),v2sigma2_c(2)
1783  type(C_PTR) :: v2rholapl_c(2),v2sigmalapl_c(2),v2lapl2_c(2)
1784  type(C_PTR) :: v2rhotau_c(2),v2sigmatau_c(2),v2lapltau_c(2),v2tau2_c(2)
1785 type(C_PTR) :: v3rho3_c(2),v3rho2sigma_c(2),v3rhosigma2_c(2),v3sigma3_c(2)
1786 #endif
1787 
1788 ! *************************************************************************
1789 
1790  if (.not.libpaw_xc_constants_initialized) call libpaw_libxc_constants_load()
1791 
1792 !Select XC functional(s)
1793  if (present(xc_functionals)) then
1794    xc_funcs => xc_functionals
1795  else
1796    xc_funcs => paw_xc_global
1797  end if
1798 
1799  is_gga =libpaw_libxc_isgga (xc_funcs)
1800  is_mgga=libpaw_libxc_ismgga(xc_funcs)
1801  needs_laplacian=(libpaw_libxc_needs_laplacian(xc_funcs).and.present(lrho))
1802 
1803  sigma_threshold_max=maxval(xc_funcs(:)%sigma_threshold,mask=(xc_funcs(:)%id>0))
1804  has_sigma_threshold=(sigma_threshold_max>zero)
1805 
1806  if (is_gga.and.(.not.present(grho2))) then
1807    msg='GGA needs gradient of density!'
1808    LIBPAW_BUG(msg)
1809  end if
1810  if (is_mgga) then
1811    if (present(vxctau).and.(.not.present(tau))) then
1812      msg='meta-GGA needs tau!'
1813      LIBPAW_BUG(msg)
1814    end if
1815    if (needs_laplacian) then
1816      if (present(vxclrho).and.(.not.present(lrho))) then
1817        msg='meta-GGA needs lrho!'
1818        LIBPAW_BUG(msg)
1819      end if
1820    end if
1821  endif
1822 
1823 !Inititalize all output arrays to zero
1824  exc=zero ; vxc=zero
1825  if (present(dvxc)) dvxc=zero
1826  if (present(d2vxc)) d2vxc=zero
1827  if (is_gga.or.is_mgga.and.present(vxcgr)) vxcgr=zero
1828  if (is_mgga.and.present(vxclrho)) vxclrho=zero
1829  if (is_mgga.and.present(vxctau)) vxctau=zero
1830 
1831 !Determine which XC outputs can be computed
1832 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
1833  do ii = 1,2
1834    if (xc_funcs(ii)%has_exc) then
1835      exc_c(ii)=c_loc(exctmp)
1836    else
1837      exc_c(ii)=C_NULL_PTR
1838    end if
1839    if (xc_funcs(ii)%has_vxc) then
1840      vxc_c(ii)=c_loc(vxctmp)
1841      vsigma_c(ii)=c_loc(vsigma)
1842      vtau_c(ii)=c_loc(vtau)
1843      vlrho_c(ii)=c_loc(vlrho)
1844    else
1845      vxc_c(ii)=C_NULL_PTR
1846      vsigma_c(ii)=c_NULL_PTR
1847      vtau_c(ii)=C_NULL_PTR
1848      vlrho_c(ii)=C_NULL_PTR
1849    end if
1850    if ((xc_funcs(ii)%has_fxc).and.(abs(order)>1)) then
1851      v2rho2_c(ii)=c_loc(v2rho2)
1852      v2sigma2_c(ii)=c_loc(v2sigma2)
1853      v2rhosigma_c(ii)=c_loc(v2rhosigma)
1854      if (is_mgga) then
1855        v2rholapl_c(ii)=c_loc(v2rholapl)
1856        v2sigmalapl_c(ii)=c_loc(v2sigmalapl)
1857        v2lapl2_c(ii)=c_loc(v2lapl2)
1858        v2rhotau_c(ii)=c_loc(v2rhotau)
1859        v2sigmatau_c(ii)=c_loc(v2sigmatau)
1860        v2lapltau_c(ii)=c_loc(v2lapltau)
1861        v2tau2_c(ii)=c_loc(v2tau2)
1862      end if
1863    else
1864      v2rho2_c(ii)=C_NULL_PTR
1865      v2sigma2_c(ii)=C_NULL_PTR
1866      v2rhosigma_c(ii)=C_NULL_PTR
1867      if (is_mgga) then
1868        v2rholapl_c(ii)=C_NULL_PTR
1869        v2sigmalapl_c(ii)=C_NULL_PTR
1870        v2lapl2_c(ii)=C_NULL_PTR
1871        v2rhotau_c(ii)=C_NULL_PTR
1872        v2sigmatau_c(ii)=C_NULL_PTR
1873        v2lapltau_c(ii)=C_NULL_PTR
1874        v2tau2_c(ii)=C_NULL_PTR
1875      end if
1876    end if
1877    if ((xc_funcs(ii)%has_kxc).and.(abs(order)>2)) then
1878      v3rho3_c(ii)=c_loc(v3rho3)
1879      v3sigma3_c(ii)=c_loc(v3sigma3)
1880      v3rho2sigma_c(ii)=c_loc(v3rho2sigma)
1881      v3rhosigma2_c(ii)=c_loc(v3rhosigma2)
1882    else
1883      v3rho3_c(ii)=C_NULL_PTR
1884      v3sigma3_c(ii)=C_NULL_PTR
1885      v3rho2sigma_c(ii)=C_NULL_PTR
1886      v3rhosigma2_c(ii)=C_NULL_PTR
1887    end if
1888  end do
1889 #endif
1890 
1891 !Initialize temporary arrays
1892 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
1893  rhotmp=zero ; rho_c=c_loc(rhotmp)
1894  if (is_gga.or.is_mgga) then
1895    sigma=zero ; sigma_c=c_loc(sigma)
1896  end if
1897  if (is_mgga) then
1898    tautmp=zero ; tau_c=c_loc(tautmp)
1899    lrhotmp=zero ; lrho_c=c_loc(lrhotmp)
1900  end if
1901 #endif
1902 
1903 !Some mGGA functionals require a special treatment
1904  if (is_mgga) then
1905    !TB09 functional requires the c parameter to be set
1906    call libpaw_libxc_compute_tb09(npts,nspden,rho,grho2,xc_funcs)
1907  end if
1908 
1909 !Loop over points
1910  do ipts=1,npts
1911 
1912 !  Convert the quantities provided to the ones needed by libxc
1913    if (nspden == 1) then
1914      ! rho_up is passed in the spin-unpolarized case, while the libxc
1915      ! expects the total density
1916      rhotmp(1:nspden) = two*rho(ipts,1:nspden)
1917    else
1918      rhotmp(1:nspden) = rho(ipts,1:nspden)
1919    end if
1920    if (is_gga.or.is_mgga) then
1921      if (nspden==1) then
1922        ! |grho_up|^2 is passed while Libxc needs |grho_tot|^2
1923        sigma(1) = four*grho2(ipts,1)
1924      else
1925        ! |grho_up|^2, |grho_dn|^2, and |grho_tot|^2 are passed
1926        ! while Libxc needs |grho_up|^2, grho_up.grho_dn, and |grho_dn|^2
1927        sigma(1) = grho2(ipts,1)
1928        sigma(2) = (grho2(ipts,3) - grho2(ipts,1) - grho2(ipts,2))/two
1929        sigma(3) = grho2(ipts,2)
1930      end if
1931      ! Apply a threshold on sigma (cannot be done in libxc6, at present)
1932      if (has_sigma_threshold) then
1933        do ii=1,2*nspden-1
1934          if (abs(sigma(ii))<=sigma_threshold_max) sigma(ii)=sigma_threshold_max
1935        end do
1936      end if
1937    end if
1938    if (is_mgga) then
1939      if (nspden==1) then
1940        tautmp(1:nspden) = two*tau(ipts,1:nspden)
1941        if (needs_laplacian) lrhotmp(1:nspden) = two*lrho(ipts,1:nspden)
1942      else
1943        tautmp(1:nspden) = tau(ipts,1:nspden)
1944        if (needs_laplacian) lrhotmp(1:nspden) = lrho(ipts,1:nspden)
1945      end if
1946    end if
1947 
1948 !  Loop over functionals
1949    do ii = 1,2
1950      if (xc_funcs(ii)%id<=0) cycle
1951 
1952 !    Get the energy and the potential (and possibly the other derivatives)
1953 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
1954      exctmp=zero ; vxctmp=zero
1955 !    ===== LDA =====
1956      if (xc_funcs(ii)%family==LIBPAW_XC_FAMILY_LDA) then
1957        exctmp=zero ; vxctmp=zero ; v2rho2=zero ; v3rho3=zero
1958        call libpaw_xc_get_lda(xc_funcs(ii)%conf,1,rho_c, &
1959 &                  exc_c(ii),vxc_c(ii),v2rho2_c(ii),v3rho3_c(ii))
1960 !    ===== GGA =====
1961      else if (xc_funcs(ii)%family==LIBPAW_XC_FAMILY_GGA.or. &
1962 &             xc_funcs(ii)%family==LIBPAW_XC_FAMILY_HYB_GGA) then
1963        exctmp=zero ; vxctmp=zero ; vsigma=zero
1964        v2rho2=zero ; v2sigma2=zero ; v2rhosigma=zero
1965        v3rho3=zero ; v3rho2sigma=zero ; v3rhosigma2=zero ; v3sigma3=zero
1966        call libpaw_xc_get_gga(xc_funcs(ii)%conf,1,rho_c,sigma_c, &
1967 &                  exc_c(ii),vxc_c(ii),vsigma_c(ii), &
1968 &                  v2rho2_c(ii),v2rhosigma_c(ii),v2sigma2_c(ii), &
1969 &                  v3rho3_c(ii),v3rho2sigma_c(ii),v3rhosigma2_c(ii),v3sigma3_c(ii))
1970 !    ===== mGGA =====
1971      else if (xc_funcs(ii)%family==LIBPAW_XC_FAMILY_MGGA.or. &
1972 &             xc_funcs(ii)%family==LIBPAW_XC_FAMILY_HYB_GGA) then
1973        exctmp=zero ; vxctmp=zero ; vsigma=zero ; vlrho=zero ; vtau=zero
1974        v2rho2=zero ; v2sigma2=zero ; v2rhosigma=zero
1975        ! At present, we don't use 2nd derivatives involving Tau or Laplacian
1976        call libpaw_xc_get_mgga(xc_funcs(ii)%conf,1,rho_c,sigma_c,lrho_c,tau_c, &
1977 &                  exc_c(ii),vxc_c(ii),vsigma_c(ii),vlrho_c(ii),vtau_c(ii), &
1978 &                  v2rho2_c(ii),v2rhosigma_c(ii),v2rholapl_c(ii),v2rhotau_c(ii),v2sigma2_c(ii), &
1979 &                  v2sigmalapl_c(ii),v2sigmatau_c(ii),v2lapl2_c(ii),v2lapltau_c(ii),v2tau2_c(ii))
1980      end if
1981 #endif
1982 
1983      exc(ipts) = exc(ipts) + exctmp
1984      vxc(ipts,1:nspden) = vxc(ipts,1:nspden) + vxctmp(1:nspden)
1985 
1986 !    Deal with fxc and kxc
1987      if (abs(order)>1) then
1988 !      ----- LDA -----
1989        if (xc_funcs(ii)%family==LIBPAW_XC_FAMILY_LDA) then
1990          if (nspden==1) then
1991            if(order>=2) then
1992              dvxc(ipts,1)=dvxc(ipts,1)+v2rho2(1)
1993              if(order>2) then
1994                d2vxc(ipts,1)=d2vxc(ipts,1)+v3rho3(1)
1995              endif
1996            else if (order==-2) then
1997              dvxc(ipts,1)=dvxc(ipts,1)+v2rho2(1)
1998              dvxc(ipts,2)=dvxc(ipts,2)+v2rho2(1)
1999            endif
2000          else
2001            dvxc(ipts,1)=dvxc(ipts,1)+v2rho2(1)
2002            dvxc(ipts,2)=dvxc(ipts,2)+v2rho2(2)
2003            dvxc(ipts,3)=dvxc(ipts,3)+v2rho2(3)
2004            if(abs(order)>2) then
2005              d2vxc(ipts,1)=d2vxc(ipts,1)+v3rho3(1)
2006              d2vxc(ipts,2)=d2vxc(ipts,2)+v3rho3(2)
2007              d2vxc(ipts,3)=d2vxc(ipts,3)+v3rho3(3)
2008              d2vxc(ipts,4)=d2vxc(ipts,4)+v3rho3(4)
2009            endif
2010          endif
2011 !      ----- GGA or mGGA -----
2012        else if (xc_funcs(ii)%family==LIBPAW_XC_FAMILY_GGA.or. &
2013 &               xc_funcs(ii)%family==LIBPAW_XC_FAMILY_HYB_GGA.or. &
2014 &               xc_funcs(ii)%family==LIBPAW_XC_FAMILY_MGGA.or. &
2015 &               xc_funcs(ii)%family==LIBPAW_XC_FAMILY_HYB_MGGA) then
2016          if (xc_funcs(ii)%kind==LIBPAW_XC_EXCHANGE) then
2017            if (nspden==1) then
2018              dvxc(ipts,1)=v2rho2(1)*two
2019              dvxc(ipts,2)=dvxc(ipts,1)
2020              dvxc(ipts,3)=two*two*vsigma(1)
2021              dvxc(ipts,4)=dvxc(ipts,3)
2022              dvxc(ipts,5)=four*two*v2rhosigma(1)
2023              dvxc(ipts,6)=dvxc(ipts,5)
2024              dvxc(ipts,7)=two*four*four*v2sigma2(1)
2025              dvxc(ipts,8)=dvxc(ipts,7)
2026            else
2027              dvxc(ipts,1)=v2rho2(1)
2028              dvxc(ipts,2)=v2rho2(3)
2029              dvxc(ipts,3)=two*vsigma(1)
2030              dvxc(ipts,4)=two*vsigma(3)
2031              dvxc(ipts,5)=two*v2rhosigma(1)
2032              dvxc(ipts,6)=two*v2rhosigma(6)
2033              dvxc(ipts,7)=four*v2sigma2(1)
2034              dvxc(ipts,8)=four*v2sigma2(6)
2035            end if
2036          else if (xc_funcs(ii)%kind==LIBPAW_XC_CORRELATION) then
2037            if (nspden==1) then
2038              dvxc(ipts,9)=v2rho2(1)
2039              dvxc(ipts,10)=dvxc(ipts,9)
2040              dvxc(ipts,11)=dvxc(ipts,9)
2041              dvxc(ipts,12)=two*vsigma(1)
2042              dvxc(ipts,13)=two*v2rhosigma(1)
2043              dvxc(ipts,14)=dvxc(ipts,13)
2044              dvxc(ipts,15)=four*v2sigma2(1)
2045            else
2046              dvxc(ipts,9)=v2rho2(1)
2047              dvxc(ipts,10)=v2rho2(2)
2048              dvxc(ipts,11)=v2rho2(3)
2049              dvxc(ipts,12)=two*vsigma(1)
2050              dvxc(ipts,13)=two*v2rhosigma(1)
2051              dvxc(ipts,14)=two*v2rhosigma(6)
2052              dvxc(ipts,15)=four*v2sigma2(1)
2053            end if
2054          end if
2055        end if
2056      end if
2057 
2058 !    Convert the quantities returned by Libxc
2059      if ((is_gga.or.is_mgga).and.present(vxcgr)) then
2060        if (nspden==1) then
2061          vxcgr(ipts,3) = vxcgr(ipts,3) + vsigma(1)*two
2062        else
2063          vxcgr(ipts,1) = vxcgr(ipts,1) + two*vsigma(1) - vsigma(2)
2064          vxcgr(ipts,2) = vxcgr(ipts,2) + two*vsigma(3) - vsigma(2)
2065          vxcgr(ipts,3) = vxcgr(ipts,3) + vsigma(2)
2066        end if
2067      end if
2068      if (is_mgga.and.present(vxctau)) then
2069        vxctau(ipts,1:nspden)  = vxctau(ipts,1:nspden)  + vtau(1:nspden)
2070      end if
2071      if (is_mgga.and.needs_laplacian.and.present(vxclrho)) then
2072        vxclrho(ipts,1:nspden) = vxclrho(ipts,1:nspden) + vlrho(1:nspden)
2073      end if
2074 
2075    end do ! ii
2076  end do   ! ipts
2077 
2078 end subroutine libpaw_libxc_getvxc

m_libpaw_libxc_funcs/libpaw_libxc_gga_from_hybrid [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_gga_from_hybrid

FUNCTION

  Returns a logical flag: TRUE if one can deduce, from the id of a hybrid functional set,
  the id(s) of the GGA functional on which it is based.
  Optionally returns the id of the GGA functional on which the hybrid functional is based
  (2 integers defining the GGA X and C functionals).
  - If an id is provided as input argument, it is used as input id;
  - If not, the input id is taken from the optional xc_functionals datastructure;
  - If no input argument is given, the input id is taken from the global paw_xc_global datastructure.

INPUTS

 [hybrid_id]=<type(libpaw_libxc_type)>, optional : id of an input hybrid functional
 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional : XC functionals from which
                     the id(s) can to be used

OUTPUT

 [gga_id(2)]=array that contains the GGA libXC id(s)
 libpaw_libxc_gga_from_hybrid=.true. if the GGA has been found from the input id

SOURCE

1603 function libpaw_libxc_gga_from_hybrid(gga_id,hybrid_id,xc_functionals)
1604 
1605 !Arguments ------------------------------------
1606 !scalars
1607  integer,intent(in),optional :: hybrid_id
1608  logical :: libpaw_libxc_gga_from_hybrid
1609 !arrays
1610  integer,intent(out),optional :: gga_id(2)
1611  type(libpaw_libxc_type),intent(inout),optional,target :: xc_functionals(2)
1612 !Local variables -------------------------------
1613 !scalars
1614  integer :: ii
1615  logical :: is_hybrid
1616  character(len=100) :: c_name,x_name,msg
1617 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
1618  character(len=100) :: xc_name
1619  character(kind=C_CHAR,len=1),pointer :: strg_c
1620 #endif
1621 !arrays
1622  integer :: trial_id(2)
1623 
1624 ! *************************************************************************
1625 
1626  libpaw_libxc_gga_from_hybrid=.false.
1627 
1628  is_hybrid=.false.
1629  if (present(hybrid_id)) then
1630    trial_id(1)=hybrid_id
1631    trial_id(2)=0
1632    is_hybrid=libpaw_libxc_is_hybrid_from_id(trial_id(1))
1633  else if (present(xc_functionals)) then
1634    trial_id(1)=xc_functionals(1)%id
1635    trial_id(2)=xc_functionals(2)%id
1636    is_hybrid=libpaw_libxc_is_hybrid(xc_functionals)
1637  else
1638    trial_id(1)=paw_xc_global(1)%id
1639    trial_id(2)=paw_xc_global(2)%id
1640    is_hybrid=libpaw_libxc_is_hybrid(paw_xc_global)
1641  end if
1642 
1643  c_name="unknown" ; x_name="unknown"
1644 
1645 !Specific treatment of the B3LYP functional, whose GGA counterpart does not exist in LibXC
1646  if (trial_id(1)==402 .or. trial_id(2)==402) then
1647    libpaw_libxc_gga_from_hybrid=.true.
1648    if (present(gga_id)) then
1649      gga_id(1)=0
1650      gga_id(2)=-1402 ! This corresponds to a native ABINIT functional,
1651                      ! actually a composite from different LibXC functionals!
1652      write(std_out,*)' libpaw_libxc_gga_from_hybrid, return with gga_id=',gga_id
1653    endif
1654    return
1655  endif
1656 
1657  do ii = 1, 2
1658 
1659    if ((trial_id(ii)<=0).or.(.not.is_hybrid)) cycle
1660 
1661    if (libpaw_libxc_gga_from_hybrid) then
1662      msg='Invalid XC functional setup: contains 2 hybrid functionals!'
1663      LIBPAW_ERROR(msg)
1664    end if
1665 
1666 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
1667 
1668    call c_f_pointer(xc_functional_get_name(trial_id(ii)),strg_c)
1669    call char_c_to_f(strg_c,xc_name)
1670 
1671 !  AVAILABLE FUNCTIONALS
1672 
1673 !  ===== PBE0 =====
1674    if (xc_name=="hyb_gga_xc_pbeh" .or. &
1675 &      xc_name=="hyb_gga_xc_pbe0_13") then
1676      c_name="GGA_C_PBE"
1677      x_name="GGA_X_PBE"
1678      libpaw_libxc_gga_from_hybrid=.true.
1679 
1680 !  ===== HSE =====
1681    else if (xc_name=="hyb_gga_xc_hse03" .or. &
1682 &           xc_name=="hyb_gga_xc_hse06" ) then
1683      c_name="GGA_C_PBE"
1684      x_name="GGA_X_PBE"
1685      libpaw_libxc_gga_from_hybrid=.true.
1686    end if
1687 
1688 #endif
1689 
1690  enddo ! ii
1691 
1692  if (present(gga_id)) then
1693    if (libpaw_libxc_gga_from_hybrid) then
1694      gga_id(1)=libpaw_libxc_getid(c_name)
1695      gga_id(2)=libpaw_libxc_getid(x_name)
1696    else
1697      gga_id(:)=-1
1698    end if
1699  end if
1700 
1701  if (.not.libpaw_libxc_gga_from_hybrid) then
1702    msg='Unable to find a GGA functional for this hybrid!'
1703    LIBPAW_ERROR(msg)
1704  end if
1705 
1706 !Note that in the case of B3LYP functional, the return happened immediately after the setup of B3LYP parameters.
1707 
1708 end function libpaw_libxc_gga_from_hybrid

m_libpaw_libxc_funcs/libpaw_libxc_has_k3xc [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_has_k3xc

FUNCTION

  Test function to identify whether the presently used (set of) functional(s)
  provides K3xc or not (kxc in the libXC convention)

INPUTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     Handle for XC functionals

SOURCE

1260 function libpaw_libxc_has_k3xc(xc_functionals)
1261 
1262 !Arguments ------------------------------------
1263  logical :: libpaw_libxc_has_k3xc
1264  type(libpaw_libxc_type),intent(in),optional,target :: xc_functionals(2)
1265 !Local variables-------------------------------
1266  integer :: ii
1267 
1268 ! *************************************************************************
1269 
1270  libpaw_libxc_has_k3xc=.true.
1271 
1272  do ii=1,2
1273    if (present(xc_functionals)) then
1274      if (.not.xc_functionals(ii)%has_kxc) libpaw_libxc_has_k3xc=.false.
1275    else
1276      if (.not.paw_xc_global(ii)%has_kxc) libpaw_libxc_has_k3xc=.false.
1277    end if
1278  end do
1279 
1280 end function libpaw_libxc_has_k3xc

m_libpaw_libxc_funcs/libpaw_libxc_has_kxc [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_has_kxc

FUNCTION

  Test function to identify whether the presently used (set of) functional(s)
  provides Kxc or not (fxc in the libXC convention)

INPUTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals

SOURCE

1221 function libpaw_libxc_has_kxc(xc_functionals)
1222 
1223 !Arguments ------------------------------------
1224  logical :: libpaw_libxc_has_kxc
1225  type(libpaw_libxc_type),intent(in),optional,target :: xc_functionals(2)
1226 !Local variables-------------------------------
1227  integer :: ii
1228 
1229 ! *************************************************************************
1230 
1231  libpaw_libxc_has_kxc=.true.
1232 
1233  do ii=1,2
1234    if (present(xc_functionals)) then
1235      if (.not.xc_functionals(ii)%has_fxc) libpaw_libxc_has_kxc=.false.
1236    else
1237      if (.not.paw_xc_global(ii)%has_fxc) libpaw_libxc_has_kxc=.false.
1238    end if
1239  end do
1240 
1241 end function libpaw_libxc_has_kxc

m_libpaw_libxc_funcs/libpaw_libxc_init [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_init

FUNCTION

  Initialize the desired (set of) XC functional(s), from LibXC.
  * Call the LibXC initializer
  * Fill preliminary fields in module structures.

INPUTS

 ixc=XC code for Abinit
 nspden=number of spin-density components
 [el_temp]=electronic temperature (optional, only for specific functionals)
 [xc_tb09_c]=special argument for the Tran-Blaha 2009 functional

SIDE EFFECTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals to initialize

SOURCE

462  subroutine libpaw_libxc_init(ixc,nspden,xc_functionals,&
463 &                             el_temp,xc_tb09_c) ! optional argument
464 
465 
466 !Arguments ------------------------------------
467  integer, intent(in) :: nspden
468  integer, intent(in) :: ixc
469  real(dp),intent(in),optional :: el_temp,xc_tb09_c
470  type(libpaw_libxc_type),intent(inout),optional,target :: xc_functionals(2)
471 !Local variables-------------------------------
472  integer :: ii,jj,nspden_eff
473  character(len=500) :: msg
474  type(libpaw_libxc_type),pointer :: xc_func
475 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
476  integer :: flags
477  integer(C_INT) :: func_id_c,iref_c,npar_c,nspin_c,success_c
478  real(C_DOUBLE) :: alpha_c,beta_c,omega_c,param_c(1)
479  character(kind=C_CHAR,len=1),pointer :: strg_c
480  type(C_PTR) :: func_ptr_c
481 #endif
482 
483 ! *************************************************************************
484 
485 !Check libXC
486  if (.not.libpaw_libxc_check(stop_if_error=.true.)) return
487  if (.not.libpaw_xc_constants_initialized) call libpaw_libxc_constants_load()
488 
489  nspden_eff=min(nspden,2)
490 
491 !Select XC functional(s) identifiers
492  if (present(xc_functionals)) then
493    xc_functionals(1)%id = -ixc/1000
494    xc_functionals(2)%id = -ixc + (ixc/1000)*1000
495  else
496    paw_xc_global(1)%id = -ixc/1000
497    paw_xc_global(2)%id = -ixc + (ixc/1000)*1000
498  end if
499 
500  do ii = 1,2
501 
502 !  Select XC functional
503    if (present(xc_functionals)) then
504      xc_func => xc_functionals(ii)
505    else
506      xc_func => paw_xc_global(ii)
507    end if
508 
509    xc_func%abi_ixc=ixc !Save abinit value for reference
510 
511    xc_func%family=LIBPAW_XC_FAMILY_UNKNOWN
512    xc_func%kind=-1
513    xc_func%nspin=nspden_eff
514    xc_func%has_exc=.false.
515    xc_func%has_vxc=.false.
516    xc_func%has_fxc=.false.
517    xc_func%has_kxc=.false.
518    xc_func%needs_laplacian=.false.
519    xc_func%is_hybrid=.false.
520    xc_func%hyb_mixing=zero
521    xc_func%hyb_mixing_sr=zero
522    xc_func%hyb_range=zero
523    xc_func%xc_tb09_c=99.99_dp
524    xc_func%sigma_threshold=-one
525 
526    if (xc_func%id<=0) cycle
527 
528 !  Get XC functional family
529    xc_func%family=libpaw_libxc_family_from_id(xc_func%id)
530    if (xc_func%family/=LIBPAW_XC_FAMILY_LDA .and. &
531 &      xc_func%family/=LIBPAW_XC_FAMILY_GGA .and. &
532 &      xc_func%family/=LIBPAW_XC_FAMILY_MGGA.and. &
533 &      xc_func%family/=LIBPAW_XC_FAMILY_HYB_GGA) then
534      write(msg, '(a,i8,2a,i8,6a)' )&
535 &      'Invalid IXC = ',ixc,ch10,&
536 &      'The LibXC functional family ',xc_func%family,&
537 &      'is currently unsupported by LibPAW',ch10,&
538 &      '(-1 means the family is unknown to the LibXC itself)',ch10,&
539 &      'Please consult the LibXC documentation',ch10
540      LIBPAW_ERROR(msg)
541    end if
542 
543 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
544 
545 !  Allocate functional
546    func_ptr_c=libpaw_xc_func_type_malloc()
547    call c_f_pointer(func_ptr_c,xc_func%conf)
548 
549 !  Initialize functional
550    func_id_c=int(xc_func%id,kind=C_INT)
551    nspin_c=int(nspden_eff,kind=C_INT)
552    success_c=xc_func_init(xc_func%conf,func_id_c,nspin_c)
553    if (success_c/=0) then
554      msg='Error in libXC functional initialization!'
555      LIBPAW_ERROR(msg)
556    end if
557 
558 !  Special treatment for LDA_C_XALPHA functional
559    if (xc_func%id==libpaw_libxc_getid('XC_LDA_C_XALPHA')) then
560      param_c(1)=real(zero,kind=C_DOUBLE);npar_c=int(1,kind=C_INT)
561      call libpaw_xc_func_set_params(xc_func%conf,param_c,npar_c)
562    end if
563 
564 !  Special treatment for XC_MGGA_X_TB09  functional
565    if (xc_func%id==libpaw_libxc_getid('XC_MGGA_X_TB09')) then
566      if (.not.present(xc_tb09_c)) then
567        msg='xc_tb09_c argument is mandatory for TB09 functional!'
568        LIBPAW_BUG(msg)
569      end if
570      xc_func%xc_tb09_c=xc_tb09_c
571    end if
572 
573 !  Get functional kind
574    xc_func%kind=int(libpaw_xc_get_info_kind(xc_func%conf))
575 
576 !  Get functional flags
577    flags=int(libpaw_xc_get_info_flags(xc_func%conf))
578    xc_func%has_exc=(iand(flags,LIBPAW_XC_FLAGS_HAVE_EXC)>0)
579    xc_func%has_vxc=(iand(flags,LIBPAW_XC_FLAGS_HAVE_VXC)>0)
580    xc_func%has_fxc=(iand(flags,LIBPAW_XC_FLAGS_HAVE_FXC)>0)
581    xc_func%has_kxc=(iand(flags,LIBPAW_XC_FLAGS_HAVE_KXC)>0)
582 
583 !  Retrieve parameters for metaGGA functionals
584    if (xc_func%family==LIBPAW_XC_FAMILY_MGGA.or. &
585 &      xc_func%family==LIBPAW_XC_FAMILY_HYB_MGGA) then
586      xc_func%needs_laplacian=(iand(flags,LIBPAW_XC_FLAGS_NEEDS_LAPLACIAN)>0)
587    end if
588 
589 !  Retrieve parameters for hybrid functionals
590    xc_func%is_hybrid=(libpaw_xc_func_is_hybrid_from_id(xc_func%id)==1)
591    if (xc_func%is_hybrid) then
592      call xc_hyb_cam_coef(xc_func%conf,omega_c,alpha_c,beta_c)
593      xc_func%hyb_mixing=real(alpha_c,kind=dp)
594      xc_func%hyb_mixing_sr=real(beta_c,kind=dp)
595      xc_func%hyb_range=real(omega_c,kind=dp)
596    end if
597 
598 !  Possible temperature dependence
599    if (present(el_temp)) then
600      if (el_temp>tol10) then
601       if (libpaw_libxc_depends_on_temp(xc_func)) then
602         xc_func%temperature=el_temp
603         call libpaw_libxc_set_temp(xc_func,el_temp)
604       end if
605     end if
606    end if
607 
608 !  Some functionals need a filter to be applied on sigma (density gradient)
609 !   because libXC v6 doesn't implement sigma_threshold
610    if (xc_func%is_hybrid) then
611      do jj=1,libpaw_n_sigma_filtered
612        if (xc_func%id==libpaw_libxc_getid(trim(libpaw_sigma_filtered(jj)))) then
613          xc_func%sigma_threshold=libpaw_sigma_threshold_def
614        end if
615      end do
616    end if
617 
618 !  Dump functional information
619    call c_f_pointer(libpaw_xc_get_info_name(xc_func%conf),strg_c)
620    call char_c_to_f(strg_c,msg)
621    call wrtout(std_out,msg,'COLL')
622    iref_c=0
623    do while (iref_c>=0)
624      call c_f_pointer(libpaw_xc_get_info_refs(xc_func%conf,iref_c),strg_c)
625      if (associated(strg_c)) then
626        call char_c_to_f(strg_c,msg)
627        call wrtout(std_out,msg,'COLL')
628        iref_c=iref_c+1
629      else
630        iref_c=-1
631      end if
632    end do
633 
634 #else
635    if (.False.) write(std_out,*)xc_tb09_c
636 #endif
637 
638  end do
639 
640 end subroutine libpaw_libxc_init

m_libpaw_libxc_funcs/libpaw_libxc_is_hybrid [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_is_hybrid

FUNCTION

  Test function to identify whether the presently used (set of) functional(s)
  is hybrid or not

INPUTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals to initialize

SOURCE

1333  function libpaw_libxc_is_hybrid(xc_functionals)
1334 
1335 !Arguments ------------------------------------
1336  logical :: libpaw_libxc_is_hybrid
1337  type(libpaw_libxc_type),intent(in),optional :: xc_functionals(2)
1338 
1339 ! *************************************************************************
1340 
1341  libpaw_libxc_is_hybrid = .false.
1342 
1343  if (present(xc_functionals)) then
1344    libpaw_libxc_is_hybrid=(any(xc_functionals%is_hybrid))
1345  else
1346    libpaw_libxc_is_hybrid=(any(paw_xc_global%is_hybrid))
1347  end if
1348 
1349 end function libpaw_libxc_is_hybrid

m_libpaw_libxc_funcs/libpaw_libxc_is_hybrid_from_id [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_is_hybrid_from_id

FUNCTION

  Test function to identify whether a functional is hybrid or not, from its id

INPUTS

  xcid= id of a LibXC functional

SOURCE

1366  function libpaw_libxc_is_hybrid_from_id(xcid)
1367 
1368 !Arguments ------------------------------------
1369  logical :: libpaw_libxc_is_hybrid_from_id
1370  integer,intent(in) :: xcid
1371 !Local variables-------------------------------
1372 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
1373  integer(C_INT) :: xcid_c
1374 #endif
1375 
1376 ! *************************************************************************
1377 
1378 #if defined LIBPAW_HAVE_LIBXC && defined LIBPAW_ISO_C_BINDING
1379  xcid_c=int(xcid,kind=C_INT)
1380  libpaw_libxc_is_hybrid_from_id =(libpaw_xc_func_is_hybrid_from_id(xcid_c)==1)
1381 #else
1382  libpaw_libxc_is_hybrid_from_id = .false.
1383  if (.false.) write(std_out,*) xcid
1384 #endif
1385 
1386 end function libpaw_libxc_is_hybrid_from_id

m_libpaw_libxc_funcs/libpaw_libxc_isgga [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_isgga

FUNCTION

  Test function to identify whether the presently used (set of) functional(s)
  is a GGA or not

INPUTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals to initialize

SOURCE

947  function libpaw_libxc_isgga(xc_functionals)
948 
949 !Arguments ------------------------------------
950  logical :: libpaw_libxc_isgga
951  type(libpaw_libxc_type),intent(in),optional :: xc_functionals(2)
952 
953 ! *************************************************************************
954 
955  libpaw_libxc_isgga = .false.
956  if (.not.libpaw_xc_constants_initialized) call libpaw_libxc_constants_load()
957 
958  if (present(xc_functionals)) then
959    libpaw_libxc_isgga=(any(xc_functionals%family==LIBPAW_XC_FAMILY_GGA) .or. &
960 &                      any(xc_functionals%family==LIBPAW_XC_FAMILY_HYB_GGA))
961  else
962    libpaw_libxc_isgga=(any(paw_xc_global%family==LIBPAW_XC_FAMILY_GGA) .or. &
963 &                      any(paw_xc_global%family==LIBPAW_XC_FAMILY_HYB_GGA))
964  end if
965 
966 end function libpaw_libxc_isgga

m_libpaw_libxc_funcs/libpaw_libxc_islda [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_islda

FUNCTION

  Test function to identify whether the presently used (set of) functional(s)
  is a LDA or not

INPUTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals to initialize

SOURCE

909  function libpaw_libxc_islda(xc_functionals)
910 
911 !Arguments ------------------------------------
912  logical :: libpaw_libxc_islda
913  type(libpaw_libxc_type),intent(in),optional :: xc_functionals(2)
914 
915 ! *************************************************************************
916 
917  libpaw_libxc_islda = .false.
918  if (.not.libpaw_xc_constants_initialized) call libpaw_libxc_constants_load()
919 
920  if (present(xc_functionals)) then
921    libpaw_libxc_islda=(any(xc_functionals%family==LIBPAW_XC_FAMILY_LDA) .or. &
922 &                      any(xc_functionals%family==LIBPAW_XC_FAMILY_HYB_LDA))
923  else
924    libpaw_libxc_islda=(any(paw_xc_global%family==LIBPAW_XC_FAMILY_LDA) .or. &
925 &                      any(paw_xc_global%family==LIBPAW_XC_FAMILY_HYB_LDA))
926  end if
927 
928 end function libpaw_libxc_islda

m_libpaw_libxc_funcs/libpaw_libxc_ismgga [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_ismgga

FUNCTION

  Test function to identify whether the presently used (set of) functional(s)
  is a Meta-GGA or not

INPUTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals to initialize

SOURCE

 985 function libpaw_libxc_ismgga(xc_functionals)
 986 
 987 !Arguments ------------------------------------
 988  logical :: libpaw_libxc_ismgga
 989  type(libpaw_libxc_type),intent(in),optional :: xc_functionals(2)
 990 
 991 ! *************************************************************************
 992 
 993  libpaw_libxc_ismgga = .false.
 994  if (.not.libpaw_xc_constants_initialized) call libpaw_libxc_constants_load()
 995 
 996  if (present(xc_functionals)) then
 997    libpaw_libxc_ismgga=(any(xc_functionals%family==LIBPAW_XC_FAMILY_MGGA) .or. &
 998 &                       any(xc_functionals%family==LIBPAW_XC_FAMILY_HYB_MGGA))
 999  else
1000    libpaw_libxc_ismgga=(any(paw_xc_global%family==LIBPAW_XC_FAMILY_MGGA) .or. &
1001 &                       any(paw_xc_global%family==LIBPAW_XC_FAMILY_HYB_MGGA))
1002  end if
1003 
1004 end function libpaw_libxc_ismgga

m_libpaw_libxc_funcs/libpaw_libxc_ixc [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_ixc

FUNCTION

  Return the value of ixc used to initialize the XC structure

INPUTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals to initialize

SOURCE

876  function libpaw_libxc_ixc(xc_functionals)
877 
878 !Arguments ------------------------------------
879  integer :: libpaw_libxc_ixc
880  type(libpaw_libxc_type),intent(in),optional :: xc_functionals(2)
881 
882 ! *************************************************************************
883 
884  if (present(xc_functionals)) then
885    libpaw_libxc_ixc=xc_functionals(1)%abi_ixc
886  else
887    libpaw_libxc_ixc=paw_xc_global(1)%abi_ixc
888  end if
889 
890 end function libpaw_libxc_ixc

m_libpaw_libxc_funcs/libpaw_libxc_needs_laplacian [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_needs_laplacian

FUNCTION

  Test function to identify whether the presently used (set of) functional(s)
  needs the laplacian of the density or not

INPUTS

 [xc_functionals(2)]=<type(libxc_functional_type)>, optional argument
                     Handle for XC functionals

SOURCE

1101  function libpaw_libxc_needs_laplacian(xc_functionals)
1102 
1103 !Arguments ------------------------------------
1104  implicit none
1105  logical :: libpaw_libxc_needs_laplacian
1106  type(libpaw_libxc_type),intent(in),optional :: xc_functionals(2)
1107 
1108 ! *************************************************************************
1109 
1110  libpaw_libxc_needs_laplacian = .false.
1111 
1112  if (present(xc_functionals)) then
1113    libpaw_libxc_needs_laplacian=(any(xc_functionals%needs_laplacian))
1114  else
1115    libpaw_libxc_needs_laplacian=(any(paw_xc_global%needs_laplacian))
1116  end if
1117 
1118  end function libpaw_libxc_needs_laplacian

m_libpaw_libxc_funcs/libpaw_libxc_needs_temperature [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_needs_temperature

FUNCTION

  Test function to identify whether the presently used (set of) functional(s)
  needs the electronic temperature or not

INPUTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     Handle for XC functionals

SOURCE

1137  function libpaw_libxc_needs_temperature(xc_functionals)
1138 
1139 !Arguments ------------------------------------
1140  implicit none
1141  logical :: libpaw_libxc_needs_temperature
1142  type(libpaw_libxc_type),intent(in),optional :: xc_functionals(2)
1143 
1144 ! *************************************************************************
1145 
1146  libpaw_libxc_needs_temperature = .false.
1147 
1148  if (present(xc_functionals)) then
1149    libpaw_libxc_needs_temperature=(any(xc_functionals%temperature>tol8))
1150  else
1151    libpaw_libxc_needs_temperature=(any(paw_xc_global%temperature>tol8))
1152  end if
1153 
1154  end function libpaw_libxc_needs_temperature

m_libpaw_libxc_funcs/libpaw_libxc_nspin [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_nspin

FUNCTION

  Returns the number of spin components for the (set of) XC functional(s)

INPUTS

 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     XC functionals to initialize

SOURCE

1298 function libpaw_libxc_nspin(xc_functionals)
1299 
1300 !Arguments ------------------------------------
1301  integer :: libpaw_libxc_nspin
1302  type(libpaw_libxc_type),intent(in),optional :: xc_functionals(2)
1303 
1304 ! *************************************************************************
1305 
1306  libpaw_libxc_nspin = 1
1307 
1308  if (present(xc_functionals)) then
1309    if (any(xc_functionals%nspin==2)) libpaw_libxc_nspin=2
1310  else
1311    if (any(paw_xc_global%nspin==2)) libpaw_libxc_nspin=2
1312  end if
1313 
1314 end function libpaw_libxc_nspin

m_libpaw_libxc_funcs/libpaw_libxc_set_temp [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_set_temp

FUNCTION

  Set the electronic temperature in a single XC functional
    No action if functional doesnt depend on temperature

INPUTS

 xc_functional=<type(libpaw_libxc_type)>, handle for XC functional
 temperature=electronic temperature (in Ha units, i.e. T_kelvin * k_B_in_Ha/K )

SOURCE

2314 subroutine libpaw_libxc_set_temp(xc_functional,temperature)
2315 
2316 !Arguments ------------------------------------
2317  real(dp),intent(in) :: temperature
2318  type(libpaw_libxc_type),intent(in) :: xc_functional
2319 !Local variables-------------------------------
2320 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
2321  integer(C_INT) :: iset_c,npar_c
2322  real(C_DOUBLE) :: temp_c,param_c(1)
2323  character(len=50) :: par_name
2324  character(kind=C_CHAR,len=1),target :: name_c(2)
2325 #endif
2326 
2327 ! *************************************************************************
2328 
2329 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
2330  if (xc_functional%temperature>zero) then
2331 
2332    par_name="T" ; name_c=char_f_to_c(trim(par_name))
2333    temp_c=real(temperature,kind=C_DOUBLE)
2334    iset_c = libpaw_xc_func_set_params_name(xc_functional%conf,c_loc(name_c),temp_c)
2335    if (iset_c /= 0) then
2336      !Try this when set_params_name method is not available (libXC<5)
2337      if (xc_functional%id==libpaw_libxc_getid('XC_LDA_XC_KSDT') .or. &
2338 &        xc_functional%id==libpaw_libxc_getid('XC_LDA_XC_GDSMFB') .or. &
2339 &        xc_functional%id==libpaw_libxc_getid('XC_LDA_XC_CORRKSDT')) then
2340        param_c(1)=real(zero,kind=C_DOUBLE);npar_c=int(1,kind=C_INT)
2341        call libpaw_xc_func_set_params(xc_functional%conf,param_c,npar_c)
2342      end if
2343    end if
2344 
2345  end if
2346 
2347 #else
2348  if (.False.) write(std_out,*) xc_functional%id
2349 #endif
2350 
2351 end subroutine libpaw_libxc_set_temp

m_libpaw_libxc_funcs/libpaw_libxc_set_temperature [ Functions ]

[ Top ] [ m_libpaw_libxc_funcs ] [ Functions ]

NAME

  libpaw_libxc_set_temperature

FUNCTION

  Set the electronic temperature in a (set of) of XC functional(s)
    No action when no temperature dependence

INPUTS

 temperature=electronic temperature (in Kelvin units)
 [xc_functionals(2)]=<type(libpaw_libxc_type)>, optional argument
                     Handle for XC functionals

OUTPUT

SOURCE

1176 subroutine libpaw_libxc_set_temperature(temperature,xc_functionals)
1177 
1178 !Arguments ------------------------------------
1179  real(dp),intent(in) :: temperature
1180  type(libpaw_libxc_type),intent(in),optional,target :: xc_functionals(2)
1181 !Local variables -------------------------------
1182  integer :: ii
1183  type(libpaw_libxc_type),pointer :: xc_func
1184 
1185 ! *************************************************************************
1186 
1187  do ii = 1, 2
1188 
1189 !  Select XC functional
1190    if (present(xc_functionals)) then
1191      xc_func => xc_functionals(ii)
1192    else
1193      xc_func => paw_xc_global(ii)
1194    end if
1195 
1196    if (xc_func%id>0) then
1197      call libpaw_libxc_set_temp(xc_func,temperature)
1198    end if
1199 
1200  end do
1201 
1202 end subroutine libpaw_libxc_set_temperature