Skip to content

Commit

Permalink
Merge branch 'merge_develop_qe68' into 'master'
Browse files Browse the repository at this point in the history
Final merge of develop before qe-6.8 release

See merge request QEF/q-e!1508
  • Loading branch information
pietrodelugas committed Jul 19, 2021
2 parents 9140bc3 + 68e7d33 commit 03a7fa6
Show file tree
Hide file tree
Showing 11 changed files with 43 additions and 22 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 Doc/user_guide.tex
Original file line number Diff line number Diff line change
Expand Up @@ -524,7 +524,7 @@ \subsection{Building with \make}
\texttt{LIBDIRS}& extra directories where to search for libraries\\
\end{tabular}\\
(note that \texttt{F90} is an ``historical'' name -- we actually use
Fortran 2003 -- and that it should be used only together with option
Fortran 2008 -- and that it should be used only together with option
\texttt{--disable-parallel}. In fact, the value of F90 must be
consistent with the parallel Fortran compiler which is determined by
\configure\ and stored in the \texttt{MPIF90} variable).
Expand Down
2 changes: 2 additions & 0 deletions LAXlib/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -107,4 +107,6 @@ if(QE_ENABLE_TEST)
add_unit_test(test_qe_lax-r1-t3 1 3 $<TARGET_FILE:qe_lax_test>)
add_unit_test(test_qe_lax-r4-t1 4 1 $<TARGET_FILE:qe_lax_test>)
add_unit_test(test_qe_lax-r9-t2 9 2 $<TARGET_FILE:qe_lax_test>)

add_subdirectory(tests)
endif(QE_ENABLE_TEST)
12 changes: 12 additions & 0 deletions LAXlib/tests/CMakeLists.txt
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
qe_add_executable(test_qe_lax_lapack_zdotc test_lapack_zdotc.f90)
set_target_properties(test_qe_lax_lapack_zdotc
PROPERTIES
OUTPUT_NAME test_qe_lax_lapack_zdotc.x
RUNTIME_OUTPUT_DIRECTORY ${CMAKE_CURRENT_BINARY_DIR}/../bin)
target_link_libraries(test_qe_lax_lapack_zdotc
PRIVATE
qe_openmp_fortran
qe_mpi_fortran
qe_lapack)

add_unit_test(test_qe_lapack_zdotc 1 1 $<TARGET_FILE:test_qe_lax_lapack_zdotc>)
18 changes: 18 additions & 0 deletions LAXlib/tests/test_lapack_zdotc.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
program test
implicit none
complex*16 :: a(2), b(2)
complex*16 res
complex*16, external :: ZDOTC

a(1) = (-9.6224246089610388d-2, 3.2442340359108593d-3)
a(2) = (-0.9037769140058165, 3.2441868631152768d-3)

b(1) = (-0.9999890875238262, -5.3357405582201908d-7)
b(2) = (-0.9999998761616069, 4.3341267956954060d-8)

res = ZDOTC(2, a, 1, b, 1)
if (ABS(res - (1.0000000308637980,6.48839729724212839E-003)) >= 1.d-6) then
write(*,*) "zdotc check failed. Expected (1.0000000308637980,6.48839729724212839E-003) but got ", res
stop 1
endif
end program
1 change: 0 additions & 1 deletion PP/src/pw2bgw.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4891,7 +4891,6 @@ SUBROUTINE write_vhub_g (output_file_name, diag_nmin, diag_nmax, offdiag_nmin, o
complex (DP), allocatable :: hc(:,:)
integer :: nspin_
integer :: kdim, kdmx
COMPLEX (DP) :: zdotc
integer :: ldim, is1, ibnd, i, na, m1, nt
character(LEN=20) :: ik_string, ib_string, is_string

Expand Down
2 changes: 0 additions & 2 deletions QEHeat/src/project.f90
Original file line number Diff line number Diff line change
Expand Up @@ -64,8 +64,6 @@ subroutine project(ipol, dvpsi_save, save_dvpsi)
! the desired convergence of linter
logical :: conv_root
! true if convergence has been achieved
COMPLEX(DP), EXTERNAL :: zdotc
real(DP), EXTERNAL ::ddot
real(DP) ::emme(nbnd, nbnd)
! logical ::l_test, exst

Expand Down
1 change: 0 additions & 1 deletion TDDFPT/src/lr_Opsi_magnons.f90
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,6 @@ SUBROUTINE lr_Opsi_magnons (ik, ip, dOpsi)
COMPLEX(DP) :: Tevc(npol*npwx,nbnd) ! T-rev op. applied to u_{-k}
COMPLEX(DP) :: Tevq(npol*npwx,nbnd) ! T-rev op. applied to u_{-k-Q}
!
COMPLEX(DP), EXTERNAL :: zdotc
INTEGER :: ibnd1, ibnd2
!
CALL start_clock ('lr_Opsi_magnons')
Expand Down
4 changes: 2 additions & 2 deletions XClib/xc_input_params_mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -101,14 +101,14 @@ MODULE dft_par_mod
INTEGER :: beefvdw = 0
!! Index for vdw term of BEEF
!
INTEGER, PARAMETER :: nxc=8, ncc=10, ngcx=46, ngcc=13, nmeta=6
INTEGER, PARAMETER :: nxc=8, ncc=12, ngcx=46, ngcc=13, nmeta=6
CHARACTER(LEN=4) :: exc, corr, gradx, gradc, meta
DIMENSION :: exc(0:nxc), corr(0:ncc), gradx(0:ngcx), gradc(0:ngcc), &
meta(0:nmeta)
!
DATA exc / 'NOX', 'SLA', 'SL1', 'RXC', 'OEP', 'HF', 'PB0X', 'B3LP', 'KZK' /
DATA corr / 'NOC', 'PZ', 'VWN', 'LYP', 'PW', 'WIG', 'HL', 'OBZ', &
'OBW', 'GL' , 'KZK' /
'OBW', 'GL' , 'KZK', 'xxxx', 'B3LP' /
!
DATA gradx / 'NOGX', 'B88', 'GGX', 'PBX', 'REVX', 'HCTH', 'OPTX', &
'xxxx', 'PB0X', 'B3LP', 'PSX', 'WCX', 'HSE', 'RW86', 'PBE', &
Expand Down
4 changes: 2 additions & 2 deletions test-suite/userconfig.tmp
Original file line number Diff line number Diff line change
Expand Up @@ -93,12 +93,12 @@ tolerance = ( (1.0e-6, 5.0e-3, 'e1'),
(1.0e-5, 1.0e-5, 'q1'),
(1.0e-5, 1.0e-5, 'dos1'),
(1.0e-3, 5.0e-3, 'e2'),
(1.5 , 2.0e-1, 'rsig'),
(5.0 , 2.0e-1, 'rsig'),
(1.5 , 5.0e-1, 'isig'),
(1.0e-2, 1.0e-2, 'rpi'),
(1.0e-2, 1.0e-2, 'ipi'),
( 100, None, 'z1'), # Unstable on unconverged grids.
(1.0e-2, None, 'lam'),
(2.0e-2, None, 'lam'),
(1.0e-5, 1.0e-5, 'lambda'),
(7.0e-1, None, 'lambda_tr'),
(1.0e-2, None, 'gamma'),
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 03a7fa6

Please sign in to comment.