References to upf_ions removed from init_*_1

This commit is contained in:
Paolo Giannozzi 2021-02-25 18:26:40 +00:00
parent 4b9f562bd7
commit 3b12e8a544
6 changed files with 15 additions and 14 deletions

View File

@ -244,7 +244,8 @@
!
qrad(:, :, :, :) = zero
! RM - need to call init_us_1 to re-calculate qrad
CALL init_us_1(omega,ngm,g,gg,intra_bgrp_comm)
! PG - maybe it would be preferable to call compute_qrad?
CALL init_us_1(nat, nsp, ityp, omega, ngm, g, gg, intra_bgrp_comm)
ENDIF
ENDIF
!

View File

@ -44,9 +44,9 @@ SUBROUTINE hinit0()
!
IF (tbeta_smoothing) CALL init_us_b0(ecutwfc,intra_bgrp_comm)
IF (tq_smoothing) CALL init_us_0(ecutrho,intra_bgrp_comm)
CALL init_us_1(omega,ngm,g,gg,intra_bgrp_comm)
CALL init_us_1(nat, nsp, ityp, omega, ngm, g, gg, intra_bgrp_comm)
IF ( lda_plus_U .AND. ( U_projection == 'pseudo' ) ) CALL init_q_aeps()
CALL init_at_1(omega,intra_bgrp_comm)
CALL init_at_1(nsp, omega, intra_bgrp_comm)
!
IF ( restart .AND. startingconfig == 'file' ) THEN
!

View File

@ -245,9 +245,9 @@ SUBROUTINE post_xml_init ( )
CALL init_vloc()
IF (tbeta_smoothing) CALL init_us_b0(ecutwfc,intra_bgrp_comm)
IF (tq_smoothing) CALL init_us_0(ecutrho,intra_bgrp_comm)
CALL init_us_1(omega,ngm,g,gg,intra_bgrp_comm)
CALL init_us_1(nat, nsp, ityp, omega, ngm, g, gg, intra_bgrp_comm)
IF ( lda_plus_U .AND. ( U_projection == 'pseudo' ) ) CALL init_q_aeps()
CALL init_at_1(omega,intra_bgrp_comm)
CALL init_at_1(nsp, omega, intra_bgrp_comm)
!
CALL struc_fact( nat, tau, nsp, ityp, ngm, g, bg, dfftp%nr1, dfftp%nr2,&
dfftp%nr3, strf, eigts1, eigts2, eigts3 )

View File

@ -7,7 +7,7 @@
!
!
!-----------------------------------------------------------------------
SUBROUTINE init_at_1(omega,intra_bgrp_comm)
SUBROUTINE init_at_1( ntyp, omega, intra_bgrp_comm)
!-----------------------------------------------------------------------
!! This routine computes a table with the radial Fourier transform
!! of the atomic wavefunctions.
@ -15,13 +15,13 @@ SUBROUTINE init_at_1(omega,intra_bgrp_comm)
USE upf_kinds, ONLY : DP
USE atom, ONLY : rgrid, msh
USE upf_const, ONLY : fpi
USE upf_ions, ONLY : ntyp => nsp
USE uspp_data, ONLY : tab_at, tab_at_d, nqx, dq
USE uspp_param, ONLY : upf
USE mp, ONLY : mp_sum
!
IMPLICIT NONE
!
INTEGER, INTENT(IN) :: ntyp
REAL(DP), INTENT(IN) :: omega
INTEGER, INTENT(IN) :: intra_bgrp_comm
!

View File

@ -7,7 +7,7 @@
!
!
!----------------------------------------------------------------------
subroutine init_us_1(omega,ngm,g,gg,intra_bgrp_comm)
subroutine init_us_1( nat, ntyp, ityp, omega, ngm, g, gg, intra_bgrp_comm )
!----------------------------------------------------------------------
!
! This routine performs the following tasks:
@ -28,7 +28,6 @@ subroutine init_us_1(omega,ngm,g,gg,intra_bgrp_comm)
USE upf_kinds, ONLY : DP
USE upf_const, ONLY : fpi, sqrt2
USE atom, ONLY : rgrid
USE upf_ions, ONLY : ntyp => nsp, ityp, nat
USE uspp_data, ONLY : nqxq, dq, nqx, spline_ps, tab, tab_d2y, qrad, &
tab_d, tab_d2y_d, qrad_d
USE uspp, ONLY : nhtol, nhtoj, nhtolm, ijtoh, dvan, qq_at, qq_nt, indv, &
@ -42,6 +41,9 @@ subroutine init_us_1(omega,ngm,g,gg,intra_bgrp_comm)
USE splinelib
implicit none
!
integer, intent(in) :: nat
integer, intent(in) :: ntyp
integer, intent(in) :: ityp(nat)
real(DP), intent(in) :: omega
integer, intent(in) :: ngm
real(DP), intent(in) :: g(3,ngm), gg(ngm)
@ -248,7 +250,7 @@ subroutine init_us_1(omega,ngm,g,gg,intra_bgrp_comm)
! here for the US types we compute the Fourier transform of the
! Q functions.
!
IF ( lmaxq > 0 ) CALL compute_qrad(omega,intra_bgrp_comm)
IF ( lmaxq > 0 ) CALL compute_qrad(ntyp, omega, intra_bgrp_comm)
!
! and finally we compute the qq coefficients by integrating the Q.
! The qq are the g=0 components of Q
@ -397,7 +399,7 @@ subroutine init_us_1(omega,ngm,g,gg,intra_bgrp_comm)
end subroutine init_us_1
!----------------------------------------------------------------------
SUBROUTINE compute_qrad (omega,intra_bgrp_comm)
SUBROUTINE compute_qrad (ntyp, omega, intra_bgrp_comm)
!----------------------------------------------------------------------
!
! Compute interpolation table qrad(i,nm,l+1,nt) = Q^{(L)}_{nm,nt}(q_i)
@ -406,7 +408,6 @@ SUBROUTINE compute_qrad (omega,intra_bgrp_comm)
!
USE upf_kinds, ONLY : dp
USE upf_const, ONLY : fpi
USE upf_ions, ONLY : ntyp => nsp
USE atom, ONLY : rgrid
USE uspp_param, ONLY : upf, lmaxq, nbetam, nh, nhm, lmaxkb
USE uspp_data, ONLY : nqxq, dq, qrad, qrad_d
@ -414,6 +415,7 @@ SUBROUTINE compute_qrad (omega,intra_bgrp_comm)
!
IMPLICIT NONE
!
integer, intent(in) :: ntyp
real(DP), intent(in) :: omega
integer, intent(in) :: intra_bgrp_comm
!

View File

@ -15,7 +15,6 @@ gth.o : upf_params.o
init_at_1.o : ../UtilXlib/mp.o
init_at_1.o : atom.o
init_at_1.o : upf_const.o
init_at_1.o : upf_ions.o
init_at_1.o : upf_kinds.o
init_at_1.o : uspp.o
init_at_1.o : uspp_data.o
@ -31,7 +30,6 @@ init_us_1.o : atom.o
init_us_1.o : paw_variables.o
init_us_1.o : splinelib.o
init_us_1.o : upf_const.o
init_us_1.o : upf_ions.o
init_us_1.o : upf_kinds.o
init_us_1.o : upf_spinorb.o
init_us_1.o : uspp.o