TABLE OF CONTENTS


ABINIT/libxc_functionals [ Modules ]

[ Top ] [ Modules ]

NAME

  libxc_functionals

FUNCTION

  Module containing interfaces to the LibXC library, for exchange
  correlation potentials and energies. The interfacing between
  the ABINIT and LibXC formats and datastructures happens here.
  Also contains basic container datatype for LibXC interfacing.

COPYRIGHT

 Copyright (C) 2008-2017 ABINIT group (MOliveira,LHH,FL,GMR,MT)
 This file is distributed under the terms of the
 GNU Gener_al Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .

NOTES

  libxc_functionals.F90 defines a structured datatype (libxc_functional_type)
  and associated methods to initialize/finalize it and get properties from it.
  Abinit used a global variable (xc_global, libxc_functional_type) which is
  initialized in the driving routine (driver) with the value of ixc specified
  by the user in the input file.
  * It is possible to change the value of ixc at run-time; for that  we have
    to reinitialize the global structure with the new value of ixc before
    computing XC quantities. Moreover one has to reinstate the old functional
    before returning so that the other routines will continue to used the
    previous ixc. This task can be accomplished with the following pseudocode:
    !!!!! if (old_ixc<0) call libxc_functionals_end()
    !!!!! if (new_ixc<0) call libxc_functionals_init(new_ixc,nspden)
    !!!!! >>>> Compute XC stuff here.
    !!!!! if (new_ixc<0) call libxc_functionals_end()
    !!!!! if (old_ixc<0) call libxc_functionals_init(old_ixc,nspden)
  * It is also possible to define a local (private) variable of type libxc_functional_type.
    For that, the different methods have to be called with an extra optional
    argument (called xc_funcs in this example):
    !!!!! call libxc_functionals_init(ixc,nspden,xc_funcs)
    !!!!! call libxc_functionals_end(xc_funcs)

PARENTS

CHILDREN

SOURCE

 46 #if defined HAVE_CONFIG_H
 47 #include "config.h"
 48 #endif
 49 
 50 #include "abi_common.h"
 51 #if defined HAVE_LIBXC
 52 #include "xc_version.h"
 53 #endif
 54 
 55 module libxc_functionals
 56 
 57  use defs_basis
 58  use m_abicore
 59  use m_errors
 60 
 61 #ifdef HAVE_FC_ISO_C_BINDING
 62  use iso_c_binding
 63 #endif
 64 
 65  implicit none
 66  private
 67 
 68 !Public functions
 69  public :: libxc_functionals_check              ! Check if the code has been compiled with libXC
 70  public :: libxc_functionals_init               ! Initialize the desired XC functional, from libXC
 71  public :: libxc_functionals_end                ! End usage of libXC functional
 72  public :: libxc_functionals_fullname           ! Return full name of the XC functional
 73  public :: libxc_functionals_getid              ! Return identifer of a XC functional from its name
 74  public :: libxc_functionals_family_from_id     ! Retrieve family of a XC functional from its id
 75  public :: libxc_functionals_ixc                ! The value of ixc used to initialize the XC functionals
 76  public :: libxc_functionals_getvxc             ! Return XC potential and energy, from input density
 77  public :: libxc_functionals_isgga              ! Return TRUE if the XC functional is GGA or meta-GGA
 78  public :: libxc_functionals_ismgga             ! Return TRUE if the XC functional is meta-GGA
 79  public :: libxc_functionals_is_hybrid          ! Return TRUE if the XC functional is hybrid (GGA or meta-GGA)
 80  public :: libxc_functionals_has_kxc            ! Return TRUE if Kxc (3rd der) is available for the XC functional
 81  public :: libxc_functionals_nspin              ! The number of spin components for the XC functionals
 82  public :: libxc_functionals_get_hybridparams   ! Retrieve parameter(s) for hybrid functionals
 83  public :: libxc_functionals_set_hybridparams   ! Change parameter(s) for a hybrid functionals
 84  public :: libxc_functionals_gga_from_hybrid    ! Return the id of the XC-GGA used for the hybrid
 85 
 86 !Private functions
 87  private :: libxc_functionals_constants_load    ! Load libXC constants from C headers
 88  private :: libxc_functionals_set_tb09          ! Compute c parameter for Tran-Blaha 2009 functional
 89  private :: xc_char_to_c                        ! Convert a string from Fortran to C
 90  private :: xc_char_to_f                        ! Convert a string from C to Fortran
 91 
 92 !Public constants (use libxc_functionals_constants_load to init them)
 93  integer,public,save :: XC_FAMILY_UNKNOWN       = -1
 94  integer,public,save :: XC_FAMILY_LDA           =  1
 95  integer,public,save :: XC_FAMILY_GGA           =  2
 96  integer,public,save :: XC_FAMILY_MGGA          =  4
 97  integer,public,save :: XC_FAMILY_LCA           =  8
 98  integer,public,save :: XC_FAMILY_OEP           = 16
 99  integer,public,save :: XC_FAMILY_HYB_GGA       = 32
