Merge lp:~nickpapior/siesta/4.1-wfs into lp:~albertog/siesta/4.1-wfs

Proposed by Nick Papior
Status: Merged
Merged at revision: 1116
Proposed branch: lp:~nickpapior/siesta/4.1-wfs
Merge into: lp:~albertog/siesta/4.1-wfs
Diff against target: 813 lines (+196/-188)
6 files modified
Src/Makefile (+1/-1)
Src/bands.F (+25/-29)
Src/print_spin.F90 (+51/-58)
Src/siesta_analysis.F (+96/-73)
Src/writewave.F (+22/-26)
version.info (+1/-1)
To merge this branch: bzr merge lp:~nickpapior/siesta/4.1-wfs
Reviewer Review Type Date Requested Status
Alberto Garcia Approve
Review via email: mp+371082@code.launchpad.net

Commit message

Implemented tSpin in bands/writewave and fixed a few output options

Using tSpin cleans up a bit some of the *magic* variables used
here and there. Actually the use of tSpin suggests that we need
a new variable in tSpin to clarify whether it is NCol .or. SO
which could help in certain places.

The output files are now a bit weird when comparing format
for NC.
- ioeig uses no_u * 2, 1
- bands uses no_u, 4 for WFS file
- bands uses no_u * 2, 1 for .bands
- wwave uses no_u, 4 for WFSX

It is not clear to me why they are different, and/or
if they *should* be different.
I would prefer if we can use the same convention all-over.
This may require changes all-around.

I don't have any preference. Probably I would prefer:

   no_u, spin%H

which clarifies exactly which type of calculation it was.
This is probably opposite of my previous perception.

Also, I have cleaned up print_spin which did lots of
duplicate work for SO calculations.

Description of the change

Once this is in, I can approve the merge.

I think it would be best if we could clean up this once and for all.
Let me know what you think!

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

I agree with your tSpin and print_spin changes. They do make the code more clear. Thanks.

The new tSpin variable (equivalent to Ncol.or.SO), and other enhancements, can maybe be defined in the 4.2 branch.

Regarding the output files headings:

  In bands and ioeig, no_u*2 refers to the number of states, and 1 to the
  number of spin blocks (=1 since there is no spin distinction).

  In the wavefunction files, no_u refers to the number of basis orbitals, and
  4 to the number of expansions of length no_u needed at each band (4 for a complex
  spinor). The number of states in the file is given by nk and the following records
  for each k-point.

One possible source of fragility is that the "spinor_dim second-dimension" trick in ioeig and bands might not work when 'neigwanted' is not no_u. This could be also handled more robustly in 4.2, after the merge, and back-ported if deemed necessary for some use cases.

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

More on the bands/EIG/WFS headings:

I agree that they could be improved, but doing so at this time would delay the pressing merge of the NC/SO wfs functionality. Besides, just changing a small set of numbers by another small set of numbers is probably not going to do a lot towards self-documentation of the files. To get out of the historical constraints we probably need a more thorough rethink of the files' contents.

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

