Moved nmr_macroscopic shape into the input

apsi


git-svn-id: http://qeforge.qe-forge.org/svn/q-e/trunk/espresso@3708 c92efa57-630b-4861-b058-cf58834340f0
This commit is contained in:
seitsonen 2007-01-24 09:51:33 +00:00
parent 17bb64fd14
commit c133bbd939
2 changed files with 26 additions and 27 deletions

View File

@ -16,10 +16,11 @@ SUBROUTINE compute_sigma_bare(chi_bare, sigma_bare)
USE gvect, ONLY : ngm, gstart, nr1, nr2, nr3, nrx1, nrx2, &
nrx3, nrxx, nl, nlm, g, gg, ecutwfc, gcutm
USE ions_base, ONLY : nat, tau, atm, ityp
USE io_global, ONLY : stdout
USE symme, ONLY : s, nsym, irt
USE io_global, ONLY : stdout
USE symme, ONLY : s, nsym, irt
USE pwcom
USE gipaw_module
USE gipaw_module, ONLY : use_nmr_macroscopic_shape, &
nmr_macroscopic_shape, b_ind
! Arguments
REAL(DP), INTENT(IN) :: chi_bare(3,3)
@ -27,16 +28,8 @@ SUBROUTINE compute_sigma_bare(chi_bare, sigma_bare)
! Local
integer :: na, ig
real(dp) :: macroscopic_shape(3,3)
real(dp) :: arg, tr_sigma
complex(dp) :: tmp_sigma(3,3)
macroscopic_shape(:,:) = 2.0_dp/3.0_dp
! like in paratec:
macroscopic_shape(:,:) = 0.0_dp
do na = 1, 3
macroscopic_shape(na,na) = 2.0_dp/3.0_dp
enddo
write(stdout,'(5X,''NMR chemical bare shifts in ppm:'')')
write(stdout,*)
@ -50,13 +43,13 @@ SUBROUTINE compute_sigma_bare(chi_bare, sigma_bare)
+ b_ind(ig,:,:) * cmplx(cos(arg),sin(arg))
enddo
#if 1
! this is the G = 0 term
if (gstart == 2) then
tmp_sigma(:,:) = tmp_sigma(:,:) &
- (4.0_dp*pi) * macroscopic_shape(:,:) * chi_bare(:,:) !*TMPTMPTMP
if ( use_nmr_macroscopic_shape ) then
! this is the G = 0 term
if (gstart == 2) then
tmp_sigma(:,:) = tmp_sigma(:,:) &
- (4.0_dp*pi) * nmr_macroscopic_shape(:,:) * chi_bare(:,:)
end if
end if
#endif
sigma_bare(:,:,na) = real(tmp_sigma(:,:))
enddo

View File

@ -22,37 +22,37 @@ MODULE gipaw_module
! speed of light in atomic units: c = 1/alpha
!REAL(DP), PARAMETER :: c = 137.03599911d0
! avogadro number
REAL(DP), PARAMETER :: avogadro = 6.022142e23_dp
! number of occupied bands at each k-point
INTEGER :: nbnd_occ(npk)
! alpha shift of the projector on the valence wfcs
REAL(DP) :: alpha_pv
! eigenvalues and eigenfunctions at k+q
COMPLEX(DP), ALLOCATABLE :: evq(:,:)
! induced current (bare term) and induced magnetic field
REAL(DP), ALLOCATABLE :: j_bare(:,:,:,:), b_ind_r(:,:,:)
! induced magnetic field in reciprocal space
COMPLEX(DP), ALLOCATABLE :: b_ind(:,:,:)
! convergence threshold for diagonalizationa and greenfunction
REAL(DP) :: conv_threshold
! q for the perturbation (in bohrradius^{-1})
REAL(DP) :: q_gipaw
! q for the EFG
REAL(DP) :: q_efg ( ntypx )
! verbosity
INTEGER :: iverbosity
! job: nmr, g_tensor, efg, hyperfine
CHARACTER(80) :: job
@ -62,6 +62,10 @@ MODULE gipaw_module
! for plotting the induced current and induced field
CHARACTER(80) :: filcurr, filfield
! macroscopic shape for the NMR
LOGICAL :: use_nmr_macroscopic_shape
REAL(DP) :: nmr_macroscopic_shape ( 3, 3 )
!<apsi>
CHARACTER(256) :: file_reconstruction ( ntypx )
LOGICAL :: read_recon_in_paratec_fmt
@ -104,7 +108,8 @@ CONTAINS
NAMELIST /inputgipaw/ job, prefix, tmp_dir, conv_threshold, &
q_gipaw, iverbosity, filcurr, filfield, &
read_recon_in_paratec_fmt, &
file_reconstruction
file_reconstruction, use_nmr_macroscopic_shape, &
nmr_macroscopic_shape
if ( .not. ionode ) goto 400
@ -118,6 +123,7 @@ CONTAINS
filfield = ''
read_recon_in_paratec_fmt = .FALSE.
file_reconstruction ( : ) = " "
nmr_macroscopic_shape = 2.0_dp / 3.0_dp
read( 5, inputgipaw, err = 200, iostat = ios )