Merge branch 'devel-upflib' into 'develop'

Compilation problem

See merge request QEF/q-e!1351
This commit is contained in:
giannozz 2021-03-02 20:32:57 +00:00
commit b241973314
4 changed files with 14 additions and 16 deletions

View File

@ -1090,7 +1090,7 @@ subroutine nlinit
use constants, ONLY : pi, fpi
use ions_base, ONLY : na, nsp
use uspp, ONLY : aainit, beta, qq_nt, dvan, nhtol, nhtolm, indv,&
dbeta
dbeta, qq_nt_d
use uspp_param, ONLY : upf, lmaxq, nbetam, lmaxkb, nhm, nh
use atom, ONLY : rgrid
use qgb_mod, ONLY : qgb, dqgb
@ -1141,6 +1141,9 @@ subroutine nlinit
allocate( dqgb( ngb, nhm*(nhm+1)/2, nsp, 3, 3 ) )
allocate( dbeta( ngw, nhm, nsp, 3, 3 ) )
END IF
#ifdef __CUDA
ALLOCATE( qq_nt_d(nhm,nhm,nsp) )
#endif
!
! initialization for vanderbilt species
!

View File

@ -212,7 +212,6 @@ set_target_properties(qe_pp_xctest_exe PROPERTIES OUTPUT_NAME xctest.x)
target_link_libraries(qe_pp_xctest_exe
PRIVATE
qe_modules
qe_cpv
qe_pp
qe_xclib)
@ -245,7 +244,6 @@ target_link_libraries(qe_pp_pw2wannier90_exe
qe_pp
qe_fftx
qe_upflib
qe_cpv
qe_xclib)
###########################################################

View File

@ -250,7 +250,6 @@ contains
IMPLICIT NONE
CHARACTER(len=256) :: tempfile, filename
INTEGER :: free_unit
INTEGER, EXTERNAL :: find_free_unit
LOGICAL :: exst
!
WRITE(stdout,'(5x,"Writing data for restart...")')
@ -264,9 +263,7 @@ contains
filename = trim(prefix) // ".restart_davidson_basis"
tempfile = trim(tmp_dir) // trim(filename)
!
free_unit = find_free_unit()
!
OPEN (free_unit, file = tempfile, form = 'formatted', status = 'unknown')
OPEN (NEWUNIT=free_unit, file = tempfile, form = 'formatted', status = 'unknown')
!
WRITE(free_unit,*) dav_iter
WRITE(free_unit,*) num_basis
@ -338,7 +335,6 @@ contains
IMPLICIT NONE
CHARACTER(len=256) :: tempfile, filename
INTEGER :: free_unit, ib
INTEGER, EXTERNAL :: find_free_unit
LOGICAL :: exst
!
IF (.NOT.restart) RETURN
@ -361,9 +357,7 @@ contains
CALL errore('lr_restart_dav', 'Restart is not possible because of missing restart files...', 1)
ENDIF
!
free_unit = find_free_unit()
!
OPEN (free_unit, file = tempfile, form = 'formatted', status = 'old')
OPEN (NEWUNIT=free_unit, file = tempfile, form = 'formatted', status = 'old')
!
READ(free_unit,*) dav_iter
READ(free_unit,*) num_basis
@ -1863,7 +1857,7 @@ contains
use io_global, only : stdout,ionode,ionode_id
use mp, only : mp_bcast,mp_barrier
use mp_world, only : world_comm
USE cell_base, ONLY : bg, ibrav, celldm
USE cell_base, ONLY : at, bg, ibrav, celldm
USE gvect, ONLY : gcutm, ngm
USE gvecw, ONLY : ecutwfc
USE ions_base, ONLY : nat, ityp, ntyp => nsp, atm, zv, tau
@ -1879,7 +1873,6 @@ contains
REAL(DP), ALLOCATABLE :: raux (:)
character(len=256) :: filename
CHARACTER(len=6), EXTERNAL :: int_to_char
integer, external :: find_free_unit
#if defined (__MPI)
! auxiliary vector for gathering info from multiple cores
REAL(DP), ALLOCATABLE :: raux1 (:)
@ -1910,11 +1903,10 @@ contains
raux(ir)=sign(sqrt(dble(rhoc(ir)*conjg(rhoc(ir)))),dble(rhoc(ir)))
end do
iunplot = find_free_unit()
plot_num = - 1
filename="drho-of-eign-"//trim(int_to_char(ieign))
IF ( ionode ) THEN
OPEN (unit = iunplot, file = trim(tmp_dir)//trim(filename),&
OPEN (NEWUNIT = iunplot, file = trim(tmp_dir)//trim(filename),&
status = 'unknown', err = 100, iostat = ios)
100 CALL errore ('plotout', 'opening file', ABS (ios) )
REWIND (iunplot)
@ -1922,6 +1914,11 @@ contains
WRITE (iunplot, '(8i8)') dfftp%nr1x, dfftp%nr2x, dfftp%nr3x, dfftp%nr1,&
dfftp%nr2, dfftp%nr3, nat, ntyp
WRITE (iunplot, '(i6,6f12.8)') ibrav, celldm
IF (ibrav == 0) THEN
DO ipol = 1,3
WRITE ( iunplot, * ) ( at(jpol,ipol),jpol=1,3 )
END DO
END IF
WRITE (iunplot, '(3f20.10,i6)') gcutm, dual, ecutwfc, plot_num
WRITE (iunplot, '(i4,3x,a2,3x,f5.2)') (nt, atm (nt), zv (nt), nt=1, ntyp)
WRITE (iunplot, '(i4,3x,3f14.10,3x,i2)') (na, &

View File

@ -3,7 +3,7 @@
include ../make.inc
QEMODS = libupf.a
MODFLAGS= $(MOD_FLAG)../UtilXlib
MODFLAGS= $(MOD_FLAG)../UtilXlib $(MOD_FLAG)../external/devxlib/src
# list of modules