Merge lp:~albertog/siesta/4.0-images-2 into lp:siesta/4.0

Proposed by Alberto Garcia
Status: Merged
Merged at revision: 576
Proposed branch: lp:~albertog/siesta/4.0-images-2
Merge into: lp:siesta/4.0
Diff against target: 686 lines (+179/-135) (has conflicts)
19 files modified
Docs/siesta.tex (+36/-9)
Src/Makefile (+1/-2)
Src/hsparse.F (+53/-77)
Src/new_dm.F (+20/-1)
Src/state_init.F (+50/-8)
Tests/born/born.fdf (+0/-3)
Tests/born_spin/born_spin.fdf (+0/-4)
Tests/force_2/force_2.fdf (+0/-4)
Tests/force_constants/force_constants.fdf (+0/-4)
Tests/graphite_c6/graphite_c6.fdf (+0/-2)
Tests/md_anneal/md_anneal.fdf (+2/-3)
Tests/md_nose/md_nose.fdf (+2/-3)
Tests/md_npr/md_npr.fdf (+2/-3)
Tests/md_pr/md_pr.fdf (+2/-3)
Tests/md_verlet/md_verlet.fdf (+2/-3)
Tests/sih_fire/sih_fire.fdf (+0/-2)
Tests/var_cell/var_cell.fdf (+2/-3)
Tests/zmatrix/zmatrix.fdf (+0/-1)
version.info (+7/-0)
Text conflict in version.info
To merge this branch: bzr merge lp:~albertog/siesta/4.0-images-2
Reviewer Review Type Date Requested Status
Nick Papior Approve
Review via email: mp+345362@code.launchpad.net

This proposal supersedes a proposal from 2018-05-08.

Commit message

(See individual commit messages)

Description of the change

Two initial independent changes:

1. The fix for the "severe folding" leading to wrong norm of the DM initialized by atomic data.
2. A saner hsparse.

Plus:

* Detection of the "severe folding" (called "diagonal_folding") in hsparse (by checking for sameness of io and jo). Harris runs with severe folding is not permitted.

* Removal of Harris option in tests.

* Update to the manual (pending removal of two obsolete auxiliary-cell options)

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

For Harris-functional calculations, severe folding is just plain crazy, as there is no time to smooth out the initial differences. We should remove the Harris option from the force_2 test.

In general, we should remove tests with non-physically small cells with gamma point (or at least flag them as showcases for the problems).

Revision history for this message
Nick Papior (nickpapior) wrote : Posted in a previous version of this proposal

Could we force the auxiliary cell for Harris functional?

1) I think very few people are using it,
2) The overhead is negligeble in this case.

Revision history for this message
Nick Papior (nickpapior) : Posted in a previous version of this proposal
review: Approve
Revision history for this message
Nick Papior (nickpapior) wrote : Posted in a previous version of this proposal

There are 2 directions to your listh_fold.

1) The indxuo is *ALWAYS* a linear array ((io,io=1:no),i_s=1:product(nsc)). So the listh_fold is unnecessary. Indxuo is also always available.
2) Since the above is valid the UCORB function in geom_helper.f90 is equivalent to the INDXUO array.

Maybe I don't get the listh_fold? Would you create a 3rd array?

Revision history for this message
Alberto Garcia (albertog) wrote : Posted in a previous version of this proposal

We are going to re-think the diagk0 issue.
I will re-submit with a different branch.

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

