Merge lp:~nickpapior/siesta/4.1-init-DM into lp:siesta/4.1

Proposed by Nick Papior
Status: Merged
Merge reported by: Nick Papior
Merged at revision: not available
Proposed branch: lp:~nickpapior/siesta/4.1-init-DM
Merge into: lp:siesta/4.1
Diff against target: 278 lines (+189/-19) (has conflicts)
3 files modified
Docs/siesta.tex (+41/-0)
Src/m_new_dm.F90 (+144/-19)
version.info (+4/-0)
Text conflict in version.info
To merge this branch: bzr merge lp:~nickpapior/siesta/4.1-init-DM
Reviewer Review Type Date Requested Status
Alberto Garcia Pending
Review via email: mp+372254@code.launchpad.net

Commit message

Added a new initialization method for DM

The current DM initialization *only* specifies the charge
on the truly diagonal DM entries. I.e. io == col(ind).
However, if one considers that atomic charges are actually
atomic *states* i.e. a state-vector with element in the
diagonal one will also get DM entries in off-diagonal
but io - 1 == col(ind) % no_u which is probably more correct.

I have added two new methods for DM initialization:

1. The DM.Init flag determines one of these methods:
   a) atomic
      the default on-site only atomic density
   b) expand to a state with on-site density
      This enables small auxiliary cell calculations
      to have the density spread amongst overlapping
      orbitals.
      In some systems this seem to behave better
      (graphite/graphene) whereas others it doesn't
      (si64).

2. Added DM.Init.RandomStates <integer> to remove
   N electrons from the initial density matrix
   and add N electrons using a randomized state.
   This state is ensured to be in the non-orthogonal
   basis but is not necessarily orthogonal to any
   other state generated (nor will it be orthogonal
   to the atomic states).
   Currently this method scales orbital coefficients with
   the atomic charges. This will match the atomic charges to
   some degree.
   This is done to limit randoized states with charge in
   high-lying shells which seems dubious in many cases.
   Generally this does not work too good, but may be good
   in some cases I don't know off.

Currently the defaults are as they have always been, but
perhaps the atomic-state would be good in the future?
This needs more heuristics.

Description of the change

I have tried atomic vs. atomic-state on the following tests:

The numbers shows the number of SCF steps needed to converge and the first step dDmax, dHmax

graphite_c6:
atomic: 9, 1.879391, 1.748376
atomic-state: 7, 1.568393, 0.207440

batio3:
atomic: 19, 1.961004, 22.268878
atomic-state: 21, 2.144922, 20.791337

sic-slab:
COMMENT: fun-fact, the SCF cycle indicates that atomic-states is better, but then suddenly atomic converges faster at iSCF 46! History has lots to say here since there is an electric field in this example.
atomic: 69, 1.746005, 13.382736
atomic-state: 144, 2.007246, 13.363516

nanotube-c-5-0:
atomic: 11, 0.741924, 4.242417
atomic-state: 11, 2.037193, 4.270371

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

I am trying to understand this a bit better.

The initial DM is used to compute the first H, but *only* the charge density computed from that DM is relevant (H0 does not use the DM, and dhscf only uses rho(r)). The initial charge density then
is the key for initialization. Currently the heuristic is that a superposition of atomic charges is an appropriate method. To improve on that we would need some extra heuristics about how bonding effects in that particular system might influence the charge density. But this cannot be guessed simply from manipulation of 'atomic' concepts.

Does your alternate method give as starting rho(r) the same atomic-charges superposition? I guess not, since the convergence results are different. So you are changing the charge heuristic, but not in a physical way, so I think that the results will be erratic and depend very much on whether your trick leads to a "closer" rho(r) for a particular system.

Besides this, the initial DM will indeed have an influence on the delta_DM found after the first scf step. For example, the 'diagonal' method disregards the nzeta-1 orbitals beyond the first in DM_in, and these are likely to be occupied in DM_out. But delta_DM(scf=1) should be discarded anyway if we are not mixing in the first scf step, as is the case when using atomic initialization.

There are other possibilites for a more targeted initialization: one could extract from a set of calculations in the same or similar system some kind of "deformation charge" estimate and add it to the initial charge density. Note that this is already implemented, but not really well explored.

Or a "physically motivated" initial H could be read. Maybe an extended-Hückel form.

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

