quantum-espresso/PW/potinit.f90

253 lines
7.8 KiB
Fortran
Raw Normal View History

!
! Copyright (C) 2001-2007 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 .
!
#include "f_defs.h"
!
!----------------------------------------------------------------------------
SUBROUTINE potinit()
!----------------------------------------------------------------------------
!
! ... This routine initializes the self consistent potential in the array
! ... vr. There are three possible cases:
!
! ... a) the code is restarting from a broken run:
! ... read rho from data stored during the previous run
! ... b) the code is performing a non-scf calculation following a scf one:
! ... read rho from the file produced by the scf calculation
! ... c) the code starts a new calculation:
! ... calculate rho as a sum of atomic charges
!
! ... In all cases the scf potential is recalculated and saved in vr
!
USE kinds, ONLY : DP
USE constants, ONLY : pi
USE io_global, ONLY : stdout
USE cell_base, ONLY : alat, omega
USE ions_base, ONLY : nat, ityp, ntyp => nsp
USE basis, ONLY : startingpot
USE klist, ONLY : nelec
USE lsda_mod, ONLY : lsda, nspin
USE gvect, ONLY : nr1, nr2, nr3, nrx1, nrx2, nrx3, nrxx, &
ngm, gstart, nl, g, gg
USE gsmooth, ONLY : doublegrid
USE control_flags, ONLY : lscf
USE scf, ONLY : rho, rho_core, rhog_core, &
vltot, v, vrs, kedtau
USE funct, ONLY : dft_is_meta
USE wavefunctions_module, ONLY : psic
USE ener, ONLY : ehart, etxc, vtxc
USE ldaU, ONLY : niter_with_fixed_ns
USE ldaU, ONLY : lda_plus_u, Hubbard_lmax, eth
USE noncollin_module, ONLY : noncolin, report
USE io_files, ONLY : tmp_dir, prefix, iunocc, input_drho
USE spin_orb, ONLY : domag
USE mp, ONLY : mp_bcast
USE mp_global, ONLY : intra_image_comm
USE io_global, ONLY : ionode, ionode_id
USE pw_restart, ONLY : pw_readfile
USE io_rho_xml, ONLY : read_rho
!
SCF with Projector-Augmented Wave Pseudopotential (PAW) routines added. This means that a lot of routines have been modified and a few files have been added. During the year several people have contributed to this code, mainly Guido Fratesi, Ricardo Mazzarello, Stefano de Gironcoli, Andrea Dal Corso and me (Lorenzo Paulatto). A brief report of modified or added files follows, further down you will find a loger report of modifications that was necessary to merge develop_PAW branch with the current CVS version. Current version is not 100% functional, but it doesn't brake anything else and can be used to generate and test PAW pseudopotential. ************************************* *** Brief report of modifications *** ************************************* Modified files: PW/clean_pw.f90 PW/electrons.f90 PW/print_clock_pw.f90 PW/hinit0.f90 PW/potinit.f90 PW/newd.f90 PW/summary.f90 PW/setup.f90 PW/read_pseudo.f90 PW/init_us_1.f90 PW/init_run.f90 PW/mix_rho.f90 atomic/atomic_paw.f90 atomic/write_paw_recon.f90 atomic/ld1_writeout.f90 atomic/write_resultsps.f90 atomic/ld1inc.f90 atomic/ld1_readin.f90 atomic/gener_pseudo.f90 atomic/parameters.f900 atomic/run_pseudo.f900 atomic/set_rho_core.f90 atomic/pseudovloc.f90 Modules/read_upf.f90 Modules/uspp.f90 Modules/pseudo_types.f90 Modules/parameters.f90 Added files: PW/grid_paw_routines.f90 PW/rad_paw_routines.f90 Modules/grid_paw_variables.f90 Modules/read_paw.f90 Added files that will be removed: PW/rad_paw_trash.f90 PW/paw_xc.f90 Examples: examples/PAWexample contains a full test of PAW pseudopotential for Oxygen. The test consist in these tasks: - 2 norm conserving, 2 US and 4 PAW pseudopotentials are generated and tested in ld1 - pw test for an isolated O atom at different cutoffs - pw test for an O2 molecule at different O-O distance please read examples/PAWexample/README for (a few) details. NOTES: 1. new modifications to atomic_paw (and related) from ADC have been rolled back, as they were breaking a lot of things, I will reintroduce them later when I am sure that everything works properly. 2. the files PW/paw_xc.f90 and Modules/rad_paw_trash.f90 will be removed in the next few weeks. TODO: 1. use new ld1 XC code as much as possible, and remove legacy XC routines from rad_paw_routines 2. full self-consistency with radial energies 3. make new Harris-Foulkes estimate paw-aware 4. provide some kind error estimate 5. FORCES and stress!! (require symmetrization of becsums) 6. cleanup ************************ *** merge of PW code *** ************************ Versions notation: OLD=version from 2 years ago used as reference to generate the patches NEW=CURRENT=current trunk version PAW=current develop_PAW version Note: pseudo-potential input and allocation routines changed a lot in the last years, this is a diagram: OLD:PW/readin ~~> PAW:PW/read_pseudo --> disappears pops out --> PAW:PW/readin ~~> NEW:PW/read_pseudo added files: Modules/read_paw.f90 (contains module read_paw_module with subroutines paw_io nullify_pseudo_paw, allocate_pseudo_paw and deallocate_pseudo_paw previously in removed file Modules/readpseudo.f90. Also contains module paw_to_internal with subroutine set_pseudo_paw, previously in upf_to_internal.f90) PW/paw_xc.f90 (contains OLD=PAW xc and gcxc routines as adapting paw grid code to use new routines was very error prone and quite worthless, as it has to be removed anyway) Conflicts reported by CVS during merge: DONE */Makefiles (all replaced with new, redone by hand) DONE flib/functionals.f90 (nothing to do) DONE Modules/functionals.f90 (RNV == replaced with NEW version) DONE Modules/atom.f90 (trivial: duped rgrid) DONE Modules/autopilot.f90 (trivial) DONE Modules/bfgs_module.f90 (RNV) DONE Modules/cell_base.f90 (RNV) DONE Modules/check_stop.f90 (RNV) DONE Modules/constants.f90 (RNV) DONE Modules/constraints_module.f90 (RNV) DONE Modules/energies.f90 (RNV) DONE Modules/input_parameters.f90 (RNV) DONE Modules/ions_base.f90 (RNV, has 3 new subs) DONE Modules/ions_nose.f90 (RNV) DONE Modules/parameters.f90 (actually RNV) DONE Modules/path_base.f90 (RNV) DONE Modules/path_opt_routines.f90 (RNV) DONE Modules/path_reparametrisation.f90 (RNV) DONE Modules/path_variables.f90 (RNV) DONE Modules/pseudo_types.f90 (cleaned double def of paw_t) DONE Modules/read_cards.f90 (RNV) DONE Modules/read_namelists.f90 (checked and RNV) DONE Modules/uspp.f90 (trivial) DONE Modules/xml_io_base.f90 (RNV) DONE PW/read_pseudo.f90 (merged by hand with PAW PW/readin) DONE PW/bp_calc_btq.f90 (trivial) DONE PW/c_bands.f90 (actually RNV) DONE PW/ccgdiagg.f90 (RNV) DONE PW/cegterg.f90 (RNV) DONE PW/cft3s.f90 (RNV) DONE PW/cinitcgg.f90 (RNV) DONE PW/c_phase_field.f90 (RNV) DONE PW/divide_et_impera.f90 (nothing to do?) DONE PW/exx.f90 (RNV) DONE PW/hinit0.f90 (easy) DONE PW/h_psi.f90 (RNV) DONE PW/init_run.f90 (easy) DONE PW/kpoint_grid.f90 (nothing to do?) DONE PW/newd.f90 (required mod in newd_paw_grid, CHECK!!) DONE PW/openfil.f90 (actually RNV) DONE PW/paw.f90 (actually RNV) DONE PW/punch.f90 (RNV) DONE PW/pwscf.f90 (quite RNV) DONE PW/set_kup_and_kdw.f90 (RNV) DONE PW/setup.f90 (RNV + 2 line merged by hand) DONE PW/sgama.f9 (actually RNV) DONE PW/sgam_at_mag.f90 (actually RNV) DONE PW/stop_run.f90 (actually RNV) DONE PW/stres_gradcorr.f90 (actually RNV) DONE PW/symrho_mag.f90 (nothing to do) DONE PW/v_of_rho.f90 (RNV) DONE PW/compute_fes_grads.f90 (RNV) DONE PW/gradcorr.f90 (RNV) DONE PW/input.f90 (RNV) DONE PW/pw_restart.f90 (RNV) DONE PW/read_ncpp.f90 (actually RNV) DONE PW/summary.f90 (RNV + inserted new PP type) DONE PW/wfcinit.f90 (RNV) the hard ones: DONE PW/electrons.f90 (adapted code to new syntaxes, a lot of cleanup, removed some PAW junk that can be readded later, removed parts that were applyed twice, or had been removed in trunk, the rhog allocations and usage may need fixes) DONE PW/mix_rho.f90 (merged tauk and paw additions, a bit of cleanup and smarter variables names) DONE PW/init_us_1.f90 (qtot redefined with "triangular" index nb,mb-->ijv) modified for compiling: Modules/io_files.f90 (depatched) PW/pwcom.f90 (depatched) Modules/parameters.f90 (temporary readded cp_lmax = lmaxx+1) PW/newd.f90 (merge was wrong, redone mostly by hand) PW/read_ncpp.f90 (depatched) PW/read_pseudo (small fixes) PW/sgam_at_mag.f90 (depatched) PW/sgama.f90 (depatched) PW/stres_gradcorr.f90 (depatched) modified for running: PW/clean_pw.f90 (added call to deallocate_paw_internals) Modifications to PAW routines: 1. compute_onecenter_charges and compute_onecenter_charges modified to comply with new structure of v_xc (in v_of_rho.f90), requiring new g-space densities to be saved and computed --> using old xc routines as this code will be removed. 2. qrad size has changed, prad and ptrad had to be changed accordingly. 3. several minor modifications to use new radial grid structure. 4. infomsg arguments changed, very funny bug followed. 5. added new routine deallocate_paw_internals, called by PW/clean_pw.f90 required to run pp.x with more than one q-point(and good programming practice) ************************* *** merge of LD1 code *** ************************* 2nd try: atomic code replaced with current version, then merge by hand the files that are used by paw subsystem: * atomic_paw.f90 (replaced with most recent version from develop_PAW routine us2paw and paw2us taken from newer trunk version, a lot of minor changes.) * gener_pseudo.f90 (fixes) * ld1inc.f90 (PAW variables added) * ld1_readin.f90 (PAW variables added, I am not sure if lpaw should go in input or inputp namelist) * ld1_writeout.f90 (it was only necessary to add a few lines) * pseudovloc.f90 (nothing to do) * run_pseudo.f90 (almost nothing to do) * set_rho_core.f90 (readded a few lines for lnc2paw) * write_paw_recon.f90 (nothing to do) * write_resultsps.f90 (nothing to do: trunk version is more PAW-aware than PAW version) Main problems were found in subroutines run_pseudo and gen_pseudo, a little code had to be rewritten to comply with new variable names and fix with merge. TODO: fix atomic_paw routines to use minimal allocated arrays insetad of ndmx sized ones; try to use the pawet as much as possible. Remove test lines and other garbage. Find a fix for PAW2. The first week of september Andrea Dal Corso uploaded a few modifications to the atomic_paw routines. I had to rollback them as the structure of atomic_paw has changed a lot and reimplementing them is probably easier and definitely safer than fixing everything. I will do it soon, I swear! LP git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@4257 c92efa57-630b-4861-b058-cf58834340f0
2007-09-18 18:05:46 +08:00
USE uspp, ONLY : becsum
USE paw_variables, ONLY : okpaw
USE paw_init, ONLY : PAW_init_becsum
USE paw_onecenter, ONLY : PAW_potential
SCF with Projector-Augmented Wave Pseudopotential (PAW) routines added. This means that a lot of routines have been modified and a few files have been added. During the year several people have contributed to this code, mainly Guido Fratesi, Ricardo Mazzarello, Stefano de Gironcoli, Andrea Dal Corso and me (Lorenzo Paulatto). A brief report of modified or added files follows, further down you will find a loger report of modifications that was necessary to merge develop_PAW branch with the current CVS version. Current version is not 100% functional, but it doesn't brake anything else and can be used to generate and test PAW pseudopotential. ************************************* *** Brief report of modifications *** ************************************* Modified files: PW/clean_pw.f90 PW/electrons.f90 PW/print_clock_pw.f90 PW/hinit0.f90 PW/potinit.f90 PW/newd.f90 PW/summary.f90 PW/setup.f90 PW/read_pseudo.f90 PW/init_us_1.f90 PW/init_run.f90 PW/mix_rho.f90 atomic/atomic_paw.f90 atomic/write_paw_recon.f90 atomic/ld1_writeout.f90 atomic/write_resultsps.f90 atomic/ld1inc.f90 atomic/ld1_readin.f90 atomic/gener_pseudo.f90 atomic/parameters.f900 atomic/run_pseudo.f900 atomic/set_rho_core.f90 atomic/pseudovloc.f90 Modules/read_upf.f90 Modules/uspp.f90 Modules/pseudo_types.f90 Modules/parameters.f90 Added files: PW/grid_paw_routines.f90 PW/rad_paw_routines.f90 Modules/grid_paw_variables.f90 Modules/read_paw.f90 Added files that will be removed: PW/rad_paw_trash.f90 PW/paw_xc.f90 Examples: examples/PAWexample contains a full test of PAW pseudopotential for Oxygen. The test consist in these tasks: - 2 norm conserving, 2 US and 4 PAW pseudopotentials are generated and tested in ld1 - pw test for an isolated O atom at different cutoffs - pw test for an O2 molecule at different O-O distance please read examples/PAWexample/README for (a few) details. NOTES: 1. new modifications to atomic_paw (and related) from ADC have been rolled back, as they were breaking a lot of things, I will reintroduce them later when I am sure that everything works properly. 2. the files PW/paw_xc.f90 and Modules/rad_paw_trash.f90 will be removed in the next few weeks. TODO: 1. use new ld1 XC code as much as possible, and remove legacy XC routines from rad_paw_routines 2. full self-consistency with radial energies 3. make new Harris-Foulkes estimate paw-aware 4. provide some kind error estimate 5. FORCES and stress!! (require symmetrization of becsums) 6. cleanup ************************ *** merge of PW code *** ************************ Versions notation: OLD=version from 2 years ago used as reference to generate the patches NEW=CURRENT=current trunk version PAW=current develop_PAW version Note: pseudo-potential input and allocation routines changed a lot in the last years, this is a diagram: OLD:PW/readin ~~> PAW:PW/read_pseudo --> disappears pops out --> PAW:PW/readin ~~> NEW:PW/read_pseudo added files: Modules/read_paw.f90 (contains module read_paw_module with subroutines paw_io nullify_pseudo_paw, allocate_pseudo_paw and deallocate_pseudo_paw previously in removed file Modules/readpseudo.f90. Also contains module paw_to_internal with subroutine set_pseudo_paw, previously in upf_to_internal.f90) PW/paw_xc.f90 (contains OLD=PAW xc and gcxc routines as adapting paw grid code to use new routines was very error prone and quite worthless, as it has to be removed anyway) Conflicts reported by CVS during merge: DONE */Makefiles (all replaced with new, redone by hand) DONE flib/functionals.f90 (nothing to do) DONE Modules/functionals.f90 (RNV == replaced with NEW version) DONE Modules/atom.f90 (trivial: duped rgrid) DONE Modules/autopilot.f90 (trivial) DONE Modules/bfgs_module.f90 (RNV) DONE Modules/cell_base.f90 (RNV) DONE Modules/check_stop.f90 (RNV) DONE Modules/constants.f90 (RNV) DONE Modules/constraints_module.f90 (RNV) DONE Modules/energies.f90 (RNV) DONE Modules/input_parameters.f90 (RNV) DONE Modules/ions_base.f90 (RNV, has 3 new subs) DONE Modules/ions_nose.f90 (RNV) DONE Modules/parameters.f90 (actually RNV) DONE Modules/path_base.f90 (RNV) DONE Modules/path_opt_routines.f90 (RNV) DONE Modules/path_reparametrisation.f90 (RNV) DONE Modules/path_variables.f90 (RNV) DONE Modules/pseudo_types.f90 (cleaned double def of paw_t) DONE Modules/read_cards.f90 (RNV) DONE Modules/read_namelists.f90 (checked and RNV) DONE Modules/uspp.f90 (trivial) DONE Modules/xml_io_base.f90 (RNV) DONE PW/read_pseudo.f90 (merged by hand with PAW PW/readin) DONE PW/bp_calc_btq.f90 (trivial) DONE PW/c_bands.f90 (actually RNV) DONE PW/ccgdiagg.f90 (RNV) DONE PW/cegterg.f90 (RNV) DONE PW/cft3s.f90 (RNV) DONE PW/cinitcgg.f90 (RNV) DONE PW/c_phase_field.f90 (RNV) DONE PW/divide_et_impera.f90 (nothing to do?) DONE PW/exx.f90 (RNV) DONE PW/hinit0.f90 (easy) DONE PW/h_psi.f90 (RNV) DONE PW/init_run.f90 (easy) DONE PW/kpoint_grid.f90 (nothing to do?) DONE PW/newd.f90 (required mod in newd_paw_grid, CHECK!!) DONE PW/openfil.f90 (actually RNV) DONE PW/paw.f90 (actually RNV) DONE PW/punch.f90 (RNV) DONE PW/pwscf.f90 (quite RNV) DONE PW/set_kup_and_kdw.f90 (RNV) DONE PW/setup.f90 (RNV + 2 line merged by hand) DONE PW/sgama.f9 (actually RNV) DONE PW/sgam_at_mag.f90 (actually RNV) DONE PW/stop_run.f90 (actually RNV) DONE PW/stres_gradcorr.f90 (actually RNV) DONE PW/symrho_mag.f90 (nothing to do) DONE PW/v_of_rho.f90 (RNV) DONE PW/compute_fes_grads.f90 (RNV) DONE PW/gradcorr.f90 (RNV) DONE PW/input.f90 (RNV) DONE PW/pw_restart.f90 (RNV) DONE PW/read_ncpp.f90 (actually RNV) DONE PW/summary.f90 (RNV + inserted new PP type) DONE PW/wfcinit.f90 (RNV) the hard ones: DONE PW/electrons.f90 (adapted code to new syntaxes, a lot of cleanup, removed some PAW junk that can be readded later, removed parts that were applyed twice, or had been removed in trunk, the rhog allocations and usage may need fixes) DONE PW/mix_rho.f90 (merged tauk and paw additions, a bit of cleanup and smarter variables names) DONE PW/init_us_1.f90 (qtot redefined with "triangular" index nb,mb-->ijv) modified for compiling: Modules/io_files.f90 (depatched) PW/pwcom.f90 (depatched) Modules/parameters.f90 (temporary readded cp_lmax = lmaxx+1) PW/newd.f90 (merge was wrong, redone mostly by hand) PW/read_ncpp.f90 (depatched) PW/read_pseudo (small fixes) PW/sgam_at_mag.f90 (depatched) PW/sgama.f90 (depatched) PW/stres_gradcorr.f90 (depatched) modified for running: PW/clean_pw.f90 (added call to deallocate_paw_internals) Modifications to PAW routines: 1. compute_onecenter_charges and compute_onecenter_charges modified to comply with new structure of v_xc (in v_of_rho.f90), requiring new g-space densities to be saved and computed --> using old xc routines as this code will be removed. 2. qrad size has changed, prad and ptrad had to be changed accordingly. 3. several minor modifications to use new radial grid structure. 4. infomsg arguments changed, very funny bug followed. 5. added new routine deallocate_paw_internals, called by PW/clean_pw.f90 required to run pp.x with more than one q-point(and good programming practice) ************************* *** merge of LD1 code *** ************************* 2nd try: atomic code replaced with current version, then merge by hand the files that are used by paw subsystem: * atomic_paw.f90 (replaced with most recent version from develop_PAW routine us2paw and paw2us taken from newer trunk version, a lot of minor changes.) * gener_pseudo.f90 (fixes) * ld1inc.f90 (PAW variables added) * ld1_readin.f90 (PAW variables added, I am not sure if lpaw should go in input or inputp namelist) * ld1_writeout.f90 (it was only necessary to add a few lines) * pseudovloc.f90 (nothing to do) * run_pseudo.f90 (almost nothing to do) * set_rho_core.f90 (readded a few lines for lnc2paw) * write_paw_recon.f90 (nothing to do) * write_resultsps.f90 (nothing to do: trunk version is more PAW-aware than PAW version) Main problems were found in subroutines run_pseudo and gen_pseudo, a little code had to be rewritten to comply with new variable names and fix with merge. TODO: fix atomic_paw routines to use minimal allocated arrays insetad of ndmx sized ones; try to use the pawet as much as possible. Remove test lines and other garbage. Find a fix for PAW2. The first week of september Andrea Dal Corso uploaded a few modifications to the atomic_paw routines. I had to rollback them as the structure of atomic_paw has changed a lot and reimplementing them is probably easier and definitely safer than fixing everything. I will do it soon, I swear! LP git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@4257 c92efa57-630b-4861-b058-cf58834340f0
2007-09-18 18:05:46 +08:00
!
IMPLICIT NONE
!
REAL(DP) :: charge ! the starting charge
REAL(DP) :: etotefield !
REAL(DP) :: fact
INTEGER :: is, ios
INTEGER :: ldim ! integer variable for I/O control
LOGICAL :: exst
CHARACTER(LEN=256) :: filename
!
CALL start_clock('potinit')
!
filename = TRIM( prefix ) // '.save/charge-density.xml'
!
IF ( ionode ) THEN
!
INQUIRE( FILE = TRIM( tmp_dir ) // TRIM( filename ), EXIST = exst )
!
END IF
!
CALL mp_bcast( exst, ionode_id, intra_image_comm )
!
IF ( startingpot == 'file' .AND. exst ) THEN
!
! ... Cases a) and b): the charge density is read from file
!
CALL pw_readfile( 'rho', ios )
!
IF ( ios /= 0 ) THEN
!
WRITE( stdout, '(/5X,"Error reading from file :"/5X,A,/)' ) &
TRIM( filename )
!
CALL errore ( 'potinit' , 'reading starting density', ios)
!
ELSE IF ( lscf ) THEN
!
WRITE( stdout, '(/5X, &
& "The initial density is read from file :"/5X,A,/)' ) &
TRIM( filename )
!
ELSE
!
WRITE( stdout, '(/5X, &
& "The potential is recalculated from file :"/5X,A,/)' ) &
TRIM( filename )
!
END IF
!
! ... The occupations ns also need to be read in order to build up
! ... the potential
!
IF ( lda_plus_u ) THEN
!
ldim = 2*Hubbard_lmax + 1
IF ( ionode ) THEN
CALL seqopn( iunocc, 'occup', 'FORMATTED', exst )
READ( UNIT = iunocc, FMT = * ) rho%ns
CLOSE( UNIT = iunocc, STATUS = 'KEEP' )
ELSE
rho%ns(:,:,:,:) = 0.D0
END IF
CALL reduce( ldim*ldim*nspin*nat, rho%ns )
CALL poolreduce( ldim*ldim*nspin*nat, rho%ns )
!
END IF
!
ELSE
!
! ... Case c): the potential is built from a superposition
! ... of atomic charges contained in the array rho_at
!
IF ( startingpot == 'file' .AND. .NOT. exst ) &
WRITE( stdout, '(5X,"Cannot read rho : file not found")' )
!
WRITE( UNIT = stdout, &
FMT = '(/5X,"Initial potential from superposition of free atoms")' )
!
! ... in the lda+U case set the initial value of ns
!
CALL atomic_rho( rho%of_r, nspin )
IF ( lda_plus_u ) CALL init_ns()
!
IF ( input_drho /= ' ' ) THEN
!
IF ( nspin > 1 ) CALL errore &
( 'potinit', 'spin polarization not allowed in drho', 1 )
!
CALL read_rho ( v%of_r, 1, input_drho )
!
WRITE( UNIT = stdout, &
FMT = '(/5X,"a scf correction to at. rho is read from",A)' ) &
TRIM( input_drho )
!
rho%of_r = rho%of_r + v%of_r
!
END IF
!
END IF
!
! ... check the integral of the starting charge
!
IF ( nspin == 2 ) THEN
!
charge = SUM ( rho%of_r(:,1:nspin) )*omega / ( nr1*nr2*nr3 )
!
ELSE
!
charge = SUM ( rho%of_r(:,1) )*omega / ( nr1*nr2*nr3 )
!
END IF
!
CALL reduce( 1, charge )
!
IF ( lscf .AND. ABS( charge - nelec ) / charge > 1.D-7 ) THEN
!
WRITE( stdout, &
'(/,5X,"starting charge ",F10.5,", renormalised to ",F10.5)') &
charge, nelec
!
IF (nat>0) THEN
rho%of_r = rho%of_r / charge * nelec
ELSE
rho%of_r = nelec / omega
ENDIF
!
ELSE IF ( .NOT. lscf .AND. ABS( charge - nelec ) / charge > 1.D-3 ) THEN
!
CALL errore( 'potinit', 'starting and expected charges differ', 1 )
!
END IF
!
! ... bring starting rho to G-space
!
DO is = 1, nspin
!
psic(:) = rho%of_r(:,is)
!
CALL cft3( psic, nr1, nr2, nr3, nrx1, nrx2, nrx3, -1 )
!
rho%of_g(:,is) = psic(nl(:))
!
END DO
!
if ( dft_is_meta()) then
! ... define a starting (TF) guess for rho%kin_r and rho%kin_g
fact = (3.d0*pi*pi)**(2.0/3.0)
DO is = 1, nspin
rho%kin_r(:,is) = fact * abs(rho%of_r(:,is)*nspin)**(5.0/3.0)/nspin
psic(:) = rho%kin_r(:,is)
CALL cft3( psic, nr1, nr2, nr3, nrx1, nrx2, nrx3, -1 )
rho%kin_g(:,is) = psic(nl(:))
END DO
!
end if
!
! ... compute the potential and store it in vr
!
CALL v_of_rho( rho, rho_core, rhog_core, &
ehart, etxc, vtxc, eth, etotefield, charge, v )
!
! ... define the total local potential (external+scf)
!
CALL set_vrs( vrs, vltot, v%of_r, kedtau, v%kin_r, nrxx, nspin, doublegrid )
!
! ... write on output the parameters used in the lda+U calculation
!
IF ( lda_plus_u ) THEN
!
WRITE( stdout, '(/5X,"Parameters of the lda+U calculation:")')
WRITE( stdout, '(5X,"Number of iteration with fixed ns =",I3)') &
niter_with_fixed_ns
WRITE( stdout, '(5X,"Starting ns and Hubbard U :")')
!
CALL write_ns()
!
END IF
!
IF ( report /= 0 .AND. &
noncolin .AND. domag .AND. lscf ) CALL report_mag()
!
SCF with Projector-Augmented Wave Pseudopotential (PAW) routines added. This means that a lot of routines have been modified and a few files have been added. During the year several people have contributed to this code, mainly Guido Fratesi, Ricardo Mazzarello, Stefano de Gironcoli, Andrea Dal Corso and me (Lorenzo Paulatto). A brief report of modified or added files follows, further down you will find a loger report of modifications that was necessary to merge develop_PAW branch with the current CVS version. Current version is not 100% functional, but it doesn't brake anything else and can be used to generate and test PAW pseudopotential. ************************************* *** Brief report of modifications *** ************************************* Modified files: PW/clean_pw.f90 PW/electrons.f90 PW/print_clock_pw.f90 PW/hinit0.f90 PW/potinit.f90 PW/newd.f90 PW/summary.f90 PW/setup.f90 PW/read_pseudo.f90 PW/init_us_1.f90 PW/init_run.f90 PW/mix_rho.f90 atomic/atomic_paw.f90 atomic/write_paw_recon.f90 atomic/ld1_writeout.f90 atomic/write_resultsps.f90 atomic/ld1inc.f90 atomic/ld1_readin.f90 atomic/gener_pseudo.f90 atomic/parameters.f900 atomic/run_pseudo.f900 atomic/set_rho_core.f90 atomic/pseudovloc.f90 Modules/read_upf.f90 Modules/uspp.f90 Modules/pseudo_types.f90 Modules/parameters.f90 Added files: PW/grid_paw_routines.f90 PW/rad_paw_routines.f90 Modules/grid_paw_variables.f90 Modules/read_paw.f90 Added files that will be removed: PW/rad_paw_trash.f90 PW/paw_xc.f90 Examples: examples/PAWexample contains a full test of PAW pseudopotential for Oxygen. The test consist in these tasks: - 2 norm conserving, 2 US and 4 PAW pseudopotentials are generated and tested in ld1 - pw test for an isolated O atom at different cutoffs - pw test for an O2 molecule at different O-O distance please read examples/PAWexample/README for (a few) details. NOTES: 1. new modifications to atomic_paw (and related) from ADC have been rolled back, as they were breaking a lot of things, I will reintroduce them later when I am sure that everything works properly. 2. the files PW/paw_xc.f90 and Modules/rad_paw_trash.f90 will be removed in the next few weeks. TODO: 1. use new ld1 XC code as much as possible, and remove legacy XC routines from rad_paw_routines 2. full self-consistency with radial energies 3. make new Harris-Foulkes estimate paw-aware 4. provide some kind error estimate 5. FORCES and stress!! (require symmetrization of becsums) 6. cleanup ************************ *** merge of PW code *** ************************ Versions notation: OLD=version from 2 years ago used as reference to generate the patches NEW=CURRENT=current trunk version PAW=current develop_PAW version Note: pseudo-potential input and allocation routines changed a lot in the last years, this is a diagram: OLD:PW/readin ~~> PAW:PW/read_pseudo --> disappears pops out --> PAW:PW/readin ~~> NEW:PW/read_pseudo added files: Modules/read_paw.f90 (contains module read_paw_module with subroutines paw_io nullify_pseudo_paw, allocate_pseudo_paw and deallocate_pseudo_paw previously in removed file Modules/readpseudo.f90. Also contains module paw_to_internal with subroutine set_pseudo_paw, previously in upf_to_internal.f90) PW/paw_xc.f90 (contains OLD=PAW xc and gcxc routines as adapting paw grid code to use new routines was very error prone and quite worthless, as it has to be removed anyway) Conflicts reported by CVS during merge: DONE */Makefiles (all replaced with new, redone by hand) DONE flib/functionals.f90 (nothing to do) DONE Modules/functionals.f90 (RNV == replaced with NEW version) DONE Modules/atom.f90 (trivial: duped rgrid) DONE Modules/autopilot.f90 (trivial) DONE Modules/bfgs_module.f90 (RNV) DONE Modules/cell_base.f90 (RNV) DONE Modules/check_stop.f90 (RNV) DONE Modules/constants.f90 (RNV) DONE Modules/constraints_module.f90 (RNV) DONE Modules/energies.f90 (RNV) DONE Modules/input_parameters.f90 (RNV) DONE Modules/ions_base.f90 (RNV, has 3 new subs) DONE Modules/ions_nose.f90 (RNV) DONE Modules/parameters.f90 (actually RNV) DONE Modules/path_base.f90 (RNV) DONE Modules/path_opt_routines.f90 (RNV) DONE Modules/path_reparametrisation.f90 (RNV) DONE Modules/path_variables.f90 (RNV) DONE Modules/pseudo_types.f90 (cleaned double def of paw_t) DONE Modules/read_cards.f90 (RNV) DONE Modules/read_namelists.f90 (checked and RNV) DONE Modules/uspp.f90 (trivial) DONE Modules/xml_io_base.f90 (RNV) DONE PW/read_pseudo.f90 (merged by hand with PAW PW/readin) DONE PW/bp_calc_btq.f90 (trivial) DONE PW/c_bands.f90 (actually RNV) DONE PW/ccgdiagg.f90 (RNV) DONE PW/cegterg.f90 (RNV) DONE PW/cft3s.f90 (RNV) DONE PW/cinitcgg.f90 (RNV) DONE PW/c_phase_field.f90 (RNV) DONE PW/divide_et_impera.f90 (nothing to do?) DONE PW/exx.f90 (RNV) DONE PW/hinit0.f90 (easy) DONE PW/h_psi.f90 (RNV) DONE PW/init_run.f90 (easy) DONE PW/kpoint_grid.f90 (nothing to do?) DONE PW/newd.f90 (required mod in newd_paw_grid, CHECK!!) DONE PW/openfil.f90 (actually RNV) DONE PW/paw.f90 (actually RNV) DONE PW/punch.f90 (RNV) DONE PW/pwscf.f90 (quite RNV) DONE PW/set_kup_and_kdw.f90 (RNV) DONE PW/setup.f90 (RNV + 2 line merged by hand) DONE PW/sgama.f9 (actually RNV) DONE PW/sgam_at_mag.f90 (actually RNV) DONE PW/stop_run.f90 (actually RNV) DONE PW/stres_gradcorr.f90 (actually RNV) DONE PW/symrho_mag.f90 (nothing to do) DONE PW/v_of_rho.f90 (RNV) DONE PW/compute_fes_grads.f90 (RNV) DONE PW/gradcorr.f90 (RNV) DONE PW/input.f90 (RNV) DONE PW/pw_restart.f90 (RNV) DONE PW/read_ncpp.f90 (actually RNV) DONE PW/summary.f90 (RNV + inserted new PP type) DONE PW/wfcinit.f90 (RNV) the hard ones: DONE PW/electrons.f90 (adapted code to new syntaxes, a lot of cleanup, removed some PAW junk that can be readded later, removed parts that were applyed twice, or had been removed in trunk, the rhog allocations and usage may need fixes) DONE PW/mix_rho.f90 (merged tauk and paw additions, a bit of cleanup and smarter variables names) DONE PW/init_us_1.f90 (qtot redefined with "triangular" index nb,mb-->ijv) modified for compiling: Modules/io_files.f90 (depatched) PW/pwcom.f90 (depatched) Modules/parameters.f90 (temporary readded cp_lmax = lmaxx+1) PW/newd.f90 (merge was wrong, redone mostly by hand) PW/read_ncpp.f90 (depatched) PW/read_pseudo (small fixes) PW/sgam_at_mag.f90 (depatched) PW/sgama.f90 (depatched) PW/stres_gradcorr.f90 (depatched) modified for running: PW/clean_pw.f90 (added call to deallocate_paw_internals) Modifications to PAW routines: 1. compute_onecenter_charges and compute_onecenter_charges modified to comply with new structure of v_xc (in v_of_rho.f90), requiring new g-space densities to be saved and computed --> using old xc routines as this code will be removed. 2. qrad size has changed, prad and ptrad had to be changed accordingly. 3. several minor modifications to use new radial grid structure. 4. infomsg arguments changed, very funny bug followed. 5. added new routine deallocate_paw_internals, called by PW/clean_pw.f90 required to run pp.x with more than one q-point(and good programming practice) ************************* *** merge of LD1 code *** ************************* 2nd try: atomic code replaced with current version, then merge by hand the files that are used by paw subsystem: * atomic_paw.f90 (replaced with most recent version from develop_PAW routine us2paw and paw2us taken from newer trunk version, a lot of minor changes.) * gener_pseudo.f90 (fixes) * ld1inc.f90 (PAW variables added) * ld1_readin.f90 (PAW variables added, I am not sure if lpaw should go in input or inputp namelist) * ld1_writeout.f90 (it was only necessary to add a few lines) * pseudovloc.f90 (nothing to do) * run_pseudo.f90 (almost nothing to do) * set_rho_core.f90 (readded a few lines for lnc2paw) * write_paw_recon.f90 (nothing to do) * write_resultsps.f90 (nothing to do: trunk version is more PAW-aware than PAW version) Main problems were found in subroutines run_pseudo and gen_pseudo, a little code had to be rewritten to comply with new variable names and fix with merge. TODO: fix atomic_paw routines to use minimal allocated arrays insetad of ndmx sized ones; try to use the pawet as much as possible. Remove test lines and other garbage. Find a fix for PAW2. The first week of september Andrea Dal Corso uploaded a few modifications to the atomic_paw routines. I had to rollback them as the structure of atomic_paw has changed a lot and reimplementing them is probably easier and definitely safer than fixing everything. I will do it soon, I swear! LP git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@4257 c92efa57-630b-4861-b058-cf58834340f0
2007-09-18 18:05:46 +08:00
! ... PAW initialization: from atomic augmentation channel occupations
! ... compute corresponding one-center charges and potentials
!
IF ( okpaw ) THEN
CALL PAW_init_becsum()
CALL PAW_potential(becsum)
ENDIF
SCF with Projector-Augmented Wave Pseudopotential (PAW) routines added. This means that a lot of routines have been modified and a few files have been added. During the year several people have contributed to this code, mainly Guido Fratesi, Ricardo Mazzarello, Stefano de Gironcoli, Andrea Dal Corso and me (Lorenzo Paulatto). A brief report of modified or added files follows, further down you will find a loger report of modifications that was necessary to merge develop_PAW branch with the current CVS version. Current version is not 100% functional, but it doesn't brake anything else and can be used to generate and test PAW pseudopotential. ************************************* *** Brief report of modifications *** ************************************* Modified files: PW/clean_pw.f90 PW/electrons.f90 PW/print_clock_pw.f90 PW/hinit0.f90 PW/potinit.f90 PW/newd.f90 PW/summary.f90 PW/setup.f90 PW/read_pseudo.f90 PW/init_us_1.f90 PW/init_run.f90 PW/mix_rho.f90 atomic/atomic_paw.f90 atomic/write_paw_recon.f90 atomic/ld1_writeout.f90 atomic/write_resultsps.f90 atomic/ld1inc.f90 atomic/ld1_readin.f90 atomic/gener_pseudo.f90 atomic/parameters.f900 atomic/run_pseudo.f900 atomic/set_rho_core.f90 atomic/pseudovloc.f90 Modules/read_upf.f90 Modules/uspp.f90 Modules/pseudo_types.f90 Modules/parameters.f90 Added files: PW/grid_paw_routines.f90 PW/rad_paw_routines.f90 Modules/grid_paw_variables.f90 Modules/read_paw.f90 Added files that will be removed: PW/rad_paw_trash.f90 PW/paw_xc.f90 Examples: examples/PAWexample contains a full test of PAW pseudopotential for Oxygen. The test consist in these tasks: - 2 norm conserving, 2 US and 4 PAW pseudopotentials are generated and tested in ld1 - pw test for an isolated O atom at different cutoffs - pw test for an O2 molecule at different O-O distance please read examples/PAWexample/README for (a few) details. NOTES: 1. new modifications to atomic_paw (and related) from ADC have been rolled back, as they were breaking a lot of things, I will reintroduce them later when I am sure that everything works properly. 2. the files PW/paw_xc.f90 and Modules/rad_paw_trash.f90 will be removed in the next few weeks. TODO: 1. use new ld1 XC code as much as possible, and remove legacy XC routines from rad_paw_routines 2. full self-consistency with radial energies 3. make new Harris-Foulkes estimate paw-aware 4. provide some kind error estimate 5. FORCES and stress!! (require symmetrization of becsums) 6. cleanup ************************ *** merge of PW code *** ************************ Versions notation: OLD=version from 2 years ago used as reference to generate the patches NEW=CURRENT=current trunk version PAW=current develop_PAW version Note: pseudo-potential input and allocation routines changed a lot in the last years, this is a diagram: OLD:PW/readin ~~> PAW:PW/read_pseudo --> disappears pops out --> PAW:PW/readin ~~> NEW:PW/read_pseudo added files: Modules/read_paw.f90 (contains module read_paw_module with subroutines paw_io nullify_pseudo_paw, allocate_pseudo_paw and deallocate_pseudo_paw previously in removed file Modules/readpseudo.f90. Also contains module paw_to_internal with subroutine set_pseudo_paw, previously in upf_to_internal.f90) PW/paw_xc.f90 (contains OLD=PAW xc and gcxc routines as adapting paw grid code to use new routines was very error prone and quite worthless, as it has to be removed anyway) Conflicts reported by CVS during merge: DONE */Makefiles (all replaced with new, redone by hand) DONE flib/functionals.f90 (nothing to do) DONE Modules/functionals.f90 (RNV == replaced with NEW version) DONE Modules/atom.f90 (trivial: duped rgrid) DONE Modules/autopilot.f90 (trivial) DONE Modules/bfgs_module.f90 (RNV) DONE Modules/cell_base.f90 (RNV) DONE Modules/check_stop.f90 (RNV) DONE Modules/constants.f90 (RNV) DONE Modules/constraints_module.f90 (RNV) DONE Modules/energies.f90 (RNV) DONE Modules/input_parameters.f90 (RNV) DONE Modules/ions_base.f90 (RNV, has 3 new subs) DONE Modules/ions_nose.f90 (RNV) DONE Modules/parameters.f90 (actually RNV) DONE Modules/path_base.f90 (RNV) DONE Modules/path_opt_routines.f90 (RNV) DONE Modules/path_reparametrisation.f90 (RNV) DONE Modules/path_variables.f90 (RNV) DONE Modules/pseudo_types.f90 (cleaned double def of paw_t) DONE Modules/read_cards.f90 (RNV) DONE Modules/read_namelists.f90 (checked and RNV) DONE Modules/uspp.f90 (trivial) DONE Modules/xml_io_base.f90 (RNV) DONE PW/read_pseudo.f90 (merged by hand with PAW PW/readin) DONE PW/bp_calc_btq.f90 (trivial) DONE PW/c_bands.f90 (actually RNV) DONE PW/ccgdiagg.f90 (RNV) DONE PW/cegterg.f90 (RNV) DONE PW/cft3s.f90 (RNV) DONE PW/cinitcgg.f90 (RNV) DONE PW/c_phase_field.f90 (RNV) DONE PW/divide_et_impera.f90 (nothing to do?) DONE PW/exx.f90 (RNV) DONE PW/hinit0.f90 (easy) DONE PW/h_psi.f90 (RNV) DONE PW/init_run.f90 (easy) DONE PW/kpoint_grid.f90 (nothing to do?) DONE PW/newd.f90 (required mod in newd_paw_grid, CHECK!!) DONE PW/openfil.f90 (actually RNV) DONE PW/paw.f90 (actually RNV) DONE PW/punch.f90 (RNV) DONE PW/pwscf.f90 (quite RNV) DONE PW/set_kup_and_kdw.f90 (RNV) DONE PW/setup.f90 (RNV + 2 line merged by hand) DONE PW/sgama.f9 (actually RNV) DONE PW/sgam_at_mag.f90 (actually RNV) DONE PW/stop_run.f90 (actually RNV) DONE PW/stres_gradcorr.f90 (actually RNV) DONE PW/symrho_mag.f90 (nothing to do) DONE PW/v_of_rho.f90 (RNV) DONE PW/compute_fes_grads.f90 (RNV) DONE PW/gradcorr.f90 (RNV) DONE PW/input.f90 (RNV) DONE PW/pw_restart.f90 (RNV) DONE PW/read_ncpp.f90 (actually RNV) DONE PW/summary.f90 (RNV + inserted new PP type) DONE PW/wfcinit.f90 (RNV) the hard ones: DONE PW/electrons.f90 (adapted code to new syntaxes, a lot of cleanup, removed some PAW junk that can be readded later, removed parts that were applyed twice, or had been removed in trunk, the rhog allocations and usage may need fixes) DONE PW/mix_rho.f90 (merged tauk and paw additions, a bit of cleanup and smarter variables names) DONE PW/init_us_1.f90 (qtot redefined with "triangular" index nb,mb-->ijv) modified for compiling: Modules/io_files.f90 (depatched) PW/pwcom.f90 (depatched) Modules/parameters.f90 (temporary readded cp_lmax = lmaxx+1) PW/newd.f90 (merge was wrong, redone mostly by hand) PW/read_ncpp.f90 (depatched) PW/read_pseudo (small fixes) PW/sgam_at_mag.f90 (depatched) PW/sgama.f90 (depatched) PW/stres_gradcorr.f90 (depatched) modified for running: PW/clean_pw.f90 (added call to deallocate_paw_internals) Modifications to PAW routines: 1. compute_onecenter_charges and compute_onecenter_charges modified to comply with new structure of v_xc (in v_of_rho.f90), requiring new g-space densities to be saved and computed --> using old xc routines as this code will be removed. 2. qrad size has changed, prad and ptrad had to be changed accordingly. 3. several minor modifications to use new radial grid structure. 4. infomsg arguments changed, very funny bug followed. 5. added new routine deallocate_paw_internals, called by PW/clean_pw.f90 required to run pp.x with more than one q-point(and good programming practice) ************************* *** merge of LD1 code *** ************************* 2nd try: atomic code replaced with current version, then merge by hand the files that are used by paw subsystem: * atomic_paw.f90 (replaced with most recent version from develop_PAW routine us2paw and paw2us taken from newer trunk version, a lot of minor changes.) * gener_pseudo.f90 (fixes) * ld1inc.f90 (PAW variables added) * ld1_readin.f90 (PAW variables added, I am not sure if lpaw should go in input or inputp namelist) * ld1_writeout.f90 (it was only necessary to add a few lines) * pseudovloc.f90 (nothing to do) * run_pseudo.f90 (almost nothing to do) * set_rho_core.f90 (readded a few lines for lnc2paw) * write_paw_recon.f90 (nothing to do) * write_resultsps.f90 (nothing to do: trunk version is more PAW-aware than PAW version) Main problems were found in subroutines run_pseudo and gen_pseudo, a little code had to be rewritten to comply with new variable names and fix with merge. TODO: fix atomic_paw routines to use minimal allocated arrays insetad of ndmx sized ones; try to use the pawet as much as possible. Remove test lines and other garbage. Find a fix for PAW2. The first week of september Andrea Dal Corso uploaded a few modifications to the atomic_paw routines. I had to rollback them as the structure of atomic_paw has changed a lot and reimplementing them is probably easier and definitely safer than fixing everything. I will do it soon, I swear! LP git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@4257 c92efa57-630b-4861-b058-cf58834340f0
2007-09-18 18:05:46 +08:00
!
CALL stop_clock('potinit')
!
RETURN
!
END SUBROUTINE potinit