diff --git a/PW/allocate_fft.f90 b/PW/allocate_fft.f90 index 0bf172410..b313ebdf6 100644 --- a/PW/allocate_fft.f90 +++ b/PW/allocate_fft.f90 @@ -7,7 +7,7 @@ ! ! !----------------------------------------------------------------------- -subroutine allocate_fft +SUBROUTINE allocate_fft !----------------------------------------------------------------------- ! This routine computes the data structure associated to the FFT ! grid and allocate memory for all the arrays which depend upon @@ -17,7 +17,7 @@ subroutine allocate_fft USE gvect, ONLY : nr1, nr2, nr3, nrxx, ngm, g, gg, nl, nlm, & ig1, ig2, ig3, eigts1, eigts2, eigts3, igtongl, ecutwfc USE gsmooth, ONLY : nr1s,nr2s,nr3s,nrxxs,ngms, nls, nlsm, doublegrid -! DCC +! DCC USE gcoarse, ONLY : nr1c,nr2c,nr3c,nrxxc,ngmc, nlc, nlcm USE ee_mod, ONLY : do_coarse USE ions_base, ONLY : nat @@ -30,24 +30,24 @@ subroutine allocate_fft report, i_cons, noncolin, npol USE wavefunctions_module, ONLY : psic, psic_nc USE funct, ONLY: dft_is_meta - implicit none + IMPLICIT NONE ! ! determines the data structure for fft arrays ! call data_structure( gamma_only ) ! ! 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 - 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 call errore ('allocate_fft', 'the nr"s are too small!', 1) endif 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 call errore ('allocate_fft', 'the nrs"s are too small!', 1) @@ -60,30 +60,30 @@ subroutine allocate_fft ! ! Allocate memory for all kind of stuff. ! - allocate (g( 3, ngm)) - allocate (gg( ngm)) - allocate (nl( ngm)) + allocate (g( 3, ngm)) + allocate (gg( ngm)) + allocate (nl( ngm)) if (gamma_only) allocate (nlm(ngm)) - allocate (igtongl( ngm)) - allocate (ig1( ngm)) - allocate (ig2( ngm)) - allocate (ig3( ngm)) + allocate (igtongl( ngm)) + allocate (ig1( ngm)) + allocate (ig2( ngm)) + allocate (ig3( ngm)) call create_scf_type(rho) call create_scf_type(v, do_not_allocate_becsum = .true.) call create_scf_type(vnew, do_not_allocate_becsum = .true.) - allocate (vltot( nrxx)) + allocate (vltot( nrxx)) allocate (rho_core( nrxx)) if (dft_is_meta() ) then allocate ( kedtau(nrxxs,nspin) ) else allocate ( kedtau(1,nspin) ) - end if - ALLOCATE( rhog_core( ngm ) ) - allocate (psic( nrxx)) - allocate (vrs( nrxx, nspin)) + endif + allocate( rhog_core( ngm ) ) + allocate (psic( nrxx)) + allocate (vrs( nrxx, nspin)) if (doublegrid) then - allocate (nls( ngms)) + allocate (nls( ngms)) if (gamma_only) allocate (nlsm(ngm)) else nls => nl @@ -91,12 +91,12 @@ subroutine allocate_fft endif ! DCC - IF( do_coarse ) THEN + if( do_coarse ) then allocate (nlc( ngmc)) if (gamma_only) allocate (nlcm(ngmc)) - END IF + endif - if (noncolin) allocate (psic_nc( nrxx, npol)) + if (noncolin) allocate (psic_nc( nrxx, npol)) if ( ((report.ne.0).or.(i_cons.ne.0)) .and. (noncolin.and.domag) .or. (i_cons.eq.1) ) then ! @@ -110,4 +110,4 @@ subroutine allocate_fft endif return -end subroutine allocate_fft +END SUBROUTINE allocate_fft