Setting the chunk size as a constant

This commit is contained in:
Ye Luo 2018-06-02 12:30:11 -05:00
parent fa21b8d52a
commit 9a94d4d047
4 changed files with 10 additions and 10 deletions

View File

@ -36,7 +36,8 @@ SUBROUTINE cegterg( h_psi, s_psi, uspp, g_psi, &
! maximum dimension of the reduced basis set :
! (the basis set is refreshed when its dimension would exceed nvecx)
! umber of spin polarizations
INTEGER :: numblock, blocksize
INTEGER, PARAMETER :: blocksize = 256
INTEGER :: numblock
! chunking parameters
COMPLEX(DP), INTENT(INOUT) :: evc(npwx,npol,nvec)
! evc contains the refined estimates of the eigenvectors
@ -121,7 +122,6 @@ SUBROUTINE cegterg( h_psi, s_psi, uspp, g_psi, &
END IF
!
! setting chunck size
blocksize = 256
numblock = (npw+blocksize-1)/blocksize
!
ALLOCATE( psi( npwx, npol, nvecx ), STAT=ierr )
@ -597,7 +597,8 @@ SUBROUTINE pcegterg(h_psi, s_psi, uspp, g_psi, &
! maximum dimension of the reduced basis set
! (the basis set is refreshed when its dimension would exceed nvecx)
! number of spin polarizations
INTEGER :: numblock, blocksize
INTEGER, PARAMETER :: blocksize = 256
INTEGER :: numblock
! chunking parameters
COMPLEX(DP), INTENT(INOUT) :: evc(npwx,npol,nvec)
! evc contains the refined estimates of the eigenvectors
@ -687,7 +688,6 @@ SUBROUTINE pcegterg(h_psi, s_psi, uspp, g_psi, &
END IF
!
! setting chunck size
blocksize = 256
numblock = (npw+blocksize-1)/blocksize
!
ALLOCATE( psi( npwx, npol, nvecx ), STAT=ierr )

View File

@ -37,13 +37,13 @@ subroutine g_psi (lda, n, m, npol, psi, e)
integer :: k, i
! counter on psi functions
! counter on G vectors
integer :: iblock, numblock, blocksize
integer, parameter :: blocksize = 256
integer :: iblock, numblock
! chunking parameters
!
call start_clock ('g_psi')
!
! setting chunck size
blocksize = 256
numblock = (n+blocksize-1)/blocksize
!
#ifdef TEST_NEW_PRECONDITIONING

View File

@ -50,7 +50,8 @@ subroutine init_us_2 (npw_, igk_, q_, vkb_)
integer :: iq
! cache blocking parameters
INTEGER :: iblock, numblock, blocksize, realblocksize
INTEGER, PARAMETER :: blocksize = 256
INTEGER :: iblock, numblock, realblocksize
!
if (lmaxkb.lt.0) return
call start_clock ('init_us_2')
@ -58,7 +59,6 @@ subroutine init_us_2 (npw_, igk_, q_, vkb_)
! write(*,'(3i4,i5,3f10.5)') size(tab,1), size(tab,2), size(tab,3), size(vq), q_
! setting cache blocking size
blocksize = 256
numblock = (npw_+blocksize-1)/blocksize
if (spline_ps) then

View File

@ -34,10 +34,10 @@ SUBROUTINE usnldiag (npw, h_diag, s_diag)
INTEGER :: ikb, jkb, ih, jh, na, nt, ig, ipol
COMPLEX(DP) :: ps1(2), ps2(2), ar
! cache blocking parameters
INTEGER :: iblock, numblock, blocksize
INTEGER, PARAMETER :: blocksize = 256
INTEGER :: iblock, numblock
!
! setting cache blocking size
blocksize = 256
numblock = (npw+blocksize-1)/blocksize
!
!$omp parallel do private(ikb, jkb, ps1, ps2, ar)