Skip to content

Commit

Permalink
redo the zpsp syntax
Browse files Browse the repository at this point in the history
  • Loading branch information
aoterodelaroza committed Feb 15, 2024
1 parent 2c21b2a commit fc7fd8e
Show file tree
Hide file tree
Showing 22 changed files with 67 additions and 118 deletions.
2 changes: 0 additions & 2 deletions src/crystalmod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -124,8 +124,6 @@ module crystalmod
real*8, allocatable :: ws_x(:,:) !< vertices of the WS cell (cryst. coords.)
logical :: isortho !< is the cell orthogonal?
logical :: isortho_del !< is the reduced cell orthogonal?
! core charges
integer :: zpsp(maxzat0)

! atomic environment of the cell
integer :: nblock(3) ! number of environemt blocks
Expand Down
3 changes: 0 additions & 3 deletions src/[email protected]
Original file line number Diff line number Diff line change
Expand Up @@ -101,9 +101,6 @@ module subroutine struct_init(c)
! no 3d molecular crystals
c%ismol3d = .false.

! core charges
c%zpsp = -1

! the crystal is not initialized until struct_new is run
c%file = ""
c%isinit = .false.
Expand Down
13 changes: 3 additions & 10 deletions src/[email protected]
Original file line number Diff line number Diff line change
Expand Up @@ -117,21 +117,14 @@ module subroutine struct_report(c,lcrys,lq)
if (lq) then
write (uout,'("+ List of atomic species: ")')
write (uout,'("# spc = atomic species. Z = atomic number. name = atomic name (symbol).")')
write (uout,'("# Q = charge. ZPSP = pseudopotential charge.")')
write (uout,'("# Q = charge.")')
write (uout,'("# ",99(A," "))') string("spc",3,ioj_center), &
string("Z",3,ioj_center), string("name",7,ioj_center),&
string("Q",length=7,justify=ioj_center),&
string("ZPSP",length=4,justify=ioj_right)
string("Q",length=7,justify=ioj_center)
do i = 1, c%nspc
str1 = " -- "
if (c%spc(i)%z > 0) then
if (c%zpsp(c%spc(i)%z) > 0) &
str1 = string(c%zpsp(c%spc(i)%z))
end if
write (uout,'(" ",99(A," "))') string(i,3,ioj_center), &
string(c%spc(i)%z,3,ioj_center), string(c%spc(i)%name,7,ioj_center),&
string(c%spc(i)%qat,'f',length=7,decimal=4,justify=ioj_right),&
str1
string(c%spc(i)%qat,'f',length=7,decimal=4,justify=ioj_right)
end do
write (uout,*)
end if
Expand Down
22 changes: 10 additions & 12 deletions src/[email protected]
Original file line number Diff line number Diff line change
Expand Up @@ -179,14 +179,13 @@ module subroutine field_set_options(ff,line,errmsg)
if (allocated(ff%wien%slm)) &
ff%wien%slm(:,1,:) = ff%wien%slm(:,1,:) * sqfp
end if
else if (equal(word,'core')) then
ff%usecore = .true.
else if (equal(word,'nocore')) then
ff%usecore = .false.
else if (equal(word,'numerical')) then
ff%numerical = .true.
else if (equal(word,'analytical')) then
ff%numerical = .false.
else if (equal(word,'nocore')) then
ff%usecore = .false.
ff%zpsp = -1
else if (equal(word,'typnuc')) then
ok = eval_next(ff%typnuc,line,lp)
if (.not.ok) then
Expand All @@ -210,6 +209,7 @@ module subroutine field_set_options(ff,line,errmsg)
end if
call ff%grid%normalize(norm,ff%c%omega)
else if (equal(word,'zpsp')) then
ff%usecore = .true.
do while (.true.)
lp2 = lp
word2 = getword(line,lp)
Expand Down Expand Up @@ -291,7 +291,7 @@ module subroutine field_new(f,seed,c,id,sptr,errmsg,ti)
f%name = adjustl(trim(seed%fid))

! inherit the pseudopotential charges from the crystal
f%zpsp = c%zpsp
f%zpsp = -1

