Merge lp:~nickpapior/siesta/merge-OSSO-class into lp:~albertog/siesta/merge-OSSO

Proposed by Nick Papior
Status: Merged
Merged at revision: 701
Proposed branch: lp:~nickpapior/siesta/merge-OSSO-class
Merge into: lp:~albertog/siesta/merge-OSSO
Diff against target: 704 lines (+173/-177)
8 files modified
Src/compute_energies.F90 (+28/-28)
Src/final_H_f_stress.F (+12/-7)
Src/nlefsm.f (+13/-11)
Src/setup_H0.F (+25/-26)
Src/setup_hamiltonian.F (+76/-85)
Src/sparse_matrices.F (+7/-7)
Src/state_init.F (+11/-12)
version.info (+1/-1)
To merge this branch: bzr merge lp:~nickpapior/siesta/merge-OSSO-class
Reviewer Review Type Date Requested Status
Alberto Garcia Approve
Review via email: mp+343801@code.launchpad.net

Commit message

Transferred H0_offsiteSO to H_so_off_2D as a class-object.

Fixed some possible inconsistencies in the conversion between
complex and real/imaginary part without kind specifications.

Clarified usage in setup_hamiltonian. Now the structure has been
re-assigned as prior to the OSSO implementation.

Description of the change

Transferred H0_offsiteSO to H_so_off_2D as a class-object.

Fixed some possible inconsistencies in the conversion between
complex and real/imaginary part without kind specifications.

Clarified usage in setup_hamiltonian. Now the structure has been
re-assigned as prior to the OSSO implementation.

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

Great. Thanks!

