Merge lp:~albertog/siesta/4.0-semic-pol-fix into lp:siesta/4.0

Proposed by Alberto Garcia
Status: Merged
Merged at revision: 590
Proposed branch: lp:~albertog/siesta/4.0-semic-pol-fix
Merge into: lp:siesta/4.0
Diff against target: 1478 lines (+1092/-101)
11 files modified
Docs/siesta.tex (+13/-2)
Src/atom.F (+82/-50)
Src/basis_specs.f (+72/-16)
Src/basis_types.f (+27/-3)
Src/old_atmfuncs.f (+24/-28)
Tests/Makefile (+1/-1)
Tests/Reference/bessel-rich.out (+817/-0)
Tests/bessel-rich/bessel-rich.fdf (+45/-0)
Tests/bessel-rich/bessel-rich.pseudos (+1/-0)
Tests/bessel-rich/makefile (+6/-0)
version.info (+4/-1)
To merge this branch: bzr merge lp:~albertog/siesta/4.0-semic-pol-fix
Reviewer Review Type Date Requested Status
Nick Papior Pending
Javier Junquera Pending
Review via email: mp+362250@code.launchpad.net

Commit message

Fix some issues with polarization orbitals. Bessel orbs improvements.

A number of issues (mostly cosmetic, or appearing in rare occasions) with
polarization orbitals have been fixed.

