Module uspp and uspp_param split

This commit is contained in:
Paolo Giannozzi 2021-12-30 15:10:13 +01:00
parent 5ac335a001
commit 4d09608f85
4 changed files with 75 additions and 66 deletions

View File

@ -45,6 +45,7 @@ set(src_upflib
upf_utils.f90
uspp.f90
uspp_data.f90
uspp_param.f90
write_upf_new.f90
xmltools.f90
ylmr2.f90

View File

@ -57,6 +57,7 @@ upf_to_internal.o \
upf_utils.o \
uspp.o \
uspp_data.o \
uspp_param.o \
write_upf_new.o \
xmltools.o \
ylmr2.o

View File

@ -11,72 +11,6 @@
#else
#define PINMEM
#endif
MODULE uspp_param
!
! ... Ultrasoft and Norm-Conserving pseudopotential parameters
!
USE pseudo_types, ONLY : pseudo_upf
IMPLICIT NONE
SAVE
!
INTEGER :: nsp = 0
TYPE (pseudo_upf), ALLOCATABLE, TARGET :: upf(:)
!! the upf structure contains all info on atomic pseudopotential parameters
INTEGER, ALLOCATABLE :: nh(:)
!! number of beta functions, with angular parts, per atomic type
INTEGER :: nhm
!! max number of beta functions, including angular parts, across atoms
INTEGER :: nbetam
!! max number of radial beta functions
INTEGER :: nwfcm
!! max number of radial atomic wavefunctions across atoms
INTEGER :: lmaxkb
!! max angular momentum of beta functions
INTEGER :: lmaxq
!! max angular momentum + 1 for Q functions
!
CONTAINS
!
SUBROUTINE init_uspp_dims ()
!
!! calculates the number of beta functions for each atomic type
!
IMPLICIT NONE
!
INTEGER :: nt, nb
!
! Check is needed, may be called more than once (but it shouldn't be!)
! Maybe nh should be allocated when upf is, when upf is read ?
!
IF ( .NOT. ALLOCATED(nh) ) ALLOCATE ( nh(nsp) )
!
lmaxkb = - 1
DO nt = 1, nsp
!
nh (nt) = 0
!
! do not add any beta projector if pseudo in 1/r fmt (AF)
!
IF ( upf(nt)%tcoulombp ) CYCLE
!
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
lmaxq = 2*lmaxkb+1
!
! calculate max numbers of beta functions and of atomic wavefunctions
!
nhm = MAXVAL (nh (1:nsp))
nbetam = MAXVAL (upf(1:nsp)%nbeta)
nwfcm = MAXVAL (upf(1:nsp)%nwfc)
!
END SUBROUTINE init_uspp_dims
!
END MODULE uspp_param
!
!
MODULE uspp

73
upflib/uspp_param.f90 Normal file
View File

@ -0,0 +1,73 @@
!
! Copyright (C) 2004-2021 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 .
!
MODULE uspp_param
!
! ... Ultrasoft and Norm-Conserving pseudopotential parameters
!
USE pseudo_types, ONLY : pseudo_upf
IMPLICIT NONE
SAVE
!
INTEGER :: nsp = 0
TYPE (pseudo_upf), ALLOCATABLE, TARGET :: upf(:)
!! the upf structure contains all info on atomic pseudopotential parameters
INTEGER, ALLOCATABLE :: nh(:)
!! number of beta functions, with angular parts, per atomic type
INTEGER :: nhm
!! max number of beta functions, including angular parts, across atoms
INTEGER :: nbetam
!! max number of radial beta functions
INTEGER :: nwfcm
!! max number of radial atomic wavefunctions across atoms
INTEGER :: lmaxkb
!! max angular momentum of beta functions
INTEGER :: lmaxq
!! max angular momentum + 1 for Q functions
!
CONTAINS
!
SUBROUTINE init_uspp_dims ()
!
!! calculates the number of beta functions for each atomic type
!
IMPLICIT NONE
!
INTEGER :: nt, nb
!
! Check is needed, may be called more than once (but it shouldn't be!)
! Maybe nh should be allocated when upf is, when upf is read ?
!
IF ( .NOT. ALLOCATED(nh) ) ALLOCATE ( nh(nsp) )
!
lmaxkb = - 1
DO nt = 1, nsp
!
nh (nt) = 0
!
! do not add any beta projector if pseudo in 1/r fmt (AF)
!
IF ( upf(nt)%tcoulombp ) CYCLE
!
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
lmaxq = 2*lmaxkb+1
!
! calculate max numbers of beta functions and of atomic wavefunctions
!
nhm = MAXVAL (nh (1:nsp))
nbetam = MAXVAL (upf(1:nsp)%nbeta)
nwfcm = MAXVAL (upf(1:nsp)%nwfc)
!
END SUBROUTINE init_uspp_dims
!
END MODULE uspp_param