mirror of https://gitlab.com/QEF/q-e.git
Minor cleanup
This commit is contained in:
parent
935fe87a42
commit
b968d99d6b
|
@ -22,7 +22,6 @@ SUBROUTINE openfil_pw4gww()
|
|||
USE io_files, ONLY : prefix, tmp_dir, iunwfc, nwordwfc, iunsat, nwordatwfc, diropn
|
||||
USE noncollin_module, ONLY : npol
|
||||
USE ldaU, ONLY : lda_plus_u
|
||||
USE basis, ONLY : natomwfc
|
||||
USE ions_base, ONLY : nat, ityp
|
||||
USE noncollin_module, ONLY : noncolin
|
||||
!
|
||||
|
|
|
@ -608,7 +608,6 @@ subroutine read_export (pp_file,kunit,uspp_spsi, ascii, single_file, raw)
|
|||
use mp, ONLY : mp_sum, mp_max
|
||||
use mp_world, ONLY : world_comm, nproc, mpime
|
||||
use ldaU, ONLY : lda_plus_u
|
||||
USE basis, ONLY : swfcatom
|
||||
USE uspp_init, ONLY : init_us_2
|
||||
|
||||
implicit none
|
||||
|
@ -776,7 +775,8 @@ subroutine read_export (pp_file,kunit,uspp_spsi, ascii, single_file, raw)
|
|||
IF( (ik >= iks) .AND. (ik <= ike) ) THEN
|
||||
|
||||
call davcio (evc, 2*nwordwfc, iunwfc, (ik-iks+1), - 1)
|
||||
IF ( lda_plus_u ) CALL davcio( swfcatom, nwordatwfc, iunsat, (ik-iks+1), -1 )
|
||||
! IF ( lda_plus_u ) CALL davcio( swfcatom, nwordatwfc, iunsat, (ik-iks+1), -1 )
|
||||
IF ( lda_plus_u ) call errore('pw4gww','DFT+U possibly unsupported',1)
|
||||
local_pw = ngk(ik-iks+1)
|
||||
|
||||
ENDIF
|
||||
|
|
|
@ -15,8 +15,6 @@ SUBROUTINE orthoUwfc(save_wfcatom)
|
|||
! "iunhub_noS" but without S (this is then used for plotting Hubbard projector
|
||||
! functions or other post-processing operations). Atomic wavefunctions
|
||||
! are orthogonalized if desired, depending upon the value of "Hubbard_projectors"
|
||||
! "swfcatom" must NOT be allocated on input.
|
||||
!
|
||||
! If save_wfcatom == .TRUE., also write atomic wavefunctions before
|
||||
! applying S to buffer.
|
||||
!
|
||||
|
@ -25,7 +23,7 @@ SUBROUTINE orthoUwfc(save_wfcatom)
|
|||
USE io_global, ONLY : stdout
|
||||
USE io_files, ONLY : iunhub, iunhub_noS, nwordwfcU
|
||||
USE ions_base, ONLY : nat
|
||||
USE basis, ONLY : natomwfc, swfcatom
|
||||
USE basis, ONLY : natomwfc
|
||||
USE klist, ONLY : nks, xk, ngk, igk_k
|
||||
USE ldaU, ONLY : Hubbard_projectors, wfcU, nwfcU, copy_U_wfc
|
||||
USE wvfct, ONLY : npwx
|
||||
|
@ -46,7 +44,7 @@ SUBROUTINE orthoUwfc(save_wfcatom)
|
|||
! ik: the k point under consideration
|
||||
! ibnd: counter on bands
|
||||
LOGICAL :: orthogonalize_wfc, normalize_only, save_flag
|
||||
COMPLEX(DP) , ALLOCATABLE :: wfcatom (:,:), wfcUaux (:,:)
|
||||
COMPLEX(DP) , ALLOCATABLE :: wfcatom (:,:), swfcatom(:,:), wfcUaux (:,:)
|
||||
!
|
||||
IF ( Hubbard_projectors == "pseudo" ) THEN
|
||||
WRITE( stdout,'(/5x,a,/)') 'Beta functions used for Hubbard projectors'
|
||||
|
|
|
@ -26,7 +26,6 @@ SUBROUTINE lr_setup_nscf ()
|
|||
USE cell_base, ONLY : at, bg, alat, tpiba, tpiba2, ibrav, omega
|
||||
USE ions_base, ONLY : nat, tau, ityp, zv
|
||||
USE force_mod, ONLY : force
|
||||
USE basis, ONLY : natomwfc
|
||||
USE klist, ONLY : xk, wk, nks, nelec, degauss, lgauss, &
|
||||
nkstot, qnorm
|
||||
USE lsda_mod, ONLY : lsda, nspin, current_spin, isk
|
||||
|
|
Loading…
Reference in New Issue