XClib - funct into XClib-fixes

This commit is contained in:
fabrizio22 2020-10-12 17:56:36 +02:00
parent 65a3bed86c
commit 04f8378f2f
5 changed files with 19 additions and 1503 deletions

View File

@ -139,7 +139,7 @@ SUBROUTINE input_sanity()
USE cellmd, ONLY : lmovecell
USE noncollin_module, ONLY : i_cons, noncolin
USE mp_bands, ONLY : nbgrp
USE funct, ONLY : dft_is_meta, dft_is_hybrid
USE xc_interfaces, ONLY : xclib_dft_is
USE ldaU, ONLY : lda_plus_u, U_projection, lda_plus_u_kind, Hubbard_J0, &
is_hubbard_back, Hubbard_V
!
@ -218,10 +218,10 @@ SUBROUTINE input_sanity()
IF (tfixed_occ) CALL errore('hp_readin', &
& 'The HP code with arbitrary occupations not tested',1)
!
IF ( dft_is_meta() ) CALL errore('hp_readin',&
IF ( xclib_dft_is('meta') ) CALL errore('hp_readin',&
'The HP code with meta-GGA functionals is not yet available',1)
!
IF ( dft_is_hybrid() ) CALL errore('hp_readin',&
IF ( xclib_dft_is('hybrid') ) CALL errore('hp_readin',&
'The HP code with hybrid functionals is not yet available',1)
!
RETURN

View File

@ -253,7 +253,7 @@ CONTAINS
inlc = 2
! Special case vdW-DF3-opt1
CASE( 'VDW-DF3-OPT1' )
dft_defined = xclib_set_dft_IDs(1,4,45,0,3,0)
dft_defined = xclib_set_dft_IDs(1,4,45,0,0,0)
inlc = 3
! Special case vdW-DF3-opt2
CASE( 'VDW-DF3-OPT2' )
@ -348,6 +348,7 @@ CONTAINS
TRIM(lda_c_name) //'-'// &
TRIM(gga_e_name) //'-'// &
TRIM(gga_c_name) //'-'// nonlocc(inlc)
!
ELSE
CALL xclib_set_dft_from_name( TRIM(dftout) )
inlc = matching( dftout, ncnl, nonlocc )
@ -387,7 +388,7 @@ CONTAINS
!
isnonlocc = (inlc > 0)
! CALL set_auxiliary_flags
CALL xclib_set_auxiliary_flags
!
! check dft has not been previously set differently
!
@ -620,7 +621,7 @@ CONTAINS
!
shortname = 'no shortname'
!
IF (inlc /= 0) THEN
IF (inlc == 0) THEN
shortname = xclib_get_dft_short()
ELSE
!
@ -628,8 +629,6 @@ CONTAINS
icorr = xclib_get_id( 'LDA', 'CORR' )
igcx = xclib_get_id( 'GGA', 'EXCH' )
igcc = xclib_get_id( 'GGA', 'CORR' )
imeta = xclib_get_id( 'MGGA','EXCH' )
imetac = xclib_get_id( 'MGGA','CORR' )
!
IF (inlc==1) THEN
!

View File

@ -193,28 +193,28 @@
dft_defined = set_dft_IDs(9,14,28,13,0,0)
! special case : TPSS meta-GGA Exc
CASE( 'TPSS' )
dft_defined = set_dft_IDs(1,4,7,6,0,1)
dft_defined = set_dft_IDs(1,4,7,6,1,0)
! special case : TPSS meta-GGA - mgga term only
CASE( 'TPSS-only' )
dft_defined = set_dft_IDs(0,0,0,0,0,1)
dft_defined = set_dft_IDs(0,0,0,0,1,0)
! special case : M06L Meta GGA
CASE( 'M06L' )
dft_defined = set_dft_IDs(0,0,0,0,0,2)
dft_defined = set_dft_IDs(0,0,0,0,2,0)
! special case : TB09 meta-GGA Exc
CASE( 'TB09' )
dft_defined = set_dft_IDs(0,0,0,0,0,3)
dft_defined = set_dft_IDs(0,0,0,0,3,0)
! special case : SCAN Meta GGA
CASE( 'SCAN' )
dft_defined = set_dft_IDs(0,0,0,0,0,5)
dft_defined = set_dft_IDs(0,0,0,0,5,0)
! special case : SCAN0
CASE( 'SCAN0' )
dft_defined = set_dft_IDs(0,0,0,0,0,6)
dft_defined = set_dft_IDs(0,0,0,0,6,0)
! special case : PZ/LDA + null meta-GGA
CASE( 'PZ+META', 'LDA+META' )
dft_defined = set_dft_IDs(1,1,0,0,0,4)
dft_defined = set_dft_IDs(1,1,0,0,4,0)
! special case : PBE + null meta-GGA
CASE( 'PBE+META' )
dft_defined = set_dft_IDs(1,4,3,4,0,4)
dft_defined = set_dft_IDs(1,4,3,4,4,0)
!
CASE DEFAULT
! IF ('INDEX:' == dftout(1:6)) THEN
@ -365,7 +365,7 @@
!dft_longname = exc (iexch) //'-'//corr (icorr) //'-'//gradx (igcx) //'-' &
! &//gradc (igcc) //'-'// nonlocc(inlc)
!
CALL set_auxiliary_flags
!CALL set_auxiliary_flags
!
! check dft has not been previously set differently
!
@ -736,8 +736,6 @@
!
has_finite_size_correction = ( iexch==8 .OR. icorr==10)
!
CALL set_exx_fraction( exx_fraction )
!
RETURN
!
END SUBROUTINE set_auxiliary_flags
@ -831,7 +829,7 @@
LOGICAL, INTENT(IN) :: exx_started_
!
IF (.NOT. ishybrid) &
CALL errore( 'start_exx', 'dft is not hybrid, wrong call', 1 )
CALL errore( 'set_exx_started', 'dft is not hybrid, wrong call', 1 )
exx_started = exx_started_
!
RETURN
@ -848,7 +846,7 @@
REAL(DP), INTENT(IN) :: exx_fraction_
!
IF (.NOT. ishybrid) &
CALL errore( 'stop_exx', 'dft is not hybrid, wrong call', 1 )
CALL errore( 'set_exx_fraction', 'dft is not hybrid, wrong call', 1 )
exx_fraction = exx_fraction_
!
RETURN

File diff suppressed because it is too large Load Diff

View File

@ -73,7 +73,7 @@ SUBROUTINE xc_metagcx_l( length, ns, np, rho, grho, tau, ex, ec, v1x, v2x, v3x,
ex = 0.0_DP ; v1x = 0.0_DP ; v2x = 0.0_DP ; v3x = 0.0_DP
ec = 0.0_DP ; v1c = 0.0_DP ; v2c = 0.0_DP ; v3c = 0.0_DP
!
CALL xclib_set_threshold( 'mgga', rho_threshold, grho2_threshold, tau_threshold )
CALL set_threshold_l( 'mgga', rho_threshold, grho2_threshold, tau_threshold )
!
POLARIZED = .FALSE.
IF (ns == 2) THEN