* Fix 'n' quantum number for high-l polarization orbitals

  When a polarization orbital had angular momentum l greater than the
  rest of the the basis, its associated principal quantum number n was
  off (it was set to the polarized shell's n).

  This error affected the metadata in the .ion files, the wavefunction
  files, and the PDOS file, so some analysis operations might have
  failed to take into account those orbitals if they were requested
  explicitly (e.g., a COOP calculation with 'O_3d' symbols might show
  the bug; but not one with 'O_d' or 'O').

* Fix for the case of polarization orbitals having the same l as a
  semicore state.

  An example: For Ti, the electronic structure is 3s2 3p6 3d2 4s2 4p0*

  4p0* is a polarization orbital, and 3p6 can be a semicore orbital.
  The outer orbitals for l=0..3 reported by the 'periodic table'
  routines for Ti are:

      4s2 3p6 3d2 4f0

  When using a pseudopotential with 3p6 in the valence (a "semicore"
  state), if 4p did not appear explicitly in a PAO.Basis block (i.e.,
  with the entry for 4s marked as "polarized"), the program did not
  identify 3p as a "semicore state", and thus it did not generate
  *two* KB operators for l=1.

  This has been fixed, together with the wrong 'n' assignment to the
  polarization orbital.

* Improve output of basis specification

  Change misleading 'n=' prefix by 'i=' (it is simply an enumeration)
  and add a proper symbolic nl identifier at the end of the line.

Some cosmetic and usability improvements have also been made to the
handling of Bessel floating orbitals:

* Extend and clarify the handling of Bessel floating orbitals

  For Bessel floating orbitals different 'zetas' correspond to
  progressively excited states (more nodes) for a given l.

  A user might want to reproduce the basis coverage of a given 'nl'
  shell with a suite of bessel functions with increasing number of
  nodes, using the 'zeta' mechanism. Up to now, it was only possible to
  do this for a single 'n' for each l, and the 'n' quantum number
  specified by the user in the (compulsory for Bessel orbitals)
  PAO.Basis block was ignored.

  This patch enables the specification of multiple 'nl' shells for the
  same l, and keeps the user's choice for the 'n' quantum number in
  the output files of the program (.ion, .PDOS, etc).

* Enable short-hand for entering rc information in PAO.Basis block

  If the number of rc's for a given shell is less than the number of
  'zetas', the program will assign the last rc value to the remaining
  zetas, rather than stopping with an error. This is particularly
  useful for Bessel suites of orbitals.

  A new test (Tests/bessel-rich) exemplifies this, as well as the
  new Bessel extensions.

Description of the change

I had a new inspiration and I think I have fixed all the issues in a simpler and less intrusive way.
'n' quantum numbers are now assigned correctly, and the KB issue for Ti is solved.

The underlying problem is documented in an "archaeological note" at the end of the header of basis_specs.f.

The "basis specs" are now more clearly output, with symbolic names for shells (similar to the
output of the psml branch).

Thank you for your patience!

To post a comment you must log in.
Revision history for this message
Nick Papior (nickpapior) wrote :

Looks good to me!

599. By Alberto Garcia

Update manual. Extend 'assumed rc' feature to contraction factors

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'Docs/siesta.tex'
2--- Docs/siesta.tex 2018-07-19 19:31:44 +0000
3+++ Docs/siesta.tex 2019-01-30 13:27:17 +0000
4@@ -1669,7 +1669,11 @@
5 \item[-] {\tt l}: Angular momentum of
6 basis orbitals of this shell
7 \item[-] {\tt nzls(lsh,is)}: Number of 'zetas' for this shell. For a filteret
8-basis this number is ignored since the number is controlled by the cutoff.
9+basis this number is ignored since the number is controlled by the
10+cutoff.
11+For bessel-floating orbitals, the different 'zetas' map to
12+increasingly excited states with the same angular momentum (with
13+increasing number of nodes).
14 \item[-] {\tt PolOrb(l+1)}: {\it Optional input}. If set equal to {\tt P}, a
15 shell of
16 polarization functions (with angular momentum $l+1$) will be constructed
17@@ -1718,9 +1722,16 @@
18 each 'zeta' for this shell. For the second zeta onwards, if this value
19 is negative, the actual rc used will be the given fraction of the
20 first zeta's rc.
21+If the number of rc's for a given shell is less than the number of
22+'zetas', the program will assign the last rc value to the remaining
23+zetas, rather than stopping with an error. This is particularly
24+useful for Bessel suites of orbitals.
25 \item[-] {\tt contrf(izeta,l,is)}: {\it Optional input}.
26 Contraction factor\index{scale factor} of
27 each 'zeta' for this shell.
28+If the number of entries for a given shell is less than the number of
29+'zetas', the program will assign the last contraction value to the remaining
30+zetas, rather than stopping with an error.
31 {\it Default value}: {\tt 1.0}
32 \end{itemize}
33
34@@ -1751,7 +1762,7 @@
35 a constant-pseudopotential atom, {\it i.e.}, the basis functions
36 generated will be spherical Bessel functions\index{Bessel functions}
37 with the specified $r_c$. In this case, $r_c$ has to be given, as
38-{\bf EnergyShift} will not calculate it.\index{basis!Bessel functions}
39+{\bf PAO.EnergyShift} will not calculate it.\index{basis!Bessel functions}
40
41 Other negative atomic numbers will be interpreted by {\sc Siesta} as
42 {\it ghosts}\index{ghost atoms}\index{basis!ghost atoms}
43
44=== modified file 'Src/atom.F'
45--- Src/atom.F 2018-04-26 13:04:08 +0000
46+++ Src/atom.F 2019-01-30 13:27:17 +0000
47@@ -289,8 +289,9 @@
48 . ' ( Floating basis ) '
49
50 elseif(iz.eq.-100) then
51- write(6,'(a,i4,a)')
52- . 'atom: Called for Z=',iz,'( Floating Bessel functions)'
53+ write(6,'(3a,i4,a,a)')
54+ . 'atom: Called for ', atm_label, ' (Z =', iz,')',
55+ . ' ( Floating Bessel functions ) '
56
57 endif
58 !
59@@ -702,7 +703,7 @@
60 slfe(is) = 0.0d0
61 ! Calculate Bessel functions
62 call Bessel(is,a,b,rofi,drdi,s,
63- . lmxo,nzeta,rco,lambda,filtercut,no)
64+ . lmxo,nzeta,rco,lambda,filtercut,no,nsemic)
65
66 write(6,'(/a,i3)')
67 . 'atom: Total number of floating Bessel orbitals:', no
68@@ -2578,7 +2579,8 @@
69 C
70 C Internal and common variables
71 C
72- integer l, lmax, nzetamax, nkblmx,nsm, nsm_max
73+ integer l, lmax, nzetamax, nkblmx,nsm, nsm_max, n_user
74+ integer npols_lm1
75 C
76 C Adding a new species to the list
77 C
78@@ -2635,27 +2637,42 @@
79
80 cnfigtb(:,:,is) = 0
81
82- if (iz.ne.-100) then
83- do l=0,lmxo
84- do nsm=1, nsemic(l)+1
85- cnfigtb(l,nsm,is)=cnfigmx(l)-(nsemic(l)+1)+nsm
86- enddo
87- enddo
88- do l=min(lmaxd,lmxo+1),lmaxd
89- cnfigtb(l,1,is)=l+1 ! AG*** Why??
90- ! To deal with polarization
91- ! orbitals beyond lmxo?
92-! BUT, what happens to "in-between" polarization orbitals?
93-!
94-!
95- enddo
96- else
97-!
98-! Arbitrary "n" for "semicore" bessel states...
99-!
100+ ! Generate the array with 'n' quantum number information
101+ if (iz.ne.-100) then ! Normal case
102+
103+ ! Note that cnfigmx and nsemic are now properly extended
104+ ! all the way to lmaxd (in basis_types) to give a proper cnfigtb
105+
106 do l=0,lmaxd
107+ do nsm=1, nsemic(l)+1
108+ cnfigtb(l,nsm,is)=cnfigmx(l)-(nsemic(l)+1)+nsm
109+ enddo
110+
111+ if (l==0) cycle
112+
113+ ! Special case where a polarization orbital has the same l
114+ ! as a lower-lying state (e.g. Ti: 3s2 3p6 4s2 3d2 4p0*) 4p0 is a polarization
115+ ! orbital, with the same l as 3p.
116+ ! (See 'archaeological note' in the header of 'basis_specs.f')
117+ npols_lm1 = sum(npolorb(l-1,:))
118+ if (npols_lm1 > 0) then
119+ nsm = nsemic(l)+2
120+ cnfigtb(l,nsm,is)= cnfigmx(l) + 1 ! in the above case, 4p
121+ endif
122+
123+ enddo
124+
125+ else
126+!
127+! For bessel-function states, the 'n' quantum number
128+! does not follow the heuristics for real 'atomic'
129+! states, but since the user has to specify them in the
130+! PAO.Basis block, we use them.
131+
132+ do l=0,lmxo
133 do nsm=1,nsemic(l)+1
134- cnfigtb(l,nsm,is)=nsm
135+ n_user = cnfigmx(l)-(nsemic(l)+1)+nsm
136+ cnfigtb(l,nsm,is) = n_user
137 enddo
138 enddo
139 endif ! iz.ne.-100
140@@ -6727,7 +6744,7 @@
141 !
142 subroutine BESSEL(is,a,b,rofi,drdi,s,lmxo,
143 . nzeta,rco,lambda,filtercut,
144- . norb)
145+ . norb,nsemic)
146
147 use basis_specs, only: restricted_grid
148 C
149@@ -6744,14 +6761,13 @@
150 . lambda(nzetmx, 0:lmaxd,nsemx),
151 . filtercut(0:lmaxd,nsemx)
152
153-
154 integer
155- . lmxo, is, nzeta(0:lmaxd,nsemx), norb
156+ . lmxo, is, nzeta(0:lmaxd,nsemx), norb, nsemic(0:lmaxd)
157 C
158 C Internal variables
159 C
160 integer
161- . l,nprin, nnodes, nodd, nrc, ir, indx, izeta
162+ . l,nprin, nnodes, nodd, nrc, ir, indx, izeta, nsm
163
164 real(dp)
165 . rc, dnrm, phi,
166@@ -6763,17 +6779,28 @@
167 indx=0
168 do l=0,lmxo
169
170- if (nzeta(l,1).gt.0) then
171-
172- write(6,'(/2A,I2)')
173- . 'Bessel: floating Bessel functions ',
174- . 'with angular momentum L=',l
175-
176- do izeta=1, nzeta(l,1)
177+ do nsm=1,nsemic(l)+1
178+ if (nzeta(l,nsm).gt.0) then
179+ write(6,'(/2A,I2)')
180+ . 'Bessel: floating Bessel functions ',
181+ . 'with angular momentum L=',l
182+ exit
183+ endif
184+ enddo
185+
186+ do nsm=1,nsemic(l)+1 ! Note extra shell loop
187+
188+ if (nzeta(l,nsm).eq.0) CYCLE
189+
190+ write(6,'(/A,I1,A)')
191+ . 'Bessel: Basis orbitals for "state" ',
192+ . cnfigtb(l,nsm,is), sym(l)
193+
194+ do izeta=1, nzeta(l,nsm)
195 C
196 C Cut-off radius for Bessel functions must be an explicit input
197 C
198- if (rco(izeta,l,1).lt.1.0d-5) then
199+ if (rco(izeta,l,nsm).lt.1.0d-5) then
200 write(6,'(a)')
201 . 'Bessel: ERROR Zero cut-off radius with Z=-100 option'
202 write(6,'(a)')
203@@ -6783,15 +6810,15 @@
204 call die
205 endif
206 C
207- if (abs(lambda(izeta,l,1)).lt.1.0d-3)
208- . lambda(izeta,l,1)=1.0d0
209- if (abs(lambda(izeta,l,1)-1.0d0).gt.1.0d-3) then
210+ if (abs(lambda(izeta,l,nsm)).lt.1.0d-3)
211+ . lambda(izeta,l,nsm)=1.0d0
212+ if (abs(lambda(izeta,l,nsm)-1.0d0).gt.1.0d-3) then
213 write(6,'(/,a)')
214 . 'Bessel: WARNING Scale factor is not active with Z=-100 option'
215 endif
216- lambda(izeta,l,1)=1.0d0
217+ lambda(izeta,l,nsm)=1.0d0
218
219- rc=rco(izeta,l,1)
220+ rc=rco(izeta,l,nsm)
221 nrc=nint(log(rc/b+1.0d0)/a)+1
222 if (restricted_grid) then
223 nodd=mod(nrc,2)
224@@ -6800,10 +6827,17 @@
225 endif
226 endif
227 rc=b*(exp(a*(nrc-1))-1.0d0)
228- rco(izeta,l,1)=rc
229-
230- nnodes=izeta
231- nprin=l+1
232+ rco(izeta,l,nsm)=rc
233+
234+ ! Instead of generating directly j_l(k*r), where
235+ ! k is chosen to have a zero at rc, the effective Schrodinger
236+ ! equation is integrated with a zero potential.
237+
238+ ! Note that the the different zetas here mean successively
239+ ! excited states for this l
240+
241+ nnodes=izeta ! Including the one at r=rc...
242+ nprin=l+1
243 call schro_eq(1.0d0,rofi,v,v,s,drdi,
244 . nrc,l,a,b,nnodes,nprin,
245 . eorb,g)
246@@ -6826,19 +6860,17 @@
247
248 write(6,'(/,(3x,a,i2),2(/,a25,f12.6))')
249 . 'izeta =',izeta,
250- . 'rc =',rco(izeta,l,1),
251+ . 'rc =',rco(izeta,l,nsm),
252 . 'energy =',eorb
253
254 norb=norb+(2*l+1)
255 indx=indx+1
256 call comBasis(is,a,b,rofi,g,l,
257- . rco(izeta,l,1),lambda(izeta,l,1),
258- . filtercut(l,1),izeta,1,nrc,indx)
259+ . rco(izeta,l,nsm),lambda(izeta,l,nsm),
260+ . filtercut(l,nsm),izeta,nsm,nrc,indx)
261
262 enddo
263-
264- endif
265-
266+ enddo
267 enddo
268
269 end subroutine bessel
270
271=== modified file 'Src/basis_specs.f'
272--- Src/basis_specs.f 2017-12-15 10:24:23 +0000
273+++ Src/basis_specs.f 2019-01-30 13:27:17 +0000
274@@ -47,9 +47,11 @@
275 !
276 ! rc_1 rc_2 .... rc_nzeta
277 !
278-! are the cutoff radii in bohrs. This line is mandatory and there must
279-! be at least nzeta values (the extra ones are discarded)
280-!
281+! are the cutoff radii in bohrs. This line is mandatory
282+! If the number of rc's for a given shell is less than the number of
283+! 'zetas', the program will assign the last rc value to the remaining
284+! zetas, rather than stopping with an error. This is particularly
285+! useful for Bessel suites of orbitals.
286 ! A line containing contraction (scale) factors is optional, but if it
287 ! appears, the values *must be* real numbers, and there must be at
288 ! least nzeta of them.
289@@ -76,7 +78,7 @@
290 ! There are no 'per l-shell' polarization orbitals, except if the
291 ! third character of 'basis_size' is 'p' (as in 'dzp'), in which
292 ! case polarization orbitals are defined so they have the minimum
293-! angular momentum l such that there are not occupied orbitals
294+! angular momentum l such that there are no occupied orbitals
295 ! with the same l in the valence shell of the ground-state
296 ! atomic configuration. They polarize the corresponding l-1 shell.
297 !
298@@ -86,7 +88,7 @@
299 !
300 ! rc(1:nzeta) is set to 0.0
301 ! lambda(1:nzeta) is set to 1.0 (this is a change from old practice)
302-!
303+!
304 ! ----------------------------------
305 !
306 ! Next come the blocks associated to the KB projectors:
307@@ -115,7 +117,28 @@
308 ! n-shells in the corresponding PAO shell with the same l. For l
309 ! greater than lmxo, it is set to 1. The reference energies are
310 ! in all cases set to huge(1.d0) to mark the default.
311-!
312+!
313+! Archaeological note: The first implementation of the basis-set generation
314+! module had only non-polarization orbitals. Polarization orbitals were added
315+! later as "second-class" companions. This shows in details like "lmxo" (the
316+! maximum l of the basis set) not taking into account polarization orbitals.
317+! Polarization orbitals were tagged at the end, without maintaining l-shell
318+! ordering.
319+! Even later, support for "semicore" orbitals was added. A new ('nsm') index was
320+! used to distinguish the different orbitals in a l-shell. Polarization orbitals
321+! were not brought into this classification.
322+! The code is strained when semicore and polarization orbitals coexist for the same l,
323+! as in Ti, whose electronic structure is []3s2 3p6 3d2 4s2 (4p0*) with 4p as the
324+! polarization orbital.
325+! Here 'nsemic' (the number of semicore states) is kept at zero for l=1
326+! (the polarization orbital is not counted), with the side-effect that only one KB
327+! projector is generated for l=1.
328+! Special checks have been implemented to cover these cases.
329+!
330+! Future work should probably remove the separate treatment of polarization orbitals.
331+! (Note that if *all* orbitals are specified in a PAO.Basis block, in effect turning
332+! perturbative polarization orbitals into 'normal' orbitals, this problem is not present.)
333+!
334 ! =======================================================================
335 !
336 use precision
337@@ -489,8 +512,21 @@
338 k%l = l
339 if (l.gt.basp%lmxo) then
340 k%nkbl = 1
341- else ! Set equal to the number of PAO shells
342- k%nkbl = basp%lshell(l)%nn
343+ else
344+ ! Set equal to the number of PAO shells with this l
345+ k%nkbl = basp%lshell(l)%nn
346+ ! Should include polarization orbs (as in Ti case: 3p..4p*)
347+ ! (See 'archaeological note' in the header of this file)
348+ if (l>0) then
349+ do i = 1, basp%lshell(l-1)%nn
350+ if (basp%lshell(l-1)%shell(i)%polarized) then
351+ k%nkbl = k%nkbl + 1
352+ write(6,"(a,i1,a)") trim(basp%label) //
353+ $ ': nkbl increased for l=',l,
354+ $ ' due to the presence of a polarization orbital'
355+ endif
356+ enddo
357+ endif
358 if (k%nkbl.eq.0) then
359 write(6,*) 'Warning: Empty PAO shell. l =', l
360 write(6,*) 'Will have a KB projector anyway...'
361@@ -592,6 +628,7 @@
362 subroutine repaobasis()
363
364 integer isp, ish, nn, i, ind, l, indexp, index_splnorm
365+ integer nrcs_zetas
366
367 type(block_fdf) :: bfdf
368 type(parsed_line), pointer :: pline
369@@ -742,11 +779,21 @@
370 s%rc(:) = 0.d0
371 s%lambda(:) = 1.d0
372 if (.not. fdf_bline(bfdf,pline)) call die("No rc's")
373- if (fdf_bnvalues(pline) .ne. s%nzeta)
374- . call die("Wrong number of rc's")
375+
376+ ! Use the last rc entered for the successive zetas
377+ ! if there are not enough values (useful for Bessel)
378+ nrcs_zetas = fdf_bnvalues(pline)
379+ if (nrcs_zetas < 1) then
380+ call die("Need at least one rc per shell in PAO.Basis block")
381+ endif
382 do i= 1, s%nzeta
383- s%rc(i) = fdf_bvalues(pline,i)
384+ if (i <= nrcs_zetas) then
385+ s%rc(i) = fdf_bvalues(pline,i)
386+ else
387+ s%rc(i) = s%rc(nrcs_zetas)
388+ endif
389 enddo
390+
391 if (s%split_norm_specified) then
392 do i = 2,s%nzeta
393 if (s%rc(i) /= 0.0_dp) then
394@@ -770,11 +817,20 @@
395 . call die('repaobasis: ERROR in PAO.Basis block')
396 cycle shells
397 else
398- if (fdf_bnreals(pline) .ne. s%nzeta)
399- . call die("Wrong number of lambda's")
400- do i=1,s%nzeta
401- s%lambda(i) = fdf_breals(pline,i)
402- enddo
403+ ! Read scale factors
404+ ! Use the last scale factor entered for the successive zetas
405+ ! if there are not enough values
406+ nrcs_zetas = fdf_bnreals(pline)
407+ if (nrcs_zetas < 1) then
408+ call die("Need at least one scale factor in PAO.Basis")
409+ endif
410+ do i= 1, s%nzeta
411+ if (i <= nrcs_zetas) then
412+ s%lambda(i) = fdf_breals(pline,i)
413+ else
414+ s%lambda(i) = s%lambda(nrcs_zetas)
415+ endif
416+ enddo
417 endif
418 endif
419
420
421=== modified file 'Src/basis_types.f'
422--- Src/basis_types.f 2017-12-15 10:24:23 +0000
423+++ Src/basis_types.f 2019-01-30 13:27:17 +0000
424@@ -578,6 +578,24 @@
425 $ cnfigmx(l,isp) = basp%ground_state%n(l)
426
427 enddo
428+
429+ ! NOTE: cnfigmx and nsemic are only initialized for l up to lmxo
430+ ! in the above loop
431+ ! Extend them so that we can deal properly with outer polarization states
432+
433+ do l=basp%lmxo+1, lmaxd
434+ ! gs is only setup up to l=3 (f)
435+ if (l <= 3) then
436+ cnfigmx(l,isp) = basp%ground_state%n(l)
437+ else
438+ ! g orbitals. Use the "l+1" heuristic
439+ ! For example, 5g pol orb associated to a 4f orb.
440+ cnfigmx(l,isp) = l + 1
441+ endif
442+ nsemic(l,isp) = 0
443+ enddo
444+
445+
446 do l=0,basp%lmxkb
447 k=>basp%kbshell(l)
448 nkbl(l,isp) = k%nkbl
449@@ -594,6 +612,10 @@
450 integer, intent(in) :: is
451
452 integer l, n, i
453+ integer :: nprin
454+ character(len=4) :: orb_id
455+ character(len=1), parameter ::
456+ $ sym(0:4) = (/ 's','p','d','f','g' /)
457
458 write(lun,'(/a/79("="))') '<basis_specs>'
459 write(lun,'(a20,1x,a2,i4,4x,a5,g12.5,4x,a7,g12.5)')
460@@ -609,9 +631,11 @@
461 $ 'Cnfigmx=', cnfigmx(l,is)
462 do n=1,nsemic(l,is)+1
463 if (nzeta(l,n,is) == 0) exit
464- write(lun,'(10x,a2,i1,2x,a6,i1,2x,a7,i1)')
465- $ 'n=', n, 'nzeta=',nzeta(l,n,is),
466- $ 'polorb=', polorb(l,n,is)
467+ nprin = cnfigmx(l,is) - nsemic(l,is) + n - 1
468+ write(orb_id,"(a1,i1,a1,a1)") "(",nprin, sym(l), ")"
469+ write(lun,'(10x,a2,i1,2x,a6,i1,2x,a7,i1,2x,a4)')
470+ $ 'i=', n, 'nzeta=',nzeta(l,n,is),
471+ $ 'polorb=', polorb(l,n,is), orb_id
472 if (basistype(is).eq.'filteret') then
473 write(lun,'(10x,a10,2x,g12.5)')
474 $ 'fcutoff:', filtercut(l,n,is)
475
476=== modified file 'Src/old_atmfuncs.f'
477--- Src/old_atmfuncs.f 2016-01-25 16:00:16 +0000
478+++ Src/old_atmfuncs.f 2019-01-30 13:27:17 +0000
479@@ -399,18 +399,17 @@
480 integer, intent(in) :: is ! Species index
481 integer, intent(in) :: io ! Orbital index (within atom)
482
483-C Returns the valence-shell configuration in the atomic ground state
484-C (i.e. the principal quatum number for orbitals of angular momentum l)
485-
486-C INTEGER CNFIGFIO: Principal quantum number of the shell to what
487-C the orbital belongs ( for polarization orbitals
488-C the quantum number corresponds to the shell which
489-C is polarized by the orbital io)
490-
491- integer l, norb, lorb, izeta, ipol,nsm
492- integer indx, nsmorb
493-
494-C
495+C INTEGER CNFIGFIO: Principal quantum number of the shell to which
496+C the orbital belongs
497+
498+C (Formerly, for polarization orbitals
499+C the quantum number corresponded to the shell which
500+C is polarized by the orbital io.
501+C This behavior for polarization orbitals is meaningless,
502+C and has been replaced.)
503+
504+ integer l, norb, izeta, ipol, nsm
505+
506 call check_is('cnfigfio',is)
507 if ((io.gt.nomax(is)).or.(io.lt.1)) then
508 write(6,*) 'CNFIGFIO: THERE ARE NO DATA FOR IO=',IO
509@@ -419,25 +418,32 @@
510 call die()
511 endif
512
513+ ! This routine assumes that polarization orbitals are the last ones
514+ ! in the list indexed by 'io'
515+
516 norb=0
517- indx=0
518 do 10 l=0,lmxosave(is)
519 do 8 nsm=1,nsemicsave(l,is)+1
520 do 5 izeta=1,nzetasave(l,nsm,is)
521 norb=norb+(2*l+1)
522- indx=indx+1
523- if(norb.ge.io) goto 30
524+ if(norb.ge.io) then
525+ cnfigfio=cnfigtb(l,nsm,is)
526+ return
527+ endif
528 5 continue
529 8 continue
530 10 continue
531
532- indx=0
533 do 20 l=0,lmxosave(is)
534 do 18 nsm=1,nsemicsave(l,is)+1
535 do 15 ipol=1, npolorbsave(l,nsm,is)
536 norb=norb+(2*(l+1)+1)
537- indx=indx+1
538- if(norb.ge.io) goto 40
539+ if(norb.ge.io) then
540+ ! Deal properly with polarization orbitals
541+ ! Return the highest n for l+1
542+ cnfigfio=maxval(cnfigtb(l+1,:,is))
543+ return
544+ endif
545 15 continue
546 18 continue
547 20 continue
548@@ -445,16 +451,6 @@
549 write(6,*) 'CNFIGFIO: ERROR: NOT FOUND'
550 call die()
551
552-30 lorb=l
553- nsmorb=nsm
554- cnfigfio=cnfigtb(lorb,nsmorb,is)
555- return
556-
557-40 lorb=l
558- nsmorb=nsm
559- cnfigfio=cnfigtb(lorb,nsmorb,is)
560- return
561-
562 end function cnfigfio
563 !
564 !
565
566=== modified file 'Tests/Makefile'
567--- Tests/Makefile 2018-04-25 11:14:24 +0000
568+++ Tests/Makefile 2019-01-30 13:27:17 +0000
569@@ -36,7 +36,7 @@
570 #
571 label = work
572
573-tests = 32_h2o ag anneal-cont ar2_vdw batio3 benzene bessel born \
574+tests = 32_h2o ag anneal-cont ar2_vdw batio3 benzene bessel bessel-rich born \
575 born_spin carbon_nanoscroll ch4 chargeconf-h2o constant_volume \
576 dipole_correction fe fe_broyden fe_clust_noncollinear fe_cohp \
577 fen fe_noncol_kp fire_benzene floating force_2 force_constants \
578
579=== added file 'Tests/Reference/bessel-rich.out'
580--- Tests/Reference/bessel-rich.out 1970-01-01 00:00:00 +0000
581+++ Tests/Reference/bessel-rich.out 2019-01-30 13:27:17 +0000
582@@ -0,0 +1,817 @@
583+Siesta Version : siesta-4.0--589--n-fix-4
584+Architecture : gfortran-macosx64-openmpi
585+Compiler version: GNU Fortran (Homebrew GCC 7.2.0) 7.2.0
586+Compiler flags : mpif90 -g -O2
587+PP flags : -DCDF -DMPI -DF2003
588+PARALLEL version
589+NetCDF support
590+
591+* Running in serial mode with MPI
592+>> Start of run: 17-JAN-2019 15:47:45
593+
594+ ***********************
595+ * WELCOME TO SIESTA *
596+ ***********************
597+
598+reinit: Reading from standard input
599+************************** Dump of input data file ****************************
600+#
601+# Needs new feature: handling of fewer rc's than nzetas in PAO.Basis block
602+#
603+write-ion-plot-files T
604+#
605+SystemName Water molecule with various Bessel Orbitals
606+SystemLabel bessel-rich
607+NumberofAtoms 7
608+NumberOfSpecies 4
609+%block ChemicalSpeciesLabel
610+ 1 8 O # Species index, atomic number, species label
611+ 2 1 H
612+ 3 -100 Bessel
613+ 4 -100 J
614+%endblock ChemicalSpeciesLabel
615+AtomicCoordinatesFormat Ang
616+%block AtomicCoordinatesAndAtomicSpecies
617+ 0.000 0.000 0.000 1
618+ 0.757 0.586 0.000 2
619+-0.757 0.586 0.000 2
620+ 0.3785 0.293 0.000 3
621+-0.3785 0.293 0.000 3
622+ 0.3785 0.293 0.000 4
623+-0.3785 0.293 0.000 4
624+%endblock AtomicCoordinatesAndAtomicSpecies
625+%block PAO.Basis
626+Bessel 3
627+ n=1 0 1
628+ 2.0
629+ 1.0
630+ n=2 0 1
631+ 2.5
632+ 1.0
633+ n=3 1 1
634+ 3.5
635+ 1.0
636+J 2 # l-shells
637+n=2 0 7 # Note new feature: fewer rc's than zetas
638+ 4.5
639+n=2 1 3
640+ 4.5 4.5 5.0
641+%endblock PAO.Basis
642+************************** End of input data file *****************************
643+
644+reinit: -----------------------------------------------------------------------
645+reinit: System Name: Water molecule with various Bessel Orbitals
646+reinit: -----------------------------------------------------------------------
647+reinit: System Label: bessel-rich
648+reinit: -----------------------------------------------------------------------
649+
650+initatom: Reading input for the pseudopotentials and atomic orbitals ----------
651+ Species number: 1 Label: O Atomic number: 8
652+ Species number: 2 Label: H Atomic number: 1
653+ Species number: 3 Label: Bessel (floating Bessel functions)
654+ Species number: 4 Label: J (floating Bessel functions)
655+Ground state valence configuration: 2s02 2p04
656+Reading pseudopotential information in formatted form from O.psf
657+
658+Valence configuration for pseudopotential generation:
659+2s( 2.00) rc: 1.14
660+2p( 4.00) rc: 1.14
661+3d( 0.00) rc: 1.14
662+4f( 0.00) rc: 1.14
663+Dumping pseudopotential information in formatted form in O.psdump
664+Ground state valence configuration: 1s01
665+Reading pseudopotential information in formatted form from H.psf
666+
667+Valence configuration for pseudopotential generation:
668+1s( 1.00) rc: 1.25
669+2p( 0.00) rc: 1.25
670+3d( 0.00) rc: 1.25
671+4f( 0.00) rc: 1.25
672+Dumping pseudopotential information in formatted form in H.psdump
673+For O, standard SIESTA heuristics set lmxkb to 3
674+ (one more than the basis l, including polarization orbitals).
675+Use PS.lmax or PS.KBprojectors blocks to override.
676+For H, standard SIESTA heuristics set lmxkb to 2
677+ (one more than the basis l, including polarization orbitals).
678+Use PS.lmax or PS.KBprojectors blocks to override.
679+
680+<basis_specs>
681+===============================================================================
682+O Z= 8 Mass= 16.000 Charge= 0.17977+309
683+Lmxo=1 Lmxkb= 3 BasisType=split Semic=F
684+L=0 Nsemic=0 Cnfigmx=2
685+ n=1 nzeta=2 polorb=0
686+ splnorm: 0.15000
687+ vcte: 0.0000
688+ rinn: 0.0000
689+ qcoe: 0.0000
690+ qyuk: 0.0000
691+ qwid: 0.10000E-01
692+ rcs: 0.0000 0.0000
693+ lambdas: 1.0000 1.0000
694+L=1 Nsemic=0 Cnfigmx=2
695+ n=1 nzeta=2 polorb=1
696+ splnorm: 0.15000
697+ vcte: 0.0000
698+ rinn: 0.0000
699+ qcoe: 0.0000
700+ qyuk: 0.0000
701+ qwid: 0.10000E-01
702+ rcs: 0.0000 0.0000
703+ lambdas: 1.0000 1.0000
704+-------------------------------------------------------------------------------
705+L=0 Nkbl=1 erefs: 0.17977+309
706+L=1 Nkbl=1 erefs: 0.17977+309
707+L=2 Nkbl=1 erefs: 0.17977+309
708+L=3 Nkbl=1 erefs: 0.17977+309
709+===============================================================================
710+</basis_specs>
711+
712+atom: Called for O (Z = 8)
713+
714+read_vps: Pseudopotential generation method:
715+read_vps: ATM3 Troullier-Martins
716+Total valence charge: 6.00000
717+
718+xc_check: Exchange-correlation functional:
719+xc_check: Ceperley-Alder
720+V l=0 = -2*Zval/r beyond r= 1.1278
721+V l=1 = -2*Zval/r beyond r= 1.1278
722+V l=2 = -2*Zval/r beyond r= 1.1278
723+V l=3 = -2*Zval/r beyond r= 1.1138
724+All V_l potentials equal beyond r= 1.1278
725+This should be close to max(r_c) in ps generation
726+All pots = -2*Zval/r beyond r= 1.1278
727+
728+VLOCAL1: 99.0% of the norm of Vloc inside 34.126 Ry
729+VLOCAL1: 99.9% of the norm of Vloc inside 77.774 Ry
730+atom: Maximum radius for 4*pi*r*r*local-pseudopot. charge 1.37759
731+atom: Maximum radius for r*vlocal+2*Zval: 1.18566
732+GHOST: No ghost state for L = 0
733+GHOST: No ghost state for L = 1
734+GHOST: No ghost state for L = 2
735+GHOST: No ghost state for L = 3
736+
737+KBgen: Kleinman-Bylander projectors:
738+ l= 0 rc= 1.294105 el= -1.742414 Ekb= 9.135903 kbcos= 0.326910
739+ l= 1 rc= 1.294105 el= -0.676589 Ekb= -8.124878 kbcos= -0.395047
740+ l= 2 rc= 1.448233 el= 0.002386 Ekb= -2.039267 kbcos= -0.003484
741+ l= 3 rc= 1.561052 el= 0.003508 Ekb= -0.799141 kbcos= -0.000344
742+
743+KBgen: Total number of Kleinman-Bylander projectors: 16
744+atom: -------------------------------------------------------------------------
745+
746+atom: SANKEY-TYPE ORBITALS:
747+atom: Selected multiple-zeta basis: split
748+
749+SPLIT: Orbitals with angular momentum L= 0
750+
751+SPLIT: Basis orbitals for state 2s
752+
753+SPLIT: PAO cut-off radius determined from an
754+SPLIT: energy shift= 0.020000 Ry
755+
756+ izeta = 1
757+ lambda = 1.000000
758+ rc = 3.305093
759+ energy = -1.723766
760+ kinetic = 1.614911
761+ potential(screened) = -3.338677
762+ potential(ionic) = -11.304675
763+
764+ izeta = 2
765+ rmatch = 2.510382
766+ splitnorm = 0.150000
767+ energy = -1.471299
768+ kinetic = 2.446434
769+ potential(screened) = -3.917732
770+ potential(ionic) = -12.476133
771+
772+SPLIT: Orbitals with angular momentum L= 1
773+
774+SPLIT: Basis orbitals for state 2p
775+
776+SPLIT: PAO cut-off radius determined from an
777+SPLIT: energy shift= 0.020000 Ry
778+
779+ izeta = 1
780+ lambda = 1.000000
781+ rc = 3.937239
782+ energy = -0.658841
783+ kinetic = 5.005986
784+ potential(screened) = -5.664827
785+ potential(ionic) = -13.452360
786+
787+ izeta = 2
788+ rmatch = 2.541963
789+ splitnorm = 0.150000
790+ energy = -0.367441
791+ kinetic = 7.530509
792+ potential(screened) = -7.897949
793+ potential(ionic) = -16.611953
794+
795+POLgen: Perturbative polarization orbital with L= 2
796+
797+POLgen: Polarization orbital for state 2p
798+
799+ izeta = 1
800+ rc = 3.937239
801+ energy = 2.398520
802+ kinetic = 4.716729
803+ potential(screened) = -2.318209
804+ potential(ionic) = -8.603170
805+atom: Total number of Sankey-type orbitals: 13
806+
807+atm_pop: Valence configuration (for local Pseudopot. screening):
808+ 2s( 2.00)
809+ 2p( 4.00)
810+Vna: chval, zval: 6.00000 6.00000
811+
812+Vna: Cut-off radius for the neutral-atom potential: 3.937239
813+
814+atom: _________________________________________________________________________
815+
816+<basis_specs>
817+===============================================================================
818+H Z= 1 Mass= 1.0100 Charge= 0.17977+309
819+Lmxo=0 Lmxkb= 2 BasisType=split Semic=F
820+L=0 Nsemic=0 Cnfigmx=1
821+ n=1 nzeta=2 polorb=1
822+ splnorm: 0.15000
823+ vcte: 0.0000
824+ rinn: 0.0000
825+ qcoe: 0.0000
826+ qyuk: 0.0000
827+ qwid: 0.10000E-01
828+ rcs: 0.0000 0.0000
829+ lambdas: 1.0000 1.0000
830+-------------------------------------------------------------------------------
831+L=0 Nkbl=1 erefs: 0.17977+309
832+L=1 Nkbl=1 erefs: 0.17977+309
833+L=2 Nkbl=1 erefs: 0.17977+309
834+===============================================================================
835+</basis_specs>
836+
837+atom: Called for H (Z = 1)
838+
839+read_vps: Pseudopotential generation method:
840+read_vps: ATM3 Troullier-Martins
841+Total valence charge: 1.00000
842+
843+xc_check: Exchange-correlation functional:
844+xc_check: Ceperley-Alder
845+V l=0 = -2*Zval/r beyond r= 1.2343
846+V l=1 = -2*Zval/r beyond r= 1.2189
847+V l=2 = -2*Zval/r beyond r= 1.2189
848+All V_l potentials equal beyond r= 1.2343
849+This should be close to max(r_c) in ps generation
850+All pots = -2*Zval/r beyond r= 1.2343
851+
852+VLOCAL1: 99.0% of the norm of Vloc inside 28.493 Ry
853+VLOCAL1: 99.9% of the norm of Vloc inside 64.935 Ry
854+atom: Maximum radius for 4*pi*r*r*local-pseudopot. charge 1.45251
855+atom: Maximum radius for r*vlocal+2*Zval: 1.21892
856+GHOST: No ghost state for L = 0
857+GHOST: No ghost state for L = 1
858+GHOST: No ghost state for L = 2
859+
860+KBgen: Kleinman-Bylander projectors:
861+ l= 0 rc= 1.364359 el= -0.467325 Ekb= -2.005361 kbcos= -0.336422
862+ l= 1 rc= 1.434438 el= 0.001430 Ekb= -0.501708 kbcos= -0.021697
863+ l= 2 rc= 1.470814 el= 0.002365 Ekb= -0.190555 kbcos= -0.002281
864+
865+KBgen: Total number of Kleinman-Bylander projectors: 9
866+atom: -------------------------------------------------------------------------
867+
868+atom: SANKEY-TYPE ORBITALS:
869+atom: Selected multiple-zeta basis: split
870+
871+SPLIT: Orbitals with angular momentum L= 0
872+
873+SPLIT: Basis orbitals for state 1s
874+
875+SPLIT: PAO cut-off radius determined from an
876+SPLIT: energy shift= 0.020000 Ry
877+
878+ izeta = 1
879+ lambda = 1.000000
880+ rc = 4.828263
881+ energy = -0.449375
882+ kinetic = 0.929372
883+ potential(screened) = -1.378747
884+ potential(ionic) = -1.915047
885+
886+ izeta = 2
887+ rmatch = 3.854947
888+ splitnorm = 0.150000
889+ energy = -0.336153
890+ kinetic = 1.505294
891+ potential(screened) = -1.841447
892+ potential(ionic) = -2.413582
893+
894+POLgen: Perturbative polarization orbital with L= 1
895+
896+POLgen: Polarization orbital for state 1s
897+
898+ izeta = 1
899+ rc = 4.828263
900+ energy = 0.706972
901+ kinetic = 1.396397
902+ potential(screened) = -0.689424
903+ potential(ionic) = -1.169792
904+atom: Total number of Sankey-type orbitals: 5
905+
906+atm_pop: Valence configuration (for local Pseudopot. screening):
907+ 1s( 1.00)
908+Vna: chval, zval: 1.00000 1.00000
909+
910+Vna: Cut-off radius for the neutral-atom potential: 4.828263
911+
912+atom: _________________________________________________________________________
913+
914+<basis_specs>
915+===============================================================================
916+Bessel Z=-100 Mass= 0.10000E+41 Charge= 0.17977+309
917+Lmxo=1 Lmxkb=-1 BasisType=split Semic=F
918+L=0 Nsemic=1 Cnfigmx=2
919+ n=1 nzeta=1 polorb=0
920+ splnorm: 0.15000
921+ vcte: 0.0000
922+ rinn: 0.0000
923+ qcoe: 0.0000
924+ qyuk: 0.0000
925+ qwid: 0.10000E-01
926+ rcs: 2.0000
927+ lambdas: 1.0000
928+ n=2 nzeta=1 polorb=0
929+ splnorm: 0.15000
930+ vcte: 0.0000
931+ rinn: 0.0000
932+ qcoe: 0.0000
933+ qyuk: 0.0000
934+ qwid: 0.10000E-01
935+ rcs: 2.5000
936+ lambdas: 1.0000
937+L=1 Nsemic=0 Cnfigmx=3
938+ n=1 nzeta=1 polorb=0
939+ splnorm: 0.15000
940+ vcte: 0.0000
941+ rinn: 0.0000
942+ qcoe: 0.0000
943+ qyuk: 0.0000
944+ qwid: 0.10000E-01
945+ rcs: 3.5000
946+ lambdas: 1.0000
947+-------------------------------------------------------------------------------
948+===============================================================================
949+</basis_specs>
950+
951+atom: Called for Bessel (Z =-100) ( Floating Bessel functions )
952+
953+Bessel: floating Bessel functions with angular momentum L= 0
954+
955+Bessel: Basis orbitals for "state" 1s
956+
957+ izeta = 1
958+ rc = 2.011274
959+ energy = 2.439817
960+
961+Bessel: Basis orbitals for "state" 2s
962+
963+ izeta = 1
964+ rc = 2.519390
965+ energy = 1.554924
966+
967+Bessel: floating Bessel functions with angular momentum L= 1
968+
969+Bessel: Basis orbitals for "state" 3p
970+
971+ izeta = 1
972+ rc = 3.487864
973+ energy = 1.659713
974+
975+atom: Total number of floating Bessel orbitals: 5
976+
977+atom: _________________________________________________________________________
978+
979+<basis_specs>
980+===============================================================================
981+J Z=-100 Mass= 0.10000E+41 Charge= 0.17977+309
982+Lmxo=1 Lmxkb=-1 BasisType=split Semic=F
983+L=0 Nsemic=0 Cnfigmx=2
984+ n=1 nzeta=7 polorb=0
985+ splnorm: 0.15000
986+ vcte: 0.0000
987+ rinn: 0.0000
988+ qcoe: 0.0000
989+ qyuk: 0.0000
990+ qwid: 0.10000E-01
991+ rcs: 4.5000 4.5000 4.5000 4.5000
992+ lambdas: 1.0000 1.0000 1.0000 1.0000
993+L=1 Nsemic=0 Cnfigmx=2
994+ n=1 nzeta=3 polorb=0
995+ splnorm: 0.15000
996+ vcte: 0.0000
997+ rinn: 0.0000
998+ qcoe: 0.0000
999+ qyuk: 0.0000
1000+ qwid: 0.10000E-01
1001+ rcs: 4.5000 4.5000 5.0000
1002+ lambdas: 1.0000 1.0000 1.0000
1003+-------------------------------------------------------------------------------
1004+===============================================================================
1005+</basis_specs>
1006+
1007+atom: Called for J (Z =-100) ( Floating Bessel functions )
1008+
1009+Bessel: floating Bessel functions with angular momentum L= 0
1010+
1011+Bessel: Basis orbitals for "state" 2s
1012+
1013+ izeta = 1
1014+ rc = 4.479210
1015+ energy = 0.491923
1016+
1017+ izeta = 2
1018+ rc = 4.479210
1019+ energy = 1.967691
1020+
1021+ izeta = 3
1022+ rc = 4.479210
1023+ energy = 4.427304
1024+
1025+ izeta = 4
1026+ rc = 4.479210
1027+ energy = 7.870760
1028+
1029+ izeta = 5
1030+ rc = 4.479210
1031+ energy = 12.298054
1032+
1033+ izeta = 6
1034+ rc = 4.479210
1035+ energy = 17.709175
1036+
1037+ izeta = 7
1038+ rc = 4.479210
1039+ energy = 24.104105
1040+
1041+Bessel: floating Bessel functions with angular momentum L= 1
1042+
1043+Bessel: Basis orbitals for "state" 2p
1044+
1045+ izeta = 1
1046+ rc = 4.479210
1047+ energy = 1.006350
1048+
1049+ izeta = 2
1050+ rc = 4.479210
1051+ energy = 2.974558
1052+
1053+ izeta = 3
1054+ rc = 5.075940
1055+ energy = 4.614751
1056+
1057+atom: Total number of floating Bessel orbitals: 16
1058+
1059+atom: _________________________________________________________________________
1060+
1061+prinput: Basis input ----------------------------------------------------------
1062+
1063+PAO.BasisType split
1064+
1065+%block ChemicalSpeciesLabel
1066+ 1 8 O # Species index, atomic number, species label
1067+ 2 1 H # Species index, atomic number, species label
1068+ 3 -100 Bessel # Species index, atomic number, species label
1069+ 4 -100 J # Species index, atomic number, species label
1070+%endblock ChemicalSpeciesLabel
1071+
1072+%block PAO.Basis # Define Basis set
1073+O 2 # Species label, number of l-shells
1074+ n=2 0 2 # n, l, Nzeta
1075+ 3.305 2.510
1076+ 1.000 1.000
1077+ n=2 1 2 P 1 # n, l, Nzeta, Polarization, NzetaPol
1078+ 3.937 2.542
1079+ 1.000 1.000
1080+H 1 # Species label, number of l-shells
1081+ n=1 0 2 P 1 # n, l, Nzeta, Polarization, NzetaPol
1082+ 4.828 3.855
1083+ 1.000 1.000
1084+Bessel 3 # Species label, number of l-shells
1085+ n=1 0 1 # n, l, Nzeta
1086+ 2.011
1087+ 1.000
1088+ n=2 0 1 # n, l, Nzeta
1089+ 2.519
1090+ 1.000
1091+ n=3 1 1 # n, l, Nzeta
1092+ 3.488
1093+ 1.000
1094+J 2 # Species label, number of l-shells
1095+ n=2 0 7 # n, l, Nzeta
1096+ 4.479 4.479 4.479 4.479 4.479 4.479 4.479
1097+ 1.000 1.000 1.000 1.000 1.000 1.000 1.000
1098+ n=2 1 3 # n, l, Nzeta
1099+ 4.479 4.479 5.076
1100+ 1.000 1.000 1.000
1101+%endblock PAO.Basis
1102+
1103+prinput: ----------------------------------------------------------------------
1104+
1105+Dumping basis to NetCDF file O.ion.nc
1106+Dumping basis to NetCDF file H.ion.nc
1107+Dumping basis to NetCDF file Bessel.ion.nc
1108+Dumping basis to NetCDF file J.ion.nc
1109+coor: Atomic-coordinates input format = Cartesian coordinates
1110+coor: (in Angstroms)
1111+
1112+siesta: Atomic coordinates (Bohr) and species
1113+siesta: 0.00000 0.00000 0.00000 1 1
1114+siesta: 1.43052 1.10738 0.00000 2 2
1115+siesta: -1.43052 1.10738 0.00000 2 3
1116+siesta: 0.71526 0.55369 0.00000 3 4
1117+siesta: -0.71526 0.55369 0.00000 3 5
1118+siesta: 0.71526 0.55369 0.00000 4 6
1119+siesta: -0.71526 0.55369 0.00000 4 7
1120+
1121+siesta: Automatic unit cell vectors (Ang):
1122+siesta: 7.286412 0.000000 0.000000
1123+siesta: 0.000000 6.087484 0.000000
1124+siesta: 0.000000 0.000000 5.909356
1125+
1126+siesta: System type = molecule
1127+
1128+initatomlists: Number of atoms, orbitals, and projectors: 7 65 34
1129+
1130+siesta: ******************** Simulation parameters ****************************
1131+siesta:
1132+siesta: The following are some of the parameters of the simulation.
1133+siesta: A complete list of the parameters used, including default values,
1134+siesta: can be found in file out.fdf
1135+siesta:
1136+redata: Non-Collinear-spin run = F
1137+redata: SpinPolarized (Up/Down) run = F
1138+redata: Number of spin components = 1
1139+redata: Long output = F
1140+redata: Number of Atomic Species = 4
1141+redata: Charge density info will appear in .RHO file
1142+redata: Write Mulliken Pop. = NO
1143+redata: Matel table size (NRTAB) = 1024
1144+redata: Mesh Cutoff = 100.0000 Ry
1145+redata: Net charge of the system = 0.0000 |e|
1146+redata: Min. number of SCF Iter = 0
1147+redata: Max. number of SCF Iter = 50
1148+redata: Mix DM or H after convergence = F
1149+redata: Recompute H after scf cycle = F
1150+redata: Mixing is linear
1151+redata: Mix DM in first SCF step ? = F
1152+redata: Write Pulay info on disk? = F
1153+redata: Discard 1st Pulay DM after kick = F
1154+redata: New DM Mixing Weight = 0.2500
1155+redata: New DM Occupancy tolerance = 0.000000000001
1156+redata: No kicks to SCF
1157+redata: DM Mixing Weight for Kicks = 0.5000
1158+redata: DM Tolerance for SCF = 0.000100
1159+redata: Require (free) Energy convergence in SCF = F
1160+redata: DM (free)Energy tolerance for SCF = 0.000010 eV
1161+redata: Require Harris convergence for SCF = F
1162+redata: DM Harris energy tolerance for SCF = 0.000010 eV
1163+redata: Using Saved Data (generic) = F
1164+redata: Use continuation files for DM = F
1165+redata: Neglect nonoverlap interactions = F
1166+redata: Method of Calculation = Diagonalization
1167+redata: Divide and Conquer = T
1168+redata: Electronic Temperature = 0.0019 Ry
1169+redata: Fix the spin of the system = F
1170+redata: Dynamics option = Single-point calculation
1171+redata: ***********************************************************************
1172+Total number of electrons: 8.000000
1173+Total ionic charge: 8.000000
1174+
1175+* ProcessorY, Blocksize: 1 24
1176+
1177+
1178+* Orbital distribution balance (max,min): 65 65
1179+
1180+ Kpoints in: 1 . Kpoints trimmed: 1
1181+
1182+siesta: k-grid: Number of k-points = 1
1183+siesta: k-grid: Cutoff (effective) = 2.955 Ang
1184+siesta: k-grid: Supercell and displacements
1185+siesta: k-grid: 1 0 0 0.000
1186+siesta: k-grid: 0 1 0 0.000
1187+siesta: k-grid: 0 0 1 0.000
1188+
1189+ ====================================
1190+ Single-point calculation
1191+ ====================================
1192+
1193+outcell: Unit cell vectors (Ang):
1194+ 7.286412 0.000000 0.000000
1195+ 0.000000 6.087484 0.000000
1196+ 0.000000 0.000000 5.909356
1197+
1198+outcell: Cell vector modules (Ang) : 7.286412 6.087484 5.909356
1199+outcell: Cell angles (23,13,12) (deg): 90.0000 90.0000 90.0000
1200+outcell: Cell volume (Ang**3) : 262.1149
1201+New_DM. Step: 1
1202+Initializing Density Matrix...
1203+New grid distribution: 1
1204+ 1 1: 24 1: 20 1: 18
1205+
1206+InitMesh: MESH = 48 x 40 x 36 = 69120
1207+InitMesh: (bp) = 24 x 20 x 18 = 8640
1208+InitMesh: Mesh cutoff (required, used) = 100.000 102.571 Ry
1209+ExtMesh (bp) on 0 = 60 x 56 x 54 = 181440
1210+PhiOnMesh: Number of (b)points on node 0 = 8640
1211+PhiOnMesh: nlist on node 0 = 119152
1212+
1213+stepf: Fermi-Dirac step function
1214+
1215+siesta: Program's energy decomposition (eV):
1216+siesta: Ebs = -124.892071
1217+siesta: Eions = 815.854478
1218+siesta: Ena = 175.155695
1219+siesta: Ekin = 341.667406
1220+siesta: Enl = -52.736859
1221+siesta: DEna = -0.000003
1222+siesta: DUscf = 0.000000
1223+siesta: DUext = 0.000000
1224+siesta: Exc = -109.898170
1225+siesta: eta*DQ = 0.000000
1226+siesta: Emadel = 0.000000
1227+siesta: Emeta = 0.000000
1228+siesta: Emolmec = 0.000000
1229+siesta: Ekinion = 0.000000
1230+siesta: Eharris = -467.297614
1231+siesta: Etot = -461.666410
1232+siesta: FreeEng = -461.666410
1233+
1234+ scf: iscf Eharris(eV) E_KS(eV) FreeEng(eV) dDmax Ef(eV)
1235+ scf: 1 -467.2976 -461.6664 -461.6664 1.77421 -8.4794
1236+timer: Routine,Calls,Time,% = IterSCF 1 0.073 0.70
1237+ scf: 2 -467.9568 -465.9473 -465.9473 0.17421 0.7795
1238+ scf: 3 -466.7456 -466.2075 -466.2075 0.03742 -1.0131
1239+ scf: 4 -466.6648 -466.3262 -466.3262 0.02266 -1.4679
1240+ scf: 5 -466.6584 -466.4096 -466.4096 0.02027 -1.5893
1241+ scf: 6 -466.6578 -466.4717 -466.4717 0.01648 -1.6214
1242+ scf: 7 -466.6578 -466.5182 -466.5182 0.01273 -1.6293
1243+ scf: 8 -466.6577 -466.5531 -466.5531 0.00965 -1.6311
1244+ scf: 9 -466.6577 -466.5793 -466.5793 0.00727 -1.6314
1245+ scf: 10 -466.6577 -466.5989 -466.5989 0.00545 -1.6314
1246+ scf: 11 -466.6577 -466.6136 -466.6136 0.00409 -1.6315
1247+ scf: 12 -466.6577 -466.6246 -466.6246 0.00306 -1.6316
1248+ scf: 13 -466.6577 -466.6329 -466.6329 0.00229 -1.6317
1249+ scf: 14 -466.6577 -466.6391 -466.6391 0.00171 -1.6318
1250+ scf: 15 -466.6577 -466.6438 -466.6438 0.00128 -1.6319
1251+ scf: 16 -466.6577 -466.6472 -466.6472 0.00096 -1.6319
1252+ scf: 17 -466.6577 -466.6499 -466.6499 0.00072 -1.6320
1253+ scf: 18 -466.6577 -466.6518 -466.6518 0.00054 -1.6320
1254+ scf: 19 -466.6577 -466.6533 -466.6533 0.00040 -1.6321
1255+ scf: 20 -466.6577 -466.6544 -466.6544 0.00030 -1.6321
1256+ scf: 21 -466.6577 -466.6552 -466.6552 0.00022 -1.6321
1257+ scf: 22 -466.6577 -466.6559 -466.6559 0.00017 -1.6321
1258+ scf: 23 -466.6577 -466.6563 -466.6563 0.00012 -1.6322
1259+ scf: 24 -466.6577 -466.6567 -466.6567 0.00009 -1.6322
1260+
1261+SCF Convergence by dMax criterion
1262+max |DM_out - DM_in|: 0.00009343
1263+SCF cycle converged after 24 iterations
1264+
1265+Using DM_out to compute the final energy and forces
1266+
1267+siesta: E_KS(eV) = -466.6577
1268+
1269+siesta: E_KS - E_eggbox = -466.6577
1270+
1271+siesta: Atomic forces (eV/Ang):
1272+----------------------------------------
1273+ Tot -0.000000 -0.032764 -0.000000
1274+----------------------------------------
1275+ Max 0.376555
1276+ Res 0.167768 sqrt( Sum f_i^2 / 3N )
1277+----------------------------------------
1278+ Max 0.376555 constrained
1279+
1280+Stress-tensor-Voigt (kbar): -3.42 -0.89 -1.16 0.00 0.00 0.00
1281+(Free)E + p*V (eV/cell) -466.3595
1282+Target enthalpy (eV/cell) -466.6577
1283+
1284+siesta: Program's energy decomposition (eV):
1285+siesta: Ebs = -107.092904
1286+siesta: Eions = 815.854478
1287+siesta: Ena = 175.155695
1288+siesta: Ekin = 351.559238
1289+siesta: Enl = -63.040421
1290+siesta: DEna = -2.430290
1291+siesta: DUscf = 0.775212
1292+siesta: DUext = 0.000000
1293+siesta: Exc = -112.822678
1294+siesta: eta*DQ = 0.000000
1295+siesta: Emadel = 0.000000
1296+siesta: Emeta = 0.000000
1297+siesta: Emolmec = 0.000000
1298+siesta: Ekinion = 0.000000
1299+siesta: Eharris = -466.657724
1300+siesta: Etot = -466.657724
1301+siesta: FreeEng = -466.657724
1302+
1303+siesta: Final energy (eV):
1304+siesta: Band Struct. = -107.092904
1305+siesta: Kinetic = 351.559238
1306+siesta: Hartree = 388.214304
1307+siesta: Ext. field = 0.000000
1308+siesta: Exch.-corr. = -112.822678
1309+siesta: Ion-electron = -1087.255665
1310+siesta: Ion-ion = -6.352922
1311+siesta: Ekinion = 0.000000
1312+siesta: Total = -466.657724
1313+
1314+siesta: Atomic forces (eV/Ang):
1315+siesta: 1 0.000000 -0.018600 0.000000
1316+siesta: 2 0.376555 0.275107 -0.000000
1317+siesta: 3 -0.376555 0.275107 -0.000000
1318+siesta: 4 -0.001135 -0.003186 0.000000
1319+siesta: 5 0.001135 -0.003186 0.000000
1320+siesta: 6 -0.005249 -0.279003 0.000000
1321+siesta: 7 0.005249 -0.279003 0.000000
1322+siesta: ----------------------------------------
1323+siesta: Tot -0.000000 -0.032764 -0.000000
1324+
1325+siesta: Stress tensor (static) (eV/Ang**3):
1326+siesta: -0.002134 0.000000 -0.000000
1327+siesta: 0.000000 -0.000556 -0.000000
1328+siesta: 0.000000 0.000000 -0.000724
1329+
1330+siesta: Cell volume = 262.114919 Ang**3
1331+
1332+siesta: Pressure (static):
1333+siesta: Solid Molecule Units
1334+siesta: 0.00001239 0.00000224 Ry/Bohr**3
1335+siesta: 0.00113783 0.00020528 eV/Ang**3
1336+siesta: 1.82302327 0.32889750 kBar
1337+(Free)E+ p_basis*V_orbitals = -464.513364
1338+(Free)Eharris+ p_basis*V_orbitals = -464.513364
1339+
1340+siesta: Electric dipole (a.u.) = 0.000000 0.657893 0.000000
1341+siesta: Electric dipole (Debye) = 0.000000 1.672200 0.000000
1342+
1343+timer: Elapsed wall time (sec) = 11.961
1344+timer: CPU execution times (sec):
1345+
1346+Routine Calls Time/call Tot.time %
1347+siesta 1 11.909 11.909 100.00
1348+Setup 1 0.365 0.365 3.06
1349+bands 1 0.000 0.000 0.00
1350+KSV_init 1 0.000 0.000 0.00
1351+IterGeom 1 11.539 11.539 96.90
1352+state_init 1 2.127 2.127 17.86
1353+hsparse 1 0.002 0.002 0.02
1354+overlap 1 2.123 2.123 17.83
1355+Setup_H0 1 7.766 7.766 65.22
1356+naefs 2 0.000 0.001 0.00
1357+MolMec 2 0.000 0.000 0.00
1358+kinefsm 2 0.990 1.979 16.62
1359+nlefsm 2 2.848 5.695 47.82
1360+DHSCF_Init 1 0.097 0.097 0.81
1361+DHSCF1 1 0.007 0.007 0.06
1362+INITMESH 1 0.000 0.000 0.00
1363+DHSCF2 1 0.090 0.090 0.75
1364+REMESH 1 0.008 0.008 0.07
1365+REORD 58 0.000 0.006 0.05
1366+PHION 1 0.067 0.067 0.56
1367+COMM_BSC 53 0.000 0.006 0.05
1368+POISON 26 0.007 0.174 1.46
1369+fft 52 0.003 0.152 1.27
1370+IterSCF 24 0.061 1.464 12.29
1371+setup_H 24 0.059 1.420 11.92
1372+DHSCF 25 0.064 1.592 13.37
1373+DHSCF3 25 0.059 1.475 12.38
1374+rhoofd 25 0.029 0.714 6.00
1375+cellXC 25 0.004 0.108 0.90
1376+vmat 25 0.018 0.449 3.77
1377+compute_dm 24 0.001 0.028 0.24
1378+diagon 24 0.001 0.027 0.22
1379+r-eigvec 24 0.001 0.025 0.21
1380+r-buildHS 24 0.000 0.000 0.00
1381+rdiag 24 0.001 0.025 0.21
1382+rdiag1 24 0.000 0.001 0.01
1383+rdiag2 24 0.000 0.002 0.02
1384+rdiag3 24 0.001 0.018 0.15
1385+rdiag4 24 0.000 0.003 0.02
1386+r-buildD 24 0.000 0.001 0.01
1387+MIXER 23 0.000 0.000 0.00
1388+WriteDM 24 0.000 0.010 0.09
1389+PostSCF 1 0.180 0.180 1.51
1390+DHSCF4 1 0.118 0.118 0.99
1391+dfscf 1 0.112 0.112 0.94
1392+overfsm 1 0.001 0.001 0.01
1393+state_analysis 1 0.002 0.002 0.02
1394+siesta_move 1 0.000 0.000 0.00
1395+siesta_analysis 1 0.003 0.003 0.02
1396+optical 1 0.000 0.000 0.00
1397+
1398+>> End of run: 17-JAN-2019 15:47:57
1399+Job completed
1400
1401=== added directory 'Tests/bessel-rich'
1402=== added file 'Tests/bessel-rich/bessel-rich.fdf'
1403--- Tests/bessel-rich/bessel-rich.fdf 1970-01-01 00:00:00 +0000
1404+++ Tests/bessel-rich/bessel-rich.fdf 2019-01-30 13:27:17 +0000
1405@@ -0,0 +1,45 @@
1406+#
1407+# Needs new feature: handling of fewer rc's than nzetas in PAO.Basis block
1408+#
1409+write-ion-plot-files T
1410+#
1411+SystemName Water molecule with various Bessel Orbitals
1412+SystemLabel bessel-rich
1413+NumberofAtoms 7
1414+NumberOfSpecies 4
1415+%block ChemicalSpeciesLabel
1416+ 1 8 O # Species index, atomic number, species label
1417+ 2 1 H
1418+ 3 -100 Bessel
1419+ 4 -100 J
1420+%endblock ChemicalSpeciesLabel
1421+
1422+AtomicCoordinatesFormat Ang
1423+%block AtomicCoordinatesAndAtomicSpecies
1424+ 0.000 0.000 0.000 1
1425+ 0.757 0.586 0.000 2
1426+-0.757 0.586 0.000 2
1427+ 0.3785 0.293 0.000 3
1428+-0.3785 0.293 0.000 3
1429+ 0.3785 0.293 0.000 4
1430+-0.3785 0.293 0.000 4
1431+%endblock AtomicCoordinatesAndAtomicSpecies
1432+
1433+%block PAO.Basis
1434+Bessel 3
1435+ n=1 0 1
1436+ 2.0
1437+ 1.0
1438+ n=2 0 1
1439+ 2.5
1440+ 1.0
1441+ n=3 1 1
1442+ 3.5
1443+ 1.0
1444+J 2 # l-shells
1445+n=2 0 7 # Note new feature: fewer rc's than zetas
1446+ 4.5
1447+n=2 1 3
1448+ 4.5 4.5 5.0
1449+%endblock PAO.Basis
1450+
1451\ No newline at end of file
1452
1453=== added file 'Tests/bessel-rich/bessel-rich.pseudos'
1454--- Tests/bessel-rich/bessel-rich.pseudos 1970-01-01 00:00:00 +0000
1455+++ Tests/bessel-rich/bessel-rich.pseudos 2019-01-30 13:27:17 +0000
1456@@ -0,0 +1,1 @@
1457+H O
1458
1459=== added file 'Tests/bessel-rich/makefile'
1460--- Tests/bessel-rich/makefile 1970-01-01 00:00:00 +0000
1461+++ Tests/bessel-rich/makefile 2019-01-30 13:27:17 +0000
1462@@ -0,0 +1,6 @@
1463+#
1464+# Single-test makefile
1465+#
1466+name=bessel-rich
1467+#
1468+include ../test.mk
1469
1470=== modified file 'version.info'
1471--- version.info 2018-12-19 13:52:34 +0000
1472+++ version.info 2019-01-30 13:27:17 +0000
1473@@ -1,1 +1,4 @@
1474-siesta-4.0--589
1475+siesta-4.0--589--n-fix-5--semic-5
1476+
1477+
1478+

Subscribers

People subscribed via source and target branches