Some more smallbox cleanup

git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@7472 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2011-02-03 17:14:47 +00:00
parent 4de2134c36
commit b9e599a2a9
4 changed files with 30 additions and 39 deletions

View File

@ -90,7 +90,6 @@
USE gvecw, ONLY: ecutwfc, gcutw
USE gvect, ONLY: ecutrho, gcutm
USE gvecs, ONLY: ecuts, gcutms
USE smallbox_gvec, ONLY: ecutb, gcutb
USE gvecw, ONLY: ekcut, gkcut
USE constants, ONLY: eps8, pi
@ -153,7 +152,6 @@
USE gvecw, ONLY: ecfixed, qcutz, q2sigma
USE gvecw, ONLY: ekcut, gkcut
USE gvecs, ONLY: ecuts, gcutms
USE smallbox_gvec, ONLY: ecutb, gcutb
use betax, only: mmx, refg
USE io_global, ONLY: stdout

View File

@ -25,7 +25,7 @@
use control_flags, only: gamma_only, iprsta
use grid_dimensions, only: nr1, nr2, nr3
use cell_base, only: ainv, at, omega, alat
use small_box, only: tpibab, bgb, small_box_set
use small_box, only: small_box_set
use smallbox_grid_dim, only: nr1b, nr2b, nr3b, &
smallbox_grid_init,smallbox_grid_info
USE grid_subroutines, ONLY: realspace_grids_init, realspace_grids_info
@ -35,7 +35,6 @@
ecutrho, gcutm, gvect_init
use gvecs, only: gcutms, gvecs_init
use gvecw, only: gkcut, gvecw_init, g2kin_init
use smallbox_gvec, only: gcutb
USE smallbox_subs, ONLY: ggenb
USE fft_base, ONLY: dfftp, dffts
USE fft_scalar, ONLY: cft_b_omp_init
@ -156,24 +155,22 @@
allocate( eigts2(-nr2:nr2,nat) )
allocate( eigts3(-nr3:nr3,nat) )
!
! generation of little box g-vectors
! small boxes
!
IF ( nr1b > 0 .AND. nr2b > 0 .AND. nr3b > 0 ) THEN
! sets the small box parameters
! set the small box parameters
rat1 = DBLE( nr1b ) / DBLE( nr1 )
rat2 = DBLE( nr2b ) / DBLE( nr2 )
rat3 = DBLE( nr3b ) / DBLE( nr3 )
CALL small_box_set( alat, omega, at, rat1, rat2, rat3 )
! now set gcutb
gcutb = ecutrho / tpibab / tpibab
!
CALL ggenb ( bgb, gcutb, iprsta )
! initialize FFT table
CALL small_box_set( alat, omega, at, rat1, rat2, rat3 )
!
! generate small-box G-vectors, initialize FFT tables
!
CALL ggenb ( ecutrho, iprsta )
!
#if defined __OPENMP && defined __FFTW
CALL cft_b_omp_init( nr1b, nr2b, nr3b )
#endif
@ -338,7 +335,7 @@
USE gvecw, ONLY : g2kin_init
USE gvect, ONLY : g, gg, ngm, mill
USE grid_dimensions, ONLY : nr1, nr2, nr3
USE small_box, ONLY : bgb, small_box_set
USE small_box, ONLY : small_box_set
USE smallbox_subs, ONLY : gcalb
USE io_global, ONLY : stdout, ionode
USE smallbox_grid_dim, ONLY : nr1b, nr2b, nr3b
@ -380,7 +377,7 @@
rat3 = DBLE( nr3b ) / DBLE( nr3 )
CALL small_box_set( alat, omega, at, rat1, rat2, rat3 )
!
call gcalb ( bgb )
call gcalb ( )
!
return
end subroutine newinit

View File