I have not updated the Reference outputs.

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

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-04-24 08:40:31 +0000
3+++ Docs/siesta.tex 2018-05-10 13:49:56 +0000
4@@ -3044,6 +3044,7 @@
5 MaxSCFIterations, SCFMustConverge and DM.MixSCF1 are automatically set
6 up to False, 1, False and False respectively, no matter whatever other
7 specification are in the INPUT file.
8+
9 \end{itemize}
10
11 {\it Default value:} {\tt .false.}
12@@ -4184,20 +4185,32 @@
13 the matrix elements involving orbitals in different unit cells.
14 It is computed automatically by the program at every geometry step.
15
16+Note that for gamma-point-only calculations there is an implicit
17+``folding'' of matrix elements corresponding to the images of orbitals
18+outside the unit cell. If information about the specific values of
19+these matrix elements is needed (as for COOP/COHP analysis), one has
20+to make sure that the unit cell is large enough, or force the use
21+of an aunxiliary supercell.
22+\index{COOP/COHP curves!Folding in Gamma-point calculations}
23+
24 \begin{description}
25
26 \item[{\bf FixAuxiliaryCell}] ({\it logical}):
27 \index{FixAuxiliaryCell@{\bf FixAuxiliaryCell}}
28
29 Logical variable to control whether the auxiliary cell is changed
30-during a variable cell optimization.
31+during a variable cell optimization. If this option is used, care
32+should be taken that the supercell is appropriate for the whole
33+duration of the run.
34+
35+{\it Default value:} {\tt .false.}
36
37 \item[{\bf NaiveAuxiliaryCell}] ({\it logical}):
38 \index{NaiveAuxiliaryCell@{\bf NaiveAuxiliaryCell}}
39
40 If true, the program does not check whether the auxiliary cell
41-constructed with a naive algorithm is appropriate. This variable is
42-only useful if one wishes to reproduce calculations done with previous
43+constructed with a naive algorithm is appropriate. This variable should
44+only be used if one wishes to reproduce calculations done with previous
45 versions of the program in which the auxiliary cell was not large
46 enough, as indicated by warnings such as:
47
48@@ -4205,12 +4218,26 @@
49
50 Only small numerical differences in the results are to be expected.
51
52-Note that for gamma-point-only calculations there is an implicit
53-``folding'' of matrix elements corresponding to the images of orbitals
54-outside the unit cell. If information about the specific values of
55-these matrix elements is needed (as for COOP/COHP analysis), one has
56-to make sure that the unit cell is large enough.
57-\index{COOP/COHP curves!Folding in Gamma-point calculations}
58+{\it Default value:} {\tt .false.}
59+
60+\item[{\bf ForceAuxCell}] ({\it logical}):
61+\index{ForceAuxCell@{\bf ForceAuxCell}}
62+
63+If true, the program uses an auxiliary cell even for gamma-point-only
64+calculations. This might be needed for COOP/COHP calculations, as
65+noted above, \index{COOP/COHP curves!Folding in Gamma-point
66+ calculations} or in degenerate cases, such as when the cell is so
67+small that a given orbital ``self-interacts'' with its own images (via
68+direct overlap or through a KB projector). In this case, the diagonal
69+value of the overlap matrix S for this orbital is different from 1, and an
70+initialization of the DM via atomic data would be faulty. The
71+program corrects the problem to zeroth-order by dividing the DM value
72+by the corresponding overlap matrix entry, but the initial charge
73+density would exhibit distortions from a true atomic superposition
74+(See routine \texttt{new\_dm.F}). The distortion of the charge density
75+is a serious problem for Harris functional calculations, so this
76+option must be enabled for them if self-folding is present. (Note that
77+this should not happen in any serious calculation...)
78
79 {\it Default value:} {\tt .false.}
80
81
82=== modified file 'Src/Makefile'
83--- Src/Makefile 2018-04-11 11:00:02 +0000
84+++ Src/Makefile 2018-05-10 13:49:56 +0000
85@@ -528,8 +528,7 @@
86 grdsam.o: alloc.o dhscf.o files.o m_mpi_utils.o m_partial_charges.o parallel.o
87 grdsam.o: precision.o siesta_geom.o siesta_options.o sys.o units.o
88 hsparse.o: alloc.o atm_types.o atmfuncs.o atomlist.o listsc.o mneighb.o
89-hsparse.o: parallel.o parallelsubs.o precision.o siesta_options.o sorting.o
90-hsparse.o: sparse_matrices.o sys.o
91+hsparse.o: parallel.o parallelsubs.o precision.o sorting.o sparse_matrices.o
92 idiag.o: parallel.o sys.o
93 initatom.o: atmparams.o atom.o atom_options.o basis_io.o basis_specs.o
94 initatom.o: basis_types.o electrostatic.o old_atmfuncs.o precision.o
95
96=== modified file 'Src/hsparse.F'
97--- Src/hsparse.F 2016-01-25 16:00:16 +0000
98+++ Src/hsparse.F 2018-05-10 13:49:56 +0000
99@@ -48,7 +48,8 @@
100 subroutine hsparse( negl, cell, nsc, na, isa, xa,
101 & lasto, lastkb, iphorb, iphkb,
102 & nlhmax, gamma,
103- $ set_xijo, folding)
104+ $ set_xijo, folding,
105+ $ diagonal_folding, debug_folding)
106
107 use precision
108 use parallel, only : Node, Nodes
109@@ -59,9 +60,8 @@
110 use sorting
111 use neighbour, only : jna=>jan, xij, r2ij, maxna=>maxnna
112 use neighbour, only : mneighb, reset_neighbour_arrays
113- use sys, only : die
114 use alloc, only : re_alloc, de_alloc
115- use atomlist, only : no_l
116+ use atomlist, only : no_l, indxuo
117 use sparse_matrices, only : listhptr, numh, listh, xijo
118 implicit none
119
120@@ -76,6 +76,8 @@
121 logical, intent(in) :: gamma
122 logical, intent(in) :: set_xijo
123 logical, intent(out) :: folding
124+ logical, intent(out) :: diagonal_folding
125+ logical, intent(in), optional :: debug_folding
126
127 external timer
128
129@@ -99,8 +101,6 @@
130 & rci, rcj, rck, rij, rik, rjk,
131 & rmax, rmaxkb, rmaxo
132
133- logical, save :: warn1 = .false.
134-
135 real(dp), dimension(:), pointer :: rckb
136 logical, dimension(:), pointer :: conect
137 integer, dimension(:), pointer :: index
138@@ -108,14 +108,18 @@
139 integer, dimension(:), pointer :: listhtmp
140
141 logical :: connected
142-
143+ logical :: debug
144+ integer :: nprints ! for debugging
145 C -------------------------------------
146-#ifdef DEBUG
147- call write_debug( ' PRE hsparse' )
148-#endif
149+
150 C Start time counter
151 call timer( 'hsparse', 1 )
152
153+ debug = .false.
154+ if (present(debug_folding)) then
155+ debug = debug_folding
156+ endif
157+
158 C Check size of internal arrays
159 ncells = nsc(1) * nsc(2) * nsc(3)
160 nua = na / ncells
161@@ -192,6 +196,7 @@
162 enddo
163
164 folding = .false.
165+ diagonal_folding = .false.
166
167 C------------------------------------C
168 C Find number of non-zeros in H C
169@@ -324,6 +329,7 @@
170 C------------------------------------C
171 C Find full H sparsity pattern C
172 C------------------------------------C
173+ nprints = 0
174 C Loop on atoms in unit cell
175 do ia = 1,nua
176 C Find neighbour atoms within maximum range
177@@ -396,62 +402,53 @@
178 endif
179
180 if (connected) then
181- if (conect(jo)) then
182- folding = .true.
183-
184- ! This test is now deferred to be able
185- ! to catch multiple images while avoiding
186- ! false positives (i.e., we test first
187- ! whether there is indeed a connection).
188-
189- if (.true.) then
190- ! If already connected and using supercell,
191- ! the latter might not be big enough...
192- ! We warn the user and keep the first instance
193+ if (conect(jo)) then
194+ folding = .true.
195+ if (io == indxuo(jo)) then
196+ diagonal_folding = .true.
197+ endif
198+
199+ ! If already connected and using supercell, the
200+ ! latter might not be big enough... We defer
201+ ! the decision on whether to kill the program
202+ ! to the caller. Here keep the first instance
203 ! of xij (same behavior as the old xijorb, as
204 ! earlier jnats are closer)
205- ! Warn also if Gamma-point calculation, just
206- ! in case
207- if (.not.warn1) then
208- if (Node.eq.0) then
209- if (gamma) then
210- call check_cohp(io,jo)
211- else
212- write(6,'(/,a,2i6,a,/,a)')
213- . 'WARNING: orbital pair ',io,jo,
214+ if (debug) then
215+ ! This might not be pretty in
216+ ! parallel. Better to build a list of a few
217+ ! cases, and pass it to the caller.
218+ if (nprints <= 20) then
219+ print "(a,2i6,a)",
220+ . 'WARNING: orbital pair ',io,indxuo(jo),
221 . ' is multiply connected'
222- endif
223+ nprints = nprints + 1
224 endif
225- warn1 = .true.
226- endif
227- endif
228-
229- else
230-
231- conect(jo) = .true.
232- numh(iio) = numh(iio) + 1
233- ind = listhptr(iio)+numh(iio)
234- listh(ind) = jo
235- if (set_xijo) then
236- xijo(1:3,ind) = xij(1:3,jnat)
237+ endif
238+
239+ else
240+
241+ conect(jo) = .true.
242+ numh(iio) = numh(iio) + 1
243+ ind = listhptr(iio)+numh(iio)
244+ listh(ind) = jo
245+ if (set_xijo) then
246+ xijo(1:3,ind) = xij(1:3,jnat)
247+ endif
248 endif
249 endif
250- endif
251+ enddo
252 enddo
253- enddo
254
255 C Restore conect array for next orbital io
256- do j = 1,numh(iio)
257- jo = listh(listhptr(iio)+j)
258- conect(jo) = .false.
259- enddo
260- endif ! iio > 0
261- enddo ! io
262- enddo ! ia
263+ do j = 1,numh(iio)
264+ jo = listh(listhptr(iio)+j)
265+ conect(jo) = .false.
266+ enddo
267+ endif ! iio > 0
268+ enddo ! io
269+ enddo ! ia
270
271-!! print "(a5,i3,a40,3i8)",
272-!! $ "Node: ", Node, "in hsparse nuo, nuotot, nlhmax: ",
273-!! $ nuo, nuotot, nlhmax
274
275 C Initialize listsc
276 call LISTSC_INIT( nsc, nuotot )
277@@ -466,28 +463,7 @@
278 call de_alloc( rckb, 'rckb', 'hsparse' )
279
280 call timer( 'hsparse', 2 )
281-#ifdef DEBUG
282- call write_debug( ' POS hsparse' )
283-#endif
284+
285 end subroutine hsparse
286-
287- subroutine check_cohp(io,jo)
288- use siesta_options, only: write_coop
289-
290- integer, intent(in) :: io, jo
291-
292- if (write_coop) then
293- write(6,'(/,a,2i6,a,/,a)')
294- . 'NOTE: orbital pair ',io,jo,
295- . ' (at least) is multiply connected.',
296- . 'NOTE: Your COOP/COHP analysis might ' //
297- $ 'be affected by folding.'
298- write(0,'(/,a,2i6,a,/,a)')
299- . 'NOTE: orbital pair ',io,jo,
300- . ' (at least) is multiply connected.',
301- . 'NOTE: Your COOP/COHP analysis might ' //
302- $ 'be affected by folding.'
303- endif
304- end subroutine check_cohp
305
306 end module m_hsparse
307
308=== modified file 'Src/new_dm.F'
309--- Src/new_dm.F 2018-04-06 12:32:04 +0000
310+++ Src/new_dm.F 2018-05-10 13:49:56 +0000
311@@ -485,6 +485,7 @@
312 use mpi_siesta
313 #endif
314 use units, only : pi
315+ use sparse_matrices, only: S
316
317 implicit none
318
319@@ -655,7 +656,7 @@
320 endif
321
322
323- else
324+ else ! Initialize with neutral atoms
325
326 C See whether specific initial spins are given in a DM.InitSpin block
327 C and read them in a loop on atoms where lines are read and parsed
328@@ -903,6 +904,24 @@
329
330 endif
331
332+ ! We have initialized with atomic information. Correct in case we
333+ ! are using such a small cell that there are direct interactions
334+ ! of orbitals with their own images, and we insist on using the
335+ ! Gamma-point only. Otherwise S(diagonal) is always 1.0 and the
336+ ! simple atomic-orbital superposition works as intended.
337+
338+
339+ do io = 1, no_l
340+ call LocalToGlobalOrb(io,Node,Nodes,iio)
341+ do in = 1,numh(io)
342+ ind = listhptr(io)+in
343+ jo = listh(ind)
344+ if (iio .eq. jo) then ! diagonal element
345+ Dscf(ind,:) = Dscf(ind,:) / S(ind)
346+ endif
347+ enddo
348+ enddo
349+
350 endif
351
352 end subroutine initdm
353
354=== modified file 'Src/state_init.F'
355--- Src/state_init.F 2018-04-11 09:23:27 +0000
356+++ Src/state_init.F 2018-05-10 13:49:56 +0000
357@@ -48,7 +48,8 @@
358 use m_mpi_utils, only: globalize_or
359 use m_mpi_utils, only: globalize_sum
360 use domain_decom, only: domainDecom, use_dd, use_dd_perm
361-
362+ use fdf, only: fdf_get
363+ use sys, only: message, die
364 #ifdef TRANSIESTA
365 use m_ts_options, only : onlyS
366 use sys, only : bye
367@@ -69,6 +70,7 @@
368 integer :: i, ix, iadispl, ixdispl
369 logical :: auxchanged ! Auxiliary supercell changed?
370 logical :: folding, folding1
371+ logical :: diag_folding, diag_folding1
372 logical :: foundxv ! dummy for call to ioxv
373 real(dp) :: dummy_qspin(8)
374 external :: madelung, timer
375@@ -255,7 +257,38 @@
376 ! analyses.
377 call hsparse( negl, scell, nsc, na_s, isa, xa, lasto,
378 & lastkb, iphorb, iphKB, maxnh, gamma,
379- $ set_xijo=.true., folding=folding1)
380+ $ set_xijo=.true., folding=folding1,
381+ $ diagonal_folding=diag_folding1,
382+ $ debug_folding=fdf_get('debug-folding',.false.))
383+!
384+ call globalize_or(diag_folding1,diag_folding)
385+ call globalize_or(folding1,folding)
386+ if (diag_folding .and. gamma) then
387+ call message("WARNING","Gamma-point calculation " //
388+ $ "with interaction between periodic images")
389+ call message("WARNING",
390+ $ "Some features might not work optimally:")
391+ call message("WARNING",
392+ $ "e.g. DM initialization from atomic data")
393+ if (harrisfun) call die("Harris functional run needs " //
394+ $ "'force-aux-cell T'")
395+
396+ else if (folding) then
397+ if (gamma) then
398+ call message("INFO","Gamma-point calculation " //
399+ $ "with multiply-connected orbital pairs")
400+ call message("INFO",
401+ $ "Folding of H and S implicitly performed")
402+ call check_cohp()
403+ else
404+ write(6,"(a,/,a)") "Non Gamma-point calculation " //
405+ $ "with multiply-connected orbital pairs " //
406+ $ "in auxiliary supercell.",
407+ $ "Possible internal error. " //
408+ $ "Use 'debug-folding T' to debug."
409+ call die("Inadequate auxiliary supercell")
410+ endif
411+ endif
412 !
413 call globalize_sum(maxnh,nnz)
414 if (cml_p) then
415@@ -269,12 +302,6 @@
416 call cmlEndPropertyList(mainXML)
417 endif
418 !
419- call globalize_or(folding1,folding)
420- if (folding) then
421- if (IOnode) then
422- print *, "Folding of H and S is implicitly performed"
423- endif
424- endif
425 !
426 ! If using domain decomposition, redistribute orbitals
427 ! for this geometry, based on the hsparse info.
428@@ -387,4 +414,19 @@
429
430 !--------------------------------------------------------------------------- END
431 END subroutine state_init
432+
433+ subroutine check_cohp()
434+ use siesta_options, only: write_coop
435+ use sys, only: message
436+
437+ if (write_coop) then
438+ call message("WARNING","There are multiply-connected "//
439+ $ "orbitals.")
440+ call message("WARNING","Your COOP/COHP analysis might " //
441+ $ "be affected by folding.")
442+ call message("WARNING",'Use "force-aux-cell T "' //
443+ $ 'or k-point sampling')
444+ endif
445+ end subroutine check_cohp
446+
447 END module m_state_init
448
449=== modified file 'Tests/born/born.fdf'
450--- Tests/born/born.fdf 2007-06-05 09:59:21 +0000
451+++ Tests/born/born.fdf 2018-05-10 13:49:56 +0000
452@@ -25,8 +25,5 @@
453 #DM.MixingWeight 0.3
454 #DM.NumberPulay 3
455 #DM.Tolerance 1.0d-5
456-# Here we use Harris since we are just interested in testing the displacement
457-# logic
458
459-HarrisFunctional T
460
461
462=== modified file 'Tests/born_spin/born_spin.fdf'
463--- Tests/born_spin/born_spin.fdf 2007-06-05 09:59:21 +0000
464+++ Tests/born_spin/born_spin.fdf 2018-05-10 13:49:56 +0000
465@@ -26,8 +26,4 @@
466 #DM.MixingWeight 0.3
467 #DM.NumberPulay 3
468 #DM.Tolerance 1.0d-5
469-# Here we use Harris since we are just interested in testing the displacement
470-# logic
471-
472-HarrisFunctional T
473
474
475=== modified file 'Tests/force_2/force_2.fdf'
476--- Tests/force_2/force_2.fdf 2007-11-21 11:45:49 +0000
477+++ Tests/force_2/force_2.fdf 2018-05-10 13:49:56 +0000
478@@ -15,10 +15,6 @@
479 #DM.MixingWeight 0.3
480 #DM.NumberPulay 3
481 #DM.Tolerance 1.0d-5
482-# Here we use Harris since we are just interested in testing the displacement
483-# logic
484-
485-HarrisFunctional T
486
487 %include FC.fdf
488
489
490=== modified file 'Tests/force_constants/force_constants.fdf'
491--- Tests/force_constants/force_constants.fdf 2007-11-21 11:45:49 +0000
492+++ Tests/force_constants/force_constants.fdf 2018-05-10 13:49:56 +0000
493@@ -15,10 +15,6 @@
494 #DM.MixingWeight 0.3
495 #DM.NumberPulay 3
496 #DM.Tolerance 1.0d-5
497-# Here we use Harris since we are just interested in testing the displacement
498-# logic
499-
500-HarrisFunctional T
501
502 %include FC.fdf
503
504
505=== modified file 'Tests/graphite_c6/graphite_c6.fdf'
506--- Tests/graphite_c6/graphite_c6.fdf 2018-04-25 07:34:20 +0000
507+++ Tests/graphite_c6/graphite_c6.fdf 2018-05-10 13:49:56 +0000
508@@ -31,5 +31,3 @@
509 kgrid_cutoff 4.0 Ang
510
511 ElectronicTemperature 0 K
512-
513-HarrisFunctional T
514
515=== modified file 'Tests/md_anneal/md_anneal.fdf'
516--- Tests/md_anneal/md_anneal.fdf 2012-10-24 13:10:17 +0000
517+++ Tests/md_anneal/md_anneal.fdf 2018-05-10 13:49:56 +0000
518@@ -1,10 +1,10 @@
519 # -----------------------------------------------------------------------------
520 # Primitive c-Si supercell, using STRUCT file
521-# Annealing, HarrisFunctional
522+# Annealing
523 # Alberto Garcia, August-December 2005, January 2006
524 # -----------------------------------------------------------------------------
525
526-SystemName Primitive silicon, Annealing, Harris, Struct File
527+SystemName Primitive silicon, Annealing, Struct File
528 SystemLabel md_anneal
529
530 NumberOfAtoms 2
531@@ -27,7 +27,6 @@
532
533 SolutionMethod diagon
534 ElectronicTemperature 100 K
535-HarrisFunctional T
536 WriteMDHistory T
537
538 MD.TypeOfRun anneal
539
540=== modified file 'Tests/md_nose/md_nose.fdf'
541--- Tests/md_nose/md_nose.fdf 2006-02-02 14:00:17 +0000
542+++ Tests/md_nose/md_nose.fdf 2018-05-10 13:49:56 +0000
543@@ -1,7 +1,7 @@
544 #
545-# MgCO3 in primitive cell. SZ Harris. Some MD steps in Nose MD
546+# MgCO3 in primitive cell. SZ. Some MD steps in Nose MD
547 #
548-SystemName MgCo3 MD Nose test -- SZ, 100 Ry Harris
549+SystemName MgCo3 MD Nose test -- SZ, 100 Ry
550 SystemLabel md_nose
551 NumberOfSpecies 3
552 NumberOfAtoms 10
553@@ -37,7 +37,6 @@
554 0.0274 -0.25 -0.5274 3
555 %endblock AtomicCoordinatesAndAtomicSpecies
556
557-HarrisFunctional T
558 Solution.Method diagon
559 MeshCutoff 100 Ry
560
561
562=== modified file 'Tests/md_npr/md_npr.fdf'
563--- Tests/md_npr/md_npr.fdf 2006-01-27 17:09:47 +0000
564+++ Tests/md_npr/md_npr.fdf 2018-05-10 13:49:56 +0000
565@@ -1,7 +1,7 @@
566 #
567-# MgCO3 in primitive cell. SZ. Nose-Parrinello-Rahman. Harris
568+# MgCO3 in primitive cell. SZ. Nose-Parrinello-Rahman.
569 #
570-SystemName MgCo3 R-3c Harris -- SZ, 50 R -- NPR at 10 Gpa, 500K
571+SystemName MgCo3 R-3c -- SZ, 50 R -- NPR at 10 Gpa, 500K
572 SystemLabel md_npr
573 NumberOfSpecies 3
574 NumberOfAtoms 10
575@@ -51,7 +51,6 @@
576
577 WriteCoorStep .true.
578 WriteForces .true.
579-HarrisFunctional T
580
581 WriteMDHistory .true.
582 MD.UseSaveXV T
583
584=== modified file 'Tests/md_pr/md_pr.fdf'
585--- Tests/md_pr/md_pr.fdf 2006-01-27 17:09:47 +0000
586+++ Tests/md_pr/md_pr.fdf 2018-05-10 13:49:56 +0000
587@@ -1,7 +1,7 @@
588 #
589-# MgCO3 in primitive cell. SZ. Parrinello-Rahman. Harris
590+# MgCO3 in primitive cell. SZ. Parrinello-Rahman
591 #
592-SystemName MgCo3 R-3c Harris -- SZ, 50 R -- PR at 10 Gpa
593+SystemName MgCo3 R-3c -- SZ, 50 R -- PR at 10 Gpa
594 SystemLabel md_pr
595 NumberOfSpecies 3
596 NumberOfAtoms 10
597@@ -51,7 +51,6 @@
598
599 WriteCoorStep .true.
600 WriteForces .true.
601-HarrisFunctional T
602
603 WriteMDHistory .true.
604 MD.UseSaveXV T
605
606=== modified file 'Tests/md_verlet/md_verlet.fdf'
607--- Tests/md_verlet/md_verlet.fdf 2006-02-02 14:00:17 +0000
608+++ Tests/md_verlet/md_verlet.fdf 2018-05-10 13:49:56 +0000
609@@ -1,7 +1,7 @@
610 #
611-# MgCO3 in primitive cell. SZ Harris. Some MD steps in Verlet MD
612+# MgCO3 in primitive cell. SZ. Some MD steps in Verlet MD
613 #
614-SystemName MgCo3 MD Verlet test -- SZ, 100 Ry Harris
615+SystemName MgCo3 MD Verlet test -- SZ, 100 Ry
616 SystemLabel md_verlet
617 NumberOfSpecies 3
618 NumberOfAtoms 10
619@@ -37,7 +37,6 @@
620 0.0274 -0.25 -0.5274 3
621 %endblock AtomicCoordinatesAndAtomicSpecies
622
623-HarrisFunctional T
624 Solution.Method diagon
625 MeshCutoff 100 Ry
626
627
628=== modified file 'Tests/sih_fire/sih_fire.fdf'
629--- Tests/sih_fire/sih_fire.fdf 2006-12-11 15:30:16 +0000
630+++ Tests/sih_fire/sih_fire.fdf 2018-05-10 13:49:56 +0000
631@@ -39,8 +39,6 @@
632
633 MeshCutoff 40.0 Ry
634
635-Harris_Functional
636-
637 MaxSCFIterations 50
638 DM.MixingWeight 0.3
639 DM.NumberPulay 3
640
641=== modified file 'Tests/var_cell/var_cell.fdf'
642--- Tests/var_cell/var_cell.fdf 2006-02-12 18:45:29 +0000
643+++ Tests/var_cell/var_cell.fdf 2018-05-10 13:49:56 +0000
644@@ -1,7 +1,7 @@
645 #
646-# MgCO3 in primitive cell. SZ. Variable cell. Harris. Broyden Optim
647+# MgCO3 in primitive cell. SZ. Variable cell. Broyden Optim
648 #
649-SystemName MgCo3 R-3c Harris -- SZ, 100 R -- variable cell at 100 Gpa
650+SystemName MgCo3 R-3c -- SZ, 100 R -- variable cell at 100 Gpa
651 SystemLabel var_cell
652 NumberOfSpecies 3
653 NumberOfAtoms 10
654@@ -51,7 +51,6 @@
655
656 WriteCoorStep .true.
657 WriteForces .true.
658-HarrisFunctional T
659
660 MD.TypeOfRun Broyden
661 MD.Variable-Cell T
662
663=== modified file 'Tests/zmatrix/zmatrix.fdf'
664--- Tests/zmatrix/zmatrix.fdf 2008-10-13 12:44:47 +0000
665+++ Tests/zmatrix/zmatrix.fdf 2018-05-10 13:49:56 +0000
666@@ -35,7 +35,6 @@
667 xc.functional LDA
668 xc.authors PZ
669
670-HarrisFunctional T
671 MD.TypeOfRun CG
672 MD.NumCGsteps 4
673 MD.VariableCell T
674
675=== modified file 'version.info'
676--- version.info 2018-05-07 12:07:29 +0000
677+++ version.info 2018-05-10 13:49:56 +0000
678@@ -1,1 +1,8 @@
679+<<<<<<< TREE
680 siesta-4.0--575
681+=======
682+siesta-4.0--573--folding-579
683+
684+
685+
686+>>>>>>> MERGE-SOURCE

Subscribers

People subscribed via source and target branches