[skip-CI] Unused variable in call removed

This commit is contained in:
Paolo Giannozzi 2023-06-07 14:43:03 +02:00
parent 2146399c30
commit f049cf51b2
6 changed files with 9 additions and 11 deletions

View File

@ -55,7 +55,7 @@ SUBROUTINE dvpsi_kb(ik,nu)
mu = 3*(na-1)
IF ( u(mu+1,nu)**2+u(mu+2,nu)**2+u(mu+3,nu)**2> 1.0d-12) THEN
nt=ityp(na)
IF (upf(nt)%nlcc) CALL drhoc (nt, ngl, gl, omega, tpiba2, rhocg )
IF (upf(nt)%nlcc) CALL drhoc (nt, ngl, gl, tpiba2, rhocg )
has_nlcc = has_nlcc .or. upf(nt)%nlcc
DO ng = 1,ngm
gtau = tpi * ( g(1,ng)*tau(1,na) + &

View File

@ -63,7 +63,7 @@ SUBROUTINE dynmatcc(dyncc)
DO na=1,nat
nta=ityp(na)
IF ( upf(nta)%nlcc ) THEN
CALL drhoc (nta, ngl, gl, omega, tpiba2,, rhocg)
CALL drhoc (nta, ngl, gl, tpiba2,, rhocg)
DO ig=1,ngm
exg = tpi* ( g(1,ig)*tau(1,na) + &
g(2,ig)*tau(2,na) + &
@ -89,7 +89,7 @@ SUBROUTINE dynmatcc(dyncc)
DO nb=1,nat
ntb=ityp(nb)
IF ( upf(ntb)%nlcc ) THEN
CALL drhoc (ntb, ngl, gl, omega, tpiba2, rhocg)
CALL drhoc (ntb, ngl, gl, tpiba2, rhocg)
DO ig=1,ngm
exg = tpi* ( g(1,ig)*tau(1,nb) + &
g(2,ig)*tau(2,nb) + &

View File

@ -87,7 +87,7 @@ SUBROUTINE add_shift_cc (shift_cc)
DO nt = 1, ntyp
IF ( upf(nt)%nlcc ) THEN
CALL drhoc (nt, ngl, gl, omega, tpiba2, rhocg)
CALL drhoc (nt, ngl, gl, tpiba2, rhocg)
DO na = 1, nat
IF (nt == ityp (na) ) THEN
IF (gstart==2) shift_(na) = omega * rhocg (igtongl (1) ) * &

View File

@ -7,9 +7,9 @@
!
!
!-----------------------------------------------------------------------
SUBROUTINE drhoc( nt, ngl, gl, omega, tpiba2, rhocg )
SUBROUTINE drhoc( nt, ngl, gl, tpiba2, rhocg )
!-----------------------------------------------------------------------
!! Calculates the Fourier transform of the core charge.
!! Calculates the radial Fourier transform of the core charge.
!
USE kinds, ONLY : dp
USE uspp_data, ONLY : tab_rhc, dq
@ -22,8 +22,6 @@ SUBROUTINE drhoc( nt, ngl, gl, omega, tpiba2, rhocg )
!! input: the number of g shell
REAL(DP) :: gl(ngl)
!! input: the number of G shells
REAL(DP) :: omega
!! input: the volume of the unit cell
REAL(DP) :: tpiba2
!! input: 2 times pi / alat
REAL(DP) :: rhocg(ngl)
@ -37,7 +35,7 @@ SUBROUTINE drhoc( nt, ngl, gl, omega, tpiba2, rhocg )
INTEGER :: igl, i0, i1, i2, i3
! counters
!
!$acc data present_or_copyin(gl) present_or_copyout(rhocg)
!$acc data present_or_copyin(gl) present_or_copyout(rhocg) present(tab_rhc)
!$acc parallel loop
DO igl = 1, ngl
gx = SQRT(gl(igl) * tpiba2)

View File

@ -89,7 +89,7 @@ SUBROUTINE force_cc( forcecc )
DO nt = 1, ntyp
IF ( upf(nt)%nlcc ) THEN
!
CALL drhoc( nt, ngl, gl, omega, tpiba2, rhocg )
CALL drhoc( nt, ngl, gl, tpiba2, rhocg )
!
#if !defined(_OPENACC)
!$omp parallel do private( tau1,tau2,tau3,forcecc_x,forcecc_y,forcecc_z,&

View File

@ -87,7 +87,7 @@ SUBROUTINE stres_cc( sigmaxcc )
DO nt = 1, ntyp
IF ( upf(nt)%nlcc ) THEN
!
CALL drhoc( nt, ngl, gl, omega, tpiba2, rhocg )
CALL drhoc( nt, ngl, gl, tpiba2, rhocg )
!
! ... diagonal term
IF (gstart==2) THEN