@ -13,30 +13,23 @@
IMPLICIT NONE
SAVE
! ... G vectors less than the box grid cut-off ( ? )
! ... Variables describing G-vectors for the small box grid
! ... Basically the same meaning as for the corresponding
! ... quantities for the true lattice
!
INTEGER :: ngb = 0 ! local number of G vectors
INTEGER :: ngbt = 0 ! in parallel execution global number of G vectors,
! in serial execution this is equal to ngw
INTEGER :: ngbl = 0 ! number of G-vector shells up to ngw
INTEGER :: ngbx = 0 ! maximum local number of G vectors
REAL(DP), ALLOCATABLE :: gb(:), gxb(:,:), glb(:)
INTEGER, ALLOCATABLE :: npb(:), nmb(:)
INTEGER, ALLOCATABLE :: mill_b(:,:)
REAL(DP), ALLOCATABLE :: gb(:) ! G(i)^2 in (tpi/alatb)**2 units
REAL(DP), ALLOCATABLE :: gxb(:,:) ! G(:,i) in tpi/alatb units
REAL(DP), ALLOCATABLE :: glb(:) ! shells of G(i)^2
INTEGER, ALLOCATABLE :: npb(:), nmb(:) ! FFT indices
INTEGER, ALLOCATABLE :: mill_b(:,:) ! miller indices
REAL(DP) :: ecutb = 0.0_DP
REAL(DP) :: gcutb = 0.0_DP
REAL(DP) :: gcutb = 0.0_DP ! effective cut-off in (tpi/alatb)**2 units
CONTAINS
SUBROUTINE smallbox_gvec_set( ecut, tpibab )
IMPLICIT NONE
REAL(DP), INTENT(IN) :: ecut, tpibab
ecutb = ecut
gcutb = ecut / tpibab / tpibab
RETURN
END SUBROUTINE smallbox_gvec_set
SUBROUTINE deallocate_smallbox_gvec()
IF( ALLOCATED( gb ) ) DEALLOCATE( gb )
IF( ALLOCATED( gxb ) ) DEALLOCATE( gxb )

View File

@ -14,8 +14,8 @@ MODULE smallbox_subs
! ... G-vector components onto the FFT grid(s) in reciprocal space
! ... Small-Box grid
USE smallbox_gvec, ONLY : ngb, ngbt, ngbl, ngbx, gb, gxb, glb, &
npb, nmb, mill_b
USE small_box, ONLY : bgb, tpibab
USE smallbox_gvec, ONLY : ngb, ngbl, gb, gxb, glb, npb, nmb, mill_b, gcutb
USE smallbox_grid_dim, ONLY : nr1b, nr2b, nr3b, nr1bx, nr2bx, nr3bx
PRIVATE
@ -27,7 +27,7 @@ MODULE smallbox_subs
CONTAINS
!=----------------------------------------------------------------------=
!
SUBROUTINE ggenb ( bgb, gcutb, iprsta )
SUBROUTINE ggenb ( ecutrho, iprsta )
!-----------------------------------------------------------------------
!
! As ggen, for the box grid. A "b" is appended to box variables.
@ -38,7 +38,7 @@ CONTAINS
!
IMPLICIT NONE
!
REAL(DP), INTENT(in) :: bgb(3,3), gcutb
REAL(DP), INTENT(in) :: ecutrho
INTEGER, INTENT (in) :: iprsta
!
INTEGER, ALLOCATABLE:: idx(:), iglb(:)
@ -46,6 +46,10 @@ CONTAINS
INTEGER it, icurr, nr1m1, nr2m1, nr3m1, ir, ig, i,j,k, itv(3), ip
REAL(DP) t(3), g2
!
! gcutb is the effective cut-off for G-vectors of the small box grid
!
gcutb = ecutrho / tpibab**2
!
nr1m1=nr1b-1
nr2m1=nr2b-1
nr3m1=nr3b-1
@ -261,7 +265,7 @@ CONTAINS
END SUBROUTINE gshcount
!
!
SUBROUTINE gcalb ( bgb )
SUBROUTINE gcalb ( )
!
! re-generation of little box g-vectors
!
@ -269,7 +273,6 @@ CONTAINS
!
IMPLICIT NONE
!
REAL(DP), INTENT(in) :: bgb(3,3)
INTEGER :: ig, i1,i2,i3
IF ( nr1b == 0 .OR. nr2b == 0 .OR. nr3b == 0 ) return