More explicit variable name and comments to clarify how to activate/deactivate

band parallelization inside h_psi and s_psi. Variable "use_bgrp_in_hpsi" 
should be actually moved in a more appropriate module, since it is related to
how h_psi behaves, not strictly to the parallelization over bands


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@12052 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2016-01-23 11:53:56 +00:00
parent 77c4735451
commit 253e497c21
3 changed files with 46 additions and 35 deletions

View File

@ -25,7 +25,10 @@ MODULE mp_bands
INTEGER :: my_bgrp_id = 0 ! index of my band group
INTEGER :: inter_bgrp_comm = 0 ! inter band group communicator
INTEGER :: intra_bgrp_comm = 0 ! intra band group communicator
LOGICAL :: tbgrp = .FALSE. ! logical flag. .TRUE. when nbgrp > 1
! Next variable is .T. if band parallelization is performed inside H\psi
! and S\psi, .F. otherwise (band parallelization can be performed outside
! H\psi and S\psi, though)
LOGICAL :: use_bgrp_in_hpsi = .FALSE.
!
! ... "task" groups (for band parallelization of FFT)
!
@ -64,9 +67,10 @@ CONTAINS
IF ( MOD( parent_nproc, nbgrp ) /= 0 ) CALL errore( 'mp_start_bands', &
'n. of band groups must be divisor of parent_nproc', 1 )
!
! set the logical flag tbgrp
! set logical flag so that band parallelization in H\psi is allowed
! (can be disabled before calling H\psi if not desired)
!
tbgrp = ( nbgrp > 1 )
use_bgrp_in_hpsi = ( nbgrp > 1 )
!
! ... Set number of processors per band group
!

View File

@ -1,5 +1,5 @@
! Copyright (C) 2002-2009 Quantum ESPRESSO group
! Copyright (C) 2002-2016 Quantum ESPRESSO group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
@ -21,12 +21,13 @@ SUBROUTINE h_psi( lda, n, m, psi, hpsi )
! ... output:
! ... hpsi H*psi
!
! --- bgrp parallelization allowed
! --- Wrapper routine: performs bgrp parallelization on non-distributed bands
! --- if suitable and required, calls old H\psi routine h_psi_
!
USE kinds, ONLY : DP
USE noncollin_module, ONLY : npol
USE funct, ONLY : exx_is_active
USE mp_bands, ONLY : tbgrp, set_bgrp_indices, inter_bgrp_comm
USE mp_bands, ONLY : use_bgrp_in_hpsi, set_bgrp_indices, inter_bgrp_comm
USE mp, ONLY : mp_sum
!
IMPLICIT NONE
@ -39,19 +40,24 @@ SUBROUTINE h_psi( lda, n, m, psi, hpsi )
!
CALL start_clock( 'h_psi_bgrp' )
! if exx_is_active bgrp parallelization is already used in exx routines that are part of Hpsi !
! if m <= 1 there is nothing to distribute so we can avoid the communication step.
! moreover if a band by band diagonalization (such as ParO for instance) is used it may
! be useful/necessary to operate on different vectors independently.
if (tbgrp .and. .not. exx_is_active() .and. m > 1) then
hpsi(:,:) = (0.d0,0.d0)
call set_bgrp_indices(m,m_start,m_end)
if (m_end >= m_start) & !! at least one band in this band group
call h_psi_( lda, n, m_end-m_start+1, psi(1,m_start), hpsi(1,m_start) )
call mp_sum(hpsi,inter_bgrp_comm)
else ! no one else to communicate with
call h_psi_( lda, n, m, psi, hpsi )
end if
! band parallelization with non-distributed bands is performed if
! 1. enabled (variable use_bgrp_in_hpsi must be set to .T.)
! 2. exact exchange is not active (if it is, band parallelization is already
! used in exx routines called by Hpsi)
! 3. there is more than one band, otherwise there is nothing to parallelize
!
IF (use_bgrp_in_hpsi .AND. .NOT. exx_is_active() .AND. m > 1) THEN
! use band parallelization here
hpsi(:,:) = (0.d0,0.d0)
CALL set_bgrp_indices(m,m_start,m_end)
! Check if there at least one band in this band group
IF (m_end >= m_start) &
CALL h_psi_( lda, n, m_end-m_start+1, psi(1,m_start), hpsi(1,m_start) )
CALL mp_sum(hpsi,inter_bgrp_comm)
ELSE
! don't use band parallelization here
CALL h_psi_( lda, n, m, psi, hpsi )
END IF
CALL stop_clock( 'h_psi_bgrp' )
RETURN

View File

@ -1,5 +1,5 @@
!
! Copyright (C) 2001-2015 Quantum ESPRESSO group
! Copyright (C) 2001-2016 Quantum ESPRESSO group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
@ -26,12 +26,14 @@ SUBROUTINE s_psi( lda, n, m, psi, spsi )
!
! ... spsi S*psi
!
! ... bgrp parallelization allowed
! --- Wrapper routine: performs bgrp parallelization on non-distributed bands
! --- if suitable and required, calls old S\psi routine s_psi_
! --- See comments in h_psi.f90 about band parallelization
!
USE kinds, ONLY : DP
USE noncollin_module, ONLY : npol
USE funct, ONLY : exx_is_active
USE mp_bands, ONLY : tbgrp, set_bgrp_indices, inter_bgrp_comm
USE mp_bands, ONLY : use_bgrp_in_hpsi, set_bgrp_indices, inter_bgrp_comm
USE mp, ONLY : mp_sum
!
IMPLICIT NONE
@ -44,19 +46,18 @@ SUBROUTINE s_psi( lda, n, m, psi, spsi )
!
CALL start_clock( 's_psi_bgrp' )
! if exx_is_active bgrp parallelization is already used in exx routines that are part of Hpsi !
! if m <= 1 there is nothing to distribute so we can avoid the communication step.
! moreover if a band by band diagonalization (such as ParO for instance) is used it may
! be useful/necessary to operate on different vectors independently.
if (tbgrp .and. .not. exx_is_active() .and. m > 1) then
spsi(:,:) = (0.d0,0.d0)
call set_bgrp_indices(m,m_start,m_end)
if (m_end >= m_start) & !! at least one band in this band group
call s_psi_( lda, n, m_end-m_start+1, psi(1,m_start), spsi(1,m_start) )
call mp_sum(spsi,inter_bgrp_comm)
else ! no one else to communicate with
call s_psi_( lda, n, m, psi, spsi )
end if
IF (use_bgrp_in_hpsi .AND. .NOT. exx_is_active() .AND. m > 1) THEN
! use band parallelization here
spsi(:,:) = (0.d0,0.d0)
CALL set_bgrp_indices(m,m_start,m_end)
! Check if there at least one band in this band group
IF (m_end >= m_start) &
CALL s_psi_( lda, n, m_end-m_start+1, psi(1,m_start), spsi(1,m_start) )
CALL mp_sum(spsi,inter_bgrp_comm)
ELSE
! don't use band parallelization here
CALL s_psi_( lda, n, m, psi, spsi )
END IF
CALL stop_clock( 's_psi_bgrp' )
RETURN