1. Agreed on your first paragraph.

2. Regarding the 2nd paragraph.
The *diagonal* Currently the initial DM is made from *only* diagonal elements in the DM. I.e. for supercell systems where orbital io connects with mirror io only io, io is initialized.
For my *state* option the DM is populated as though the identity matrix is the set of eigenvectors (rescaled for the non-orthogonal basis). And thus in this case one will find DM values in both io, io, AND io, mirror io.
My main motivation was that an eigenstate with {1,0,0,0,...} would expand to also mirror io couplings as for calculations without auxiliary supercells.
Do you think this is *very* unphysical? If so then non-auxiliary supercells should always be turned off for diagonal indices since this leads to non atomic initial DM charges. This is substantiated by the sic-slab calculation performed in 3 different settings (in all cases the SCF has only the Gamma-point):
diagonal-forced-auxiliary: 83, 1.820250, 13.346312
diagonal-no-auxiliary: 96, 1.767353, 13.326340
state-forced-auxiliary: 139, 1.767353, 13.326336

Here it can be seen that the initial DM change for the diagonal-no-auxiliary vs. state-forced-auxiliary are the same (as expected via the above).

3. This was my *first* and most basic attempt to try and investigate implications of initial DM. As I have told you previously this could be moved to sisl (I have tried this with success) to do more advanced things quicker, but for now I thought that these would be nice to have for certain cases.
Note that my implementation for *randomized* states was inspired by PW codes which does this (apparently with great success?) and hence I thought it could be used as well here. However, they are much worse, but sometimes using 1 randomized state helps...

4. Agreed that some better heuristic and more thorough investigations could be needed here.

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

I was trying to frame the issue in a more general setting to understand it better.
And my "unphysical" label refers just to not including system-specific 'bonding' effects.

From what you say I might have missed an important more concrete point: is the current
algorithm not giving atomic-charge superpositions in all cases?
I thought we had fixed this (in a zeroth order approximation) in rev 576 of 4.0, which deals with the (arguably pathological) case of severe folding (diagonal images) and gamma-point.

Are there any other cases in which rho(r)[DM_initial] is not a perfect superposition of atomic charges?

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

1. Ok :)

2. No, the current algorithm will *not* give atomic-only-charges IFF 1) the auxiliary is not used AND 2) if the cell is so small that orbitals have interactions with its own mirror orbitals (diagonal images).

If we always *only* want atomic-only charges (i.e. no supercell image overlap charges), then my state solution should not go in.

3. Let me however note that rarely would people do NO k-point sampling for cells needing an auxiliary supercell.

This is probably also a notice for us to consider why we get different results (in SCF cycles) for small cells with/without auxiliary supercells.

lp:~nickpapior/siesta/4.1-init-DM updated
1114. By Nick Papior

Removed the atomic-state method which should never be used

Retained the randomized initialization for experimental
use.

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

