Skip to content

Commit

Permalink
Changes to init_us_1
Browse files Browse the repository at this point in the history
  • Loading branch information
dceresoli committed Feb 6, 2024
1 parent fbf75e9 commit feff95f
Show file tree
Hide file tree
Showing 2 changed files with 7 additions and 4 deletions.
9 changes: 6 additions & 3 deletions src/gipaw_setup.f90
Original file line number Diff line number Diff line change
Expand Up @@ -17,10 +17,11 @@ SUBROUTINE gipaw_setup
USE wvfct, ONLY : nbnd, et, wg
USE lsda_mod, ONLY : nspin
USE scf, ONLY : v, vrs, vltot, kedtau, rho
USE cellmd, ONLY : cell_factor
USE fft_base, ONLY : dfftp
USE gvecs, ONLY : doublegrid
USE gvect, ONLY : ecutrho, ngm, g, gg, eigts1, eigts2, eigts3
USE klist, ONLY : degauss, ngauss, nks, lgauss, wk, two_fermi_energies, ltetra
USE klist, ONLY : degauss, ngauss, nks, lgauss, wk, two_fermi_energies, ltetra, qnorm
USE ions_base, ONLY : nat, nsp, ityp, tau
USE noncollin_module, ONLY : noncolin
USE constants, ONLY : degspin, pi
Expand All @@ -36,7 +37,7 @@ SUBROUTINE gipaw_setup

implicit none
integer :: ik, ibnd
real(dp) :: emin, emax, xmax, small, fac, target
real(dp) :: emin, emax, xmax, small, fac, target, qmax


call start_clock ('gipaw_setup')
Expand All @@ -46,7 +47,9 @@ SUBROUTINE gipaw_setup
! call test_symmetries ( s, nsym )

! initialize pseudopotentials and projectors for LDA+U
call init_us_1(nat, ityp, omega, ngm, g, gg, intra_bgrp_comm)
cell_factor = 1.2
qmax = (qnorm + sqrt(ecutrho))*cell_factor
call init_us_1(nat, ityp, omega, qmax, intra_bgrp_comm)
call init_tab_atwfc(omega, intra_bgrp_comm)

call plugin_initbase()
Expand Down
2 changes: 1 addition & 1 deletion src/gipaw_version.f90
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,6 @@ MODULE gipaw_version
!
SAVE
!
CHARACTER (LEN=40) :: gipaw_git_revision = "75b01b694c9ba4df55d294cacc27cf28591b2161"
CHARACTER (LEN=40) :: gipaw_git_revision = "fbf75e9b8c8f0314042fb39ad7a0982f3503ae81"
!
END MODULE gipaw_version

0 comments on commit feff95f

Please sign in to comment.