quantum-espresso/PW/init_run.f90

141 lines
3.4 KiB
Fortran
Raw Normal View History

!
! Copyright (C) 2001-2006 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 init_run()
!----------------------------------------------------------------------------
!
USE klist, ONLY : nkstot
USE wvfct, ONLY : nbnd, et, wg, btype
USE control_flags, ONLY : lmd,gamma_only
USE dynamics_module, ONLY : allocate_dyn_vars
USE paw_variables, ONLY : okpaw
USE paw_init, ONLY : paw_init_onecenter, allocate_paw_internals
#ifdef __PARA
USE paw_init, ONLY : paw_post_init
#endif
USE bp, ONLY : lberry, lelfield
USE gvect, ONLY : nrxx, nrx1, nrx2, nrx3, nr1, nr2, nr3, ecutwfc
! DCC
USE ee_mod, ONLY : do_comp, do_coarse
! Wannier_ac
USE wannier_new, ONLY : use_wannier
!
IMPLICIT NONE
!
!
CALL start_clock( 'init_run' )
!
! ... calculate limits of some indices, used in subsequent allocations
!
CALL pre_init()
!
! ... allocate memory for G- and R-space fft arrays
!
CALL allocate_fft()
!
! ... generate reciprocal-lattice vectors and fft indices
!
CALL ggen()
!
CALL summary()
!
! ... allocate memory for all other arrays (potentials, wavefunctions etc)
!
CALL allocate_nlpot()
IF (okpaw) THEN
CALL allocate_paw_internals()
CALL paw_init_onecenter()
ENDIF
CALL allocate_locpot()
CALL allocate_wfc()
CALL allocate_bp_efield()
IF( lberry .or. lelfield) call bp_global_map()
! DCC
! ... Initializes EE variables
!
IF ( do_comp ) CALL init_ee(nrx1,nrx2,nrx3)
!
IF ( do_coarse ) THEN
CALL ggen_coarse()
CALL data_structure_coarse( gamma_only, nr1,nr2,nr3, ecutwfc )
END IF
CALL memory_report()
!
ALLOCATE( et( nbnd, nkstot ) , wg( nbnd, nkstot ), btype( nbnd, nkstot ) )
!
et(:,:) = 0.D0
wg(:,:) = 0.D0
!
btype(:,:) = 1
!
CALL openfil()
!
CALL hinit0()
!
CALL potinit()
!
CALL newd()
!
CALL wfcinit()
!
IF(use_wannier) CALL wannier_init()
!
#ifdef __PARA
! Cleanup PAW arrays that are only used for init
IF (okpaw) CALL paw_post_init() ! only parallel!
#endif
!
IF ( lmd ) CALL allocate_dyn_vars()
!
CALL stop_clock( 'init_run' )
!
This is a quite complex check-in, but actually not very much is done. Changelog follows. LP UPF file format updated completely, UPFv2 introduced: * ld1.x can still produce old format, with the switch upf_v1_format=.true. in inputp this is disabled by default, but we can discuss if it should be the opposite. * pw.x cp.x and all utilities should notice no difference * some utilities in upftools still need to be updated, anyway conversion UPFv1 to UPFv2 is very easy, so this should be no big issue * starting from now to produce an UPF file you need to fill the pseudo_upf derivedd type and feed it to write_upf woutine in upf_module (Modules/upf.f90) * extensive use of iotk I have tried to make the new format as self contained as possible, e.g. there should be minimal need for post-processing after the data is read, no more reconstruction of known quantities, and no more odd syntax to save negligible quantity of space. Also the human readable section is a bit richer, all the rest is more machine readable. I hope this will not cause any throuble, and tried really hard to, all examples and all tests works as fine as before and gives (what really looks like) the same results. Other changes that I needed to make: * radial grids are now allocatable, they management is a bit less of a hack too * paw and uspp augmentation are stored in the same place * paw print total all-electron energy if all atoms are paw, not very useful, but nice * most of the pseudopotential-writing reading files have been renamed to some more logical name, I spare you the list. E.g. read_oldpseudo -> read_pseudo_rrkj3 * paw_t derived type was only used in atomic, so I have put it there (as the pseudo_type module take ages to recompile it was awkward to leave it there). PAW tests inserted in test/ there are 6 of them, as a consequence I have also put 5 paw pseudopotentials in the pseudo/ directory. I will update the PAW scf examples soon, by deleting them (as running a pw with a PAW pseudopotential requires no option at all). PAW generation examples should be updated. A lot of small bugfixes here & there mostly uninitialized variables or unallocated pointers used as subrotuine arguments. git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@4769 c92efa57-630b-4861-b058-cf58834340f0
2008-04-03 23:50:43 +08:00
RETURN
!
END SUBROUTINE init_run
!
!----------------------------------------------------------------------------
SUBROUTINE pre_init()
!----------------------------------------------------------------------------
!
USE ions_base, ONLY : nat, nsp, ityp
USE uspp_param, ONLY : upf, lmaxkb, nh, nhm, nbetam
USE uspp, ONLY : nkb, nkbus
IMPLICIT NONE
INTEGER :: na, nt, nb
!
! calculate the number of beta functions for each atomic type
!
lmaxkb = - 1
do nt = 1, nsp
nh (nt) = 0
do nb = 1, upf(nt)%nbeta
nh (nt) = nh (nt) + 2 * upf(nt)%lll(nb) + 1
lmaxkb = max (lmaxkb, upf(nt)%lll(nb) )
enddo
enddo
!
! calculate the maximum number of beta functions
!
nhm = MAXVAL (nh (1:nsp))
nbetam = MAXVAL (upf(:)%nbeta)
!
! calculate the number of beta functions of the solid
!
nkb = 0
nkbus = 0
do na = 1, nat
nt = ityp(na)
nkb = nkb + nh (nt)
if (upf(nt)%tvanp) nkbus = nkbus + nh (nt)
enddo
END SUBROUTINE pre_init