allocate_fft.f90: src cleanup (N. Nemec)

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@6352 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
nn245 2010-02-04 08:26:22 +00:00
parent 74d9b5ebd6
commit 0f6969c681
1 changed files with 23 additions and 23 deletions

View File

@ -7,7 +7,7 @@
! !
! !
!----------------------------------------------------------------------- !-----------------------------------------------------------------------
subroutine allocate_fft SUBROUTINE allocate_fft
!----------------------------------------------------------------------- !-----------------------------------------------------------------------
! This routine computes the data structure associated to the FFT ! This routine computes the data structure associated to the FFT
! grid and allocate memory for all the arrays which depend upon ! grid and allocate memory for all the arrays which depend upon
@ -30,24 +30,24 @@ subroutine allocate_fft
report, i_cons, noncolin, npol report, i_cons, noncolin, npol
USE wavefunctions_module, ONLY : psic, psic_nc USE wavefunctions_module, ONLY : psic, psic_nc
USE funct, ONLY: dft_is_meta USE funct, ONLY: dft_is_meta
implicit none IMPLICIT NONE
! !
! determines the data structure for fft arrays ! determines the data structure for fft arrays
! !
call data_structure( gamma_only ) call data_structure( gamma_only )
! !
! DCC ! DCC
IF( do_coarse ) CALL data_structure_coarse( gamma_only, nr1,nr2,nr3, ecutwfc ) if( do_coarse ) call data_structure_coarse( gamma_only, nr1,nr2,nr3, ecutwfc )
! !
if (nrxx.lt.ngm) then if (nrxx.lt.ngm) then
WRITE( stdout, '(/,4x," nr1=",i4," nr2= ", i4, " nr3=",i4, & write( stdout, '(/,4x," nr1=",i4," nr2= ", i4, " nr3=",i4, &
&" nrxx = ",i8," ngm=",i8)') nr1, nr2, nr3, nrxx, ngm &" nrxx = ",i8," ngm=",i8)') nr1, nr2, nr3, nrxx, ngm
call errore ('allocate_fft', 'the nr"s are too small!', 1) call errore ('allocate_fft', 'the nr"s are too small!', 1)
endif endif
if (nrxxs.lt.ngms) then if (nrxxs.lt.ngms) then
WRITE( stdout, '(/,4x," nr1s=",i4," nr2s= ", i4, " nr3s=",i4, & write( stdout, '(/,4x," nr1s=",i4," nr2s= ", i4, " nr3s=",i4, &
&" nrxxs = ",i8," ngms=",i8)') nr1s, nr2s, nr3s, nrxxs, ngms &" nrxxs = ",i8," ngms=",i8)') nr1s, nr2s, nr3s, nrxxs, ngms
call errore ('allocate_fft', 'the nrs"s are too small!', 1) call errore ('allocate_fft', 'the nrs"s are too small!', 1)
@ -78,8 +78,8 @@ subroutine allocate_fft
allocate ( kedtau(nrxxs,nspin) ) allocate ( kedtau(nrxxs,nspin) )
else else
allocate ( kedtau(1,nspin) ) allocate ( kedtau(1,nspin) )
end if endif
ALLOCATE( rhog_core( ngm ) ) allocate( rhog_core( ngm ) )
allocate (psic( nrxx)) allocate (psic( nrxx))
allocate (vrs( nrxx, nspin)) allocate (vrs( nrxx, nspin))
if (doublegrid) then if (doublegrid) then
@ -91,10 +91,10 @@ subroutine allocate_fft
endif endif
! DCC ! DCC
IF( do_coarse ) THEN if( do_coarse ) then
allocate (nlc( ngmc)) allocate (nlc( ngmc))
if (gamma_only) allocate (nlcm(ngmc)) if (gamma_only) allocate (nlcm(ngmc))
END IF endif
if (noncolin) allocate (psic_nc( nrxx, npol)) if (noncolin) allocate (psic_nc( nrxx, npol))
@ -110,4 +110,4 @@ subroutine allocate_fft
endif endif
return return
end subroutine allocate_fft END SUBROUTINE allocate_fft