Skip to content

Commit

Permalink
CP with CG not working any longer with norm-conserving pseudopotentials.
Browse files Browse the repository at this point in the history
Fixes issue #340, I hope (no warranty)
  • Loading branch information
giannozz committed Jul 16, 2021
1 parent 74dad98 commit 8dd7371
Show file tree
Hide file tree
Showing 2 changed files with 6 additions and 13 deletions.
17 changes: 5 additions & 12 deletions CPV/src/gram.f90
Original file line number Diff line number Diff line change
Expand Up @@ -74,8 +74,6 @@ SUBROUTINE gram_bgrp( betae, bec_bgrp, nkbx, cp_bgrp, ngwx )
anorm = cscnorm( bec_bgrp, cp_bgrp, ibgrp_i, nbspx_bgrp )
cp_bgrp(:,ibgrp_i) = cp_bgrp(:,ibgrp_i) / anorm
bec_bgrp(:,ibgrp_i) = bec_bgrp(:,ibgrp_i) / anorm
!CALL dscal( 2*ngw, 1.0d0/anorm, cp_bgrp(1,ibgrp_i), 1 )
!CALL dscal( nkbx, 1.0d0/anorm, bec_bgrp(1,ibgrp_i), 1 )
END IF
END DO
END DO
Expand Down Expand Up @@ -208,16 +206,11 @@ SUBROUTINE gracsc_bgrp( i, csc, iss, nk )
IF( ibgrp_i > 0 ) THEN
DO ia = 1, nat
is = ityp(ia)
IF( upf(is)%tvanp ) THEN
DO iv=1,nh(is)
inl=ofsbeta(ia)+iv
bec_tmp(inl) = 2.d0 * DDOT( 2*ngw, cp_bgrp(1,ibgrp_i), 1, betae(1,inl), 1) &
- g0 * DBLE(cp_bgrp(1,ibgrp_i) * CONJG(betae(1,inl)))
END DO
ELSE
inl= ofsbeta(ia)
bec_tmp( inl + 1: inl + nh(is) ) = 0.0d0
END IF
DO iv=1,nh(is)
inl=ofsbeta(ia)+iv
bec_tmp(inl) = 2.d0 * DDOT( 2*ngw, cp_bgrp(1,ibgrp_i), 1, betae(1,inl), 1) &
- g0 * DBLE(cp_bgrp(1,ibgrp_i) * CONJG(betae(1,inl)))
END DO
END DO
CALL mp_sum( bec_tmp, intra_bgrp_comm ) ! parallel sum over G vectors within a band group
bec_bgrp( : , ibgrp_i ) = bec_tmp( : )
Expand Down
2 changes: 1 addition & 1 deletion upflib/ylmr2_gpu.f90
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
! or http://www.gnu.org/copyleft/gpl.txt .
!
#define __PGI_1910_WORKAROUND
! use the CUDA Kernel version insetad of the simple CUF version
! use the CUDA Kernel version instead of the simple CUF version
! that for some obscure reason crashes on (obsolescent) PGI v.19.10

module ylmr2_gpum
Expand Down

0 comments on commit 8dd7371

Please sign in to comment.