Since I accidentally deleted data_structure_custom.f90, here is the rest of

the EXX patch, that may or may not work (but cannot be any worse than before).
The problem was in the definition of the reduced FFT grid (cutoff ecutfock)
used by EXX: it must be the same for all pools. Not sure the way it is defined
now it is completely correct, though.


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@13728 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
giannozz 2017-08-19 13:06:13 +00:00
parent 1e2d541c27
commit 3ac7eed5cb
5 changed files with 57 additions and 32 deletions

View File

@ -5,7 +5,10 @@ New in svn version:
Fixed in svn version
* __USE_3D_FFT was broken since v.6.0 (r13700)
* EXX with k-points and pool parallelization was occasionally crashing
due to questionable custom FFT grid initialization (r137XX)
* __USE_3D_FFT was broken since v.6.0 (r13700, r13706)
* Some constants in the definition of PBE functionals were truncated to
6 significant digits. While not a bug, this could lead to tiny differences
@ -56,7 +59,7 @@ Incompatible changes in svn version:
* Restructuring of C routines, introduction of ISO_C_BINDING:
- memstat moved to module wrappers
- f_wall and f_tcpu, in module mytime, replace previous fortran wrappers
- for cclock and scnds, respectively. The latter remain as C functions.
for cclock and scnds, respectively. The latter remain as C functions.
- fft_defs.h and related configure and makedep stuff deleted
* module pwcom no longer contains modules gvect, gvecs, references to
some variables in modules constants, cell_base

View File

@ -53,7 +53,6 @@ compute_ux.o \
coset.o \
d_matrix.o \
data_structure.o \
data_structure_custom.o \
deriv_drhoc.o \
divide_class.o \
divide_class_so.o \

View File

