Several bad INTENT's fixed (courtesy of Vittorio Zecca)

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@6620 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2010-04-12 19:59:12 +00:00
parent 0fe34d206a
commit 9b560923a6
7 changed files with 11 additions and 12 deletions

View File

@ -35,7 +35,7 @@ SUBROUTINE add_vuspsi( lda, n, m, hpsi )
! ... I/O variables ! ... I/O variables
! !
INTEGER, INTENT(IN) :: lda, n, m INTEGER, INTENT(IN) :: lda, n, m
COMPLEX(DP), INTENT(OUT) :: hpsi(lda*npol,m) COMPLEX(DP), INTENT(INOUT) :: hpsi(lda*npol,m)
! !
! ... here the local variables ! ... here the local variables
! !

View File

@ -109,6 +109,8 @@ SUBROUTINE atomic_wfc (ik, wfcatom)
eigts3 (ig3 (iig), na) eigts3 (ig3 (iig), na)
enddo enddo
! !
wfcatom(:,:,:) = (0.0_dp, 0.0_dp)
!
nt = ityp (na) nt = ityp (na)
do nb = 1, upf(nt)%nwfc do nb = 1, upf(nt)%nwfc
if (upf(nt)%oc(nb) >= 0.d0) then if (upf(nt)%oc(nb) >= 0.d0) then

View File

@ -1,5 +1,5 @@
! !
! Copyright (C) 2001-2004 Quantum ESPRESSO group ! Copyright (C) 2001-2010 Quantum ESPRESSO group
! This file is distributed under the terms of the ! This file is distributed under the terms of the
! GNU General Public License. See the file `License' ! GNU General Public License. See the file `License'
! in the root directory of the present distribution, ! in the root directory of the present distribution,
@ -10,7 +10,7 @@ SUBROUTINE gk_sort( k, ngm, g, ecut, ngk, igk, gk )
!---------------------------------------------------------------------------- !----------------------------------------------------------------------------
! !
! ... sorts k+g in order of increasing magnitude, up to ecut ! ... sorts k+g in order of increasing magnitude, up to ecut
! ... NB: this version will yield the same ordering for different ecut ! ... NB: this version should yield the same ordering for different ecut
! ... and the same ordering in all machines ! ... and the same ordering in all machines
! !
USE kinds, ONLY : DP USE kinds, ONLY : DP
@ -37,6 +37,8 @@ SUBROUTINE gk_sort( k, ngm, g, ecut, ngk, igk, gk )
q2x = ( sqrt( sum(k(:)**2) ) + sqrt( ecut ) )**2 q2x = ( sqrt( sum(k(:)**2) ) + sqrt( ecut ) )**2
! !
ngk = 0 ngk = 0
igk(:) = 0
gk (:) = 0.0_dp
! !
DO ng = 1, ngm DO ng = 1, ngm
q = sum( ( k(:) + g(:,ng) )**2 ) q = sum( ( k(:) + g(:,ng) )**2 )
@ -49,7 +51,6 @@ SUBROUTINE gk_sort( k, ngm, g, ecut, ngk, igk, gk )
IF ( ngk > npwx ) & IF ( ngk > npwx ) &
CALL errore( 'gk_sort', 'array gk out-of-bounds', 1 ) CALL errore( 'gk_sort', 'array gk out-of-bounds', 1 )
! !
! gk is a fake quantity giving the same ordering on all machines
gk(ngk) = q gk(ngk) = q
! !
! set the initial value of index array ! set the initial value of index array

View File

@ -26,7 +26,7 @@ SUBROUTINE gradcorr( rho, rhog, rho_core, rhog_core, etxc, vtxc, v )
! !
REAL(DP), INTENT(IN) :: rho(nrxx,nspin), rho_core(nrxx) REAL(DP), INTENT(IN) :: rho(nrxx,nspin), rho_core(nrxx)
COMPLEX(DP), INTENT(IN) :: rhog(ngm,nspin), rhog_core(ngm) COMPLEX(DP), INTENT(IN) :: rhog(ngm,nspin), rhog_core(ngm)
REAL(DP), INTENT(OUT) :: v(nrxx,nspin) REAL(DP), INTENT(INOUT) :: v(nrxx,nspin)
REAL(DP), INTENT(INOUT) :: vtxc, etxc REAL(DP), INTENT(INOUT) :: vtxc, etxc
! !
INTEGER :: k, ipol, is, nspin0, ir, jpol INTEGER :: k, ipol, is, nspin0, ir, jpol

View File

@ -55,11 +55,11 @@ SUBROUTINE h_psi( lda, n, m, psi, hpsi )
! ... Here we apply the kinetic energy (k+G)^2 psi ! ... Here we apply the kinetic energy (k+G)^2 psi
! !
DO ibnd = 1, m DO ibnd = 1, m
hpsi (1:n, ibnd) = g2kin (1:n) * psi (1:n, ibnd)
hpsi (n+1:lda,ibnd) = (0.0_dp, 0.0_dp)
IF ( noncolin ) THEN IF ( noncolin ) THEN
hpsi (1:n, ibnd) = g2kin (1:n) * psi (1:n, ibnd)
hpsi (lda+1:lda+n, ibnd) = g2kin (1:n) * psi (lda+1:lda+n, ibnd) hpsi (lda+1:lda+n, ibnd) = g2kin (1:n) * psi (lda+1:lda+n, ibnd)
ELSE hpsi (lda+n+1:lda*npol, ibnd) = (0.0_dp, 0.0_dp)
hpsi(1:n,ibnd) = g2kin(1:n) * psi(1:n,ibnd)
END IF END IF
END DO END DO
! !

View File

@ -56,8 +56,6 @@ SUBROUTINE rotate_wfc_k( npwx, npw, nstart, nbnd, npol, psi, overlap, evc, e )
ALLOCATE( sc( nstart, nstart) ) ALLOCATE( sc( nstart, nstart) )
ALLOCATE( vc( nstart, nstart) ) ALLOCATE( vc( nstart, nstart) )
ALLOCATE( en( nstart ) ) ALLOCATE( en( nstart ) )
aux=(0.0_DP,0.0_DP)
! !
! ... Set up the Hamiltonian and Overlap matrix on the subspace : ! ... Set up the Hamiltonian and Overlap matrix on the subspace :
! !

View File

@ -191,8 +191,6 @@ SUBROUTINE init_wfc ( ik )
! !
ALLOCATE( wfcatom( npwx, npol, n_starting_wfc ) ) ALLOCATE( wfcatom( npwx, npol, n_starting_wfc ) )
! !
wfcatom (:,:,:) = (0.d0, 0.d0)
!
IF ( starting_wfc(1:6) == 'atomic' ) THEN IF ( starting_wfc(1:6) == 'atomic' ) THEN
! !
CALL atomic_wfc( ik, wfcatom ) CALL atomic_wfc( ik, wfcatom )