Merged on GitLab.

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 2019-08-22 07:58:14 +0000
3+++ Docs/siesta.tex 2019-09-19 13:04:58 +0000
4@@ -5149,6 +5149,25 @@
5
6 \end{fdflogicalF}
7
8+\begin{fdfentry}{DM!Init}<atomic>
9+ \index{spin!initialization}%
10+
11+ Specify the initial density matrix composition. All these methods
12+ also obey \fdf{DM!InitSpin!AF}.
13+
14+ \begin{fdfoptions}
15+
16+ \option[atomic]%
17+ \fdfindex*{DM!Init!atomic}
18+
19+ Only initialize the diagonal (on-site) density matrices according
20+ to the initial charges on the atomic orbital.
21+
22+ \end{fdfoptions}
23+
24+\end{fdfentry}
25+
26+
27 \begin{fdflogicalF}{DM!InitSpin!AF}
28 \index{spin!initialization}%
29 \index{ferromagnetic initial DM}%
30@@ -5205,6 +5224,28 @@
31
32 \end{fdfentry}
33
34+\begin{fdfentry}{DM!Init.RandomStates}[integer]<0>
35+
36+ Randomize $N$ number of states in the initial density-matrix. This
37+ may be useful to give the system an initial kick. The randomized
38+ states only has coefficients where the initial atomic charges are
39+ non-zero. This prohibits initial charges in high-lying shells.
40+
41+ This only has an effect if the density matrix is started from an
42+ atomic density and/or when using \fdf{DM!InitSpin}.
43+
44+ In case it is used together with \fdf{DM!InitSpin} it also
45+ randomizes the spin-configuration which may be undesirable.
46+
47+ \note this is currently experimental since the randomized states are
48+ not ensured orthogonal. This flag may be removed in later
49+ revisions with some super seeding functions. If testing this, start
50+ with a value of $1$ to see if it has an effect, any higher numbers
51+ will probably be worse.
52+
53+\end{fdfentry}
54+
55+
56 \begin{fdflogicalT}{DM!AllowReuse}
57
58 Controls whether density matrix information from previous geometry
59
60=== modified file 'Src/m_new_dm.F90'
61--- Src/m_new_dm.F90 2019-08-22 07:58:14 +0000
62+++ Src/m_new_dm.F90 2019-09-19 13:04:58 +0000
63@@ -935,6 +935,8 @@
64
65 ! *** Local variables
66 type(block_fdf) :: bfdf
67+ character(len=32) :: method
68+ integer :: i_method ! 1 == atomic
69 logical :: init_spin_block
70 type(dData2D) :: arr_2D
71 ! The pointers for the sparse pattern
72@@ -942,14 +944,21 @@
73 integer :: io, gio, i, ind, jo
74 integer, pointer :: ncol(:), ptr(:), col(:)
75 real(dp), pointer :: DM(:,:)
76+
77+ method = fdf_get('DM.Init', 'atomic')
78+ if ( leqi(method, 'atomic') ) then
79+ i_method = 1
80+ else
81+ call die('m_new_dm: erroneous option: DM.Init [atomic]')
82+ end if
83
84 ! First we need to figure out the options
85 if ( spin%DM > 1 ) then
86- init_spin_block = fdf_block('DM.InitSpin', bfdf)
87+ init_spin_block = fdf_block('DM.InitSpin', bfdf)
88 else
89- ! Do not read the initspin block in case of
90- ! non-polarized calculation
91- init_spin_block = .false.
92+ ! Do not read the initspin block in case of
93+ ! non-polarized calculation
94+ init_spin_block = .false.
95 end if
96
97 ! Retrieve pointers to data
98@@ -963,10 +972,10 @@
99 call delete(arr_2D)
100 DM => val(DM_2D)
101
102- if ( .not. init_spin_block ) then
103- call init_atomic()
104- else
105- call init_user()
106+ if ( init_spin_block ) then
107+ call init_user()
108+ else if ( i_method == 1 ) then
109+ call init_atomic()
110 end if
111
112 ! We have initialized with atomic information. Correct in case we
113@@ -975,18 +984,27 @@
114 ! Gamma-point only. Otherwise S(diagonal) is always 1.0 and the
115 ! simple atomic-orbital superposition works as intended.
116
117+ if ( init_spin_block .or. i_method == 1 ) then
118+
119 do io = 1, no_l
120- ! Retrieve global orbital index
121- gio = index_local_to_global(dit, io)
122- do i = 1 , ncol(io)
123- ind = ptr(io) + i
124- jo = col(ind)
125- ! Check for diagonal element
126- if ( gio == jo ) then
127- DM(ind,:) = DM(ind,:) / S(ind)
128- endif
129- end do
130+ ! Retrieve global orbital index
131+ gio = index_local_to_global(dit, io)
132+ do i = 1 , ncol(io)
133+ ind = ptr(io) + i
134+ jo = col(ind)
135+ ! Check for diagonal element
136+ if ( gio == jo ) then
137+ DM(ind,:) = DM(ind,:) / S(ind)
138+ endif
139+ end do
140 end do
141+
142+ end if
143+
144+ ! Check if we should randomize some states
145+ ! The default is *no* states are randomized
146+ ! Also, this method does not obey anti-ferro!
147+ call init_randomize()
148
149 contains
150
151@@ -1346,9 +1364,116 @@
152
153 end subroutine init_user
154
155+ subroutine init_randomize()
156+
157+ use parallel, only: Node
158+ use geom_helper, only: ucorb
159+#ifdef MPI
160+ use mpi_siesta
161+#endif
162+
163+ integer :: io, gio, i, ind, jo, i1, i2
164+ integer :: n_random, ir
165+ real(dp), allocatable :: rs(:)
166+ real(dp) :: qtot, qinit, scale
167+#ifdef MPI
168+ integer :: ierr
169+#endif
170+
171+ n_random = fdf_get('DM.Init.RandomStates', 0)
172+
173+ ! If the user does not request any randomization, simply return
174+ if ( n_random == 0 ) return
175+
176+ ! Calculate the number of charges in the current DM (this will be our target!)
177+ qtot = 0._dp
178+ do i2 = 1 , spin%DM
179+ do i1 = 1 , nnz
180+ qtot = qtot + DM(i1,i2) * S(i1)
181+ end do
182+ end do
183+#ifdef MPI
184+ call MPI_AllReduce(qtot, qinit, 1, mpi_double_precision, MPI_SUM, &
185+ MPI_COMM_WORLD, ierr)
186+ qtot = qinit
187+#endif
188+
189+ ! Truncate number of random states (NOT nint)
190+ if ( qtot < n_random ) n_random = int(qtot)
191+
192+ ! Calculate the target *initial DM*
193+ qinit = qtot - n_random
194+ scale = qinit / qtot
195+
196+ ! Rescale DM to remove n_random electrons
197+ do i2 = 1 , spin%spinor
198+ do i1 = 1 , nnz
199+ DM(i1,i2) = DM(i1,i2) * scale
200+ end do
201+ end do
202+
203+ ! Allocate for random states
204+ ! TODO allocate all states and make them orthogonal
205+ allocate(rs(no_u))
206+
207+ do ir = 1, n_random
208+
209+ if ( Node == 0 ) then
210+ call random_number(rs)
211+ ! Scale with atomic weights to not have *random* states
212+ ! on, say, f-shells ;)
213+ do io = 1 , no_u
214+ rs(io) = (rs(io) - 0.5_dp) * DM_atom(io)
215+ end do
216+ end if
217+#ifdef MPI
218+ call MPI_Bcast(rs,no_u,MPI_Double_Precision,0,Mpi_Comm_World,ierr)
219+#endif
220+
221+ ! Calculate inner product to rescale for 1 electron for this state
222+ scale = 0._dp
223+ do io = 1, no_l
224+ gio = index_local_to_global(dit, io)
225+ do ind = ptr(io) + 1 , ptr(io) + ncol(io)
226+ jo = ucorb(col(ind), no_u)
227+ scale = scale + rs(gio) * S(ind) * rs(jo)
228+ end do
229+ end do
230+#ifdef MPI
231+ call MPI_AllReduce(scale, qinit, 1, mpi_double_precision, MPI_SUM, &
232+ MPI_COMM_WORLD, ierr)
233+ scale = qinit
234+#endif
235+ ! Inner product value for getting a charge of 1
236+ scale = sqrt(scale)
237+ if ( spin%spinor > 1 ) then
238+ ! Same state for spin-up/down
239+ rs(:) = rs(:) / (scale * 2)
240+ else
241+ rs(:) = rs(:) / scale
242+ end if
243+
244+ do io = 1, no_l
245+ gio = index_local_to_global(dit, io)
246+ do ind = ptr(io) + 1 , ptr(io) + ncol(io)
247+ jo = ucorb(col(ind), no_u)
248+ DM(ind,1:spin%spinor) = DM(ind,1:spin%spinor) + rs(gio) * rs(jo)
249+ end do
250+ end do
251+ end do
252+
253+ ! Clean-up
254+ deallocate(rs)
255+
256+ if ( IONode ) then
257+ write(*,'(a,i0,a)') 'DM randomized ', n_random, ' states'
258+ end if
259+
260+ end subroutine init_randomize
261+
262 end subroutine init_DM_atomic
263
264-
265+
266 subroutine extrapolate_dm_with_coords(DM_history,na_u,xa,sparse_pattern,DMnew)
267 use class_Sparsity
268 use class_dData2D
269
270=== modified file 'version.info'
271--- version.info 2019-09-19 12:58:46 +0000
272+++ version.info 2019-09-19 13:04:58 +0000
273@@ -1,1 +1,5 @@
274+<<<<<<< TREE
275 siesta-4.1-1120
276+=======
277+siesta-4.1-1112--init-DM-2
278+>>>>>>> MERGE-SOURCE

Subscribers

People subscribed via source and target branches