! set the default field flags
call f%set_default_options()
Expand Down Expand Up @@ -481,7 +481,8 @@ module subroutine field_new(f,seed,c,id,sptr,errmsg,ti)
f%name = "<generated>, promolecular grid"
end if
else
call c%promolecular_grid(f%grid,seed%n,zpsp=c%zpsp)
call f%set_options(seed%elseopt,errmsg) ! I need the zpsp now
call c%promolecular_grid(f%grid,seed%n,zpsp=f%zpsp)
f%name = "<generated>, core grid"
end if
f%type = type_grid
Expand Down Expand Up @@ -573,12 +574,11 @@ module subroutine load_ghost(f,c,id,name,expr,sptr)
f%id = id
f%isinit = .true.
f%type = type_ghost
f%usecore = .false.
f%numerical = .true.
f%exact = .false.
f%name = adjustl(name)
f%file = ""
f%zpsp = c%zpsp
f%zpsp = -1
f%expr = expr
f%sptr = sptr
call f%init_cplist()
Expand Down Expand Up @@ -607,13 +607,12 @@ module subroutine load_promolecular(f,c,id,name,fr)
else
f%type = type_promol
end if
f%usecore = .false.
f%numerical = .false.
f%exact = .false.
f%name = adjustl(name)
f%file = ""
f%typnuc = -3
f%zpsp = c%zpsp
f%zpsp = -1
call f%init_cplist()

end subroutine load_promolecular
Expand Down Expand Up @@ -671,13 +670,12 @@ module subroutine load_as_fftgrid(f,c,id,name,g,ityp,isry_,n)
elseif (ityp == ifformat_as_resample) then
call f%grid%resample(g,n)
end if
f%usecore = .false.
f%numerical = .false.
f%exact = .false.
f%name = adjustl(name)
f%file = ""
f%typnuc = -3
f%zpsp = c%zpsp
f%zpsp = -1
call f%init_cplist()

end subroutine load_as_fftgrid
Expand Down
2 changes: 1 addition & 1 deletion src/[email protected]
Original file line number Diff line number Diff line change
Expand Up @@ -134,7 +134,7 @@ module subroutine critic_main()
end if

! q/qat, zpsp, nocore
elseif (equal(word,'q') .or. equal(word,'qat') .or. equal(word,'zpsp') .or. equal(word,'nocore')) then
elseif (equal(word,'q') .or. equal(word,'qat')) then
call check_structure_defined(ok)
if (.not.ok) cycle
call struct_charges(sy,line,ok)
Expand Down
8 changes: 0 additions & 8 deletions src/[email protected]
Original file line number Diff line number Diff line change
Expand Up @@ -2675,15 +2675,7 @@ subroutine calc_di3_wannier(res,nmo,nbnd,nlat,nattr,nspin,atom1,atom2)
end do ! iat_b
end do ! iat_a

! xxxx !
! if (imo == kmo) then
! fac = 1d0
! else
! fac = 2d0
! end if

!$omp critical (addfa)
! res%fa3(:,:,:,:,:,is) = res%fa3(:,:,:,:,:,is) + fac * f3temp
res%fa3(:,:,:,:,:,is) = res%fa3(:,:,:,:,:,is) + f3temp
!$omp end critical (addfa)
end do ! kmo
Expand Down
49 changes: 9 additions & 40 deletions src/[email protected]
Original file line number Diff line number Diff line change
Expand Up @@ -470,67 +470,36 @@ module subroutine struct_charges(s,line,oksyn)
logical, intent(out) :: oksyn

character(len=:), allocatable :: word
integer :: lp, nn, i, j, zpsp0(maxzat0)
integer :: lp, nn, i, j
logical :: ok, do1
real*8 :: xx

