quantum-espresso/PW/hinit0.f90

106 lines
3.1 KiB
Fortran
Raw Normal View History

!
! Copyright (C) 2001-2005 Quantum ESPRESSO group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
! or http://www.gnu.org/copyleft/gpl.txt .
!
!-----------------------------------------------------------------------
SUBROUTINE hinit0()
!-----------------------------------------------------------------------
!
! ... hamiltonian initialization:
! ... atomic position independent initialization for nonlocal PP,
! ... structure factors, local potential, core charge
!
USE ions_base, ONLY : nat, nsp, ityp, tau
USE basis, ONLY : startingconfig
USE cell_base, ONLY : at, bg, omega, tpiba2
USE cellmd, ONLY : omega_old, at_old, lmovecell
USE klist, ONLY : nks, xk
USE grid_dimensions, ONLY : nr1, nr2, nr3
USE gvect, ONLY : ngm, ig_l2g, g, eigts1, eigts2, eigts3
USE vlocal, ONLY : strf
USE wvfct, ONLY : npw, g2kin, igk, ecutwfc
USE io_files, ONLY : iunigk
This is the first iteration in trying to implement a real space treatment of projectors in USPPs. Hopefully this will allow one to study larger systems. The modifications are done primarily keeping TDDFPT code in mind (a branch of QE, you may see detailed explanation in qe-forge which I am trying to keep tightly integrated). Please do not modify/beautify/make more elegant the corresponding subroutines without prior notice, due to their dependencies. I have tested that the current modifications do not alter the behaviour of pw.x other than designed with a number of small tests in HG1. Some Pointers: -All the new subroutines reside in PW/realus.f90 -A new flag real_space in &electrons control the implementation -tqr flag is treated seperately. -The implementation works only for (serial) gamma point single point calculations. ToDo: -I have written K point and task groups implementations of most of the corresponding routines, but did not have time to implement. -Parallelism issues are still to be checked. -The discrepancy in total energy is <0.002 eV for cutoff of 55Ry/550Ry however, there are some strange force components. I do not know how this will effect a possible optimization scheme. Other: Trying the compile CVS version in HG1 of sissa, using the "default" compiler sets, I encountered a very strange compiler bug. Please have a look at Modules/read_cards.f90 for details. Remove the stupid workaround to your liking. git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@5493 c92efa57-630b-4861-b058-cf58834340f0
2009-04-03 00:05:09 +08:00
USE realus, ONLY : qpointlist,betapointlist,init_realspace_vars,real_space
USE control_flags, ONLY : tqr
USE io_global, ONLY : stdout
!
IMPLICIT NONE
!
INTEGER :: ik
! counter on k points
!
! ... calculate the Fourier coefficients of the local part of the PP
!
CALL init_vloc()
!
! ... k-point independent parameters of non-local pseudopotentials
!
CALL init_us_1()
CALL init_at_1()
!
REWIND( iunigk )
!
! ... The following loop must NOT be called more than once in a run
! ... or else there will be problems with variable-cell calculations
!
DO ik = 1, nks
!
! ... g2kin is used here as work space
!
CALL gk_sort( xk(1,ik), ngm, g, ecutwfc / tpiba2, npw, igk, g2kin )
!
! ... if there is only one k-point npw and igk stay in memory
!
IF ( nks > 1 ) WRITE( iunigk ) igk
!
END DO
!
IF ( lmovecell .AND. startingconfig == 'file' ) THEN
!
! ... If lmovecell and restart are both true the cell shape is read from
! ... the restart file and stored. The xxx_old variables are used instead
! ... of the current (read from input) ones.
! ... xxx and xxx_old are swapped, the atomic positions rescaled and
! ... the hamiltonian scaled.
!
CALL cryst_to_cart( nat, tau, bg, - 1 )
!
CALL dswap( 9, at, 1, at_old, 1 )
CALL dswap( 1, omega, 1, omega_old, 1 )
!
CALL cryst_to_cart( nat, tau, at, + 1 )
!
CALL recips( at(1,1), at(1,2), at(1,3), bg(1,1), bg(1,2), bg(1,3) )
CALL scale_h()
!
END IF
!
! ... initialize the structure factor
!
CALL struc_fact( nat, tau, nsp, ityp, ngm, g, bg, &
nr1, nr2, nr3, strf, eigts1, eigts2, eigts3 )
!
! ... calculate the total local potential
!
CALL setlocal()
!
! ... calculate the core charge (if any) for the nonlinear core correction
!
CALL set_rhoc()
!
This is the first iteration in trying to implement a real space treatment of projectors in USPPs. Hopefully this will allow one to study larger systems. The modifications are done primarily keeping TDDFPT code in mind (a branch of QE, you may see detailed explanation in qe-forge which I am trying to keep tightly integrated). Please do not modify/beautify/make more elegant the corresponding subroutines without prior notice, due to their dependencies. I have tested that the current modifications do not alter the behaviour of pw.x other than designed with a number of small tests in HG1. Some Pointers: -All the new subroutines reside in PW/realus.f90 -A new flag real_space in &electrons control the implementation -tqr flag is treated seperately. -The implementation works only for (serial) gamma point single point calculations. ToDo: -I have written K point and task groups implementations of most of the corresponding routines, but did not have time to implement. -Parallelism issues are still to be checked. -The discrepancy in total energy is <0.002 eV for cutoff of 55Ry/550Ry however, there are some strange force components. I do not know how this will effect a possible optimization scheme. Other: Trying the compile CVS version in HG1 of sissa, using the "default" compiler sets, I encountered a very strange compiler bug. Please have a look at Modules/read_cards.f90 for details. Remove the stupid workaround to your liking. git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@5493 c92efa57-630b-4861-b058-cf58834340f0
2009-04-03 00:05:09 +08:00
IF ( tqr ) CALL qpointlist()
IF (real_space ) then
!call qpointlist()
call betapointlist()
call init_realspace_vars()
write(stdout,'(5X,"Real space initialisation completed")')
endif
!
RETURN
!
END SUBROUTINE hinit0