100  integer,public,save :: XC_FAMILY_HYB_MGGA      = 64
101  integer,public,save :: XC_FLAGS_HAVE_EXC       =  1
102  integer,public,save :: XC_FLAGS_HAVE_VXC       =  2
103  integer,public,save :: XC_FLAGS_HAVE_FXC       =  4
104  integer,public,save :: XC_FLAGS_HAVE_KXC       =  8
105  integer,public,save :: XC_FLAGS_HAVE_LXC       = 16
106  integer,public,save :: XC_EXCHANGE             =  0
107  integer,public,save :: XC_CORRELATION          =  1
108  integer,public,save :: XC_EXCHANGE_CORRELATION =  2
109  integer,public,save :: XC_KINETIC              =  3
110  integer,public,save :: XC_SINGLE_PRECISION     =  0
111  logical,private,save :: libxc_constants_initialized=.false.
112 
113 !XC functional public type
114  type,public :: libxc_functional_type
115    integer  :: id              ! identifier
116    integer  :: family          ! LDA, GGA, etc.
117    integer  :: kind            ! EXCHANGE, CORRELATION, etc.
118    integer  :: nspin           ! # of spin components
119    integer  :: abi_ixc         ! Abinit IXC id for this functional
120    logical  :: has_exc         ! TRUE is exc is available for the functional
121    logical  :: has_vxc         ! TRUE is vxc is available for the functional
122    logical  :: has_fxc         ! TRUE is fxc is available for the functional
123    logical  :: has_kxc         ! TRUE is kxc is available for the functional
124    real(dp) :: hyb_mixing      ! Hybrid functional: mixing factor of Fock contribution (default=0)
125    real(dp) :: hyb_mixing_sr   ! Hybrid functional: mixing factor of SR Fock contribution (default=0)
126    real(dp) :: hyb_range       ! Range (for separation) for a hybrid functional (default=0)
127 #ifdef HAVE_FC_ISO_C_BINDING
128    type(C_PTR),pointer :: conf => null() ! C pointer to the functional itself
129 #endif
130  end type libxc_functional_type
131 
132 !----------------------------------------------------------------------
133 
134 !Private global XC functional
135  type(libxc_functional_type),target,save :: xc_global(2)
136 
137 !----------------------------------------------------------------------
138 
139 !Interfaces for C bindings
140 #ifdef HAVE_FC_ISO_C_BINDING
141  interface
142    integer(C_INT) function xc_func_init(xc_func,functional,nspin) bind(C)
143      use iso_c_binding, only : C_INT,C_PTR
144      integer(C_INT),value :: functional,nspin
145      type(C_PTR) :: xc_func
146    end function xc_func_init
147  end interface
148 !
149  interface
150    subroutine xc_func_end(xc_func) bind(C)
151      use iso_c_binding, only : C_PTR
152      type(C_PTR) :: xc_func
153    end subroutine xc_func_end
154  end interface
155 !
156  interface
157    integer(C_INT) function xc_functional_get_number(name) bind(C)
158      use iso_c_binding, only : C_INT,C_PTR
159      type(C_PTR),value :: name
160    end function xc_functional_get_number
161  end interface
162 !
163  interface
164    type(C_PTR) function xc_functional_get_name(number) bind(C)
165      use iso_c_binding, only : C_INT,C_PTR
166      integer(C_INT),value :: number
167    end function xc_functional_get_name
168  end interface
169 !
170  interface
171    integer(C_INT) function xc_family_from_id(id,family,number) bind(C)
172      use iso_c_binding, only : C_INT,C_PTR
173      integer(C_INT),value :: id
174      type(C_PTR),value :: family,number
175    end function xc_family_from_id
176  end interface
177 !
178  interface
179    subroutine xc_hyb_cam_coef(xc_func,omega,alpha,beta) bind(C)
180      use iso_c_binding, only : C_DOUBLE,C_PTR
181      real(C_DOUBLE) :: omega,alpha,beta
182      type(C_PTR) :: xc_func
183    end subroutine xc_hyb_cam_coef
184  end interface
185 !
186  interface
187    subroutine xc_lda(xc_func,np,rho,zk,vrho,v2rho2,v3rho3) bind(C)
188      use iso_c_binding, only : C_INT,C_PTR
189      integer(C_INT),value :: np
190      type(C_PTR),value :: rho,zk,vrho,v2rho2,v3rho3
191      type(C_PTR) :: xc_func
192    end subroutine xc_lda
193  end interface
194 !
195  interface
196    subroutine xc_gga(xc_func,np,rho,sigma,zk,vrho,vsigma,v2rho2,v2rhosigma,v2sigma2, &
197 &                    v3rho3,v3rho2sigma,v3rhosigma2,v3sigma3) bind(C)
198      use iso_c_binding, only : C_INT,C_PTR
199      integer(C_INT),value :: np
200      type(C_PTR),value :: rho,sigma,zk,vrho,vsigma,v2rho2,v2rhosigma,v2sigma2, &
201 &                         v3rho3,v3rho2sigma,v3rhosigma2,v3sigma3
202      type(C_PTR) :: xc_func
203    end subroutine xc_gga
204  end interface
205 !
206  interface
207    subroutine xc_mgga(xc_func,np,rho,sigma,lapl,tau,zk,vrho,vsigma,vlapl,vtau, &
208 &                     v2rho2,v2sigma2,v2lapl2,v2tau2,v2rhosigma,v2rholapl,v2rhotau, &
209 &                     v2sigmalapl,v2sigmatau,v2lapltau) bind(C)
210      use iso_c_binding, only : C_INT,C_PTR
211      integer(C_INT),value :: np
212      type(C_PTR),value :: rho,sigma,lapl,tau,zk,vrho,vsigma,vlapl,vtau, &
213 &                         v2rho2,v2sigma2,v2lapl2,v2tau2,v2rhosigma,v2rholapl,v2rhotau, &
214 &                         v2sigmalapl,v2sigmatau,v2lapltau
215      type(C_PTR) :: xc_func
216    end subroutine xc_mgga
217  end interface
218 !
219 #if ( XC_MAJOR_VERSION < 4 )
220  interface
221    subroutine xc_hyb_gga_xc_pbeh_set_params(xc_func, alpha) bind(C)
222      use iso_c_binding, only : C_DOUBLE,C_PTR
223      real(C_DOUBLE),value :: alpha
224      type(C_PTR) :: xc_func
225    end subroutine xc_hyb_gga_xc_pbeh_set_params
226  end interface
227 !
228  interface
229    subroutine xc_hyb_gga_xc_hse_set_params(xc_func, alpha, omega) bind(C)
230      use iso_c_binding, only : C_DOUBLE,C_PTR
231      real(C_DOUBLE),value :: alpha, omega
232      type(C_PTR) :: xc_func
233    end subroutine xc_hyb_gga_xc_hse_set_params
234  end interface
235 !
236  interface
237    subroutine xc_lda_c_xalpha_set_params(xc_func,alpha) bind(C)
238      use iso_c_binding, only : C_DOUBLE,C_PTR
239      real(C_DOUBLE),value :: alpha
240      type(C_PTR) :: xc_func
241    end subroutine xc_lda_c_xalpha_set_params
242  end interface
243 !
244  interface
245    subroutine xc_mgga_x_tb09_set_params(xc_func,c) bind(C)
246      use iso_c_binding, only : C_DOUBLE,C_PTR
247      real(C_DOUBLE),value :: c
248      type(C_PTR) :: xc_func
249    end subroutine xc_mgga_x_tb09_set_params
250  end interface
251 #endif
252 !
253  interface
254    subroutine xc_get_singleprecision_constant(xc_cst_singleprecision) bind(C)
255      use iso_c_binding, only : C_INT
256      integer(C_INT) :: xc_cst_singleprecision
257    end subroutine xc_get_singleprecision_constant
258  end interface
259 !
260  interface
261    subroutine xc_get_family_constants(xc_cst_unknown,xc_cst_lda,xc_cst_gga,xc_cst_mgga, &
262 &                                     xc_cst_lca,xc_cst_oep,xc_cst_hyb_gga,xc_cst_hyb_mgga) &
263 &                                     bind(C)
264      use iso_c_binding, only : C_INT
265      integer(C_INT) :: xc_cst_unknown,xc_cst_lda,xc_cst_gga,xc_cst_mgga, &
266 &                      xc_cst_lca,xc_cst_oep,xc_cst_hyb_gga,xc_cst_hyb_mgga
267    end subroutine xc_get_family_constants
268  end interface
269 !
270  interface
271    subroutine xc_get_flags_constants(xc_cst_flags_have_exc,xc_cst_flags_have_vxc, &
272               xc_cst_flags_have_fxc,xc_cst_flags_have_kxc,xc_cst_flags_have_lxc) bind(C)
273      use iso_c_binding, only : C_INT
274      integer(C_INT) :: xc_cst_flags_have_exc,xc_cst_flags_have_vxc,xc_cst_flags_have_fxc, &
275 &                      xc_cst_flags_have_kxc,xc_cst_flags_have_lxc
276    end subroutine xc_get_flags_constants
277  end interface
278 !
279  interface
280    subroutine xc_get_kind_constants(xc_cst_exchange,xc_cst_correlation, &
281 &                                   xc_cst_exchange_correlation,xc_cst_kinetic) bind(C)
282      use iso_c_binding, only : C_INT
283      integer(C_INT) :: xc_cst_exchange,xc_cst_correlation, &
284 &                      xc_cst_exchange_correlation,xc_cst_kinetic
285    end subroutine xc_get_kind_constants
286  end interface
287 !
288  interface
289    type(C_PTR) function xc_func_type_malloc() bind(C)
290      use iso_c_binding, only : C_PTR
291    end function xc_func_type_malloc
292  end interface
293 !
294  interface
295    subroutine xc_func_type_free(xc_func) bind(C)
296      use iso_c_binding, only : C_PTR
297      type(C_PTR) :: xc_func
298    end subroutine xc_func_type_free
299  end interface
300 !
301  interface
302    type(C_PTR) function xc_get_info_name(xc_func) bind(C)
303      use iso_c_binding, only : C_PTR
304      type(C_PTR) :: xc_func
305    end function xc_get_info_name
306  end interface
307 !
308  interface
309    type(C_PTR) function xc_get_info_refs(xc_func,iref) bind(C)
310      use iso_c_binding, only : C_INT,C_PTR
311      type(C_PTR) :: xc_func
312      integer(C_INT) :: iref
313    end function xc_get_info_refs
314  end interface
315 !
316  interface
317    integer(C_INT) function xc_get_info_flags(xc_func) bind(C)
318      use iso_c_binding, only : C_INT,C_PTR
319      type(C_PTR) :: xc_func
320    end function xc_get_info_flags
321  end interface
322 !
323  interface
324    integer(C_INT) function xc_get_info_kind(xc_func) bind(C)
325      use iso_c_binding, only : C_INT,C_PTR
326      type(C_PTR) :: xc_func
327    end function xc_get_info_kind
328  end interface
329 #endif
330 
331 contains