oksyn = .false.
lp = 1
word = lgetword(line,lp)
zpsp0 = -2
if (equal(word,'q') .or. equal(word,'zpsp') .or. equal(word,'qat')) then
do1 = equal(word,'zpsp')
if (equal(word,'q') .or. equal(word,'qat')) then
do while (.true.)
word = getword(line,lp)
if (len_trim(word) < 1) exit
nn = zatguess(word)
if (nn == -1) then
call ferror('struct_charges','Unknown atomic symbol in Q/QAT/ZPSP',faterr,line,syntax=.true.)
call ferror('struct_charges','Unknown atomic symbol in Q/QAT',faterr,line,syntax=.true.)
return
end if
ok = eval_next(xx,line,lp)
if (.not.ok) then
call ferror('struct_charges','Incorrect Q/QAT/ZPSP syntax',faterr,line,syntax=.true.)
call ferror('struct_charges','Incorrect Q/QAT syntax',faterr,line,syntax=.true.)
return
end if
if (.not.do1) then
do i = 1, s%c%nspc
if (s%c%spc(i)%z == nn) &
s%c%spc(i)%qat = xx
end do
else
zpsp0(nn) = nint(xx)
if (nn > 0 .and. zpsp0(nn) > 0) &
call grid1_register_core(nn,zpsp0(nn))
end if
do i = 1, s%c%nspc
if (s%c%spc(i)%z == nn) &
s%c%spc(i)%qat = xx
end do
end do
elseif (equal(word,'nocore')) then
zpsp0 = -1
word = getword(line,lp)
if (len_trim(word) > 0) then
call ferror('critic','Unknown extra keyword',faterr,line,syntax=.true.)
return
end if
endif
oksyn = .true.

! fill the crystal zpsp
do j = 1, maxzat0
if (zpsp0(j) /= -2) &
s%c%zpsp(j) = zpsp0(j)
end do

! fill the current fields zpsp
do i = 1, s%nf
if (s%f(i)%isinit) then
do j = 1, maxzat0
if (zpsp0(j) /= -2) &
s%f(i)%zpsp(j) = zpsp0(j)
end do
end if
end do

! report the charges and zpsp
! report the charges
call s%c%report(.false.,.true.)
call s%report(.false.,.false.,.false.,.false.,.false.,.true.,.false.)

Expand Down
2 changes: 1 addition & 1 deletion tests/004_load/005_load-cubezpsp.cri
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
## check: 005_load-cubezpsp_02.line -a1e-10
## labels: regression quick
crystal ../zz_source/qe-6.1/graphite/rho.cube
load ../zz_source/qe-6.1/graphite/rho.cube zpsp C 4 core
load ../zz_source/qe-6.1/graphite/rho.cube zpsp C 4
line 0 0 3/4 1 1 3/4 101 file 005_load-cubezpsp_01.line field 1

load ../zz_source/qe-6.1/graphite/rho.cube nocore
Expand Down
13 changes: 7 additions & 6 deletions tests/004_load/032_load-core.cri
Original file line number Diff line number Diff line change
Expand Up @@ -2,10 +2,11 @@
## labels: regression quick
crystal ../zz_source/qe-6.1/graphite/rho.cube

zpsp C 4
load ../zz_source/qe-6.1/graphite/rho.cube core
load ../zz_source/qe-6.1/graphite/rho.cube nocore
load as core 10 10 10
load as core sizeof 3
load as "$1-$2-$4" sizeof 3
load ../zz_source/qe-6.1/graphite/rho.cube zpsp C 4
load ../zz_source/qe-6.1/graphite/rho.cube
load as core 10 10 10 zpsp C 4
load as core sizeof 3 zpsp C 4
load as "$1-$2" sizeof 3
reference 0
point 0.1 0.2 0.3 all

2 changes: 1 addition & 1 deletion tests/004_load/042_setfield.cri
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ setfield 3 trispline
setfield 4 tricubic
setfield 5 numerical
setfield 6 analytical
setfield 7 core zpsp c 4
setfield 7 zpsp c 4
setfield 8 nocore
setfield 9 typnuc 1
setfield 10 normalize 1.0
Expand Down
6 changes: 3 additions & 3 deletions tests/004_load/050_load-corekeyw.cri
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
## check: 050_load-corekeyw.cro -a1e-10
## labels: regression quick
crystal ../zz_source/qe-6.1/graphite/rho.cube
load ../zz_source/qe-6.1/graphite/rho.cube core
load ../zz_source/qe-6.1/graphite/rho.cube