review: Approve

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'Src/compute_energies.F90'
2--- Src/compute_energies.F90 2018-04-23 07:36:55 +0000
3+++ Src/compute_energies.F90 2018-04-23 11:10:59 +0000
4@@ -48,8 +48,7 @@
5 rmaxo, no_l
6 use m_ntm, only: ntm
7
8- use m_spin, only: spin
9- use sparse_matrices, only: H0_offsiteSO
10+ use m_spin, only: spin
11 use parallel, only: IONode
12
13 use m_dipol, only: dipol
14@@ -300,10 +299,15 @@
15 use files, only : filesOut_t ! derived type for output file names
16 use class_dSpData1D, only : val
17 use class_dSpData2D, only : val
18- use sparse_matrices, only: H_kin_1D, H_vkb_1D, H_so_2D
19+ use class_zSpData2D, only : val
20+ use sparse_matrices, only: H_kin_1D, H_vkb_1D
21+ use sparse_matrices, only: H_so_on_2D, H_so_off_2D
22+
23
24 type(filesOut_t) :: filesOut ! blank output file names
25- real(dp), pointer :: H_vkb(:), H_kin(:), H_so(:,:)
26+ real(dp), pointer :: H_vkb(:), H_kin(:), H_so_on(:,:)
27+ complex(dp), pointer :: H_so_off(:,:)
28+
29
30 complex(dp) :: Hc, Dc
31 real(dp) :: dummy_stress(3,3), dummy_fa(1,1)
32@@ -356,41 +360,37 @@
33 Eso = 0._dp
34
35 if ( spin%SO_offsite ) then
36+ H_so_off => val(H_so_off_2D)
37
38- ! The computation of the trace is different here, as H0_offsiteSO has
39+ ! The computation of the trace is different here, as H_so_off has
40 ! a different structure from H and the DM.
41 do io = 1, maxnh
42
43 !-------- Eso(u,u)
44- Dc = cmplx(Dscf(io,1),Dscf(io,5),kind=dp)
45- Hc = H0_offsiteSO(io,1)
46- Eso = Eso + real( Hc*Dc )
47+ Dc = cmplx(Dscf(io,1),Dscf(io,5), dp)
48+ Eso = Eso + real( H_so_off(io,1)*Dc, dp)
49 !-------- Eso(d,d)
50- Dc = cmplx(Dscf(io,2),Dscf(io,6),kind=dp)
51- Hc = H0_offsiteSO(io,2)
52- Eso = Eso + real( Hc*Dc )
53+ Dc = cmplx(Dscf(io,2),Dscf(io,6), dp)
54+ Eso = Eso + real( H_so_off(io,2)*Dc, dp)
55 !-------- Eso(u,d)
56- Dc = cmplx(Dscf(io,3),Dscf(io,4),kind=dp)
57- Hc = H0_offsiteSO(io,4)
58- Eso = Eso + real( Hc*Dc )
59+ Dc = cmplx(Dscf(io,3),Dscf(io,4), dp)
60+ Eso = Eso + real( H_so_off(io,4)*Dc, dp)
61 !-------- Eso(d,u)
62- Dc = cmplx(Dscf(io,7),-Dscf(io,8),kind=dp)
63- Hc = H0_offsiteSO(io,3)
64- Eso = Eso + real( Hc*Dc )
65-
66- enddo
67-
68- endif
69-
70- if ( spin%SO_onsite ) then
71+ Dc = cmplx(Dscf(io,7),-Dscf(io,8), dp)
72+ Eso = Eso + real( H_so_off(io,3)*Dc, dp)
73+
74+ end do
75+
76+ else if ( spin%SO_onsite ) then
77 ! Sadly some compilers (g95), does
78 ! not allow bounds for pointer assignments :(
79- H_so => val(H_so_2D)
80+ H_so_on => val(H_so_on_2D)
81 do io = 1,maxnh
82- Eso = Eso + H_so(io,1)*Dscf(io,7) + H_so(io,2)*Dscf(io,8) &
83- + H_so(io,5)*Dscf(io,3) + H_so(io,6)*Dscf(io,4) &
84- - H_so(io,3)*Dscf(io,5) - H_so(io,4)*Dscf(io,6)
85- end do
86+ Eso = Eso + H_so_on(io,1)*Dscf(io,7) + H_so_on(io,2)*Dscf(io,8) &
87+ + H_so_on(io,5)*Dscf(io,3) + H_so_on(io,6)*Dscf(io,4) &
88+ - H_so_on(io,3)*Dscf(io,5) - H_so_on(io,4)*Dscf(io,6)
89+ end do
90+
91 end if
92
93 #ifdef MPI
94
95=== modified file 'Src/final_H_f_stress.F'
96--- Src/final_H_f_stress.F 2018-04-20 09:41:55 +0000
97+++ Src/final_H_f_stress.F 2018-04-23 11:10:59 +0000
98@@ -21,8 +21,9 @@
99 use siesta_options, only: recompute_H_after_scf
100 use sparse_matrices, only: numh, listh, listhptr
101 use sparse_matrices, only: H, S, Dscf, Escf, maxnh, xijo
102- use sparse_matrices, only: H_ldau_2D
103+ use sparse_matrices, only: H_ldau_2D, H_so_off_2D
104 use class_dSpData2D, only: val
105+ use class_zSpData2D, only: val
106
107 use siesta_geom
108 use atomlist, only: no_u, iaorb, iphkb, qtot, indxuo, datm,
109@@ -30,7 +31,7 @@
110 & rmaxo, no_l, iza
111 use metaforce, only: lMetaForce, meta
112 use molecularmechanics, only : twobody
113- use m_nlefsm, only: nlefsm, nlefsm_offsiteSO
114+ use m_nlefsm, only: nlefsm, nlefsm_SO_off
115 use m_overfsm, only: overfsm
116 use m_kinefsm, only: kinefsm
117 use m_naefs, only: naefs
118@@ -91,6 +92,8 @@
119 real(dp), pointer :: H_tmp(:,:) => null()
120 real(dp), pointer :: S_tmp(:) => null()
121 real(dp), pointer :: H_ldau(:,:)
122+ complex(dp), pointer :: H_so_off(:,:)
123+
124 #ifdef FINAL_CHECK_HS
125 real(dp) :: diff_H, diff_S
126 #endif
127@@ -176,13 +179,14 @@
128 call globalize_sum(Enl,buffer1)
129 Enl = buffer1
130 #endif
131- else
132- call nlefsm_offsiteSO(scell, na_u, na_s, isa, xa, indxua,
133+ else
134+ H_so_off => val(H_so_off_2D)
135+ call nlefsm_SO_off(scell, na_u, na_s, isa, xa, indxua,
136 & maxnh, maxnh, lasto, lastkb, iphorb, iphKB,
137 & numh, listhptr, listh, numh, listhptr, listh,
138 & spin%Grid,
139 & Enl, Eso, fal,
140- & stressl, H_tmp,
141+ & stressl, H_tmp, H_so_off,
142 & matrix_elements_only=.false.)
143 #ifdef MPI
144 ! Global reduction of energy terms
145@@ -193,7 +197,7 @@
146 #endif
147 endif
148
149- if ( spin%SO_onsite) then
150+ if ( spin%SO_onsite ) then
151 call spinorb(no_u,no_l,iaorb,iphorb,isa,indxuo,
152 & maxnh,numh,listhptr,listh,Dscf,H_tmp(:,3:),Eso)
153 endif
154@@ -292,7 +296,8 @@
155 & diff_S
156 end if
157 #endif
158-
159+
160+ ! TODO I am not sure this works with SO_offsite?
161 if (recompute_H_after_scf) then
162 if (ionode) then
163 write(6,"(a)") ":!: Updating H after scf cycle" //
164
165=== modified file 'Src/nlefsm.f'
166--- Src/nlefsm.f 2018-04-23 09:26:04 +0000
167+++ Src/nlefsm.f 2018-04-23 11:10:59 +0000
168@@ -8,11 +8,10 @@
169 module m_nlefsm
170
171 use precision, only : dp
172- use sparse_matrices, only: H0_offsiteSO
173
174 implicit none
175
176- public :: nlefsm, nlefsm_offsiteSO, calc_Vj_offsiteSO
177+ public :: nlefsm, nlefsm_SO_off
178
179 private
180
181@@ -445,11 +444,12 @@
182 C nlefsm_offsiteSO calculates the KB elements to the total Hamiltonian
183 C (including the SO contribution)
184 C when Off-Site Spin Orbit is included in the calculation
185- subroutine nlefsm_offsiteSO( scell, nua, na, isa, xa, indxua,
186+ subroutine nlefsm_SO_off( scell, nua, na, isa, xa, indxua,
187 . maxnh, maxnd, lasto, lastkb, iphorb,
188 . iphKB, numd, listdptr, listd, numh,
189 . listhptr, listh, nspin, Enl, Enl_offsiteSO,
190- . fa, stress, H0 , matrix_elements_only)
191+ . fa, stress, H0 , H0_off,
192+ & matrix_elements_only)
193
194
195 C *********************************************************************
196@@ -496,7 +496,8 @@
197 C ******************* INPUT and OUTPUT *********************************
198 C real*8 fa(3,na) : NL forces (added to input fa)
199 C real*8 stress(3,3) : NL stress (added to input stress)
200-C real*8 H(maxnh,nspin) : NL Hamiltonian (added to input H)
201+C real*8 H0(maxnh,nspin) : NL Hamiltonian (added to input H)
202+C complex*16 H0_off(maxnh,nspin) : NL off-site Hamiltonian (added to input H)
203 C **************************** OUTPUT *********************************
204 C real*8 Enl : NL energy
205 C *********************************************************************
206@@ -525,7 +526,8 @@
207
208 real(dp), intent(in) :: scell(3,3), xa(3,na)
209 real(dp), intent(inout) :: fa(3,nua), stress(3,3)
210- real(dp), intent(inout) :: H0(maxnh)
211+ real(dp), intent(inout) :: H0(maxnh)
212+ complex(dp), intent(inout) :: H0_off(maxnh,4)
213
214 real(dp), intent(out) :: Enl, Enl_offsiteSO
215 logical, intent(in) :: matrix_elements_only
216@@ -853,10 +855,10 @@
217 ind = listhptr(iio)+j
218 jo = listh(ind)
219 H0(ind) = H0(ind) + Vi(jo)
220- H0_offsiteSO(ind,1) = H0_offsiteSO(ind,1) + V_so(1,1,jo)
221- H0_offsiteSO(ind,2) = H0_offsiteSO(ind,2) + V_so(2,2,jo)
222- H0_offsiteSO(ind,3) = H0_offsiteSO(ind,3) + V_so(1,2,jo)
223- H0_offsiteSO(ind,4) = H0_offsiteSO(ind,4) + V_so(2,1,jo)
224+ H0_off(ind,1) = H0_off(ind,1) + V_so(1,1,jo)
225+ H0_off(ind,2) = H0_off(ind,2) + V_so(2,2,jo)
226+ H0_off(ind,3) = H0_off(ind,3) + V_so(1,2,jo)
227+ H0_off(ind,4) = H0_off(ind,4) + V_so(2,1,jo)
228
229
230 C Careful with this Vi()
231@@ -894,7 +896,7 @@
232
233 call timer( 'nlefsm', 2 )
234
235- end subroutine nlefsm_offsiteSO
236+ end subroutine nlefsm_SO_off
237
238 c-----------------------------------------------------------------------
239 c
240
241=== modified file 'Src/setup_H0.F'
242--- Src/setup_H0.F 2018-04-19 12:47:26 +0000
243+++ Src/setup_H0.F 2018-04-23 11:10:59 +0000
244@@ -17,11 +17,10 @@
245
246 USE siesta_options, only: g2cut
247 use sparse_matrices, only: H_kin_1D, H_vkb_1D
248- use sparse_matrices, only: H_so_2D
249+ use sparse_matrices, only: H_so_on_2D, H_so_off_2D
250 use sparse_matrices, only: Dscf
251
252- use sparse_matrices, only: H0_offsiteSO
253- use m_nlefsm, only: nlefsm_offsiteSO
254+ use m_nlefsm, only: nlefsm_SO_off
255 use m_spin, only: spin
256
257 use sparse_matrices, only: listh, listhptr, numh, maxnh
258@@ -44,6 +43,7 @@
259 use alloc, only: re_alloc, de_alloc
260 use class_dSpData1D, only: val
261 use class_dSpData2D, only: val
262+ use class_zSpData2D, only: val
263
264 #ifdef MPI
265 use m_mpi_utils, only: globalize_sum
266@@ -57,13 +57,15 @@
267 integer :: ia, is
268
269 real(dp) :: dummy_Eso
270- integer :: io, ispin, i, j
271- complex(dp) :: Hc, Dc
272+ integer :: ispin, i, j
273+ complex(dp) :: Dc
274 #ifdef MPI
275- real(dp) :: buffer1
276+ real(dp) :: buffer1
277 #endif
278
279- real(dp), pointer :: H_val(:), H_so(:,:)
280+ real(dp), pointer :: H_val(:), H_so_on(:,:)
281+ complex(dp), pointer :: H_so_off(:,:)
282+
283
284 #ifdef DEBUG
285 call write_debug( ' PRE setup_H0' )
286@@ -136,13 +138,14 @@
287 & H_val,
288 & matrix_elements_only=.true.)
289 else
290- H0_offsiteSO=dcmplx(0.0d0,0.0d0)
291- call nlefsm_offsiteSO(scell, na_u, na_s, isa, xa, indxua,
292+ H_so_off => val(H_so_off_2D)
293+ H_so_off = dcmplx(0._dp, 0._dp)
294+ call nlefsm_SO_off(scell, na_u, na_s, isa, xa, indxua,
295 & maxnh, maxnh, lasto, lastkb, iphorb, iphKB,
296 & numh, listhptr, listh, numh, listhptr, listh,
297 & spin%Grid,
298 & dummy_E, dummy_Eso, dummy_fa,
299- & dummy_stress, H_val,
300+ & dummy_stress, H_val, H_so_off,
301 & matrix_elements_only=.true.)
302
303
304@@ -153,24 +156,20 @@
305 ! DM in a such way that the result gives Re{Tr[H_SO*DM]}.
306 !
307
308- do io = 1, maxnh
309+ do i = 1, maxnh
310
311 !-------- Eso(u,u)
312- Dc = cmplx(Dscf(io,1),Dscf(io,5),kind=dp)
313- Hc = H0_offsiteSO(io,1)
314- Eso = Eso + real( Hc*Dc )
315+ Dc = cmplx(Dscf(i,1),Dscf(i,5), dp)
316+ Eso = Eso + real( H_so_off(i,1)*Dc, dp)
317 !-------- Eso(d,d)
318- Dc = cmplx(Dscf(io,2),Dscf(io,6),kind=dp)
319- Hc = H0_offsiteSO(io,2)
320- Eso = Eso + real( Hc*Dc )
321+ Dc = cmplx(Dscf(i,2),Dscf(i,6),dp)
322+ Eso = Eso + real( H_so_off(i,2)*Dc, dp)
323 !-------- Eso(u,d)
324- Dc = cmplx(Dscf(io,3),Dscf(io,4),kind=dp)
325- Hc = H0_offsiteSO(io,4)
326- Eso = Eso + real( Hc*Dc )
327+ Dc = cmplx(Dscf(i,3),Dscf(i,4), dp)
328+ Eso = Eso + real( H_so_off(i,4)*Dc, dp)
329 !-------- Eso(d,u)
330- Dc = cmplx(Dscf(io,7),-Dscf(io,8),kind=dp)
331- Hc = H0_offsiteSO(io,3)
332- Eso = Eso + real( Hc*Dc )
333+ Dc = cmplx(Dscf(i,7),-Dscf(i,8), dp)
334+ Eso = Eso + real( H_so_off(i,3)*Dc, dp)
335
336 enddo
337
338@@ -188,12 +187,12 @@
339 ! should be enough
340 !
341 if ( spin%SO_onsite ) then
342- H_so => val(H_so_2D)
343+ H_so_on => val(H_so_on_2D)
344 !$OMP parallel workshare default(shared)
345- H_so = 0._dp
346+ H_so_on(:,:) = 0._dp
347 !$OMP end parallel workshare
348 call spinorb(no_u,no_l,iaorb,iphorb,isa,indxuo,
349- & maxnh,numh,listhptr,listh,Dscf,H_so,Eso)
350+ & maxnh,numh,listhptr,listh,Dscf,H_so_on,Eso)
351 end if
352
353 C This will take care of possible changes to the mesh and atomic-related
354
355=== modified file 'Src/setup_hamiltonian.F'
356--- Src/setup_hamiltonian.F 2018-04-20 09:41:55 +0000
357+++ Src/setup_hamiltonian.F 2018-04-23 11:10:59 +0000
358@@ -14,12 +14,14 @@
359
360 USE siesta_options
361 use sparse_matrices, only: H_kin_1D, H_vkb_1D
362- use sparse_matrices, only: H_ldau_2D, H_so_2D
363+ use sparse_matrices, only: H_ldau_2D
364+ use sparse_matrices, only: H_so_on_2D, H_so_off_2D
365 use sparse_matrices, only: listh, listhptr, numh, maxnh
366 use sparse_matrices, only: H, S, Hold
367 use sparse_matrices, only: Dscf, Escf, xijo
368 use class_dSpData1D, only: val
369 use class_dSpData2D, only: val
370+ use class_zSpData2D, only: val
371
372 use siesta_geom
373 use atmfuncs, only: uion
374@@ -42,7 +44,6 @@
375 use m_ntm
376
377 use m_spin, only: spin
378- use sparse_matrices, only: H0_offsiteSO
379
380 use m_dipol
381 use alloc, only: re_alloc, de_alloc
382@@ -71,9 +72,11 @@
383 type(filesOut_t) :: filesOut ! blank output file names
384 logical :: use_rhog_in
385
386- real(dp), pointer :: H_vkb(:), H_kin(:), H_ldau(:,:), H_so(:,:)
387+ real(dp), pointer :: H_vkb(:), H_kin(:), H_ldau(:,:)
388+ real(dp), pointer :: H_so_on(:,:)
389+ complex(dp), pointer:: H_so_off(:,:)
390
391- complex(dp):: Hc, Dc
392+ complex(dp):: Dc
393 integer :: ind, i, j
394
395 !------------------------------------------------------------------------- BEGIN
396@@ -90,53 +93,53 @@
397 do ispin = 1, spin%H
398 do io = 1,maxnh
399 Hold(io,ispin) = H(io,ispin)
400- enddo
401- enddo
402+ end do
403+ end do
404 !$OMP end do
405
406 !$OMP single
407 H_kin => val(H_kin_1D)
408 H_vkb => val(H_vkb_1D)
409+
410 if ( spin%SO_onsite ) then
411- ! Sadly some compilers (g95), does
412- ! not allow bounds for pointer assignments :(
413- H_so => val(H_so_2D)
414+ ! Sadly some compilers (g95), does
415+ ! not allow bounds for pointer assignments :(
416+ H_so_on => val(H_so_on_2D)
417+
418+ else if ( spin%SO_offsite ) then
419+ H_so_off => val(H_so_off_2D)
420+
421 end if
422 !$OMP end single ! keep wait
423
424- if ( .not. spin%SO_offsite ) then
425- do ispin = 1, spin%spinor
426- if (ispin .le. 2) then
427-!$OMP do
428- do io = 1,maxnh
429- H(io,ispin) = H_kin(io) + H_vkb(io)
430- end do
431-!$OMP end do nowait
432- else
433-!$OMP do
434- do io = 1,maxnh
435- H(io,ispin) = 0.0_dp
436- end do
437-!$OMP end do nowait
438- end if
439- end do
440- end if
441+ ! Initialize diagonal Hamiltonian
442+ do ispin = 1, spin%spinor
443+!$OMP do
444+ do io = 1,maxnh
445+ H(io,ispin) = H_kin(io) + H_vkb(io)
446+ end do
447+!$OMP end do nowait
448+ end do
449
450 if ( spin%SO_onsite ) then
451 !$OMP do collapse(2)
452- do ispin = 3 , spin%H
453- do io = 1,maxnh
454- H(io,ispin) = H_so(io,ispin-2)
455- end do
456- end do
457-!$OMP end do nowait
458- else if ( spin%NCol ) then
459-!$OMP do
460- do io = 1,maxnh
461- H(io,3) = 0._dp
462- H(io,4) = 0._dp
463- end do
464-!$OMP end do nowait
465+ do ispin = 3 , spin%H
466+ do io = 1,maxnh
467+ H(io,ispin) = H_so_on(io,ispin-2)
468+ end do
469+ end do
470+!$OMP end do nowait
471+
472+ else
473+
474+!$OMP do collapse(2)
475+ do ispin = 3 , spin%H
476+ do io = 1,maxnh
477+ H(io,ispin) = 0._dp
478+ end do
479+ end do
480+!$OMP end do nowait
481+
482 end if
483
484 ! ..................
485@@ -171,40 +174,36 @@
486 ! DM in a such way that the result gives Re{Tr[H_SO*DM]}.
487 !
488
489- if( spin%SO_offsite ) then
490-
491+ if ( spin%SO_offsite ) then
492 do io = 1, maxnh
493
494 !-------- Eso(u,u)
495- Dc = cmplx(Dscf(io,1),Dscf(io,5),kind=dp)
496- Hc = H0_offsiteSO(io,1)
497- Eso = Eso + real( Hc*Dc )
498+ Dc = cmplx(Dscf(io,1),Dscf(io,5), dp)
499+ Eso = Eso + real( H_so_off(io,1)*Dc, dp)
500 !-------- Eso(d,d)
501- Dc = cmplx(Dscf(io,2),Dscf(io,6),kind=dp)
502- Hc = H0_offsiteSO(io,2)
503- Eso = Eso + real( Hc*Dc )
504+ Dc = cmplx(Dscf(io,2),Dscf(io,6), dp)
505+ Eso = Eso + real( H_so_off(io,2)*Dc, dp)
506 !-------- Eso(u,d)
507- Dc = cmplx(Dscf(io,3),Dscf(io,4),kind=dp)
508- Hc = H0_offsiteSO(io,4)
509- Eso = Eso + real( Hc*Dc )
510+ Dc = cmplx(Dscf(io,3),Dscf(io,4), dp)
511+ Eso = Eso + real( H_so_off(io,4)*Dc, dp)
512 !-------- Eso(d,u)
513- Dc = cmplx(Dscf(io,7),-Dscf(io,8),kind=dp)
514- Hc = H0_offsiteSO(io,3)
515- Eso = Eso + real( Hc*Dc )
516-
517- enddo
518-
519- endif
520-
521- if ( spin%SO_onsite ) then
522+ Dc = cmplx(Dscf(io,7),-Dscf(io,8), dp)
523+ Eso = Eso + real( H_so_off(io,3)*Dc, dp)
524+
525+ end do
526+
527+ else if ( spin%SO_onsite ) then
528+
529 !$OMP do reduction(+:Eso)
530 do io = 1, maxnh
531- Eso = Eso + H_so(io,1)*Dscf(io,7) + H_so(io,2)*Dscf(io,8)
532- . + H_so(io,5)*Dscf(io,3) + H_so(io,6)*Dscf(io,4)
533- . - H_so(io,3)*Dscf(io,5) - H_so(io,4)*Dscf(io,6)
534+ Eso = Eso + H_so_on(io,1)*Dscf(io,7) +
535+ & H_so_on(io,2)*Dscf(io,8)+ H_so_on(io,5)*Dscf(io,3) +
536+ & H_so_on(io,6)*Dscf(io,4)- H_so_on(io,3)*Dscf(io,5) -
537+ & H_so_on(io,4)*Dscf(io,6)
538 end do
539 !$OMP end do nowait
540- end if
541+
542+ end if
543
544 !$OMP end parallel
545
546@@ -224,10 +223,6 @@
547 ! Non-SCF part of total energy
548 call update_E0()
549
550- if ( spin%SO_offsite ) then
551- H(:,:) = 0.0_dp
552- endif
553-
554 ! Hubbard term for LDA+U: energy, forces, stress and matrix elements ....
555 if( switch_ldau ) then
556 if ( spin%NCol ) then
557@@ -285,24 +280,20 @@
558
559 if ( spin%SO_offsite ) then
560
561- do is = 1 , spin%spinor
562- do io = 1, maxnh
563- H(io,is) = H(io,is) + H_kin(io) + H_vkb(io)
564- enddo
565- enddo
566-
567-C------- H(u,u)
568- H(:,1) = H(:,1) + real(H0_offsiteSO(:,1))
569- H(:,5) = imag(H0_offsiteSO(:,1))
570-C------- H(d,d)
571- H(:,2) = H(:,2) + real(H0_offsiteSO(:,2))
572- H(:,6) = imag(H0_offsiteSO(:,2))
573-C------- H(u,d)
574- H(:,3) = H(:,3) + real(H0_offsiteSO(:,3))
575- H(:,4) = H(:,4) + imag(H0_offsiteSO(:,3))
576-C------- H(d,u)
577- H(:,7) = H(:,7) + real(H0_offsiteSO(:,4))
578- H(:,8) = H(:,8) - imag(H0_offsiteSO(:,4))
579+! H(:, [5, 6]) are not updated in dhscf, see vmat for details.
580+
581+!------- H(u,u)
582+ H(:,1) = H(:,1) + real(H_so_off(:,1), dp)
583+ H(:,5) = dimag(H_so_off(:,1))
584+!------- H(d,d)
585+ H(:,2) = H(:,2) + real(H_so_off(:,2), dp)
586+ H(:,6) = dimag(H_so_off(:,2))
587+!------- H(u,d)
588+ H(:,3) = H(:,3) + real(H_so_off(:,3), dp)
589+ H(:,4) = H(:,4) +dimag(H_so_off(:,3))
590+!------- H(d,u)
591+ H(:,7) = H(:,7) + real(H_so_off(:,4), dp)
592+ H(:,8) = H(:,8) -dimag(H_so_off(:,4))
593
594 endif
595
596
597=== modified file 'Src/sparse_matrices.F'
598--- Src/sparse_matrices.F 2018-04-19 12:47:26 +0000
599+++ Src/sparse_matrices.F 2018-04-23 11:10:59 +0000
600@@ -9,6 +9,7 @@
601 use precision
602 use class_dSpData1D
603 use class_dSpData2D
604+ use class_zSpData2D
605 use class_Sparsity
606 use class_OrbitalDistribution
607 use class_Fstack_Pair_Geometry_dSpData2D
608@@ -37,7 +38,10 @@
609 ! Formerly there was a single array H0 for this
610 type(dSpData1D), public, save :: H_vkb_1D, H_kin_1D
611 ! LDA+U and spin-orbit coupling Hamiltonian
612- type(dSpData2D), public, save :: H_ldau_2D, H_so_2D
613+ type(dSpData2D), public, save :: H_ldau_2D, H_so_on_2D
614+ ! Spin-orbit off-site
615+ type(zSpData2D), public, save :: H_so_off_2D
616+
617
618 ! New interface data
619 type(Sparsity), public, save :: sparse_pattern
620@@ -56,7 +60,6 @@
621
622 subroutine resetSparseMatrices( )
623 use alloc, only : de_alloc
624- use m_spin, only : spin
625
626 implicit none
627
628@@ -67,7 +70,8 @@
629 call delete( H_kin_1D )
630 call delete( H_vkb_1D )
631 call delete( H_ldau_2D )
632- call delete( H_so_2D )
633+ call delete( H_so_on_2D )
634+ call delete( H_so_off_2D )
635
636 call delete( DM_2D ) ; nullify(Dscf)
637 call delete( EDM_2D ) ; nullify(Escf)
638@@ -76,10 +80,6 @@
639 call delete( xij_2D ) ; nullify(xijo)
640
641 call delete( DM_history )
642-
643- if( spin%SO_offsite ) then
644- call de_alloc( H0_offsiteSO, 'H0_offsiteSO', 'sparseMat' )
645- endif
646
647 ! Using MixH is bad as several utilities
648 ! are not relying on FoX, better to leave out
649
650=== modified file 'Src/state_init.F'
651--- Src/state_init.F 2018-04-19 12:47:26 +0000
652+++ Src/state_init.F 2018-04-23 11:10:59 +0000
653@@ -26,10 +26,9 @@
654 use sparse_matrices, only: xijo, xij_2D
655 use sparse_matrices, only: S , S_1D
656
657- use sparse_matrices, only: H0_offsiteSO
658-
659 use sparse_matrices, only: H_kin_1D, H_vkb_1D
660- use sparse_matrices, only: H_ldau_2D, H_so_2D
661+ use sparse_matrices, only: H_ldau_2D
662+ use sparse_matrices, only: H_so_on_2D, H_so_off_2D
663
664 use sparse_matrices, only: sparse_pattern
665 use sparse_matrices, only: block_dist, single_dist
666@@ -100,6 +99,7 @@
667 use class_Sparsity
668 use class_dSpData1D
669 use class_dSpData2D
670+ use class_zSpData2D
671 use class_dData2D
672 #ifdef TEST_IO
673 use m_test_io
674@@ -564,15 +564,14 @@
675 end if
676 end if
677
678- if ( spin%SO_onsite ) then
679- write(oname,"(a,i0)") "H_so (onsite) at geom step ", istep
680- call newdSpData2D(sparse_pattern,spin%H - 2,
681- & block_dist,H_so_2D,name=oname)
682- end if
683-
684- if ( spin%SO_offsite ) then
685- call re_alloc(H0_offsiteSO, 1,maxnh, 1,4, 'H0_offsiteSO',
686- $ 'state_init')
687+ if ( spin%SO_onsite ) then
688+ write(oname,"(a,i0)") "H_so (onsite) at geom step ", istep
689+ call newdSpData2D(sparse_pattern,spin%H - 2,
690+ & block_dist,H_so_on_2D,name=oname)
691+ else if ( spin%SO_offsite ) then
692+ write(oname,"(a,i0)") "H_so (offsite) at geom step ", istep
693+ call newzSpData2D(sparse_pattern,4,
694+ & block_dist,H_so_off_2D,name=oname)
695 endif
696
697 write(oname,"(a,i0)") "S at geom step ", istep
698
699=== modified file 'version.info'
700--- version.info 2018-04-23 09:26:04 +0000
701+++ version.info 2018-04-23 11:10:59 +0000
702@@ -1,2 +1,2 @@
703-trunk-688--merge-OSSO-700
704+trunk-688--merge-OSSO-700--class-1
705

Subscribers

People subscribed via source and target branches

to all changes: