Merge lp:~albertog/siesta/4.0-n-fix into lp:siesta/4.0

Proposed by Alberto Garcia
Status: Superseded
Proposed branch: lp:~albertog/siesta/4.0-n-fix
Merge into: lp:siesta/4.0
Diff against target: 1246 lines (+985/-57)
11 files modified
Docs/siesta.tex (+5/-1)
Src/atom.F (+63/-45)
Src/basis_specs.f (+14/-3)
Src/basis_types.f (+18/-0)
Src/old_atmfuncs.f (+13/-6)
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 (+2/-1)
To merge this branch: bzr merge lp:~albertog/siesta/4.0-n-fix
Reviewer Review Type Date Requested Status
Nick Papior Approve
Yann Pouillon (community) Approve
Javier Junquera Pending
Review via email: mp+361644@code.launchpad.net

Commit message

  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').

To post a comment you must log in.
Revision history for this message
Alberto Garcia (albertog) wrote :

This is the fix for the 4.0 branch. 4.1 is similar, but trunk needs slightly different logic.
I will propagate the fix once you approve this merge.

Revision history for this message
Alberto Garcia (albertog) wrote :

I have added Nick as reviewer to get feedback on the way to present the impact on analysis tools (and to check whether anything else might have been affected)

Revision history for this message
Yann Pouillon (pouillon) wrote :

Ok for me.

review: Approve
Revision history for this message
Nick Papior (nickpapior) wrote :

LGTM.

One comment.
For bessel-functions there is an inconsistency in that one can request an "n" quantum number, but it is not used and thus *always* prints out n=1 in the PDOS or other meta-data.

This may be confusing for users, consider e.g. this PAO.Basis block:

J 2 # l-shells
 n=2 0 1
   14.5
 n=2 1 1
   14.5

Above is just a place-holder for future!

review: Approve
Revision history for this message
Nick Papior (nickpapior) wrote :

PS. I ran some calculations using 4.0 and 4.0-n-fix with Bessel functions just to be sure nothing changed. So all is fine.

PPS. @Yann, as we discussed in Dublin, these Bessel + floating orbitals should be handled with care in the hybrid implementation. :)

PPPS. Should the hybrid implementation disallow synthetic atoms?

Revision history for this message
Javier Junquera (javier-junquera) wrote :

 I also approve the changes.
 They also run properly for the cases I have tested.

 Javier

> El 15 ene 2019, a las 12:52, Nick Papior <email address hidden> escribió:
>
> PS. I ran some calculations using 4.0 and 4.0-n-fix with Bessel functions just to be sure nothing changed. So all is fine.
>
> PPS. @Yann, as we discussed in Dublin, these Bessel + floating orbitals should be handled with care in the hybrid implementation. :)
>
> PPPS. Should the hybrid implementation disallow synthetic atoms?
> --
> https://code.launchpad.net/~albertog/siesta/4.0-n-fix/+merge/361644
> You are requested to review the proposed merge of lp:~albertog/siesta/4.0-n-fix into lp:siesta/4.0.

  <http://web.unican.es/> <http://web.unican.es/departamentos/citimac/>
Javier Junquera
Profesor Titular de Universidad
Departamento de Ciencias de la Tierra y Física de la Materia Condensada
Facultad de Ciencias​
Avda. de los Castros, s/n. 39005 Santander
UNIVERSIDAD DE CANTABRIA
  <http://personales.unican.es/junqueraj> <https://es-es.facebook.com/universidaddecantabria> <https://twitter.com/2nd_principles>
Tel. + 34 942 20 15 16
Email: <email address hidden> <mailto:<email address hidden>>
 Antes de imprimir este mensaje, asegúrate de que es necesario. Proteger el medio ambiente está en tus manos.

lp:~albertog/siesta/4.0-n-fix updated
592. By Alberto Garcia

Add better info for Bessel states

* Include the atomic label in header output.
* Warn about internal 'n' quantum number changes.

593. By Alberto Garcia

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).

594. By Alberto Garcia

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, and the previous
patches' Bessel extensions.

Unmerged revisions

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

Subscribers

People subscribed via source and target branches