point 0 0 3/4
zpsp C 4
setfield 1 zpsp C 4
point 0 0 3/4
nocore
setfield 1 nocore
point 0 0 3/4
43 changes: 22 additions & 21 deletions tests/004_load/ref/050_load-corekeyw.cro
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@
Average: 6.77829564E-02
Max: 3.25200000E-01
Interpolation mode (1=nearest,2=linear,3=spline,4=tricubic,5=smoothrho): 4
Use core densities? T
Use core densities? F
Numerical derivatives? F
Nuclear CP signature: -3
Number of non-equivalent critical points: 2
Expand All @@ -40,16 +40,17 @@
0.000000000E+00 0.000000000E+00 6.821697181E-01
Hessian eigenvalues: 6.821697181E-01 1.470218414E+00 2.188340358E+00

+ List of atomic species:
# spc = atomic species. Z = atomic number. name = atomic name (symbol).
# Q = charge. ZPSP = pseudopotential charge.
# spc Z name Q ZPSP
1 6 C_ 0.0000 4

* List of core and pseudopotential charges for each field
# id type core? ZPSP
0 promol no
1 grid yes C(4)
+ Field number 1
Name: rho.cube
Source: ../zz_source/qe-6.1/graphite/rho.cube
Type: grid
Interpolation mode (1=nearest,2=linear,3=spline,4=tricubic,5=smoothrho): 4
Use core densities? T
Core charges (ZPSP): C(4)
Numerical derivatives? F
Nuclear CP signature: -3
Number of non-equivalent critical points: 2
Number of critical points in the unit cell: 4

* POINT 0.0000000 0.0000000 0.7500000
Coordinates (bohr): 0.0000000 0.0000000 9.4901828
Expand All @@ -69,16 +70,16 @@
-1.620753029E+02 -2.701255046E+01 -1.373763895E+06
Hessian eigenvalues: -1.374364171E+06 -1.374363459E+06 -1.373718900E+06

+ List of atomic species:
# spc = atomic species. Z = atomic number. name = atomic name (symbol).
# Q = charge. ZPSP = pseudopotential charge.
# spc Z name Q ZPSP
1 6 C_ 0.0000 --

* List of core and pseudopotential charges for each field
# id type core? ZPSP
0 promol no
1 grid yes
+ Field number 1
Name: rho.cube
Source: ../zz_source/qe-6.1/graphite/rho.cube
Type: grid
Interpolation mode (1=nearest,2=linear,3=spline,4=tricubic,5=smoothrho): 4
Use core densities? F
Numerical derivatives? F
Nuclear CP signature: -3
Number of non-equivalent critical points: 2
Number of critical points in the unit cell: 4

* POINT 0.0000000 0.0000000 0.7500000
Coordinates (bohr): 0.0000000 0.0000000 9.4901828
Expand Down
2 changes: 1 addition & 1 deletion tests/009_intgrid/001_yt_basic.cri
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

crystal ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_DEN

load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_PAWDEN core zpsp si 4 o 6
load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_PAWDEN zpsp si 4 o 6
load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_DEN

reference 1
Expand Down
2 changes: 1 addition & 1 deletion tests/009_intgrid/002_yt_options.cri
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

crystal ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_DEN

load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_PAWDEN core zpsp si 4 o 6
load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_PAWDEN zpsp si 4 o 6
load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_DEN

reference 1
Expand Down
2 changes: 1 addition & 1 deletion tests/009_intgrid/004_yt_plot.cri
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@

crystal ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_DEN

load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_PAWDEN core zpsp si 4 o 6
load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_PAWDEN zpsp si 4 o 6
load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_DEN

reference 1
Expand Down
2 changes: 1 addition & 1 deletion tests/009_intgrid/005_bader_basic.cri
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

crystal ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_DEN

load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_PAWDEN core zpsp si 4 o 6
load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_PAWDEN zpsp si 4 o 6
load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_DEN

reference 1
Expand Down
2 changes: 1 addition & 1 deletion tests/009_intgrid/006_bader_options.cri
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

crystal ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_DEN

load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_PAWDEN core zpsp si 4 o 6
load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_PAWDEN zpsp si 4 o 6
load ../zz_source/abinit-8.10.3/quartz-paw/quartz_o_DEN

reference 1
Expand Down
Loading

0 comments on commit fc7fd8e

Please sign in to comment.