@ -15,7 +15,7 @@ SUBROUTINE data_structure( gamma_only )
!
USE kinds, ONLY : DP
USE mp, ONLY : mp_max
USE mp_bands, ONLY : me_bgrp, nproc_bgrp, root_bgrp, intra_bgrp_comm, nyfft, ntask_groups
USE mp_bands, ONLY : nproc_bgrp, intra_bgrp_comm, nyfft, ntask_groups
USE mp_pools, ONLY : inter_pool_comm
USE fft_base, ONLY : dfftp, dffts, fft_base_info, smap
USE fft_types, ONLY : fft_type_init
@ -34,6 +34,8 @@ SUBROUTINE data_structure( gamma_only )
#else
LOGICAL :: lpara = .false.
#endif
IF ( .NOT. lpara .AND. nproc_bgrp /= 1 ) CALL errore('data_structure', &
'parallel FFT needed: unset __'//'USE_3D_FFT, recompile', nproc_bgrp )
!
! ... calculate gkcut = max |k+G|^2, in (2pi/a)^2 units
!
@ -61,8 +63,10 @@ SUBROUTINE data_structure( gamma_only )
! ... set up fft descriptors, including parallel stuff: sticks, planes, etc.
!
dffts%have_task_groups = (ntask_groups >1)
CALL fft_type_init( dffts, smap, "wave", gamma_only, lpara, intra_bgrp_comm, at, bg, gkcut, gcutms/gkcut, nyfft=nyfft )
CALL fft_type_init( dfftp, smap, "rho", gamma_only, lpara, intra_bgrp_comm, at, bg, gcutm , 4.d0, nyfft=nyfft)
CALL fft_type_init( dffts, smap, "wave", gamma_only, lpara, intra_bgrp_comm,&
at, bg, gkcut, gcutms/gkcut, nyfft=nyfft )
CALL fft_type_init( dfftp, smap, "rho" , gamma_only, lpara, intra_bgrp_comm,&
at, bg, gcutm , 4.d0, nyfft=nyfft )
CALL fft_base_info( ionode, stdout )
ngs_ = dffts%ngl( dffts%mype + 1 )
ngm_ = dfftp%ngl( dfftp%mype + 1 )

View File

@ -199,15 +199,26 @@ MODULE exx
!
!------------------------------------------------------------------------
SUBROUTINE exx_fft_create ()
USE gvecw, ONLY : ecutwfc
USE gvect, ONLY : ecutrho, ig_l2g
USE klist, ONLY : qnorm
USE cell_base, ONLY : at, bg, tpiba2
USE fft_custom, ONLY : set_custom_grid, ggent
USE fft_custom, ONLY : ggent, gvec_init
USE fft_base, ONLY : smap
USE fft_types, ONLY : fft_type_init
USE mp_exx, ONLY : negrp, intra_egrp_comm
USE mp_bands, ONLY : intra_bgrp_comm, nyfft
USE control_flags,ONLY : tqr
USE realus, ONLY : qpointlist, tabxx, tabp!, tabs
IMPLICIT NONE
INTEGER :: intra_comm, ngs_
#if defined (__MPI) && ! defined (__USE_3D_FFT)
LOGICAL :: lpara = .true.
#else
LOGICAL :: lpara = .false.
#endif
IF( exx_fft%initialized) RETURN
@ -224,21 +235,40 @@ MODULE exx
ENDIF
!
exx_fft%gcutmt = exx_fft%dual_t*exx_fft%ecutt / tpiba2
CALL data_structure_custom(exx_fft, smap_exx, gamma_only)
!
! ... set up fft descriptors, including parallel stuff: sticks, planes, etc.
!
IF( negrp == 1 ) THEN
intra_comm = intra_bgrp_comm
CALL fft_type_init( exx_fft%dfftt, smap, "rho", gamma_only, lpara, &
intra_comm, at, bg, exx_fft%gcutmt, exx_fft%dual_t, nyfft=nyfft )
ELSE
intra_comm = intra_egrp_comm
CALL fft_type_init( exx_fft%dfftt, smap_exx, "rho", gamma_only, lpara, &
intra_comm, at, bg, exx_fft%gcutmt, exx_fft%dual_t, nyfft=nyfft )
END IF
!
ngs_ = exx_fft%dfftt%ngl( exx_fft%dfftt%mype + 1 )
IF( gamma_only ) THEN
ngs_ = (ngs_ + 1)/2
END IF
!
! on output, ngm_ and ngs_ contain the local number of G-vectors
! for the two grids. Initialize local and global number of G-vectors
!
CALL gvec_init (exx_fft, ngs_ , intra_comm )
!
CALL ggent(exx_fft)
exx_fft%initialized = .true.
!
IF(tqr)THEN
WRITE(stdout, '(5x,a)') "Initializing real-space augmentation for EXX grid"
IF(ecutfock==ecutrho)THEN
WRITE(stdout, '(7x,a)') " EXX grid -> DENSE grid"
tabxx => tabp
! ELSEIF(ecutfock==ecutwfc)THEN
! WRITE(stdout, '(7x,a)') " EXX grid -> SMOOTH grid"
! tabxx => tabs
ELSE
CALL qpointlist(exx_fft%dfftt, tabxx)
ENDIF
WRITE(stdout, '(5x,a)') "Initializing real-space augmentation for EXX grid"
IF(ecutfock==ecutrho)THEN
WRITE(stdout, '(7x,a)') " EXX grid -> DENSE grid"
tabxx => tabp
ELSE
CALL qpointlist(exx_fft%dfftt, tabxx)
ENDIF
ENDIF
RETURN
@ -354,6 +384,8 @@ MODULE exx
USE wvfct, ONLY : nbnd
USE start_k, ONLY : nk1,nk2,nk3
USE control_flags, ONLY : iverbosity
USE mp_pools, ONLY : inter_pool_comm
USE mp, ONLY : mp_max
!
IMPLICIT NONE
!
@ -567,6 +599,7 @@ MODULE exx
qnorm = max(qnorm, sqrt( sum((xk(:,ik)-xkq_collect(:,iq))**2) ))
ENDDO
ENDDO
CALL mp_max( qnorm, inter_pool_comm )
!
CALL stop_clock ('exx_grid')
!
@ -796,7 +829,6 @@ MODULE exx
! Note that nxxs is not the same as nrxxs in parallel case
nxxs = exx_fft%dfftt%nr1x *exx_fft%dfftt%nr2x *exx_fft%dfftt%nr3x
nrxxs= exx_fft%dfftt%nnr
!allocate psic_exx
IF(.not.allocated(psic_exx))THEN
ALLOCATE(psic_exx(nrxxs))
@ -4226,7 +4258,6 @@ END SUBROUTINE compute_becpsi
nproc_egrp, me_egrp, negrp, my_egrp_id, nibands, ibands, &
max_ibands, all_start, all_end
USE parallel_include
USE klist, ONLY : xk, wk, nkstot, nks, qnorm
!
!
IMPLICIT NONE
@ -4917,7 +4948,6 @@ END SUBROUTINE compute_becpsi
USE mp_exx, ONLY : intra_egrp_comm, inter_egrp_comm, &
nproc_egrp, me_egrp, negrp, my_egrp_id, iexx_istart, iexx_iend
USE parallel_include
USE klist, ONLY : xk, wk, nkstot, nks, qnorm
USE wvfct, ONLY : current_k
!
!

View File

@ -338,17 +338,6 @@ data_structure.o : ../../Modules/mp_pools.o
data_structure.o : ../../Modules/recvec.o
data_structure.o : ../../UtilXlib/mp.o
data_structure.o : pwcom.o
data_structure_custom.o : ../../FFTXlib/fft_types.o
data_structure_custom.o : ../../FFTXlib/stick_base.o
data_structure_custom.o : ../../Modules/cell_base.o
data_structure_custom.o : ../../Modules/fft_base.o
data_structure_custom.o : ../../Modules/fft_custom.o
data_structure_custom.o : ../../Modules/kind.o
data_structure_custom.o : ../../Modules/mp_bands.o
data_structure_custom.o : ../../Modules/mp_exx.o
data_structure_custom.o : ../../Modules/recvec.o
data_structure_custom.o : ../../UtilXlib/mp.o
data_structure_custom.o : pwcom.o
deriv_drhoc.o : ../../KS_Solvers/CG/constants.o
deriv_drhoc.o : ../../Modules/kind.o
divide.o : ../../UtilXlib/mp.o