For EIG files etc. Agreed, it isn't totally necessary. I just wanted this on the table since it is rather confusing ;)
Once you know what they mean, it is easy to bypass the problems they yield.

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
=== modified file 'Src/Makefile'
--- Src/Makefile 2019-06-20 13:50:42 +0000
+++ Src/Makefile 2019-08-08 11:56:55 +0000
@@ -1346,7 +1346,7 @@
1346write_subs.o: m_steps.o m_stress.o m_ts_global_vars.o parallel.o precision.o1346write_subs.o: m_steps.o m_stress.o m_ts_global_vars.o parallel.o precision.o
1347write_subs.o: siesta_cml.o siesta_geom.o siesta_options.o units.o zmatrix.o1347write_subs.o: siesta_cml.o siesta_geom.o siesta_options.o units.o zmatrix.o
1348writewave.o: alloc.o atmfuncs.o atomlist.o densematrix.o diag.o diag_option.o1348writewave.o: alloc.o atmfuncs.o atomlist.o densematrix.o diag.o diag_option.o
1349writewave.o: get_kpoints_scale.o kpoint_grid.o m_spin.o parallel.o1349writewave.o: get_kpoints_scale.o kpoint_grid.o m_spin.o m_spin.o parallel.o
1350writewave.o: parallelsubs.o precision.o siesta_geom.o sys.o units.o1350writewave.o: parallelsubs.o precision.o siesta_geom.o sys.o units.o
1351xml.o: precision.o1351xml.o: precision.o
1352zm_broyden_optim.o: m_broyddj_nocomm.o parallel.o precision.o sys.o units.o1352zm_broyden_optim.o: m_broyddj_nocomm.o parallel.o precision.o sys.o units.o
13531353
=== modified file 'Src/bands.F'
--- Src/bands.F 2019-02-24 16:24:33 +0000
+++ Src/bands.F 2019-08-08 11:56:55 +0000
@@ -296,7 +296,7 @@
296 end subroutine initbands296 end subroutine initbands
297297
298298
299 subroutine bands( no_s, h_spin_dim, spinor_dim,299 subroutine bands( no_s, spin,
300 . no_u, no_l,maxnh, maxk,300 . no_u, no_l,maxnh, maxk,
301 . numh, listhptr, listh, H, S, ef, xij, indxuo,301 . numh, listhptr, listh, H, S, ef, xij, indxuo,
302 . writeb, nk, kpoint, ek, occtol, getPSI )302 . writeb, nk, kpoint, ek, occtol, getPSI )
@@ -306,11 +306,11 @@
306C Written by J.Soler, August 1997 and August 1998.306C Written by J.Soler, August 1997 and August 1998.
307C Initialisation moved into a separate routine, JDG Jan 2000.307C Initialisation moved into a separate routine, JDG Jan 2000.
308C WFS options by A. Garcia, April 2012308C WFS options by A. Garcia, April 2012
309C Cleaned for tSpin by N. Papior, August 2019
309310
310C **************************** INPUT **********************************311C **************************** INPUT **********************************
311C integer no_s : Number of basis orbitals in supercell312C integer no_s : Number of basis orbitals in supercell
312C integer h_spin_dim : 313C type(tSpin) spin : Containing all spin-information
313C integer spinor_dim :
314C integer maxnh : Maximum number of orbitals interacting314C integer maxnh : Maximum number of orbitals interacting
315C with any orbital315C with any orbital
316C integer maxk : Last dimension of kpoint and ek316C integer maxk : Last dimension of kpoint and ek
@@ -320,7 +320,7 @@
320C hamiltonian matrix320C hamiltonian matrix
321C integer listh(maxlh) : Nonzero hamiltonian-matrix element321C integer listh(maxlh) : Nonzero hamiltonian-matrix element
322C column indexes for each matrix row322C column indexes for each matrix row
323C real*8 H(maxnh,h_spin_dim) : Hamiltonian in sparse form323C real*8 H(maxnh,spin%H) : Hamiltonian in sparse form
324C real*8 S(maxnh) : Overlap in sparse form324C real*8 S(maxnh) : Overlap in sparse form
325C real*8 ef : Fermi energy325C real*8 ef : Fermi energy
326C real*8 xij(3,maxnh) : Vectors between orbital centers (sparse)326C real*8 xij(3,maxnh) : Vectors between orbital centers (sparse)
@@ -338,7 +338,7 @@
338C real*8 kpoint(3,maxk) : k point vectors338C real*8 kpoint(3,maxk) : k point vectors
339C real*8 occtol : Occupancy threshold for DM build339C real*8 occtol : Occupancy threshold for DM build
340C *************************** OUTPUT **********************************340C *************************** OUTPUT **********************************
341C real*8 ek(no_u,spinor_dim,maxk) : Eigenvalues341C real*8 ek(no_u,spin%spinor,maxk) : Eigenvalues
342C *************************** UNITS ***********************************342C *************************** UNITS ***********************************
343C Lengths in atomic units (Bohr).343C Lengths in atomic units (Bohr).
344C k vectors in reciprocal atomic units.344C k vectors in reciprocal atomic units.
@@ -366,7 +366,7 @@
366 use atmfuncs, only : symfio, cnfigfio, labelfis, nofis366 use atmfuncs, only : symfio, cnfigfio, labelfis, nofis
367 use writewave, only : wfs_filename367 use writewave, only : wfs_filename
368368
369 use m_spin, only: NoMagn, SPpol, NonCol, SpOrb369 use t_spin, only: tSpin
370370
371 use m_diag_option, only: ParallelOverK, Serial371 use m_diag_option, only: ParallelOverK, Serial
372 use m_diag, only: diag_init372 use m_diag, only: diag_init
@@ -374,13 +374,13 @@
374374
375 implicit none375 implicit none
376376
377 integer :: h_spin_dim377 type(tSpin), intent(in) :: spin
378 integer :: maxk, maxnh, spinor_dim, no_u, no_l, nk, no_s,378 integer :: maxk, maxnh, no_u, no_l, nk, no_s,
379 . indxuo(no_s), listh(maxnh), numh(no_l),379 . indxuo(no_s), listh(maxnh), numh(no_l),
380 . listhptr(*)380 . listhptr(*)
381 logical :: writeb381 logical :: writeb
382 real(dp) :: ef, ek(no_u,spinor_dim,maxk),382 real(dp) :: ef, ek(no_u,spin%spinor,maxk),
383 . H(maxnh,h_spin_dim), kpoint(3,maxk),383 . H(maxnh,spin%H), kpoint(3,maxk),
384 . S(maxnh), xij(3,maxnh), occtol384 . S(maxnh), xij(3,maxnh), occtol
385 logical, intent(in) :: getPSI385 logical, intent(in) :: getPSI
386386
@@ -394,8 +394,7 @@
394 logical, parameter :: fixspin = .false.394 logical, parameter :: fixspin = .false.
395395
396 integer :: ik, il, io, ispin, iu, iu_wfs, iuo, naux, nhs, j396 integer :: ik, il, io, ispin, iu, iu_wfs, iuo, naux, nhs, j
397 integer :: nspin_flag ! For wfs output397 logical :: SaveParallelOverK
398 logical :: SaveParallelOverK, non_coll
399 398
400 real(dp)399 real(dp)
401 . Dnew, qs(2), e1, e2, efs(2), emax, emin, Enew, eV, qk, qtot,400 . Dnew, qs(2), e1, e2, efs(2), emax, emin, Enew, eV, qk, qtot,
@@ -424,15 +423,12 @@
424423
425C Allocate local arrays - only aux is relevant here424C Allocate local arrays - only aux is relevant here
426425
427 non_coll = (h_spin_dim >= 4)426 if ( spin%Grid == 4 ) then
428 if ( non_coll ) then427 nhs = 2 * (2*no_u) * (2*no_l)
429 nspin_flag = 4
430 nhs = 2 * (2*no_u) * (2*no_l)
431 else428 else
432 nspin_flag = h_spin_dim
433 nhs = 2 * no_u*no_l429 nhs = 2 * no_u*no_l
434 endif430 endif
435 naux = 2*no_u*5431 naux = 2*no_u*5
436 call allocDenseMatrix(nhs, nhs, nhs)432 call allocDenseMatrix(nhs, nhs, nhs)
437 call re_alloc( aux, 1, naux, 'aux', 'bands' )433 call re_alloc( aux, 1, naux, 'aux', 'bands' )
438434
@@ -445,7 +441,7 @@
445 rewind (iu_wfs)441 rewind (iu_wfs)
446442
447 write(iu_wfs) nk, .false. ! nk, Gamma, same file-format in WFS as for Gamma-point443 write(iu_wfs) nk, .false. ! nk, Gamma, same file-format in WFS as for Gamma-point
448 write(iu_wfs) nspin_flag444 write(iu_wfs) spin%Grid
449 write(iu_wfs) no_u445 write(iu_wfs) no_u
450 write(iu_wfs) (iaorb(j),labelfis(isa(iaorb(j))),446 write(iu_wfs) (iaorb(j),labelfis(isa(iaorb(j))),
451 . iphorb(j), cnfigfio(isa(iaorb(j)),iphorb(j)),447 . iphorb(j), cnfigfio(isa(iaorb(j)),iphorb(j)),
@@ -455,7 +451,7 @@
455 endif451 endif
456452
457C Find the band energies453C Find the band energies
458 if (NoMagn .or. SPpol) then454 if ( spin%Grid < 4 ) then
459C fixspin and qs are not used in diagk, since getD=.false. ...455C fixspin and qs are not used in diagk, since getD=.false. ...
460 qs(1) = 0.0_dp456 qs(1) = 0.0_dp
461 qs(2) = 0.0_dp457 qs(2) = 0.0_dp
@@ -472,7 +468,7 @@
472 call diag_init()468 call diag_init()
473 end if469 end if
474470
475 call diagk( h_spin_dim, no_l, no_s, spinor_dim, 471 call diagk( spin%H, no_l, no_s, spin%spinor,
476 . maxnh, maxnh, 472 . maxnh, maxnh,
477 . no_u, numh, listhptr, listh, numh, listhptr,473 . no_u, numh, listhptr, listh, numh, listhptr,
478 . listh, H, S, getD, getPSI, fixspin, qtot, qs, temp,474 . listh, H, S, getD, getPSI, fixspin, qtot, qs, temp,
@@ -484,7 +480,7 @@
484 ParallelOverK = SaveParallelOverK480 ParallelOverK = SaveParallelOverK
485 if ( ParallelOverK ) Serial = .true.481 if ( ParallelOverK ) Serial = .true.
486482
487 elseif ( NonCol ) then483 elseif ( spin%NCol ) then
488 call diag2k(no_l, no_s, maxnh, maxnh, no_u,484 call diag2k(no_l, no_s, maxnh, maxnh, no_u,
489 . numh, listhptr, listh, numh, listhptr,485 . numh, listhptr, listh, numh, listhptr,
490 . listh, H, S, getD, getPSI, qtot, temp, e1, e2,486 . listh, H, S, getD, getPSI, qtot, temp, e1, e2,
@@ -493,7 +489,7 @@
493 . Haux, Saux, psi, Haux, Saux, aux,489 . Haux, Saux, psi, Haux, Saux, aux,
494 . no_u, occtol, 1, no_u )490 . no_u, occtol, 1, no_u )
495491
496 elseif ( SpOrb ) then492 elseif ( spin%SO ) then
497 call diag3k(no_l, no_s, maxnh, maxnh, no_u, numh,493 call diag3k(no_l, no_s, maxnh, maxnh, no_u, numh,
498 . listhptr, listh, numh, listhptr, listh,494 . listhptr, listh, numh, listhptr, listh,
499 . H, S, getD, getPSI, qtot, temp, e1, e2, xij,495 . H, S, getD, getPSI, qtot, temp, e1, e2, xij,
@@ -502,7 +498,7 @@
502 . Haux, Saux, psi, Haux, Saux, aux,498 . Haux, Saux, psi, Haux, Saux, aux,
503 . no_u, occtol, 1, no_u )499 . no_u, occtol, 1, no_u )
504 else500 else
505 call die( 'bands: ERROR: incorrect value of h_spin_dim')501 call die( 'bands: ERROR: incorrect value of spin%H')
506 endif502 endif
507503
508C Write bands504C Write bands
@@ -525,7 +521,7 @@
525 . path = path + sqrt( (kpoint(1,ik)-kpoint(1,ik-1))**2 +521 . path = path + sqrt( (kpoint(1,ik)-kpoint(1,ik-1))**2 +
526 . (kpoint(2,ik)-kpoint(2,ik-1))**2 +522 . (kpoint(2,ik)-kpoint(2,ik-1))**2 +
527 . (kpoint(3,ik)-kpoint(3,ik-1))**2 )523 . (kpoint(3,ik)-kpoint(3,ik-1))**2 )
528 do ispin = 1,spinor_dim524 do ispin = 1, spin%spinor
529 do io = 1, no_u525 do io = 1, no_u
530 emax = max( emax, ek(io,ispin,ik) )526 emax = max( emax, ek(io,ispin,ik) )
531 emin = min( emin, ek(io,ispin,ik) )527 emin = min( emin, ek(io,ispin,ik) )
@@ -537,10 +533,10 @@
537 write(iu,*) emin/eV, emax/eV533 write(iu,*) emin/eV, emax/eV
538534
539C Write eigenvalues535C Write eigenvalues
540 if ( non_coll) then536 if ( spin%Grid == 4 ) then
541 write(iu,*) 2*no_u, 1, nk ! A single spin channel, double number of bands537 write(iu,*) 2*no_u, 1, nk ! A single spin channel, double number of bands
542 else 538 else
543 write(iu,*) no_u, spinor_dim, nk539 write(iu,*) no_u, spin%spinor, nk
544 endif540 endif
545541
546 ! For non-collinear calculations, the ek array will contain the first no_u542 ! For non-collinear calculations, the ek array will contain the first no_u
@@ -554,11 +550,11 @@
554 . (kpoint(3,ik)-kpoint(3,ik-1))**2 )550 . (kpoint(3,ik)-kpoint(3,ik-1))**2 )
555 write(iu,'(f10.6,10f12.4,/,(10x,10f12.4))')551 write(iu,'(f10.6,10f12.4,/,(10x,10f12.4))')
556 . path, ((ek(io,ispin,ik)/eV,io=1,no_u),552 . path, ((ek(io,ispin,ik)/eV,io=1,no_u),
557 . ispin=1,spinor_dim)553 . ispin=1,spin%spinor)
558 else554 else
559 write(iu,'(3f9.5,8f12.4,/,(27x,8f12.4))')555 write(iu,'(3f9.5,8f12.4,/,(27x,8f12.4))')
560 . kpoint(1,ik), kpoint(2,ik), kpoint(3,ik),556 . kpoint(1,ik), kpoint(2,ik), kpoint(3,ik),
561 . ((ek(io,ispin,ik)/eV,io=1,no_u),ispin=1,spinor_dim)557 . ((ek(io,ispin,ik)/eV,io=1,no_u),ispin=1,spin%spinor)
562 endif558 endif
563 enddo559 enddo
564560
565561
=== modified file 'Src/print_spin.F90'
--- Src/print_spin.F90 2019-03-29 13:10:59 +0000
+++ Src/print_spin.F90 2019-08-08 11:56:55 +0000
@@ -2,7 +2,6 @@
2 !2 !
3 ! Prints spin in output and CML files3 ! Prints spin in output and CML files
4 !4 !
5 use m_spin, only: nspin ! This is spin%grid (1, 2, or 4)
6 use m_spin, only: spin5 use m_spin, only: spin
7 use atomlist, only: no_l6 use atomlist, only: no_l
8 use sparse_matrices, only: listhptr, numh7 use sparse_matrices, only: listhptr, numh
@@ -16,79 +15,73 @@
1615
17 implicit none16 implicit none
18 17
19 real(dp), intent(out) :: qspin(4)18 real(dp), intent(out) :: qspin(spin%Grid)
2019
21 integer :: ispin, io, j, ind20 integer :: ispin, io, j, ind
22 real(dp) :: qaux21 real(dp) :: qaux
23 real(dp) :: Stot ! Total spin magnitude22 real(dp) :: Stot ! Total spin magnitude
24 real(dp) :: Svec(3) ! Total spin vector23 real(dp) :: Svec(3) ! Total spin vector
25 real(dp) :: dm_aux(4) ! Auxiliary array to hermitify Dscf for SOC
26#ifdef MPI24#ifdef MPI
27 real(dp) :: qtmp(4)25 real(dp) :: qtmp(spin%Grid)
28#endif26#endif
2927
30 if (nspin < 2) RETURN28 qspin(:) = 0.0_dp
3129
32 if (spin%SO) then30 if ( spin%Grid < 2 ) return
31
32 if ( spin%SO ) then
33 33
34 do ispin = 1,nspin34 do io = 1,no_l
35 qspin(ispin) = 0.0_dp35 do j = 1,numh(io)
36 do io = 1,no_l36 ind = listhptr(io)+j
37 do j = 1,numh(io)37 ! In the SOC case, hermitify Dscf
38 ind = listhptr(io)+j38 qspin(1:2) = qspin(1:2) + dscf(ind,1:2) * S(ind)
39 ! In the SOC case, hermitify Dscf39 qspin(3) = qspin(3) + 0.5_dp*(dscf(ind,3)+dscf(ind,7)) * S(ind)
40 dm_aux(1:4) = dscf(ind,1:4)40 qspin(4) = qspin(4) + 0.5_dp*(dscf(ind,4)+dscf(ind,8)) * S(ind)
41 dm_aux(3) = 0.5_dp*(dm_aux(3)+dscf(ind,7))41 end do
42 dm_aux(4) = 0.5_dp*(dm_aux(4)+dscf(ind,8))42 end do
43 qspin(ispin) = qspin(ispin) + dm_aux(ispin) * S(ind)
44 enddo
45 enddo
46 enddo
4743
48 else44 else
49 45
50 do ispin = 1,nspin46 do io = 1,no_l
51 qspin(ispin) = 0.0_dp47 do j = 1,numh(io)
52 do io = 1,no_l48 ind = listhptr(io)+j
53 do j = 1,numh(io)49 qspin(:) = qspin(:) + Dscf(ind,:) * S(ind)
54 ind = listhptr(io)+j50 end do
55 qspin(ispin) = qspin(ispin) + Dscf(ind,ispin) * S(ind)51 end do
56 enddo
57 enddo
58 enddo
59 52
60 endif53 endif
61#ifdef MPI54#ifdef MPI
62 ! Global reduction of spin components55 ! Global reduction of spin components
63 call globalize_sum(qspin(1:nspin),qtmp(1:nspin))56 call globalize_sum(qspin(1:spin%Grid),qtmp(1:spin%Grid))
64 qspin(1:nspin) = qtmp(1:nspin)57 qspin(1:spin%Grid) = qtmp(1:spin%Grid)
65#endif58#endif
6659
67 if (nspin .eq. 2) then60 ! We are left with printing out to stdout
6861 if ( .not. IONode ) return
69 if (IOnode) then62
70 Svec(1) = 0.0_dp63 if ( spin%Grid == 2) then
71 Svec(2) = 0.0_dp64
72 Svec(3) = qspin(1) - qspin(2)65 Svec(1) = 0.0_dp
73 Stot = Svec(3)66 Svec(2) = 0.0_dp
74 write(6,'(5x,a,f10.5,2f10.1,f10.5)') 'spin moment: S , {S} = ', Stot, Svec67 Svec(3) = qspin(1) - qspin(2)
75 endif68 Stot = Svec(3)
76 if (cml_p) call cmlAddProperty(xf=mainXML, &69 write(6,'(5x,a,f10.5,2f10.1,f10.5)') 'spin moment: S , {S} = ', Stot, Svec
77 value=qspin(1)-qspin(2), dictref='siesta:stot', &70 if (cml_p) call cmlAddProperty(xf=mainXML, &
78 units='siestaUnits:spin')71 value=qspin(1)-qspin(2), dictref='siesta:stot', &
7972 units='siestaUnits:spin')
80 elseif (nspin .eq. 4) then73
8174 else if ( spin%Grid == 4 ) then
82 call spnvec( nspin, qspin, qaux, Stot, Svec )75
83 if (IONode) then76 call spnvec( spin%Grid, qspin, qaux, Stot, Svec )
84 write(6,'(5x,a,4f10.5)') 'spin moment: S , {S} = ', Stot, Svec77 write(6,'(5x,a,4f10.5)') 'spin moment: S , {S} = ', Stot, Svec
85 if (cml_p) then78 if (cml_p) then
86 call cmlAddProperty(xf=mainXML, value=Stot, &79 call cmlAddProperty(xf=mainXML, value=Stot, &
87 dictref='siesta:stot', units='siestaUnits:spin')80 dictref='siesta:stot', units='siestaUnits:spin')
88 call cmlAddProperty(xf=mainXML, value=Svec, &81 call cmlAddProperty(xf=mainXML, value=Svec, &
89 dictref='siesta:svec', units='siestaUnits:spin')82 dictref='siesta:svec', units='siestaUnits:spin')
90 endif !cml_p83 end if !cml_p
91 endif84
92 endif85 end if
9386
94end subroutine print_spin87end subroutine print_spin
9588
=== modified file 'Src/siesta_analysis.F'
--- Src/siesta_analysis.F 2019-02-27 08:38:58 +0000
+++ Src/siesta_analysis.F 2019-08-08 11:56:55 +0000
@@ -46,8 +46,7 @@
46 use m_energies46 use m_energies
47 use m_steps, only: final47 use m_steps, only: final
48 use m_ntm48 use m_ntm
49 use m_spin, only: nspin, spinor_dim, h_spin_dim49 use m_spin, only: spin
50 use m_spin, only: SpOrb, NonCol, SPpol, NoMagn
51 use m_dipol50 use m_dipol
52 use m_eo51 use m_eo
53 use m_forces, only: fa52 use m_forces, only: fa
@@ -68,10 +67,10 @@
6867
69 real(dp) :: dummy_str(3,3)68 real(dp) :: dummy_str(3,3)
70 real(dp) :: dummy_strl(3,3)69 real(dp) :: dummy_strl(3,3)
71 real(dp) :: qspin(4) ! Local70 real(dp) :: qspin(spin%Grid) ! Local
7271
73 real(dp) :: polxyz(3,nspin) ! Autom., small72 real(dp) :: polxyz(3,spin%Grid) ! Autom., small
74 real(dp) :: polR(3,nspin) ! Autom., small73 real(dp) :: polR(3,spin%Grid) ! Autom., small
75 real(dp) :: qaux74 real(dp) :: qaux
76 real(dp), pointer :: ebk(:,:,:) ! Band energies75 real(dp), pointer :: ebk(:,:,:) ! Band energies
7776
@@ -127,7 +126,7 @@
127126
128 if (fdf_get("Read-H-from-file",.false.)) then127 if (fdf_get("Read-H-from-file",.false.)) then
129 if (SIESTA_worker) then128 if (SIESTA_worker) then
130 call read_spmatrix(maxnh, no_l, h_spin_dim, numh,129 call read_spmatrix(maxnh, no_l, spin%H, numh,
131 . listhptr, listh, H, found, userfile="H_IN")130 . listhptr, listh, H, found, userfile="H_IN")
132 if (.not. found) call die("Could not find H_IN")131 if (.not. found) call die("Could not find H_IN")
133 current_ef = ef132 current_ef = ef
@@ -137,7 +136,7 @@
137136
138#ifdef SIESTA__PEXSI137#ifdef SIESTA__PEXSI
139 if (fdf_get("PEXSI.DOS",.false.)) then138 if (fdf_get("PEXSI.DOS",.false.)) then
140 call pexsi_dos(no_u, no_l, spinor_dim,139 call pexsi_dos(no_u, no_l, spin%spinor,
141 $ maxnh, numh, listhptr, listh, H, S, qtot, ef)140 $ maxnh, numh, listhptr, listh, H, S, qtot, ef)
142 141
143 endif142 endif
@@ -263,6 +262,17 @@
263! latest DM, although this is probably too much).262! latest DM, although this is probably too much).
264! See the logic in siesta_forces.263! See the logic in siesta_forces.
265264
265! Setup the number of states depending on the used method
266! For polarized calculations we use no_u and separate spin-channels.
267! For NC/SO we have mixed spin-channels and separating makes no
268! sense.
269 if ( spin%Grid == 4 ) then
270! We are NC/SO
271 max_n_states = no_u * 2
272 else
273 max_n_states = no_u
274 end if
275
266! Find and print wavefunctions at selected k-points276! Find and print wavefunctions at selected k-points
267!** This uses H,S, and xa277!** This uses H,S, and xa
268 if (nwk.gt.0) then278 if (nwk.gt.0) then
@@ -270,7 +280,7 @@
270 if (IONode) print "(a)",280 if (IONode) print "(a)",
271 $ "Writing WFSX for selected k-points in "281 $ "Writing WFSX for selected k-points in "
272 $ // trim(wfs_filename)282 $ // trim(wfs_filename)
273 call wwave( no_s, h_spin_dim, spinor_dim, no_u, no_l, maxnh, 283 call wwave( no_s, spin, no_u, no_l, maxnh,
274 & nwk,284 & nwk,
275 & numh, listhptr, listh, H, S, Ef, xijo, indxuo,285 & numh, listhptr, listh, H, S, Ef, xijo, indxuo,
276 & gamma_wavefunctions, nwk, wfk, no_u, occtol )286 & gamma_wavefunctions, nwk, wfk, no_u, occtol )
@@ -278,13 +288,10 @@
278288
279289
280!** This uses H,S, and xa290!** This uses H,S, and xa
281 if (write_coop) then291 if ( write_coop ) then
282 ! Output the wavefunctions for the kpoints in the SCF set292 ! Output the wavefunctions for the kpoints in the SCF set
283 ! Note that we allow both a band number and an energy range293 ! Note that we allow both a band number and an energy range
284 ! The user is responsible for using appropriate values.294 ! The user is responsible for using appropriate values.
285 max_n_states = no_u
286 if (h_spin_dim >= 4) max_n_states = 2*no_u
287
288 wfs_band_min = fdf_get("WFS.BandMin",1)295 wfs_band_min = fdf_get("WFS.BandMin",1)
289 wfs_band_max = fdf_get("WFS.BandMax",max_n_states)296 wfs_band_max = fdf_get("WFS.BandMax",max_n_states)
290 call setup_wfs_list(nkpnt,max_n_states,297 call setup_wfs_list(nkpnt,max_n_states,
@@ -294,7 +301,7 @@
294 wfs_filename = trim(slabel)//".fullBZ.WFSX"301 wfs_filename = trim(slabel)//".fullBZ.WFSX"
295 if (IONode) print "(a)", "Writing WFSX for COOP/COHP in " 302 if (IONode) print "(a)", "Writing WFSX for COOP/COHP in "
296 $ // trim(wfs_filename)303 $ // trim(wfs_filename)
297 call wwave( no_s, h_spin_dim, spinor_dim, no_u, no_l, maxnh, 304 call wwave( no_s, spin, no_u, no_l, maxnh,
298 . nkpnt,305 . nkpnt,
299 . numh, listhptr, listh, H, S, Ef, xijo, indxuo,306 . numh, listhptr, listh, H, S, Ef, xijo, indxuo,
300 . gamma_SCF, nkpnt, kpoint, no_u, occtol)307 . gamma_SCF, nkpnt, kpoint, no_u, occtol)
@@ -303,85 +310,101 @@
303! Compute bands310! Compute bands
304!** This uses H,S, and xa311!** This uses H,S, and xa
305 nullify( ebk )312 nullify( ebk )
306 call re_alloc( ebk, 1, no_u, 1, spinor_dim, 1, maxbk,313 if ( spin%Grid == 4 ) then
307 & 'ebk', 'siesta_analysis' )314 call re_alloc( ebk, 1, no_u*2, 1, 1, 1, maxbk,
308315 & 'ebk', 'siesta_analysis' )
309 if (nbk.gt.0) then316 else
317 call re_alloc( ebk, 1, no_u, 1, spin%spinor, 1, maxbk,
318 & 'ebk', 'siesta_analysis' )
319 end if
320
321 if ( nbk > 0 ) then
310 if (IONode) print "(a)", "Computing bands..."322 if (IONode) print "(a)", "Computing bands..."
311 getPSI = fdf_get('WFS.Write.For.Bands', .false.)323 getPSI = fdf_get('WFS.Write.For.Bands', .false.)
312 if (getPSI) then324 if (getPSI) then
313 wfs_filename = trim(slabel)//".bands.WFSX"325 wfs_filename = trim(slabel)//".bands.WFSX"
314 if (IONode) print "(a)", "Writing WFSX for bands in "326 if (IONode) print "(a)", "Writing WFSX for bands in "
315 $ // trim(wfs_filename)327 $ // trim(wfs_filename)
316 max_n_states = no_u328 wfs_band_min = fdf_get("WFS.BandMin",1)
317 if (h_spin_dim >= 4) max_n_states = 2*no_u329 wfs_band_max = fdf_get("WFS.BandMax",max_n_states)
318 wfs_band_min = fdf_get("WFS.BandMin",1)330 call setup_wfs_list(nbk,max_n_states,
319 wfs_band_max = fdf_get("WFS.BandMax",max_n_states)331 $ wfs_band_min,wfs_band_max,
320 call setup_wfs_list(nbk,max_n_states,332 $ use_scf_weights=.false.,
321 $ wfs_band_min,wfs_band_max,333 $ use_energy_window=.false.)
322 $ use_scf_weights=.false.,334 end if
323 $ use_energy_window=.false.)335 call bands( no_s, spin, no_u, no_l, maxnh,
324 endif
325 call bands( no_s, h_spin_dim, spinor_dim, no_u, no_l, maxnh,
326 . maxbk,336 . maxbk,
327 . numh, listhptr, listh, H, S, Ef, xijo, indxuo,337 . numh, listhptr, listh, H, S, Ef, xijo, indxuo,
328 . .true., nbk, bk, ebk, occtol, getPSI )338 . .true., nbk, bk, ebk, occtol, getPSI )
329 if (IOnode) then339
340 if ( IOnode ) then
330 if ( writbk ) then341 if ( writbk ) then
331 write(6,'(/,a,/,a4,a12)')342 write(6,'(/,a,/,a4,tr1,a12)')
332 & 'siesta: Band k vectors (Bohr**-1):', 'ik', 'k'343 & 'siesta: Band k vectors (Bohr**-1):', 'ik', 'k'
333 do ik = 1,nbk344 do ik = 1,nbk
334 write(6,'(i4,3f12.6)') ik, (bk(ix,ik),ix=1,3)345 write(6,'(i4,3(tr1,f12.6))') ik, (bk(ix,ik),ix=1,3)
335 enddo346 end do
336 endif347 end if
337 348
338 if ( writb ) then349 if ( writb ) then
339 write(6,'(/,a,/,a4,a3,a7)')350 if ( spin%Grid == 4 ) then
340 & 'siesta: Band energies (eV):', 'ik', 'is', 'eps'351 write(6,'(/,a,/,a4,tr1,a9)')
341 do ispin = 1, spinor_dim352 & 'siesta: Band energies (eV):', 'ik', 'eps'
342 do ik = 1,nbk353 do ik = 1,nbk
343 write(6,'(i4,i3,10f7.2)')354 write(6,'(i4,10(tr1,f9.4))')
344 & ik, ispin, (ebk(io,ispin,ik)/eV,io=1,min(10,no_u))355 & ik, (ebk(io,1,ik)/eV,io=1,min(10,2*no_u))
345 if (no_u.gt.10) write(6,'(7x,10f7.2)')356 if ( 2*no_u > 10 ) write(6,'(4x,10(tr1,f9.4))')
346 & (ebk(io,ispin,ik)/eV,io=11,no_u)357 & (ebk(io,1,ik)/eV,io=11,no_u*2)
358 end do
359
360 else
361 write(6,'(/,a,/,a4,a3,tr1,a9)')
362 & 'siesta: Band energies (eV):', 'ik', 'is', 'eps'
363 do ispin = 1, spin%spinor
364 do ik = 1,nbk
365 write(6,'(i4,i3,10(tr1,f9.4))')
366 & ik, ispin, (ebk(io,ispin,ik)/eV,io=1,min(10,no_u))
367 if ( no_u > 10 ) write(6,'(7x,10(tr1,f9.4))')
368 & (ebk(io,ispin,ik)/eV,io=11,no_u)
369 enddo
347 enddo370 enddo
348 enddo371 end if
349 endif372 endif
373
350 endif374 endif
351 endif375 endif
352376
353! Print eigenvalues377! Print eigenvalues
354 if (IOnode .and. writeig) then378 if ( IOnode .and. writeig .and. no_l < 1000 .and.
355 if ((isolve.eq.SOLVE_DIAGON .or.379 & (isolve.eq.SOLVE_DIAGON .or.
356 & ((isolve.eq.SOLVE_MINIM) .and. minim_calc_eigenvalues))380 & (isolve.eq.SOLVE_MINIM .and. minim_calc_eigenvalues)) ) then
357 & .and. no_l.lt.1000) then381
358 if ( h_spin_dim <= 2 ) then382 if ( spin%Grid == 4 ) then
359 write(6,'(/,a,/,a4,a3,a7)')383 write(6,'(/,a)') 'siesta: Eigenvalues (eV):'
360 & 'siesta: Eigenvalues (eV):', 'ik', 'is', 'eps'384 do ik = 1,nkpnt
361 do ik = 1,nkpnt385 write(6,'(a,i6)') 'ik =', ik
362 do ispin = 1,spinor_dim386 write(6,'(10(tr1,f9.4))') (eo(io,1,ik)/eV,io=1,2*neigwanted)
363 write(6,'(i4,i3,10f7.2)')387 end do
388
389 else
390 write(6,'(/,a,/,a4,a3,tr1,a9)')
391 & 'siesta: Eigenvalues (eV):', 'ik', 'is', 'eps'
392 do ik = 1,nkpnt
393 do ispin = 1, spin%spinor
394 write(6,'(i4,i3,10(tr1,f9.4))')
364 & ik,ispin,(eo(io,ispin,ik)/eV,io=1,min(10,neigwanted))395 & ik,ispin,(eo(io,ispin,ik)/eV,io=1,min(10,neigwanted))
365 if (no_u.gt.10) write(6,'(7x,10f7.2)')396 if (no_u.gt.10) write(6,'(7x,10(tr1,f9.4))')
366 & (eo(io,ispin,ik)/eV,io=11,neigwanted)397 & (eo(io,ispin,ik)/eV,io=11,neigwanted)
367 enddo398 end do
368 enddo399 end do
369 else400 end if
370 write(6,'(/,a)') 'siesta: Eigenvalues (eV):'401 write(6,'(a,f15.6,a)') 'siesta: Fermi energy =', ef/eV, ' eV'
371 do ik = 1,nkpnt
372 write(6,'(a,i6)') 'ik =', ik
373 write(6,'(10f7.2)')
374 & ((eo(io,ispin,ik)/eV,io=1,neigwanted),ispin=1,2)
375 enddo
376 endif
377 write(6,'(a,f15.6,a)') 'siesta: Fermi energy =', ef/eV, ' eV'
378 endif
379 endif402 endif
380403
381 if (((isolve.eq.SOLVE_DIAGON).or.404 if (((isolve.eq.SOLVE_DIAGON).or.
382 & ((isolve.eq.SOLVE_MINIM).and.minim_calc_eigenvalues))405 & ((isolve.eq.SOLVE_MINIM).and.minim_calc_eigenvalues))
383 & .and.IOnode)406 & .and.IOnode)
384 & call ioeig(eo,ef,neigwanted,nspin,nkpnt,no_u,spinor_dim,407 & call ioeig(eo,ef,neigwanted,spin%H,nkpnt,no_u,spin%spinor,
385 & nkpnt,kpoint, kweight)408 & nkpnt,kpoint, kweight)
386409
387410
@@ -437,7 +460,7 @@
437! Calculation of the bulk polarization using the Berry phase460! Calculation of the bulk polarization using the Berry phase
438! formulas by King-Smith and Vanderbilt461! formulas by King-Smith and Vanderbilt
439 if (nkpol.gt.0 .and. .not.bornz) then462 if (nkpol.gt.0 .and. .not.bornz) then
440 if (NonCol .or. SpOrb) then463 if ( spin%NCol .or. spin%SO ) then
441 if (IOnode) then464 if (IOnode) then
442 write(6,'(/a)')465 write(6,'(/a)')
443 . 'siesta_analysis: bulk polarization implemented only for'466 . 'siesta_analysis: bulk polarization implemented only for'
@@ -446,7 +469,7 @@
446 endif469 endif
447 else470 else
448 call KSV_pol(na_u, na_s, xa_last, rmaxo, scell_last, 471 call KSV_pol(na_u, na_s, xa_last, rmaxo, scell_last,
449 & ucell_last,no_u, no_l, no_s, nspin, qspin, 472 & ucell_last,no_u, no_l, no_s, spin%Grid, qspin,
450 & maxnh, nkpol, numh, listhptr, listh, 473 & maxnh, nkpol, numh, listhptr, listh,
451 & H, S, xijo, indxuo, isa, iphorb, 474 & H, S, xijo, indxuo, isa, iphorb,
452 & iaorb, lasto, shape,475 & iaorb, lasto, shape,
@@ -456,7 +479,7 @@
456479
457! Calculation of the optical conductivity480! Calculation of the optical conductivity
458 call optical(na_u, na_s, xa_last, scell_last, ucell_last,481 call optical(na_u, na_s, xa_last, scell_last, ucell_last,
459 & no_u, no_l, no_s, nspin, qspin,482 & no_u, no_l, no_s, spin%Grid, qspin,
460 & maxnh, numh, listhptr, listh, H, S, xijo,483 & maxnh, numh, listhptr, listh, H, S, xijo,
461 $ indxuo, ebk, ef, temp,484 $ indxuo, ebk, ef, temp,
462 & isa, iphorb, iphKB, lasto, lastkb, shape )485 & isa, iphorb, iphKB, lasto, lastkb, shape )
@@ -486,7 +509,7 @@
486 g2max = g2cut509 g2max = g2cut
487 dummy_str = 0.0510 dummy_str = 0.0
488 dummy_strl = 0.0511 dummy_strl = 0.0
489 call dhscf( nspin, no_s, iaorb, iphorb, no_l,512 call dhscf( spin%Grid, no_s, iaorb, iphorb, no_l,
490 . no_u, na_u, na_s, isa, xa_last, indxua, 513 . no_u, na_u, na_s, isa, xa_last, indxua,
491 & ntm, 0, 0, 0, filesOut, 514 & ntm, 0, 0, 0, filesOut,
492 & maxnh, numh, listhptr, listh, Dscf, Datm,515 & maxnh, numh, listhptr, listh, Dscf, Datm,
493516
=== modified file 'Src/writewave.F'
--- Src/writewave.F 2019-06-17 08:37:13 +0000
+++ Src/writewave.F 2019-08-08 11:56:55 +0000
@@ -40,7 +40,7 @@
40 USE alloc, only: re_alloc40 USE alloc, only: re_alloc
41 USE sys, only: die41 USE sys, only: die
42 USE atomlist, only: no_u42 USE atomlist, only: no_u
43 USE m_spin, only: h_spin_dim43 USE m_spin, only: spin
4444
45 implicit none45 implicit none
4646
@@ -51,11 +51,11 @@
51 nullify(wfk)51 nullify(wfk)
5252
53 nwk = 053 nwk = 0
54 if (h_spin_dim < 4) then54 if ( spin%Grid == 4 ) then
55 max_n_states = no_u55 max_n_states = 2 * no_u
56 else56 else
57 max_n_states = 2*no_u57 max_n_states = no_u
58 endif58 end if
59 call initwave( max_n_states, nwk, wfk )59 call initwave( max_n_states, nwk, wfk )
6060
61 if (nwk .eq. 0) then61 if (nwk .eq. 0) then
@@ -391,7 +391,7 @@
391391
392 end subroutine initwave392 end subroutine initwave
393393
394 subroutine wwave( no, nspin, maxspn, maxo, maxuo, maxnh, 394 subroutine wwave( no, spin, maxo, maxuo, maxnh,
395 . maxk,395 . maxk,
396 . numh, listhptr, listh, H, S, ef, xij, indxuo,396 . numh, listhptr, listh, H, S, ef, xij, indxuo,
397 . gamma, nk, kpoint, nuotot, occtol)397 . gamma, nk, kpoint, nuotot, occtol)
@@ -399,10 +399,10 @@
399C Finds wavefunctions at selected k-points.399C Finds wavefunctions at selected k-points.
400C Written by P. Ordejon, June 2003400C Written by P. Ordejon, June 2003
401C from routine 'bands' written by J.M.Soler401C from routine 'bands' written by J.M.Soler
402C Changed to use tSpin, N. Papior, August 2019
402C **************************** INPUT **********************************403C **************************** INPUT **********************************
403C integer no : Number of basis orbitals404C integer no : Number of basis orbitals
404C integer nspin = h_spin_dim : Number of spin components of H, D405C tSpin spin : Contains spin information
405C integer maxspn = spinor_dim : Second dimension of ek
406C integer maxo : First dimension of ek406C integer maxo : First dimension of ek
407C integer maxuo : Second dimension of H and S407C integer maxuo : Second dimension of H and S
408C integer maxnh : Maximum number of orbitals interacting 408C integer maxnh : Maximum number of orbitals interacting
@@ -414,7 +414,7 @@
414C hamiltonian matrix414C hamiltonian matrix
415C integer listh(maxlh) : Nonzero hamiltonian-matrix element 415C integer listh(maxlh) : Nonzero hamiltonian-matrix element
416C column indexes for each matrix row416C column indexes for each matrix row
417C real*8 H(maxnh,nspin) : Hamiltonian in sparse form417C real*8 H(maxnh,spin%H) : Hamiltonian in sparse form
418C real*8 S(maxnh) : Overlap in sparse form418C real*8 S(maxnh) : Overlap in sparse form
419C real*8 ef : Fermi energy419C real*8 ef : Fermi energy
420C real*8 xij(3,maxnh) : Vectors between orbital centers (sparse)420C real*8 xij(3,maxnh) : Vectors between orbital centers (sparse)
@@ -446,7 +446,7 @@
446 use atmfuncs, only : symfio, cnfigfio, labelfis, nofis446 use atmfuncs, only : symfio, cnfigfio, labelfis, nofis
447 use atomlist, only : iaorb, iphorb447 use atomlist, only : iaorb, iphorb
448 use siesta_geom, only : isa448 use siesta_geom, only : isa
449 use m_spin, only : NoMagn, SPpol, NonCol, SpOrb449 use t_spin, only: tSpin
450 use units, only : eV450 use units, only : eV
451451
452#ifdef MPI452#ifdef MPI
@@ -457,12 +457,12 @@
457457
458 implicit none458 implicit none
459459
460 type(tSpin), intent(in) :: spin
460 logical, intent(in) :: Gamma461 logical, intent(in) :: Gamma
461 integer maxk, maxnh, maxo, maxuo, nk, no, 462 integer maxk, maxnh, maxo, maxuo, nk, no,
462 . h_spin_dim, spinor_dim, nspin, maxspn,
463 . nuotot, indxuo(no), listh(maxnh), numh(*), 463 . nuotot, indxuo(no), listh(maxnh), numh(*),
464 . listhptr(*)464 . listhptr(*)
465 real(dp) ef, H(:,:), kpoint(3,maxk), 465 real(dp) ef, H(maxnh,spin%H), kpoint(3,maxk),
466 . S(maxnh), xij(3,maxnh), occtol466 . S(maxnh), xij(3,maxnh), occtol
467467
468 external io_assign, io_close, memory468 external io_assign, io_close, memory
@@ -488,11 +488,7 @@
488 data Dnew, Enew, e1, e2, qk, qtot, temp, wk /8*0.d0/488 data Dnew, Enew, e1, e2, qk, qtot, temp, wk /8*0.d0/
489489
490 logical :: SaveParallelOverK490 logical :: SaveParallelOverK
491 integer :: nspin_flag
492 491
493 h_spin_dim=size(H,dim=2)
494 nspin_flag = h_spin_dim
495 if (h_spin_dim == 8) nspin_flag = 4
496492
497C Get local number of orbitals493C Get local number of orbitals
498#ifdef MPI494#ifdef MPI
@@ -517,15 +513,15 @@
517C Check spin513C Check spin
518514
519C Allocate local arrays - only aux is relevant here515C Allocate local arrays - only aux is relevant here
520 if ( h_spin_dim >= 4 ) then516 if ( spin%Grid == 4 ) then
521 nhs = 2 * (2*nuotot) * (2*nuo)517 nhs = 2 * (2*nuotot) * (2*nuo)
522 else518 else
523 nhs = 2 * nuotot * nuo519 nhs = 2 * nuotot * nuo
524 endif520 endif
525 call allocDenseMatrix(nhs, nhs, nhs) 521 call allocDenseMatrix(nhs, nhs, nhs)
526522
527 allocate(ek(nuotot,maxspn,nk))523 allocate(ek(nuotot,spin%spinor,nk))
528 call memory('A','D',maxspn*nk*nuotot,'writewave')524 call memory('A','D',nuotot*spin%spinor*nk,'writewave')
529 naux = 2*nuotot*5525 naux = 2*nuotot*5
530 allocate(aux(naux))526 allocate(aux(naux))
531 call memory('A','D',naux,'writewave')527 call memory('A','D',naux,'writewave')
@@ -544,12 +540,12 @@
544 write(6,'(a)') 'writewave: Wave Functions Coefficients'540 write(6,'(a)') 'writewave: Wave Functions Coefficients'
545 write(6,*)541 write(6,*)
546 write(6,'(a26,2x,i6)') 'Number of k-points = ', nk542 write(6,'(a26,2x,i6)') 'Number of k-points = ', nk
547 write(6,'(a26,2x,i6)') 'Number of Spins = ', nspin_flag543 write(6,'(a26,2x,i6)') 'Number of Spins = ', spin%Grid
548 write(6,'(a26,2x,i6)') 'Number of basis orbs = ',nuotot544 write(6,'(a26,2x,i6)') 'Number of basis orbs = ',nuotot
549 write(6,*)545 write(6,*)
550 endif546 endif
551 write(iu) nk, gamma547 write(iu) nk, gamma
552 write(iu) nspin_flag ! This will be 1, 2, or 4548 write(iu) spin%Grid ! This will be 1, 2, or 4
553 write(iu) nuotot549 write(iu) nuotot
554 write(iu) (iaorb(j),labelfis(isa(iaorb(j))),550 write(iu) (iaorb(j),labelfis(isa(iaorb(j))),
555 . iphorb(j), cnfigfio(isa(iaorb(j)),iphorb(j)),551 . iphorb(j), cnfigfio(isa(iaorb(j)),iphorb(j)),
@@ -567,9 +563,9 @@
567563
568C Call appropriate diagonalization routine564C Call appropriate diagonalization routine
569565
570 if (NoMagn .or. SPpol) then566 if ( spin%Grid <= 2 ) then
571 if (gamma) then567 if (gamma) then
572 call diagg( h_spin_dim, nuo, maxuo, maxnh, maxnh, 568 call diagg( spin%H, nuo, maxuo, maxnh, maxnh,
573 . maxo, numh, listhptr, listh, numh, listhptr, 569 . maxo, numh, listhptr, listh, numh, listhptr,
574 . listh, H, S, getD, getPSI,570 . listh, H, S, getD, getPSI,
575 . fixspin, qtot, qs, temp,571 . fixspin, qtot, qs, temp,
@@ -589,7 +585,7 @@
589 call diag_init()585 call diag_init()
590 end if586 end if
591587
592 call diagk( h_spin_dim, nuo, no, maxspn, maxnh, maxnh,588 call diagk( spin%H, nuo, no, spin%spinor, maxnh, maxnh,
593 . maxo, numh, listhptr, listh, numh, listhptr, 589 . maxo, numh, listhptr, listh, numh, listhptr,
594 . listh, H, S, getD, getPSI,590 . listh, H, S, getD, getPSI,
595 . fixspin, qtot, qs, temp,591 . fixspin, qtot, qs, temp,
@@ -603,7 +599,7 @@
603 599
604 endif600 endif
605601
606 elseif (NonCol) then602 elseif ( spin%NCol) then
607 if (gamma) then603 if (gamma) then
608 call diag2g( nuo, no, maxnh, maxnh, maxo, numh,604 call diag2g( nuo, no, maxnh, maxnh, maxo, numh,
609 . listhptr, listh, numh, listhptr, listh,605 . listhptr, listh, numh, listhptr, listh,
@@ -620,7 +616,7 @@
620 . Haux, Saux, psi, Haux, Saux, aux,616 . Haux, Saux, psi, Haux, Saux, aux,
621 . nuotot, occtol, 1, nuotot )617 . nuotot, occtol, 1, nuotot )
622 endif618 endif
623 elseif (SpOrb) then619 elseif ( spin%SO ) then
624 if (gamma) then620 if (gamma) then
625 call diag3g( nuo, no, maxnh, maxnh, maxo, numh,621 call diag3g( nuo, no, maxnh, maxnh, maxo, numh,
626 . listhptr, listh, numh, listhptr, listh,622 . listhptr, listh, numh, listhptr, listh,
627623
=== modified file 'version.info'
--- version.info 2019-06-20 13:50:42 +0000
+++ version.info 2019-08-08 11:56:55 +0000
@@ -1,1 +1,1 @@
1siesta-4.1-1074--wfs-11151siesta-4.1-1074--wfs-1115--nicpa-1

Subscribers

People subscribed via source and target branches

to all changes: