Move DFT-D* printout to summary

(avoid mixing of computational and physical information)
This commit is contained in:
Paolo Giannozzi 2022-01-08 17:12:25 +01:00
parent 70a6551f36
commit 3c155ebdaf
4 changed files with 32 additions and 32 deletions

View File

@ -76,8 +76,6 @@ MODULE london_module
USE mp, ONLY : mp_bcast
USE mp_images, ONLY : intra_image_comm
!
IMPLICIT NONE
!
INTEGER, PARAMETER :: maxZ = 86
REAL (DP) :: vdw_coeffs(2,maxZ)
!
@ -195,7 +193,7 @@ MODULE london_module
!
! and some buffers on ionode
!
ALLOCATE ( R_vdw ( ntyp ) )
IF (.NOT. ALLOCATED( R_vdw) ) ALLOCATE ( R_vdw ( ntyp ) )
!
! here we initialize parameters to unphysical values
!
@ -254,21 +252,6 @@ MODULE london_module
!
END DO
!
WRITE ( stdout ,'( /, 5X, "-------------------------------------------------" , &
& /, 5X, "Parameters for Dispersion (Grimme-D2) Correction:" , &
& /, 5X, "-------------------------------------------------" , &
& /, 5X, " atom VdW radius C_6 " , / )' )
DO ata = 1 , ntyp
!
WRITE (stdout , '( 8X, A3 , 6X , F7.3 , 6X , F9.3 )' ) &
atom_label ( ata ) , R_vdw ( ata ) , C6_i ( ata )
!
END DO
!
! ... atomic parameters are deallocated
!
DEALLOCATE ( R_vdw )
!
! ... cutoff radius in alat units
!
r_cut = lon_rcut / alat
@ -292,6 +275,27 @@ MODULE london_module
!
END SUBROUTINE init_london
!
SUBROUTINE print_london
!
USE io_global, ONLY : ionode, stdout
USE ions_base , ONLY : ntyp => nsp, atom_label => atm
INTEGER :: ata
!
IF ( ionode ) THEN
WRITE ( stdout ,'( /, 5X, "-------------------------------------------------" , &
& /, 5X, "Parameters for Dispersion (Grimme-D2) Correction:" , &
& /, 5X, "-------------------------------------------------" , &
& /, 5X, " atom VdW radius C_6 " , / )' )
DO ata = 1 , ntyp
!
WRITE (stdout , '( 8X, A3 , 6X , F7.3 , 6X , F9.3 )' ) &
atom_label ( ata ) , R_vdw ( ata ) , C6_i ( ata )
!
END DO
END IF
!
END SUBROUTINE print_london
!
!---------------------------------------------------------------------------
! Compute dispersion energy
!---------------------------------------------------------------------------
@ -307,8 +311,6 @@ MODULE london_module
USE mp_images, ONLY : me_image , nproc_image, intra_image_comm
USE mp, ONLY : mp_sum
!
IMPLICIT NONE
!
INTEGER , INTENT ( IN ) :: nat
!! number of atoms
INTEGER , INTENT ( IN ) :: ityp ( nat )
@ -410,8 +412,6 @@ MODULE london_module
USE mp_images, ONLY : me_image , nproc_image , intra_image_comm
USE mp, ONLY : mp_sum
!
IMPLICIT NONE
!
INTEGER , INTENT ( IN ) :: nat
!! number of atoms
INTEGER , INTENT ( IN ) :: ityp ( nat )
@ -530,8 +530,6 @@ MODULE london_module
USE mp_images, ONLY : me_image , nproc_image , intra_image_comm
USE mp, ONLY : mp_sum
!
IMPLICIT NONE
!
INTEGER , INTENT ( IN ) :: nat
!! number of atoms
INTEGER , INTENT ( IN ) :: ityp ( nat )
@ -657,8 +655,6 @@ MODULE london_module
!
!! Clean memory.
!
IMPLICIT NONE
!
IF ( ALLOCATED ( R_vdw ) ) DEALLOCATE ( R_vdw )
IF ( ALLOCATED ( C6_ij ) ) DEALLOCATE ( C6_ij )
IF ( ALLOCATED ( R_sum ) ) DEALLOCATE ( R_sum )

View File

@ -319,7 +319,7 @@ SUBROUTINE iosys()
USE dftd3_api, ONLY : dftd3_init, dftd3_set_params, &
dftd3_set_functional, dftd3_calc, &
dftd3_input
USE dftd3_qe, ONLY : dftd3_printout, dftd3_xc, dftd3, dftd3_in
USE dftd3_qe, ONLY : dftd3_xc, dftd3, dftd3_in
USE xdm_module, ONLY : init_xdm, a1i, a2i
USE tsvdw_module, ONLY : vdw_isolated, vdw_econv_thr
USE uspp_data, ONLY : spline_ps_ => spline_ps
@ -1696,8 +1696,6 @@ SUBROUTINE iosys()
if (dftd3_version==2) dftd3_threebody=.false.
dftd3_in%threebody = dftd3_threebody
CALL dftd3_init(dftd3, dftd3_in)
CALL dftd3_printout(dftd3, dftd3_in, stdout, ntyp, atm, nat, ityp,&
tau, at, alat )
dft_ = get_dft_short( )
dft_ = dftd3_xc ( dft_ )
CALL dftd3_set_functional(dftd3, func=dft_, version=dftd3_version,tz=.false.)

View File

@ -34,7 +34,8 @@ SUBROUTINE summary()
USE klist, ONLY : degauss, smearing, lgauss, ltetra, nkstot, xk, &
wk, nelec, nelup, neldw, two_fermi_energies
USE control_flags, ONLY : imix, nmix, mixing_beta, nstep, lscf, &
tr2, isolve, lmd, lbfgs, iverbosity, tqr, tq_smoothing, tbeta_smoothing
tr2, isolve, lmd, lbfgs, iverbosity, tqr, &
tq_smoothing, tbeta_smoothing, llondon, ldftd3
USE noncollin_module,ONLY : noncolin, domag, lspinorb
USE funct, ONLY : write_dft_name
USE xc_lib, ONLY : xclib_dft_is
@ -54,6 +55,8 @@ SUBROUTINE summary()
USE gcscf_module, ONLY : lgcscf, gcscf_summary
USE relax, ONLY : epse, epsf, epsp
USE environment, ONLY : print_cuda_info
USE london_module, ONLY : print_london
USE dftd3_qe, ONLY : dftd3_printout, dftd3, dftd3_in
!
IMPLICIT NONE
!
@ -295,7 +298,7 @@ SUBROUTINE summary()
!
! description of symmetries
!
CALL print_symmetries ( iverbosity, noncolin, domag )
CALL print_symmetries ( iverbosity, noncolin, domag )
!
! description of the atoms inside the unit cell
!
@ -305,6 +308,10 @@ SUBROUTINE summary()
WRITE( stdout, '(6x,i4,8x,a6," tau(",i4,") = (",3f12.7," )")') &
(na, atm(ityp(na)), na, (tau(ipol,na), ipol=1,3), na=1,nat)
!
IF ( llondon ) CALL print_london ( )
IF ( ldftd3 ) CALL dftd3_printout(dftd3, dftd3_in, stdout, ntyp, atm, &
nat, ityp, tau, at, alat )
!
! output of starting magnetization
!
IF (iverbosity > 0) THEN

View File

@ -33,7 +33,6 @@ MODULE dftd3_qe
!> Convert XC labels from QE to those used by DFT-D3
FUNCTION dftd3_xc ( dft )
IMPLICIT NONE
CHARACTER(LEN=*), INTENT(in) :: dft
CHARACTER(LEN=256) :: dftd3_xc
CHARACTER(LEN=1), EXTERNAL :: lowercase