libxc_functionals/libxc_functionals_check [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_check

FUNCTION

  Check if the code has been compiled with libXC

INPUTS

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

PARENTS

CHILDREN

SOURCE

415  function libxc_functionals_check(stop_if_error)
416 
417 
418 !This section has been created automatically by the script Abilint (TD).
419 !Do not modify the following lines by hand.
420 #undef ABI_FUNC
421 #define ABI_FUNC 'libxc_functionals_check'
422 !End of the abilint section
423 
424  implicit none
425 
426 !Arguments ------------------------------------
427  logical :: libxc_functionals_check
428  logical,intent(in),optional :: stop_if_error
429 !Local variables-------------------------------
430  character(len=100) :: msg
431 
432 ! *************************************************************************
433 
434  libxc_functionals_check=.true. ; msg=""
435 
436 #if defined HAVE_LIBXC
437 #if defined FC_G95
438  libxc_functionals_check=.false.
439  msg='LibXC cannot be used with G95 Fortran compiler!'
440 #endif
441 #if defined HAVE_FC_ISO_C_BINDING
442  if (.not.libxc_constants_initialized) call libxc_functionals_constants_load()
443  if (XC_SINGLE_PRECISION==1) then
444    libxc_functionals_check=.false.
445    msg='LibXC should be compiled with double precision!'
446  end if
447 #else
448  libxc_functionals_check=.false.
449  msg='LibXC cannot be used without ISO_C_BINDING support by the Fortran compiler!'
450 #endif
451 #else
452  libxc_functionals_check=.false.
453  msg='ABINIT was not compiled with LibXC support.'
454 #endif
455 
456  if (present(stop_if_error)) then
457    if (stop_if_error.and.trim(msg)/="") then
458      MSG_ERROR(msg)
459    end if
460  end if
461 
462  end function libxc_functionals_check

libxc_functionals/libxc_functionals_constants_load [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_constants_load

FUNCTION

  Load libXC constants from C headers

PARENTS

      m_libxc_functionals

CHILDREN

SOURCE

350  subroutine libxc_functionals_constants_load()
351 
352 
353 !This section has been created automatically by the script Abilint (TD).
354 !Do not modify the following lines by hand.
355 #undef ABI_FUNC
356 #define ABI_FUNC 'libxc_functionals_constants_load'
357 !End of the abilint section
358 
359  implicit none
360 
361 !Local variables-------------------------------
362 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
363  integer(C_INT) :: i1,i2,i3,i4,i5,i6,i7,i8
364 #endif
365 
366 ! *************************************************************************
367 
368 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
369   call xc_get_singleprecision_constant(i1)
370   XC_SINGLE_PRECISION     = int(i1)
371   call xc_get_family_constants(i1,i2,i3,i4,i5,i6,i7,i8)
372   XC_FAMILY_UNKNOWN       = int(i1)
373   XC_FAMILY_LDA           = int(i2)
374   XC_FAMILY_GGA           = int(i3)
375   XC_FAMILY_MGGA          = int(i4)
376   XC_FAMILY_LCA           = int(i5)
377   XC_FAMILY_OEP           = int(i6)
378   XC_FAMILY_HYB_GGA       = int(i7)
379   XC_FAMILY_HYB_MGGA      = int(i8)
380   call xc_get_flags_constants(i1,i2,i3,i4,i5)
381   XC_FLAGS_HAVE_EXC       = int(i1)
382   XC_FLAGS_HAVE_VXC       = int(i2)
383   XC_FLAGS_HAVE_FXC       = int(i3)
384   XC_FLAGS_HAVE_KXC       = int(i4)
385   XC_FLAGS_HAVE_LXC       = int(i5)
386   call xc_get_kind_constants(i1,i2,i3,i4)
387   XC_EXCHANGE             = int(i1)
388   XC_CORRELATION          = int(i2)
389   XC_EXCHANGE_CORRELATION = int(i3)
390   XC_KINETIC              = int(i4)
391  libxc_constants_initialized=.true.
392 #endif
393 
394  end subroutine libxc_functionals_constants_load

libxc_functionals/libxc_functionals_end [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_end

FUNCTION

  End usage of LibXC functional. Call LibXC end function,
  and deallocate module contents.

INPUTS

OUTPUT

SIDE EFFECTS

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

PARENTS

      calc_vhxc_me,driver,drivexc,invars2,m_kxc,m_xc_vdw,rhotoxc
      xchybrid_ncpp_cc

CHILDREN

SOURCE

672  subroutine libxc_functionals_end(xc_functionals)
673 
674 
675 !This section has been created automatically by the script Abilint (TD).
676 !Do not modify the following lines by hand.
677 #undef ABI_FUNC
678 #define ABI_FUNC 'libxc_functionals_end'
679 !End of the abilint section
680 
681  implicit none
682 
683 !Arguments ------------------------------------
684  type(libxc_functional_type),intent(inout),optional,target :: xc_functionals(2)
685 !Local variables-------------------------------
686  integer :: ii
687  type(libxc_functional_type),pointer :: xc_func
688 
689 ! *************************************************************************
690 
691  do ii = 1,2
692 
693 !  Select XC functional
694    if (present(xc_functionals)) then
695      xc_func => xc_functionals(ii)
696    else
697      xc_func => xc_global(ii)
698    end if
699 
700    if (xc_func%id == 0) cycle
701    xc_func%id=-1
702    xc_func%family=-1
703    xc_func%kind=-1
704    xc_func%nspin=1
705    xc_func%abi_ixc=huge(0)
706    xc_func%has_exc=.false.
707    xc_func%has_vxc=.false.
708    xc_func%has_fxc=.false.
709    xc_func%has_kxc=.false.
710    xc_func%hyb_mixing=zero
711    xc_func%hyb_mixing_sr=zero
712    xc_func%hyb_range=zero
713    if (associated(xc_func%conf)) then
714 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
715      call xc_func_end(xc_func%conf)
716      call xc_func_type_free(c_loc(xc_func%conf))
717 #endif
718    end if
719 
720  end do
721 
722  end subroutine libxc_functionals_end

libxc_functionals/libxc_functionals_family_from_id [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_family_from_id

FUNCTION

  Return family of a XC functional from its id

INPUTS

  xcid= id of a LibXC functional

PARENTS

CHILDREN

SOURCE

819  function libxc_functionals_family_from_id(xcid)
820 
821 
822 !This section has been created automatically by the script Abilint (TD).
823 !Do not modify the following lines by hand.
824 #undef ABI_FUNC
825 #define ABI_FUNC 'libxc_functionals_family_from_id'
826 !End of the abilint section
827 
828  implicit none
829 
830 !Arguments ------------------------------------
831  integer :: libxc_functionals_family_from_id
832  integer,intent(in) :: xcid
833 !Local variables-------------------------------
834 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
835  integer(C_INT) :: xcid_c
836 #endif
837 
838 ! *************************************************************************
839 
840 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
841  xcid_c=int(xcid,kind=C_INT)
842  libxc_functionals_family_from_id=int(xc_family_from_id(xcid_c,C_NULL_PTR,C_NULL_PTR))
843 #else
844  libxc_functionals_family_from_id=-1
845  if (.false.) write(std_out,*) xcid
846 #endif
847 
848 end function libxc_functionals_family_from_id

libxc_functionals/libxc_functionals_fullname [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_fullname

FUNCTION

  Return full name of the XC functional

INPUTS

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

OUTPUT

PARENTS

CHILDREN

SOURCE

746  function libxc_functionals_fullname(xc_functionals)
747 
748 
749 !This section has been created automatically by the script Abilint (TD).
750 !Do not modify the following lines by hand.
751 #undef ABI_FUNC
752 #define ABI_FUNC 'libxc_functionals_fullname'
753 !End of the abilint section
754 
755  implicit none
756 
757 !Arguments ------------------------------------
758  character(len=100) :: libxc_functionals_fullname
759  type(libxc_functional_type),intent(in),optional,target :: xc_functionals(2)
760 !Local variables-------------------------------
761  type(libxc_functional_type),pointer :: xc_funcs(:)
762 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
763  character(len=100) :: xcname
764  character(kind=C_CHAR,len=1),pointer :: strg_c
765 #endif
766 
767 ! *************************************************************************
768 
769  libxc_functionals_fullname='No XC functional'
770 
771  if (present(xc_functionals)) then
772    xc_funcs => xc_functionals
773  else
774    xc_funcs => xc_global
775  end if
776 
777 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
778  if (xc_funcs(1)%id == 0) then
779    if (xc_funcs(2)%id /= 0) then
780      call c_f_pointer(xc_functional_get_name(xc_funcs(2)%id),strg_c)
781      call xc_char_to_f(strg_c,libxc_functionals_fullname)
782    end if
783  else if (xc_funcs(2)%id == 0) then
784    if (xc_funcs(1)%id /= 0) then
785      call c_f_pointer(xc_functional_get_name(xc_funcs(1)%id),strg_c)
786      call xc_char_to_f(strg_c,libxc_functionals_fullname)
787    end if
788  else
789    call c_f_pointer(xc_functional_get_name(xc_funcs(1)%id),strg_c)
790    call xc_char_to_f(strg_c,libxc_functionals_fullname)
791    call c_f_pointer(xc_functional_get_name(xc_funcs(2)%id),strg_c)
792    call xc_char_to_f(strg_c,xcname)
793    libxc_functionals_fullname=trim(libxc_functionals_fullname)//'+'//trim(xcname)
794  end if
795  libxc_functionals_fullname=trim(libxc_functionals_fullname)
796 #endif
797 
798 end function libxc_functionals_fullname

libxc_functionals/libxc_functionals_get_hybridparams [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_get_hybridparams

FUNCTION

  Returns the parameters of an hybrid functional (mixing coefficient(s) and range separation)

INPUTS

 [xc_functionals(2)]=<type(libxc_functional_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)

PARENTS

      invars2,rhotoxc

CHILDREN

SOURCE

1561 subroutine libxc_functionals_get_hybridparams(hyb_mixing,hyb_mixing_sr,hyb_range,xc_functionals)
1562 
1563 
1564 !This section has been created automatically by the script Abilint (TD).
1565 !Do not modify the following lines by hand.
1566 #undef ABI_FUNC
1567 #define ABI_FUNC 'libxc_functionals_get_hybridparams'
1568 !End of the abilint section
1569 
1570  implicit none
1571 
1572 !Arguments ------------------------------------
1573  real(dp),intent(out),optional :: hyb_mixing,hyb_mixing_sr,hyb_range
1574  type(libxc_functional_type),intent(in),optional,target :: xc_functionals(2)
1575 !Local variables -------------------------------
1576  integer :: ii
1577  character(len=500) :: msg
1578  type(libxc_functional_type),pointer :: xc_func
1579 
1580 ! *************************************************************************
1581 
1582  if (present(hyb_mixing   )) hyb_mixing   =zero
1583  if (present(hyb_mixing_sr)) hyb_mixing_sr=zero
1584  if (present(hyb_range    )) hyb_range    =zero
1585 
1586  do ii = 1, 2
1587 
1588 !  Select XC functional
1589    if (present(xc_functionals)) then
1590      xc_func => xc_functionals(ii)
1591    else
1592      xc_func => xc_global(ii)
1593    end if
1594 
1595 !  Mixing coefficient for the Fock contribution
1596    if (present(hyb_mixing)) then
1597      if (abs(xc_func%hyb_mixing) > tol8) then
1598        if (abs(hyb_mixing) <= tol8) then
1599          hyb_mixing=xc_func%hyb_mixing
1600        else
1601          msg='Invalid XC functional: contains 2 hybrid exchange functionals!'
1602          MSG_ERROR(msg)
1603        end if
1604      end if
1605    end if
1606 
1607 !  Mixing coefficient for the short-range Fock contribution
1608    if (present(hyb_mixing_sr)) then
1609      if (abs(xc_func%hyb_mixing_sr) > tol8) then
1610        if (abs(hyb_mixing_sr) <= tol8) then
1611          hyb_mixing_sr=xc_func%hyb_mixing_sr
1612        else
1613          msg='Invalid XC functional: contains 2 hybrid exchange functionals!'
1614          MSG_ERROR(msg)
1615        end if
1616      end if
1617    end if
1618 
1619 !  Range separation
1620    if (present(hyb_range)) then
1621      if (abs(xc_func%hyb_range) > tol8) then
1622        if (abs(hyb_range) <= tol8) then
1623          hyb_range=xc_func%hyb_range
1624        else
1625          msg='Invalid XC functional: contains 2 hybrid exchange functionals!'
1626          MSG_ERROR(msg)
1627        end if
1628      end if
1629    end if
1630 
1631  end do
1632 
1633 end subroutine libxc_functionals_get_hybridparams

libxc_functionals/libxc_functionals_getid [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_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

PARENTS

CHILDREN

SOURCE

870  function libxc_functionals_getid(xcname)
871 
872 
873 !This section has been created automatically by the script Abilint (TD).
874 !Do not modify the following lines by hand.
875 #undef ABI_FUNC
876 #define ABI_FUNC 'libxc_functionals_getid'
877 !End of the abilint section
878 
879  implicit none
880 
881 !Arguments ------------------------------------
882  integer :: libxc_functionals_getid
883  character(len=*),intent(in) :: xcname
884 !Local variables-------------------------------
885 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
886  character(len=256) :: str
887  character(kind=C_CHAR,len=1),target :: name_c(len_trim(xcname)+1)
888  character(kind=C_CHAR,len=1),target :: name_c_xc(len_trim(xcname)-2)
889  type(C_PTR) :: name_c_ptr
890 #endif
891 
892 ! *************************************************************************
893 
894 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
895  str=trim(xcname)
896  if (xcname(1:3)=="XC_".or.xcname(1:3)=="xc_") then
897    str=xcname(4:);name_c_xc=xc_char_to_c(str)
898    name_c_ptr=c_loc(name_c_xc)
899  else
900    name_c=xc_char_to_c(str)
901    name_c_ptr=c_loc(name_c)
902  end if
903  libxc_functionals_getid=int(xc_functional_get_number(name_c_ptr))
904 #else
905  libxc_functionals_getid=-1
906  if (.false.) write(std_out,*) xcname
907 #endif
908 
909 end function libxc_functionals_getid

libxc_functionals/libxc_functionals_getvxc [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_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
 xc_tb09_c=input value for the TB09 C parameter;
           if set to 99, C is computed from rho and grho2

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(libxc_functional_type)>, optional argument
                     XC functionals to initialize

PARENTS

      drivexc,m_pawxc,m_xc_vdw

CHILDREN

SOURCE

1256  subroutine libxc_functionals_getvxc(ndvxc,nd2vxc,npts,nspden,order,rho,exc,vxc,&
1257 &           grho2,vxcgr,lrho,vxclrho,tau,vxctau,dvxc,d2vxc,xc_tb09_c,xc_functionals) ! Optional arguments
1258 
1259 
1260 !This section has been created automatically by the script Abilint (TD).
1261 !Do not modify the following lines by hand.
1262 #undef ABI_FUNC
1263 #define ABI_FUNC 'libxc_functionals_getvxc'
1264 !End of the abilint section
1265 
1266  implicit none
1267 
1268 !Arguments ------------------------------------
1269  integer, intent(in) :: ndvxc,nd2vxc,npts,nspden,order
1270  real(dp),intent(in)  :: rho(npts,nspden)
1271  real(dp),intent(out) :: vxc(npts,nspden),exc(npts)
1272  real(dp),intent(in),optional :: grho2(npts,2*min(nspden,2)-1)
1273  real(dp),intent(out),optional :: vxcgr(npts,3)
1274  real(dp),intent(in),optional :: lrho(npts,nspden)
1275  real(dp),intent(out),optional :: vxclrho(npts,nspden)
1276  real(dp),intent(in),optional :: tau(npts,nspden)
1277  real(dp),intent(out),optional :: vxctau(npts,nspden)
1278  real(dp),intent(out),optional :: dvxc(npts,ndvxc)
1279  real(dp),intent(out),optional :: d2vxc(npts,nd2vxc)
1280  real(dp),intent(in),optional :: xc_tb09_c
1281  type(libxc_functional_type),intent(inout),optional,target :: xc_functionals(2)
1282 !Local variables -------------------------------
1283 !scalars
1284  integer  :: ii,ipts
1285  logical :: is_gga,is_mgga
1286  real(dp) :: xc_tb09_c_
1287 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
1288  type(C_PTR) :: rho_c,sigma_c,lrho_c,tau_c
1289 #endif
1290 !arrays
1291  real(dp),target :: rhotmp(nspden),sigma(3),exctmp,vxctmp(nspden),vsigma(3)
1292  real(dp),target :: v2rho2(3),v2rhosigma(6),v2sigma2(6),v3rho3(4)
1293  real(dp),target :: lrhotmp(nspden),tautmp(nspden),vlrho(nspden),vtau(nspden)
1294  type(libxc_functional_type),pointer :: xc_funcs(:)
1295 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
1296  type(C_PTR) :: exc_c(2),vxc_c(2),vsigma_c(2)
1297  type(C_PTR) :: v2rho2_c(2),v2rhosigma_c(2),v2sigma2_c(2)
1298  type(C_PTR) :: v3rho3_c(2),vlrho_c(2),vtau_c(2)
1299 #endif
1300 
1301 ! *************************************************************************
1302 
1303  if (.not.libxc_constants_initialized) call libxc_functionals_constants_load()
1304 
1305 !Select XC functional(s)
1306  if (present(xc_functionals)) then
1307    xc_funcs => xc_functionals
1308  else
1309    xc_funcs => xc_global
1310  end if
1311 
1312  is_gga =libxc_functionals_isgga (xc_funcs)
1313  is_mgga=libxc_functionals_ismgga(xc_funcs)
1314 
1315 !Inititalize all output arrays to zero
1316  exc=zero ; vxc=zero
1317  if (present(dvxc)) dvxc=zero
1318  if (present(d2vxc)) d2vxc=zero
1319  if (is_gga.or.is_mgga.and.present(vxcgr)) vxcgr=zero
1320  if (is_mgga.and.present(vxclrho)) vxclrho=zero
1321  if (is_mgga.and.present(vxctau)) vxctau=zero
1322 
1323 !Determine which XC outputs can be computed
1324 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
1325  do ii = 1,2
1326    if (xc_funcs(ii)%has_exc) then
1327      exc_c(ii)=c_loc(exctmp)
1328    else
1329      exc_c(ii)=C_NULL_PTR
1330    end if
1331    if (xc_funcs(ii)%has_vxc) then
1332      vxc_c(ii)=c_loc(vxctmp)
1333      vsigma_c(ii)=c_loc(vsigma)
1334      vlrho_c(ii)=c_loc(vlrho)
1335      vtau_c(ii)=c_loc(vtau)
1336    else
1337      vxc_c(ii)=C_NULL_PTR
1338      vsigma_c(ii)=c_NULL_PTR
1339      vlrho_c(ii)=C_NULL_PTR
1340      vtau_c(ii)=C_NULL_PTR
1341    end if
1342    if ((xc_funcs(ii)%has_fxc).and.(order**2>1)) then
1343      v2rho2_c(ii)=c_loc(v2rho2)
1344      v2sigma2_c(ii)=c_loc(v2sigma2)
1345      v2rhosigma_c(ii)=c_loc(v2rhosigma)
1346    else
1347      v2rho2_c(ii)=C_NULL_PTR
1348      v2sigma2_c(ii)=C_NULL_PTR
1349      v2rhosigma_c(ii)=C_NULL_PTR
1350    end if
1351    if ((xc_funcs(ii)%has_kxc).and.(order**2>4)) then
1352      v3rho3_c(ii)=c_loc(v3rho3)
1353    else
1354      v3rho3_c(ii)=C_NULL_PTR
1355    end if
1356  end do
1357 #endif
1358 
1359 !Initialize temporary arrays
1360 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
1361  rhotmp=zero ; rho_c=c_loc(rhotmp)
1362  if (is_gga.or.is_mgga) then
1363    sigma=zero ; sigma_c=c_loc(sigma)
1364  end if
1365  if (is_mgga) then
1366    lrhotmp=zero ; lrho_c=c_loc(lrhotmp)
1367    tautmp=zero ; tau_c=c_loc(tautmp)
1368  end if
1369 #endif
1370 
1371 !Some mGGA functionals require a special treatment
1372  if (is_mgga) then
1373    !TB09 functional requires the c parameter to be set
1374    xc_tb09_c_=99._dp;if (present(xc_tb09_c)) xc_tb09_c_=xc_tb09_c
1375    call libxc_functionals_set_tb09(npts,nspden,rho,grho2,xc_tb09_c_,xc_funcs)
1376  end if
1377 
1378 !Loop over points
1379  do ipts=1,npts
1380 
1381 !  Convert the quantities provided by ABINIT to the ones needed by libxc
1382    if (nspden == 1) then
1383      ! ABINIT passes rho_up in the spin-unpolarized case, while the libxc
1384      ! expects the total density
1385      rhotmp(1:nspden) = two*rho(ipts,1:nspden)
1386    else
1387      rhotmp(1:nspden) = rho(ipts,1:nspden)
1388    end if
1389    if (is_gga.or.is_mgga) then
1390      if (nspden==1) then
1391        ! ABINIT passes |grho_up|^2 while Libxc needs |grho_tot|^2
1392        sigma(1) = four*grho2(ipts,1)
1393      else
1394        ! ABINIT passes |grho_up|^2, |grho_dn|^2, and |grho_tot|^2
1395        ! while Libxc needs |grho_up|^2, grho_up.grho_dn, and |grho_dn|^2
1396        sigma(1) = grho2(ipts,1)
1397        sigma(2) = (grho2(ipts,3) - grho2(ipts,1) - grho2(ipts,2))/two
1398        sigma(3) = grho2(ipts,2)
1399      end if
1400    end if
1401    if (is_mgga) then
1402      if (nspden==1) then
1403        lrhotmp(1:nspden) = two*lrho(ipts,1:nspden)
1404        tautmp(1:nspden) = two*tau(ipts,1:nspden)
1405      else
1406        lrhotmp(1:nspden) = lrho(ipts,1:nspden)
1407        tautmp(1:nspden) = tau(ipts,1:nspden)
1408      end if
1409    end if
1410 
1411 !  Loop over functionals
1412    do ii = 1,2
1413      if (xc_funcs(ii)%id==0) cycle
1414 
1415 !    Get the potential (and possibly the energy)
1416 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
1417      exctmp=zero ; vxctmp=zero
1418 !    ===== LDA =====
1419      if (xc_funcs(ii)%family==XC_FAMILY_LDA) then
1420        exctmp=zero ; vxctmp=zero ; v2rho2=zero ; v3rho3=zero
1421        call xc_lda(xc_funcs(ii)%conf,1,rho_c, &
1422 &                  exc_c(ii),vxc_c(ii),v2rho2_c(ii),v3rho3_c(ii))
1423 !    ===== GGA =====
1424      else if (xc_funcs(ii)%family==XC_FAMILY_GGA.or. &
1425 &             xc_funcs(ii)%family==XC_FAMILY_HYB_GGA) then
1426        exctmp=zero ; vxctmp=zero ; vsigma=zero
1427        v2rho2=zero ; v2sigma2=zero ; v2rhosigma=zero
1428        call xc_gga(xc_funcs(ii)%conf,1,rho_c,sigma_c, &
1429 &                  exc_c(ii),vxc_c(ii),vsigma_c(ii), &
1430 &                  v2rho2_c(ii),v2rhosigma_c(ii),v2sigma2_c(ii), &
1431 &                  C_NULL_PTR,C_NULL_PTR,C_NULL_PTR,C_NULL_PTR)
1432 !    ===== mGGA =====
1433      else if (xc_funcs(ii)%family==XC_FAMILY_MGGA) then
1434        exctmp=zero ; vxctmp=zero ; vsigma=zero ; vlrho=zero ; vtau=zero
1435        call xc_mgga(xc_funcs(ii)%conf,1,rho_c,sigma_c,lrho_c,tau_c, &
1436 &                   exc_c(ii),vxc_c(ii),vsigma_c(ii),vlrho_c(ii),vtau_c(ii), &
1437 &                   C_NULL_PTR,C_NULL_PTR,C_NULL_PTR,C_NULL_PTR,C_NULL_PTR, &
1438 &                   C_NULL_PTR,C_NULL_PTR,C_NULL_PTR,C_NULL_PTR,C_NULL_PTR)
1439      end if
1440 #endif
1441 
1442      exc(ipts) = exc(ipts) + exctmp
1443      vxc(ipts,1:nspden) = vxc(ipts,1:nspden) + vxctmp(1:nspden)
1444 
1445 !    Deal with fxc and kxc
1446      if (order**2>1) then
1447 !      ----- LDA -----
1448        if (xc_funcs(ii)%family==XC_FAMILY_LDA) then
1449          if (nspden==1) then
1450            if(order>=2) then
1451              dvxc(ipts,1)=dvxc(ipts,1)+v2rho2(1)
1452              if(order==3) then
1453                d2vxc(ipts,1)=d2vxc(ipts,1)+v3rho3(1)
1454              endif
1455            else
1456              dvxc(ipts,1)=dvxc(ipts,1)+v2rho2(1)
1457              dvxc(ipts,2)=dvxc(ipts,2)+v2rho2(1)
1458            endif
1459          else
1460            dvxc(ipts,1)=dvxc(ipts,1)+v2rho2(1)
1461            dvxc(ipts,2)=dvxc(ipts,2)+v2rho2(2)
1462            dvxc(ipts,3)=dvxc(ipts,3)+v2rho2(3)
1463            if(order==3) then
1464              d2vxc(ipts,1)=d2vxc(ipts,1)+v3rho3(1)
1465              d2vxc(ipts,2)=d2vxc(ipts,2)+v3rho3(2)
1466              d2vxc(ipts,3)=d2vxc(ipts,3)+v3rho3(3)
1467              d2vxc(ipts,4)=d2vxc(ipts,4)+v3rho3(4)
1468            endif
1469          endif
1470 !      ----- GGA -----
1471        else if (xc_funcs(ii)%family==XC_FAMILY_GGA.or. &
1472 &               xc_funcs(ii)%family==XC_FAMILY_HYB_GGA) then
1473          if (xc_funcs(ii)%kind==XC_EXCHANGE) then
1474            if (nspden==1) then
1475              dvxc(ipts,1)=v2rho2(1)*two
1476              dvxc(ipts,2)=dvxc(ipts,1)
1477              dvxc(ipts,3)=two*two*vsigma(1)
1478              dvxc(ipts,4)=dvxc(ipts,3)
1479              dvxc(ipts,5)=four*two*v2rhosigma(1)
1480              dvxc(ipts,6)=dvxc(ipts,5)
1481              dvxc(ipts,7)=two*four*four*v2sigma2(1)
1482              dvxc(ipts,8)=dvxc(ipts,7)
1483            else
1484              dvxc(ipts,1)=v2rho2(1)
1485              dvxc(ipts,2)=v2rho2(3)
1486              dvxc(ipts,3)=two*vsigma(1)
1487              dvxc(ipts,4)=two*vsigma(3)
1488              dvxc(ipts,5)=two*v2rhosigma(1)
1489              dvxc(ipts,6)=two*v2rhosigma(6)
1490              dvxc(ipts,7)=four*v2sigma2(1)
1491              dvxc(ipts,8)=four*v2sigma2(6)
1492            end if
1493          else if (xc_funcs(ii)%kind==XC_CORRELATION) then
1494            if (nspden==1) then
1495              dvxc(ipts,9)=v2rho2(1)
1496              dvxc(ipts,10)=dvxc(ipts,9)
1497              dvxc(ipts,11)=dvxc(ipts,9)
1498              dvxc(ipts,12)=two*vsigma(1)
1499              dvxc(ipts,13)=two*v2rhosigma(1)
1500              dvxc(ipts,14)=dvxc(ipts,13)
1501              dvxc(ipts,15)=four*v2sigma2(1)
1502            else
1503              dvxc(ipts,9)=v2rho2(1)
1504              dvxc(ipts,10)=v2rho2(2)
1505              dvxc(ipts,11)=v2rho2(3)
1506              dvxc(ipts,12)=two*vsigma(1)
1507              dvxc(ipts,13)=two*v2rhosigma(1)
1508              dvxc(ipts,14)=two*v2rhosigma(6)
1509              dvxc(ipts,15)=four*v2sigma2(1)
1510            end if
1511          end if
1512        end if
1513      end if
1514 
1515 !    Convert the quantities returned by Libxc to the ones needed by ABINIT
1516      if (is_gga.or.is_mgga) then
1517        if (nspden==1) then
1518          vxcgr(ipts,3) = vxcgr(ipts,3) + vsigma(1)*two
1519        else
1520          vxcgr(ipts,1) = vxcgr(ipts,1) + two*vsigma(1) - vsigma(2)
1521          vxcgr(ipts,2) = vxcgr(ipts,2) + two*vsigma(3) - vsigma(2)
1522          vxcgr(ipts,3) = vxcgr(ipts,3) + vsigma(2)
1523        end if
1524      end if
1525      if (is_mgga) then
1526        vxclrho(ipts,1:nspden) = vxclrho(ipts,1:nspden) + vlrho(1:nspden)
1527        vxctau(ipts,1:nspden)  = vxctau(ipts,1:nspden)  + vtau(1:nspden)
1528      end if
1529 
1530    end do ! ii
1531  end do   ! ipts
1532 
1533 end subroutine libxc_functionals_getvxc

libxc_functionals/libxc_functionals_gga_from_hybrid [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_gga_from_hybrid

FUNCTION

  Returns a logical flag: TRUE if one can deduce, from the id of a hybrid functional,
  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 xc_global datastructure.

INPUTS

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

OUTPUT

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

SOURCE

1792 function libxc_functionals_gga_from_hybrid(gga_id,hybrid_id,xc_functionals)
1793 
1794 
1795 !This section has been created automatically by the script Abilint (TD).
1796 !Do not modify the following lines by hand.
1797 #undef ABI_FUNC
1798 #define ABI_FUNC 'libxc_functionals_gga_from_hybrid'
1799 !End of the abilint section
1800 
1801  implicit none
1802 
1803 !Arguments ------------------------------------
1804 !scalars
1805  integer,intent(in),optional :: hybrid_id
1806  logical :: libxc_functionals_gga_from_hybrid
1807 !arrays
1808  integer,intent(out),optional :: gga_id(2)
1809  type(libxc_functional_type),intent(inout),optional,target :: xc_functionals(2)
1810 !Local variables -------------------------------
1811 !scalars
1812  integer :: family,ii
1813  character(len=100) :: c_name,x_name,msg
1814 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
1815  character(len=100) :: xc_name
1816  character(kind=C_CHAR,len=1),pointer :: strg_c
1817 #endif
1818 !arrays
1819  integer :: trial_id(2)
1820 
1821 ! *************************************************************************
1822 
1823  libxc_functionals_gga_from_hybrid=.false.
1824 
1825  if (present(hybrid_id)) then
1826    trial_id(1)=hybrid_id
1827    trial_id(2)=0
1828  else if (present(xc_functionals)) then
1829    trial_id(1)=xc_functionals(1)%id
1830    trial_id(2)=xc_functionals(2)%id
1831  else
1832    trial_id(1)=xc_global(1)%id
1833    trial_id(2)=xc_global(2)%id
1834  end if
1835 
1836  c_name="unknown" ; x_name="unknown"
1837 
1838 !Specific treatment of the B3LYP functional, whose GGA counterpart does not exist in LibXC
1839  if(trial_id(1)==402 .or. trial_id(2)==402)then
1840    libxc_functionals_gga_from_hybrid=.true.
1841    if (present(gga_id)) then
1842      gga_id(1)=0
1843      gga_id(2)=-1402 ! This corresponds to a native ABINIT functional,
1844                      ! actually a composite from different LibXC functionals!
1845      write(std_out,*)' libxc_functionals_gga_from_hybrid, return with gga_id=',gga_id
1846    endif
1847    return
1848  endif
1849 
1850  do ii = 1, 2
1851 
1852    if (trial_id(ii)==0) cycle
1853    family=libxc_functionals_family_from_id(trial_id(ii))
1854    if (family/=XC_FAMILY_HYB_GGA.and.family/=XC_FAMILY_HYB_MGGA) cycle
1855 
1856    if (libxc_functionals_gga_from_hybrid) then
1857      msg='Invalid XC functional: contains 2 hybrid functionals!'
1858      MSG_ERROR(msg)
1859    end if
1860 
1861 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
1862 
1863    call c_f_pointer(xc_functional_get_name(trial_id(ii)),strg_c)
1864    call xc_char_to_f(strg_c,xc_name)
1865 
1866 !  AVAILABLE FUNCTIONALS
1867 
1868 !  ===== PBE0 =====
1869    if (xc_name=="hyb_gga_xc_pbeh" .or. &
1870 &      xc_name=="hyb_gga_xc_pbe0_13") then
1871      c_name="GGA_C_PBE"
1872      x_name="GGA_X_PBE"
1873      libxc_functionals_gga_from_hybrid=.true.
1874 
1875 !  ===== HSE =====
1876    else if (xc_name=="hyb_gga_xc_hse03" .or. &
1877 &           xc_name=="hyb_gga_xc_hse06" ) then
1878      c_name="GGA_C_PBE"
1879      x_name="GGA_X_PBE"
1880      libxc_functionals_gga_from_hybrid=.true.
1881    end if
1882 
1883 
1884 #endif
1885 
1886  enddo ! ii
1887 
1888  if (present(gga_id)) then
1889    if (libxc_functionals_gga_from_hybrid) then
1890      gga_id(1)=libxc_functionals_getid(c_name)
1891      gga_id(2)=libxc_functionals_getid(x_name)
1892    else
1893      gga_id(:)=-1
1894    end if
1895  end if
1896 
1897 !Note that in the case of B3LYP functional, the return happened immediately after the setup of B3LYP parameters.
1898 
1899 end function libxc_functionals_gga_from_hybrid

libxc_functionals/libxc_functionals_has_kxc [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_has_kxc

FUNCTION

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

INPUTS

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

PARENTS

CHILDREN

SOURCE

1134 function libxc_functionals_has_kxc(xc_functionals)
1135 
1136 
1137 !This section has been created automatically by the script Abilint (TD).
1138 !Do not modify the following lines by hand.
1139 #undef ABI_FUNC
1140 #define ABI_FUNC 'libxc_functionals_has_kxc'
1141 !End of the abilint section
1142 
1143  implicit none
1144 
1145 !Arguments ------------------------------------
1146  logical :: libxc_functionals_has_kxc
1147  type(libxc_functional_type),intent(in),optional,target :: xc_functionals(2)
1148 !Local variables-------------------------------
1149  integer :: ii
1150 
1151 ! *************************************************************************
1152 
1153  libxc_functionals_has_kxc=.true.
1154 
1155  do ii=1,2
1156    if (present(xc_functionals)) then
1157      if (.not.xc_functionals(ii)%has_fxc) libxc_functionals_has_kxc=.false.
1158    else
1159      if (.not.xc_global(ii)%has_fxc) libxc_functionals_has_kxc=.false.
1160    end if
1161  end do
1162 
1163 end function libxc_functionals_has_kxc

libxc_functionals/libxc_functionals_init [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_init

FUNCTION

  Initialize the desired XC functional, from LibXC.
  * Call the LibXC initializer
  * Fill preliminary fields in module structures.

INPUTS

 ixc=XC code for Abinit
 nspden=number of spin-density components

OUTPUT

SIDE EFFECTS

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

PARENTS

      calc_vhxc_me,driver,drivexc,invars2,m_kxc,m_xc_vdw,rhotoxc
      xchybrid_ncpp_cc

CHILDREN

SOURCE

494  subroutine libxc_functionals_init(ixc,nspden,xc_functionals)
495 
496 
497 !This section has been created automatically by the script Abilint (TD).
498 !Do not modify the following lines by hand.
499 #undef ABI_FUNC
500 #define ABI_FUNC 'libxc_functionals_init'
501 !End of the abilint section
502 
503  implicit none
504 
505 !Arguments ------------------------------------
506  integer, intent(in) :: nspden
507  integer, intent(in) :: ixc
508  type(libxc_functional_type),intent(inout),optional,target :: xc_functionals(2)
509 !Local variables-------------------------------
510  integer :: ii,nspden_eff
511  character(len=500) :: msg
512  type(libxc_functional_type),pointer :: xc_func
513 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
514  integer :: flags
515  integer(C_INT) :: func_id_c,iref_c,nspin_c,success_c
516  real(C_DOUBLE) :: alpha_c,beta_c,omega_c
517  character(kind=C_CHAR,len=1),pointer :: strg_c
518  type(C_PTR) :: func_ptr_c
519 #endif
520 
521 ! *************************************************************************
522 
523 !Check libXC
524  if (.not.libxc_functionals_check(stop_if_error=.true.)) return
525  if (.not.libxc_constants_initialized) call libxc_functionals_constants_load()
526 
527  nspden_eff=min(nspden,2)
528 
529 !Select XC functional(s) identifiers
530  if (present(xc_functionals)) then
531    xc_functionals(1)%id = -ixc/1000
532    xc_functionals(2)%id = -ixc + (ixc/1000)*1000
533  else
534    xc_global(1)%id = -ixc/1000
535    xc_global(2)%id = -ixc + (ixc/1000)*1000
536  end if
537 
538  do ii = 1,2
539 
540 !  Select XC functional
541    if (present(xc_functionals)) then
542      xc_func => xc_functionals(ii)
543    else
544      xc_func => xc_global(ii)
545    end if
546 
547    xc_func%abi_ixc=ixc !Save abinit value for reference
548 
549    xc_func%family=XC_FAMILY_UNKNOWN
550    xc_func%kind=-1
551    xc_func%nspin=nspden_eff
552    xc_func%has_exc=.false.
553    xc_func%has_vxc=.false.
554    xc_func%has_fxc=.false.
555    xc_func%has_kxc=.false.
556    xc_func%hyb_mixing=zero
557    xc_func%hyb_mixing_sr=zero
558    xc_func%hyb_range=zero
559 
560    if (xc_func%id==0) cycle
561 
562 !  Get XC functional family
563    xc_func%family=libxc_functionals_family_from_id(xc_func%id)
564    if (xc_func%family/=XC_FAMILY_LDA.and.xc_func%family/=XC_FAMILY_GGA.and. &
565 &      xc_func%family/=XC_FAMILY_HYB_GGA.and.xc_func%family/=XC_FAMILY_MGGA) then
566      write(msg, '(a,i8,2a,i8,6a)' )&
567 &      'Invalid IXC = ',ixc,ch10,&
568 &      'The LibXC functional family ',xc_func%family,&
569 &      ' is currently unsupported by ABINIT',ch10,&
570 &      '(-1 means the family is unknown to the LibXC itself)',ch10,&
571 &      'Please consult the LibXC documentation',ch10
572      MSG_ERROR(msg)
573    end if
574 
575 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
576 
577 !  Allocate functional
578    func_ptr_c=xc_func_type_malloc()
579    call c_f_pointer(func_ptr_c,xc_func%conf)
580 
581 !  Initialize functional
582    func_id_c=int(xc_func%id,kind=C_INT)
583    nspin_c=int(nspden_eff,kind=C_INT)
584    success_c=xc_func_init(xc_func%conf,func_id_c,nspin_c)
585    if (success_c/=0) then
586      msg='Error in libXC functional initialization!'
587      MSG_ERROR(msg)
588    end if
589 
590 !  Special treatment for LDA_C_XALPHA functional
591    if (xc_func%id==libxc_functionals_getid('XC_LDA_C_XALPHA')) then
592      alpha_c=real(zero,kind=C_DOUBLE)
593 #if ( XC_MAJOR_VERSION < 4 )
594      call xc_lda_c_xalpha_set_params(xc_func%conf,alpha_c);
595 #else
596      msg='seems set_params has disappeared for xalpha in libxc 4. defaults are being used'
597      MSG_WARNING(msg)
598      !call xc_hyb_gga_xc_pbeh_init(xc_func%conf)
599 #endif
600 
601    end if
602 
603 !  Get functional kind
604    xc_func%kind=int(xc_get_info_kind(xc_func%conf))
605 
606 !  Get functional flags
607    flags=int(xc_get_info_flags(xc_func%conf))
608    xc_func%has_exc=(iand(flags,XC_FLAGS_HAVE_EXC)>0)
609    xc_func%has_vxc=(iand(flags,XC_FLAGS_HAVE_VXC)>0)
610    xc_func%has_fxc=(iand(flags,XC_FLAGS_HAVE_FXC)>0)
611    xc_func%has_kxc=(iand(flags,XC_FLAGS_HAVE_KXC)>0)
612 
613 !  Retrieve parameters for hybrid functionals
614    if (xc_func%family==XC_FAMILY_HYB_GGA.or.xc_func%family==XC_FAMILY_MGGA) then
615      call xc_hyb_cam_coef(xc_func%conf,omega_c,alpha_c,beta_c)
616      xc_func%hyb_mixing=real(alpha_c,kind=dp)
617      xc_func%hyb_mixing_sr=real(beta_c,kind=dp)
618      xc_func%hyb_range=real(omega_c,kind=dp)
619    endif
620 
621 !  Dump functional information
622    call c_f_pointer(xc_get_info_name(xc_func%conf),strg_c)
623    call xc_char_to_f(strg_c,msg);msg=' '//trim(msg)
624    call wrtout(std_out,msg,'COLL')
625    iref_c=0
626    do while (iref_c>=0)
627      call c_f_pointer(xc_get_info_refs(xc_func%conf,iref_c),strg_c)
628      if (associated(strg_c)) then
629        call xc_char_to_f(strg_c,msg);msg=' '//trim(msg)
630        call wrtout(std_out,msg,'COLL')
631        iref_c=iref_c+1
632      else
633        iref_c=-1
634      end if
635    end do
636 
637 #endif
638 
639  end do
640 
641  msg='';call wrtout(std_out,msg,'COLL')
642 
643 end subroutine libxc_functionals_init

libxc_functionals/libxc_functionals_is_hybrid [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_is_hybrid

FUNCTION

  Test function to identify whether the presently used functional
  is hybrid or not

INPUTS

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

PARENTS

CHILDREN

SOURCE

1083  function libxc_functionals_is_hybrid(xc_functionals)
1084 
1085 
1086 !This section has been created automatically by the script Abilint (TD).
1087 !Do not modify the following lines by hand.
1088 #undef ABI_FUNC
1089 #define ABI_FUNC 'libxc_functionals_is_hybrid'
1090 !End of the abilint section
1091 
1092  implicit none
1093 
1094 !Arguments ------------------------------------
1095  logical :: libxc_functionals_is_hybrid
1096  type(libxc_functional_type),intent(in),optional :: xc_functionals(2)
1097 
1098 ! *************************************************************************
1099 
1100  libxc_functionals_is_hybrid = .false.
1101  if (.not.libxc_constants_initialized) call libxc_functionals_constants_load()
1102 
1103  if (present(xc_functionals)) then
1104    libxc_functionals_is_hybrid=(any(xc_functionals%family==XC_FAMILY_HYB_GGA) .or. &
1105 &                               any(xc_functionals%family==XC_FAMILY_HYB_MGGA))
1106  else
1107    libxc_functionals_is_hybrid=(any(xc_global%family==XC_FAMILY_HYB_GGA) .or. &
1108 &                               any(xc_global%family==XC_FAMILY_HYB_MGGA))
1109  end if
1110 
1111 end function libxc_functionals_is_hybrid

libxc_functionals/libxc_functionals_isgga [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_isgga

FUNCTION

  Test function to identify whether the presently used functional
  is a GGA or not

INPUTS

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

PARENTS

CHILDREN

SOURCE

 977  function libxc_functionals_isgga(xc_functionals)
 978 
 979 
 980 !This section has been created automatically by the script Abilint (TD).
 981 !Do not modify the following lines by hand.
 982 #undef ABI_FUNC
 983 #define ABI_FUNC 'libxc_functionals_isgga'
 984 !End of the abilint section
 985 
 986  implicit none
 987 
 988 !Arguments ------------------------------------
 989  logical :: libxc_functionals_isgga
 990  type(libxc_functional_type),intent(in),optional :: xc_functionals(2)
 991 
 992 ! *************************************************************************
 993 
 994  libxc_functionals_isgga = .false.
 995  if (.not.libxc_constants_initialized) call libxc_functionals_constants_load()
 996 
 997  if (present(xc_functionals)) then
 998    libxc_functionals_isgga=(any(xc_functionals%family==XC_FAMILY_GGA) .or. &
 999 &                           any(xc_functionals%family==XC_FAMILY_HYB_GGA))
1000  else
1001    libxc_functionals_isgga=(any(xc_global%family==XC_FAMILY_GGA) .or. &
1002 &                           any(xc_global%family==XC_FAMILY_HYB_GGA))
1003  end if
1004 
1005 end function libxc_functionals_isgga

libxc_functionals/libxc_functionals_ismgga [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_ismgga

FUNCTION

  Test function to identify whether the presently used functional
  is a Meta-GGA or not

INPUTS

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

PARENTS

CHILDREN

SOURCE

1028 function libxc_functionals_ismgga(xc_functionals)
1029 
1030 
1031 !This section has been created automatically by the script Abilint (TD).
1032 !Do not modify the following lines by hand.
1033 #undef ABI_FUNC
1034 #define ABI_FUNC 'libxc_functionals_ismgga'
1035 !End of the abilint section
1036 
1037  implicit none
1038 
1039 !Arguments ------------------------------------
1040  logical :: libxc_functionals_ismgga
1041  type(libxc_functional_type),intent(in),optional :: xc_functionals(2)
1042 
1043 ! *************************************************************************
1044 
1045  libxc_functionals_ismgga = .false.
1046  if (.not.libxc_constants_initialized) call libxc_functionals_constants_load()
1047 
1048  if (present(xc_functionals)) then
1049    libxc_functionals_ismgga =(any(xc_functionals%family==XC_FAMILY_MGGA))
1050  else
1051    libxc_functionals_ismgga =(any(xc_global%family==XC_FAMILY_MGGA))
1052  end if
1053 
1054 !DEBUG
1055 ! write(std_out,*)' libxc_functionals_ismgga : present(xc_functionals)=',present(xc_functionals)
1056 !write(std_out,*)' libxc_functionals_ismgga : xc_func%abi_ixc=',xc_func%abi_ixc
1057 ! write(std_out,*)' libxc_functionals_ismgga : libxc_functionals_ismgga=',libxc_functionals_ismgga
1058 !ENDDEBUG
1059 
1060 end function libxc_functionals_ismgga

libxc_functionals/libxc_functionals_ixc [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_ixc

FUNCTION

  Return the value of ixc used to initialize the XC structure

INPUTS

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

PARENTS

CHILDREN

SOURCE

931  function libxc_functionals_ixc(xc_functionals)
932 
933 
934 !This section has been created automatically by the script Abilint (TD).
935 !Do not modify the following lines by hand.
936 #undef ABI_FUNC
937 #define ABI_FUNC 'libxc_functionals_ixc'
938 !End of the abilint section
939 
940  implicit none
941 
942 !Arguments ------------------------------------
943  integer :: libxc_functionals_ixc
944  type(libxc_functional_type),intent(in),optional :: xc_functionals(2)
945 
946 ! *************************************************************************
947 
948  if (present(xc_functionals)) then
949    libxc_functionals_ixc=xc_functionals(1)%abi_ixc
950  else
951    libxc_functionals_ixc=xc_global(1)%abi_ixc
952  end if
953 
954 end function libxc_functionals_ixc

libxc_functionals/libxc_functionals_nspin [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_nspin

FUNCTION

  Returns the number of spin components for the XC functionals

INPUTS

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

PARENTS

CHILDREN

SOURCE

1185 function libxc_functionals_nspin(xc_functionals)
1186 
1187 
1188 !This section has been created automatically by the script Abilint (TD).
1189 !Do not modify the following lines by hand.
1190 #undef ABI_FUNC
1191 #define ABI_FUNC 'libxc_functionals_nspin'
1192 !End of the abilint section
1193 
1194  implicit none
1195 
1196 !Arguments ------------------------------------
1197  integer :: libxc_functionals_nspin
1198  type(libxc_functional_type),intent(in),optional :: xc_functionals(2)
1199 
1200 ! *************************************************************************
1201 
1202  libxc_functionals_nspin = 1
1203 
1204  if (present(xc_functionals)) then
1205    if (any(xc_functionals%nspin==2)) libxc_functionals_nspin=2
1206  else
1207    if (any(xc_global%nspin==2)) libxc_functionals_nspin=2
1208  end if
1209 
1210 end function libxc_functionals_nspin

libxc_functionals/libxc_functionals_set_hybridparams [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_set_hybridparams

FUNCTION

  Set the parameters of an hybrid functional (mixing coefficient(s) and range separation)

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(libxc_functional_type)>, optional argument
                     XC functionals to initialize

OUTPUT

PARENTS

      calc_vhxc_me,m_fock

CHILDREN

SOURCE

1661 subroutine libxc_functionals_set_hybridparams(hyb_mixing,hyb_mixing_sr,hyb_range,xc_functionals)
1662 
1663 
1664 !This section has been created automatically by the script Abilint (TD).
1665 !Do not modify the following lines by hand.
1666 #undef ABI_FUNC
1667 #define ABI_FUNC 'libxc_functionals_set_hybridparams'
1668 !End of the abilint section
1669 
1670  implicit none
1671 
1672 !Arguments ------------------------------------
1673  real(dp),intent(in),optional :: hyb_mixing,hyb_mixing_sr,hyb_range
1674  type(libxc_functional_type),intent(in),optional,target :: xc_functionals(2)
1675 !Local variables -------------------------------
1676  integer :: ii,id_pbe0,id_hse03,id_hse06
1677  logical :: is_pbe0,is_hse
1678  integer :: func_id(2)
1679  character(len=500) :: msg
1680 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
1681  real(C_DOUBLE) :: alpha_c,beta_c,omega_c
1682 #endif
1683  type(libxc_functional_type),pointer :: xc_func
1684 
1685 ! *************************************************************************
1686 
1687  is_pbe0=.false.
1688  is_hse =.false.
1689  id_pbe0=libxc_functionals_getid('HYB_GGA_XC_PBEH')
1690  id_hse03=libxc_functionals_getid('HYB_GGA_XC_HSE03')
1691  id_hse06=libxc_functionals_getid('HYB_GGA_XC_HSE06')
1692 
1693  do ii = 1, 2
1694 
1695 !  Select XC functional
1696    if (present(xc_functionals)) then
1697      xc_func => xc_functionals(ii)
1698    else
1699      xc_func => xc_global(ii)
1700    end if
1701    func_id(ii)=xc_func%id
1702 
1703 !  Doesnt work with all hybrid functionals
1704    if (is_pbe0.or.is_hse) then
1705      msg='Invalid XC functional: contains 2 hybrid exchange functionals!'
1706      MSG_ERROR(msg)
1707    end if
1708    is_pbe0=(xc_func%id==id_pbe0)
1709    is_hse=((xc_func%id==id_hse03).or.(xc_func%id==id_hse06))
1710    if ((.not.is_pbe0).and.(.not.is_hse)) cycle
1711 
1712 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
1713 !  New values for parameters
1714 
1715 !  PBE0 type functionals
1716    if (present(hyb_mixing))then
1717      xc_func%hyb_mixing=hyb_mixing
1718      alpha_c=real(xc_func%hyb_mixing,kind=C_DOUBLE)
1719      if(is_pbe0)then
1720 #if ( XC_MAJOR_VERSION < 4 )
1721        call xc_hyb_gga_xc_pbeh_set_params(xc_func%conf,alpha_c)
1722 #else
1723        msg='seems set_params has disappeared for pbeh in libxc 4. defaults are being used'
1724        MSG_WARNING(msg)
1725        !call xc_hyb_gga_xc_pbeh_init(xc_func%conf)
1726 #endif
1727      endif
1728    endif
1729 
1730 !  HSE type functionals
1731    if(present(hyb_mixing_sr).or.present(hyb_range))then
1732      if(present(hyb_mixing_sr))xc_func%hyb_mixing_sr=hyb_mixing_sr
1733      if(present(hyb_range))xc_func%hyb_range=hyb_range
1734      beta_c=real(xc_func%hyb_mixing_sr,kind=C_DOUBLE)
1735      omega_c=real(xc_func%hyb_range,kind=C_DOUBLE)
1736      if(is_hse)then
1737 #if ( XC_MAJOR_VERSION < 4 )
1738        call xc_hyb_gga_xc_hse_set_params(xc_func%conf,beta_c,omega_c)
1739 #else
1740        msg='seems set_params has disappeared for hse in libxc 4. defaults are being used'
1741        MSG_WARNING(msg)
1742      !call hyb_gga_xc_hse_init(xc_func%conf)
1743 #endif
1744      endif
1745    end if
1746 
1747 #else
1748    ABI_UNUSED(hyb_mixing)
1749    ABI_UNUSED(hyb_mixing_sr)
1750    ABI_UNUSED(hyb_range)
1751 #endif
1752 
1753  end do
1754 
1755  if ((.not.is_pbe0).and.(.not.is_hse)) then
1756    write(msg,'(3a,2i6,a,a,i6,a,i6,a,i6,a)')'Invalid XC functional: not able to change parameters for this functional !',ch10,&
1757 &      'The IDs are ',func_id(:),ch10,&
1758 &      'Allowed HYB_GGA_XC_PBEH, HYB_GGA_XC_HSE03, and HYB_GGA_XC_HSE06 with IDs =',id_pbe0,',',id_hse03,',',id_hse06,'.'
1759    MSG_ERROR(msg)
1760  end if
1761 
1762 end subroutine libxc_functionals_set_hybridparams

libxc_functionals/libxc_functionals_set_tb09 [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  libxc_functionals_set_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
 xc_tb09_c=input value for the TB09 C parameter;
           if set to 99, C is computed from rho and grho2

OUTPUT

SIDE EFFECTS

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

PARENTS

      m_libxc_functionals

CHILDREN

SOURCE

1932  subroutine libxc_functionals_set_tb09(npts,nspden,rho,grho2,xc_tb09_c,xc_functionals)
1933 
1934 
1935 !This section has been created automatically by the script Abilint (TD).
1936 !Do not modify the following lines by hand.
1937 #undef ABI_FUNC
1938 #define ABI_FUNC 'libxc_functionals_set_tb09'
1939 !End of the abilint section
1940 
1941  implicit none
1942 
1943 !Arguments ------------------------------------
1944  integer, intent(in) :: npts,nspden
1945  real(dp),intent(in)  :: rho(npts,nspden),grho2(npts,2*min(nspden,2)-1)
1946  real(dp),intent(in) :: xc_tb09_c
1947  type(libxc_functional_type),intent(inout),optional,target :: xc_functionals(2)
1948 !Local variables -------------------------------
1949 !scalars
1950  integer  :: ii,ipts
1951  logical :: is_mgga_tb09
1952  real(dp) :: cc
1953  character(len=500) :: msg
1954 !arrays
1955  type(libxc_functional_type),pointer :: xc_funcs(:)
1956  real(dp),allocatable :: gnon(:)
1957 
1958 ! *************************************************************************
1959 
1960  if (.not.libxc_constants_initialized) call libxc_functionals_constants_load()
1961 
1962 !Select XC functional(s)
1963  if (present(xc_functionals)) then
1964    xc_funcs => xc_functionals
1965  else
1966    xc_funcs => xc_global
1967  end if
1968 
1969  is_mgga_tb09=(any(xc_funcs%id==libxc_functionals_getid('XC_MGGA_X_TB09')))
1970 
1971  if (is_mgga_tb09) then
1972 
1973 !  C is fixed by the user
1974    if (abs(xc_tb09_c-99._dp)>tol12) then
1975      cc=xc_tb09_c
1976      write(msg,'(2a,f9.6)' ) ch10,&
1977 &      'In the mGGA functional TB09, c is fixed by the user and is equal to ',cc
1978      call wrtout(std_out,msg,'COLL')
1979 
1980 !  C is computed
1981    else
1982      ABI_ALLOCATE(gnon,(npts))
1983      do ipts=1,npts
1984        if (sum(rho(ipts,:))<=1e-7_dp) then
1985          gnon(ipts)=zero
1986        else
1987          if (nspden==1) then
1988            gnon(ipts)=sqrt(grho2(ipts,1))/rho(ipts,1)
1989          else
1990            gnon(ipts)=sqrt(grho2(ipts,3))/sum(rho(ipts,:))
1991          end if
1992        end if
1993      end do
1994      cc= -0.012_dp + 1.023_dp*sqrt(sum(gnon)/npts)
1995      ABI_DEALLOCATE(gnon)
1996      write(msg,'(2a,f9.6)' ) ch10,'In the mGGA functional TB09, c = ',cc
1997      call wrtout(std_out,msg,'COLL')
1998    end if
1999 
2000 !  Set c in XC data structure
2001    do ii=1,2
2002      if (xc_funcs(ii)%id==libxc_functionals_getid('XC_MGGA_X_TB09')) then
2003 #if defined HAVE_LIBXC && defined HAVE_FC_ISO_C_BINDING
2004 #if ( XC_MAJOR_VERSION < 4 )
2005        call xc_mgga_x_tb09_set_params(xc_funcs(ii)%conf,cc)
2006 #else
2007        msg='seems set_params has disappeared for tb09 in libxc 4. defaults are being used'
2008        MSG_WARNING(msg)
2009        !call xc_hyb_gga_xc_tb09_init(xc_func%conf)
2010 #endif
2011 #endif
2012      end if
2013    end do
2014  end if
2015 
2016 end subroutine libxc_functionals_set_tb09

libxc_functionals/xc_char_to_c [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  xc_char_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

2037 #if defined HAVE_FC_ISO_C_BINDING
2038 function xc_char_to_c(f_string) result(c_string)
2039 !Arguments ------------------------------------
2040 
2041 !This section has been created automatically by the script Abilint (TD).
2042 !Do not modify the following lines by hand.
2043 #undef ABI_FUNC
2044 #define ABI_FUNC 'xc_char_to_c'
2045 !End of the abilint section
2046 
2047  character(len=*),intent(in) :: f_string
2048  character(kind=C_CHAR,len=1) :: c_string(len_trim(f_string)+1)
2049 !Local variables -------------------------------
2050  integer :: ii,strlen
2051 !! *************************************************************************
2052  strlen=len_trim(f_string)
2053  forall(ii=1:strlen)
2054    c_string(ii)=f_string(ii:ii)
2055  end forall
2056  c_string(strlen+1)=C_NULL_CHAR
2057  end function xc_char_to_c
2058 #endif

libxc_functionals/xc_char_to_f [ Functions ]

[ Top ] [ libxc_functionals ] [ Functions ]

NAME

  xc_char_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

PARENTS

      m_libxc_functionals

CHILDREN

SOURCE

2084 #if defined HAVE_FC_ISO_C_BINDING
2085 subroutine xc_char_to_f(c_string,f_string)
2086 !Arguments ------------------------------------
2087 
2088 !This section has been created automatically by the script Abilint (TD).
2089 !Do not modify the following lines by hand.
2090 #undef ABI_FUNC
2091 #define ABI_FUNC 'xc_char_to_f'
2092 !End of the abilint section
2093 
2094  character(kind=C_CHAR,len=1),intent(in) :: c_string(*)
2095  character(len=*),intent(out) :: f_string
2096 !Local variables -------------------------------
2097  integer :: ii
2098 !! *************************************************************************
2099  ii=1
2100  do while(c_string(ii)/=C_NULL_CHAR.and.ii<=len(f_string))
2101    f_string(ii:ii)=c_string(ii) ; ii=ii+1
2102  end do
2103  if (ii<len(f_string)) f_string(ii:)=' '
2104  end subroutine xc_char_to_f
2105 #endif