Merge lp:~nickpapior/siesta/4.1-superc-gamma into lp:~albertog/siesta/4.1-superc-gamma

Proposed by Nick Papior
Status: Merged
Merged at revision: 932
Proposed branch: lp:~nickpapior/siesta/4.1-superc-gamma
Merge into: lp:~albertog/siesta/4.1-superc-gamma
Diff against target: 698 lines (+53/-89)
27 files modified
Src/Makefile (+1/-1)
Src/bands.F (+1/-5)
Src/compute_dm.F (+5/-10)
Src/diag2g.F (+4/-4)
Src/diag3g.F (+4/-4)
Src/diagg.F (+4/-4)
Src/diagon.F (+3/-4)
Src/intrinsic_missing.F90 (+1/-22)
Src/local_DOS.F (+1/-1)
Src/m_transiesta.F90 (+3/-3)
Src/pdos.F (+3/-4)
Src/post_scf_work.F (+2/-5)
Src/projected_DOS.F (+3/-2)
Src/siesta_analysis.F (+3/-4)
Src/writewave.F (+3/-4)
Util/COOP/Makefile (+1/-1)
Util/Denchar/Src/Makefile (+1/-1)
Util/Gen-basis/Makefile (+1/-1)
Util/Grimme/Makefile (+1/-1)
Util/Helpers/Makefile (+1/-1)
Util/STM/ol-stm/Src/Makefile (+1/-1)
Util/SpPivot/Makefile (+1/-1)
Util/TS/TBtrans/Makefile (+1/-1)
Util/TS/ts2ts/Makefile (+1/-1)
Util/TS/tshs2tshs/Makefile (+1/-1)
Util/VCA/Makefile (+1/-1)
version.info (+1/-1)
To merge this branch: bzr merge lp:~nickpapior/siesta/4.1-superc-gamma
Reviewer Review Type Date Requested Status
Alberto Garcia Pending
Review via email: mp+348462@code.launchpad.net

Commit message

Reinsert the Gamma variable in sub-routines for clarity.

Description of the change

I have reworked the patch to also include the Gamma variables for the corresponding k-point lists.
This should make it easier to follow the combinations.

I have also changed the keywords in transiesta, for clarity.

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

It looks good. Indeed more clear.

The only remaining problem is that, I think, the proper logic for choosing between dminim and zminim in the OMM method is based on the supercell (no_u == no_s) and not on whether the gamma point only is used. In other words. dminim will not work if we use a supercell with the gamma point.
There are places where it is obvious where to put a call to "MODP", but in other cases I am not sure.

So pending a possible optimization of this, I am going to merge retaining the "supercell" logic for this in compute_dm and post_scf_work.

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

Sorry for changing the m_dminim call. I can now see that you are correct, if a supercell is used, then OMM should use zminim.

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'Src/Makefile'
2--- Src/Makefile 2018-06-20 10:34:33 +0000
3+++ Src/Makefile 2018-06-25 11:35:23 +0000
4@@ -967,7 +967,7 @@
5 m_ts_electrode.o: precision.o sys.o units.o
6 m_ts_electype.o: class_OrbitalDistribution.o class_SpData1D.o class_SpData2D.o
7 m_ts_electype.o: class_Sparsity.o create_Sparsity_SC.o geom_helper.o
8-m_ts_electype.o: intrinsic_missing.o m_geom_box.o m_geom_plane.o
9+m_ts_electype.o: intrinsic_missing.o m_char.o m_geom_box.o m_geom_plane.o
10 m_ts_electype.o: m_handle_sparse.o m_iodm.o m_os.o m_region.o m_ts_chem_pot.o
11 m_ts_electype.o: m_ts_io.o m_ts_io_ctype.o m_ts_iodm.o parallel.o precision.o
12 m_ts_electype.o: units.o
13
14=== modified file 'Src/bands.F'
15--- Src/bands.F 2018-06-12 22:59:08 +0000
16+++ Src/bands.F 2018-06-25 11:35:23 +0000
17@@ -395,7 +395,6 @@
18 integer :: ik, il, io, ispin, iu, iu_wfs, iuo, naux, nhs, j
19
20 logical :: SaveParallelOverK
21- logical :: gamma
22
23 real(dp)
24 . Dnew, qs(2), e1, e2, efs(2), emax, emin, Enew, eV, qk, qtot,
25@@ -419,9 +418,6 @@
26 C Start time counter
27 call timer( 'bands', 1 )
28
29- ! This routine always uses diag*k routines
30- gamma = .false.
31-
32 C Check parameter maxk
33 if (nk .gt. maxk) then
34 if (Node.eq.0) then
35@@ -451,7 +447,7 @@
36
37 rewind (iu_wfs)
38
39- write(iu_wfs) nk, gamma
40+ write(iu_wfs) nk, .false. ! nk, Gamma, same file-format in WFS as for Gamma-point
41 write(iu_wfs) nspin
42 write(iu_wfs) no_u
43 write(iu_wfs) (iaorb(j),labelfis(isa(iaorb(j))),
44
45=== modified file 'Src/compute_dm.F'
46--- Src/compute_dm.F 2018-06-20 10:40:25 +0000
47+++ Src/compute_dm.F 2018-06-25 11:35:23 +0000
48@@ -66,8 +66,6 @@
49 real(dp) :: buffer1
50 integer :: mpierr
51
52- logical :: not_using_auxcell
53-
54 !-------------------------------------------------------------------- BEGIN
55
56 if (SIESTA_worker) call timer( 'compute_dm', 1 )
57@@ -92,8 +90,6 @@
58 !$OMP end parallel
59 end if
60
61- not_using_auxcell = (no_u == no_s)
62-
63 ! Compute shift in Tr(H*DM) for fermi-level bracketting
64 ! Use the current H, the previous iteration H, and the
65 ! previous iteration DM
66@@ -178,14 +174,13 @@
67 & no_l, maxnh, maxnh, no_u,
68 & numh, listhptr, listh, numh, listhptr, listh,
69 & H, S, qtot, fixspin, qtots, temp, e1, e2,
70- $ xijo, indxuo, nkpnt, kpoint, kweight,
71+ $ xijo, indxuo, gamma_SCF, nkpnt, kpoint, kweight,
72 & eo, qo, Dscf, Escf, ef, efs, Entropy, no_u,
73 & occtol, iscf, neigwanted)
74 Ecorrec = 0.0_dp
75 PreviousCallDiagon=.true.
76 elseif (isolve .eq. SOLVE_ORDERN) then
77- if ((nkpnt > 1) .or. (sum(abs(kpoint(:,1))) /= 0.0))
78- $ call die("Cannot do O(N) with k-points.")
79+ if ( .not. gamma_SCF ) call die("Cannot do O(N) with k-points.")
80 if ( spin%NCol .or. spin%SO )
81 . call die("Cannot do O(N) with non-coll spins or Spin-orbit")
82 call ordern(usesavelwf, ioptlwf, na_u, no_u, no_l, lasto,
83@@ -204,7 +199,7 @@
84 ! Test based on use of auxiliary supercell
85 ! It might still be possible to avoid the complex version
86
87- if (not_using_auxcell) then
88+ if ( gamma_SCF ) then
89 call dminim(.false., PreviousCallDiagon, iscf, istp, no_l,
90 & spin%H, no_u, maxnh, numh, listhptr, listh, Dscf,
91 & eta, qtots, H, S, H_kin)
92@@ -222,7 +217,7 @@
93 & no_l, maxnh, maxnh, no_u,
94 & numh, listhptr, listh, numh, listhptr, listh,
95 & H, S, qtot, fixspin, qtots, temp, e1, e2,
96- $ xijo, indxuo, nkpnt, kpoint, kweight,
97+ $ xijo, indxuo, gamma_SCF, nkpnt, kpoint, kweight,
98 & eo, qo, Dscf, Escf, ef, efs, Entropy, no_u,
99 & occtol, iscf, neigwanted)
100
101@@ -231,7 +226,7 @@
102 else if (TSrun) then
103
104 call transiesta(iscf,spin%H, block_dist, sparse_pattern,
105- & Not_Using_Auxcell, ucell, nsc, isc_off, no_u, na_u,
106+ & no_u == no_s, ucell, nsc, isc_off, no_u, na_u,
107 & lasto, xa, maxnh,
108 & H, S, Dscf, Escf, Ef, Qtot, .false., DE_NEGF )
109
110
111=== modified file 'Src/diag2g.F'
112--- Src/diag2g.F 2018-06-20 10:34:33 +0000
113+++ Src/diag2g.F 2018-06-25 11:35:23 +0000
114@@ -20,7 +20,7 @@
115 use parallel, only : Node, Nodes, BlockSize
116 use parallelsubs, only : LocalToGlobalOrb,GlobalToLocalOrb
117 use m_fermid, only : fermid, stepf
118- use intrinsic_missing, only: MODP1
119+ use intrinsic_missing, only: MODP
120
121 #ifdef MPI
122 use mpi_siesta
123@@ -163,7 +163,7 @@
124 do j = 1,numh(io)
125 ind = listhptr(io) + j
126 jo = listh(ind)
127- jo = MODP1(jo,nuotot) ! To allow auxiliary supercells
128+ jo = MODP(jo,nuotot) ! To allow auxiliary supercells
129 Saux(1,jo,1,io) = Saux(1,jo,1,io) + dcmplx( S(ind), 0.0_dp)
130 Saux(2,jo,2,io) = Saux(2,jo,2,io) + dcmplx( S(ind), 0.0_dp)
131 Haux(1,jo,1,io) = Haux(1,jo,1,io) + dcmplx(H(ind,1), 0.0_dp)
132@@ -189,7 +189,7 @@
133 do j = 1,numh(io)
134 ind = listhptr(io) + j
135 jo = listh(ind)
136- jo = MODP1(jo,nuotot) ! To allow auxiliary supercells
137+ jo = MODP(jo,nuotot) ! To allow auxiliary supercells
138 Saux(1,jo,1,io) = Saux(1,jo,1,io) +dcmplx( S(ind), 0.0_dp)
139 Saux(2,jo,2,io) = Saux(2,jo,2,io) +dcmplx( S(ind), 0.0_dp)
140 Haux(1,jo,1,io) = Haux(1,jo,1,io) +dcmplx(H(ind,1), 0.0_dp)
141@@ -269,7 +269,7 @@
142 do j = 1,numd(io)
143 ind = listdptr(io) + j
144 jo = listd(ind)
145- jo = MODP1(jo,nuotot) ! To allow auxiliary supercells
146+ jo = MODP(jo,nuotot) ! To allow auxiliary supercells
147
148 ! | ------- 1,1 ------- ------- 2,1 ------- |
149 ! | c_{j,up}^* c_{i,up} c_{j,dn}^* c_{i,up) |
150
151=== modified file 'Src/diag3g.F'
152--- Src/diag3g.F 2018-06-20 10:34:33 +0000
153+++ Src/diag3g.F 2018-06-25 11:35:23 +0000
154@@ -17,7 +17,7 @@
155 use parallel, only : Node, Nodes, BlockSize
156 use parallelsubs, only : LocalToGlobalOrb,GlobalToLocalOrb
157 use m_fermid, only : fermid, stepf
158- use intrinsic_missing, only: MODP1
159+ use intrinsic_missing, only: MODP
160 #ifdef MPI
161 use mpi_siesta
162 #endif
163@@ -155,7 +155,7 @@
164 do j = 1,numh(io)
165 ind = listhptr(io) + j
166 jo = listh(ind)
167- jo = MODP1(jo,nuotot) ! To allow auxiliary supercells
168+ jo = MODP(jo,nuotot) ! To allow auxiliary supercells
169 Saux(1,jo,1,io) = Saux(1,jo,1,io) + dcmplx( S(ind), 0.0_dp)
170 Saux(2,jo,2,io) = Saux(2,jo,2,io) + dcmplx( S(ind), 0.0_dp)
171 Haux(1,jo,1,io) = Haux(1,jo,1,io) + dcmplx(H(ind,1), H(ind,5))
172@@ -180,7 +180,7 @@
173 do j = 1,numh(io)
174 ind = listhptr(io) + j
175 jo = listh(ind)
176- jo = MODP1(jo,nuotot) ! To allow auxiliary supercells
177+ jo = MODP(jo,nuotot) ! To allow auxiliary supercells
178 Saux(1,jo,1,io) = Saux(1,jo,1,io) + dcmplx( S(ind), 0.0_dp)
179 Saux(2,jo,2,io) = Saux(2,jo,2,io) + dcmplx( S(ind), 0.0_dp)
180 Haux(1,jo,1,io) = Haux(1,jo,1,io) + dcmplx(H(ind,1), H(ind,5))
181@@ -264,7 +264,7 @@
182 do j = 1,numd(io)
183 ind = listdptr(io) + j
184 jo = listd(ind)
185- jo = MODP1(jo,nuotot) ! To allow auxiliary supercells
186+ jo = MODP(jo,nuotot) ! To allow auxiliary supercells
187 !------- 1,1 -----------------------------------------------------------
188 D11 = caux(1,iio) * dconjg(caux(1,jo))
189 !------- 2,2 -----------------------------------------------------------
190
191=== modified file 'Src/diagg.F'
192--- Src/diagg.F 2018-06-20 10:34:33 +0000
193+++ Src/diagg.F 2018-06-25 11:35:23 +0000
194@@ -90,7 +90,7 @@
195 use m_fermid, only : fermid, fermispin, stepf
196 use m_spin, only : spinor_dim, e_spin_dim
197 use alloc
198- use intrinsic_missing, only: MODP1
199+ use intrinsic_missing, only: MODP
200
201 #ifdef MPI
202 use mpi_siesta
203@@ -158,7 +158,7 @@
204 do j = 1,numh(io)
205 ind = listhptr(io) + j
206 jo = listh(ind)
207- jo = MODP1(jo,nuotot) ! To allow auxiliary supercells
208+ jo = MODP(jo,nuotot) ! To allow auxiliary supercells
209 Saux(jo,io) = Saux(jo,io) + S(ind)
210 Haux(jo,io) = Haux(jo,io) + H(ind,ispin)
211 enddo
212@@ -184,7 +184,7 @@
213 do j = 1,numh(io)
214 ind = listhptr(io) + j
215 jo = listh(ind)
216- jo = MODP1(jo,nuotot) ! To allow auxiliary supercells
217+ jo = MODP(jo,nuotot) ! To allow auxiliary supercells
218 Saux(jo,io) = Saux(jo,io) + S(ind)
219 Haux(jo,io) = Haux(jo,io) + H(ind,ispin)
220 enddo
221@@ -301,7 +301,7 @@
222 do j = 1,numd(io)
223 ind = listdptr(io) + j
224 jo = listd(ind)
225- jo = MODP1(jo,nuotot) ! To allow auxiliary supercells
226+ jo = MODP(jo,nuotot) ! To allow auxiliary supercells
227 Dnew(ind,ispin) = Dnew(ind,ispin) + qei*paux(jo)
228 Enew(ind,ispin) = Enew(ind,ispin) + eei*paux(jo)
229 enddo
230
231=== modified file 'Src/diagon.F'
232--- Src/diagon.F 2018-06-12 22:59:08 +0000
233+++ Src/diagon.F 2018-06-25 11:35:23 +0000
234@@ -15,7 +15,7 @@
235 subroutine diagon(no, nspin, maxuo, maxnh, maxnd,
236 . maxo, numh, listhptr, listh, numd,
237 . listdptr, listd, H, S, qtot, fixspin,
238- . qs, temp, e1, e2, xij, indxuo, nk,
239+ . qs, temp, e1, e2, xij, indxuo, gamma, nk,
240 . kpoint, wk, eo, qo, Dnew, Enew, ef, efs,
241 . Entropy, nuotot, occtol, iscf, neigwanted )
242 C *********************************************************************
243@@ -62,6 +62,7 @@
244 C Unit cell orbitals must be the first in
245 C orbital lists, i.e. indxuo.le.nuo, with
246 C nuo the number of orbitals in unit cell
247+C logical Gamma : Whether only the Gamma point is sampled.
248 C integer nk : Number of k points
249 C real*8 kpoint(3,nk) : k point vectors
250 C real*8 wk(nk) : k point weights (must sum one)
251@@ -115,6 +116,7 @@
252 implicit none
253
254 real(dp), intent(in) :: H(:,:)
255+ logical, intent(in) :: gamma
256
257 integer
258 . iscf, maxnd, maxnh, maxuo, maxo, nk, no, nuotot,
259@@ -145,7 +147,6 @@
260 #endif
261 integer :: io, iuo, naux, nhs, npsi, nuo
262 real(dp), pointer :: aux(:)
263- logical :: gamma
264 C ....................
265
266 C Get Node number and calculate local orbital range
267@@ -158,8 +159,6 @@
268 C Start time counter ................................................
269 call timer( 'diagon', 1 )
270
271- gamma = ((nk == 1) .and. (sum(abs(kpoint(:,1))) == 0.0))
272-
273 C Check internal dimensions ..........................................
274
275 if ( spin%none .or. spin%Col ) then
276
277=== modified file 'Src/intrinsic_missing.F90'
278--- Src/intrinsic_missing.F90 2018-06-20 10:34:33 +0000
279+++ Src/intrinsic_missing.F90 2018-06-25 11:35:23 +0000
280@@ -96,7 +96,6 @@
281
282 ! Elemental functions (can be called on arrays)
283 public :: MODP
284- public :: MODP1
285
286 ! Missing matrix stuff
287 public :: EYE
288@@ -232,29 +231,9 @@
289 elemental function MODP(a,p)
290 integer, intent(in) :: a,p
291 integer :: MODP
292- if ( a > p ) then
293- MODP = MOD(a,p)
294- if ( MODP == 0 ) MODP = p
295- else
296- MODP = a
297- end if
298+ MODP = MOD(a-1,p) + 1
299 end function MODP
300
301-! Another implementation of the above function
302-! NOTE that these functions should only be used on NATURAL numbers
303-! The target domain is [1,p] instead of [0,p-1]
304-! In particular, modp1(p,p) = p
305-! This makes it useful in FORTRAN do-loops which are not zero-based
306-! but 1-based.
307-
308- elemental function MODP1(a,p)
309- integer, intent(in) :: a,p
310- integer :: MODP1
311-
312- MODP1 = MOD(a-1,p) + 1
313-
314- end function MODP1
315-
316 ! Function to return the unique COUNT of an integer array.
317 ! Thus will return how many DIFFERENT entries there exists.
318 pure function UNIQC(array)
319
320=== modified file 'Src/local_DOS.F'
321--- Src/local_DOS.F 2018-06-12 22:59:08 +0000
322+++ Src/local_DOS.F 2018-06-25 11:35:23 +0000
323@@ -78,7 +78,7 @@
324 call diagon(no_s, spinor_dim, no_l, maxnh, maxnh, no_u,
325 . numh, listhptr, listh, numh, listhptr, listh,
326 . H, S, qtot, fixspin, qtots, temp, e1, e2,
327- . xijo, indxuo, nkpnt, kpoint, kweight,
328+ . xijo, indxuo, gamma_SCF, nkpnt, kpoint, kweight,
329 . eo, qo, Dscf, Escf, ef, efs, dummy_Entrop, no_u,
330 . occtol, dummy_iscf, neigwanted)
331
332
333=== modified file 'Src/m_transiesta.F90'
334--- Src/m_transiesta.F90 2018-04-04 13:22:33 +0000
335+++ Src/m_transiesta.F90 2018-06-25 11:35:23 +0000
336@@ -46,7 +46,7 @@
337
338 subroutine transiesta(TSiscf,nspin, &
339 sp_dist, sparse_pattern, &
340- Gamma, ucell, nsc, isc_off, no_u, na_u, lasto, xa, n_nzs, &
341+ no_aux_cell, ucell, nsc, isc_off, no_u, na_u, lasto, xa, n_nzs, &
342 H, S, DM, EDM, Ef, &
343 Qtot, Fermi_correct, DE_NEGF)
344
345@@ -82,7 +82,7 @@
346 integer, intent(in) :: nspin
347 type(OrbitalDistribution), intent(inout) :: sp_dist
348 type(Sparsity), intent(inout) :: sparse_pattern
349- logical, intent(in) :: Gamma
350+ logical, intent(in) :: no_aux_cell
351 real(dp), intent(in) :: ucell(3,3)
352 integer, intent(in) :: nsc(3), no_u, na_u
353 integer, intent(in) :: isc_off(3,product(nsc))
354@@ -134,7 +134,7 @@
355 ! local sparsity pattern...
356 converged = IsVolt .or. TS_RHOCORR_METHOD == TS_RHOCORR_FERMI
357 call ts_sparse_init(slabel,converged, N_Elec, Elecs, &
358- ucell, nsc, na_u, xa, lasto, sp_dist, sparse_pattern, Gamma, &
359+ ucell, nsc, na_u, xa, lasto, sp_dist, sparse_pattern, no_aux_cell, &
360 isc_off)
361
362 if ( ts_method == TS_BTD ) then
363
364=== modified file 'Src/pdos.F'
365--- Src/pdos.F 2018-06-12 22:59:08 +0000
366+++ Src/pdos.F 2018-06-25 11:35:23 +0000
367@@ -8,7 +8,7 @@
368 subroutine pdos( NO, nspin, maxspn, NO_L, MAXNH,
369 . MAXO, NUMH, LISTHPTR, LISTH, H, S,
370 . E1, E2, SIGMA, NHIST,
371- . XIJ, INDXUO, NK, KPOINT, WK, EO, NO_U )
372+ . XIJ, INDXUO, GAMMA, NK, KPOINT, WK, EO, NO_U )
373 C **********************************************************************
374 C Subroutine to calculate the projected density of states on the
375 C atomic orbitals for a given eigenvalue spectra
376@@ -43,6 +43,7 @@
377 C Unit cell orbitals must be the first in
378 C orbital lists, i.e. indxuo.le.nuo, with
379 C nuo the nuber of orbitals in the unit cell
380+C logical Gamma : whether only the Gamma point is sampled
381 C INTEGER NK : Number of k points
382 C REAL*8 KPOINT(3,NK) : k point vectors
383 C REAL*8 WK(NK) : k point weights (must sum one)
384@@ -79,6 +80,7 @@
385 . NO, NSPIN, MAXSPN, NO_L, MAXNH, NK, NHIST,
386 . MAXO, NO_U
387
388+ logical, intent(in) :: Gamma
389 integer
390 . NUMH(*), LISTH(MAXNH), LISTHPTR(*), INDXUO(NO)
391
392@@ -98,7 +100,6 @@
393 integer iat, spec, ii, iorb
394
395 logical :: orig_ParallelOverK, orig_Serial
396- logical :: gamma
397
398 real(dp), dimension(:), pointer :: tmp
399
400@@ -121,8 +122,6 @@
401
402 call timer( 'pdos', 1)
403
404- gamma = ((nk == 1) .and. (sum(abs(kpoint(:,1))) == 0.0))
405-
406 orig_Serial = Serial
407 orig_ParallelOverK = ParallelOverK
408
409
410=== modified file 'Src/post_scf_work.F'
411--- Src/post_scf_work.F 2018-06-20 10:34:33 +0000
412+++ Src/post_scf_work.F 2018-06-25 11:35:23 +0000
413@@ -50,12 +50,9 @@
414 character(len=20) :: msg
415 type(Pair_Geometry_dSpData2D) :: pair
416 type(Geometry) :: geom
417- logical :: not_using_auxcell
418
419 call timer( 'PostSCF', 1 )
420
421- not_using_auxcell = (no_s == no_u)
422-!
423 ! If converged, make one last iteration to find forces and stress
424
425 ! If we use the minimization routine, the energy-density
426@@ -79,12 +76,12 @@
427 & no_l, maxnh, maxnh, no_u,
428 & numh, listhptr, listh, numh, listhptr, listh,
429 & H, S, qtot, fixspin, qtots, temp, 1.0_dp, -1.0_dp,
430- & xijo, indxuo, nkpnt, kpoint, kweight,
431+ & xijo, indxuo, gamma_SCF, nkpnt, kpoint, kweight,
432 & eo, qo, Dscf, Escf, ef, efs, Entropy, no_u,
433 & occtol, iscf, neigwanted)
434 Ecorrec = 0.0_dp
435 else
436- if (not_using_auxcell) then
437+ if ( gamma_SCF ) then
438 call dminim(.true., .false., iscf, istp, no_l, nspin, no_u,
439 & maxnh, numh, listhptr, listh, Escf, eta, qtots)
440 else
441
442=== modified file 'Src/projected_DOS.F'
443--- Src/projected_DOS.F 2018-06-12 22:59:08 +0000
444+++ Src/projected_DOS.F 2018-06-25 11:35:23 +0000
445@@ -121,7 +121,7 @@
446 call pdos( no_s, h_spin_dim, spinor_dim, no_l,
447 . maxnh,
448 . no_u, numh, listhptr, listh, H, S,
449- . e1, e2, sigma, nhist, xijo, indxuo,
450+ . e1, e2, sigma, nhist, xijo, indxuo, gamma_PDOS,
451 . nkpnt_pdos, kpoints_pdos, kweight_pdos, eo,
452 . no_u)
453 else
454@@ -130,7 +130,8 @@
455 . maxnh,
456 . no_u, numh, listhptr, listh, H, S,
457 . e1, e2, sigma, nhist,
458- . xijo, indxuo, nkpnt, kpoint, kweight, eo,
459+ . xijo, indxuo, gamma_SCF,
460+ . nkpnt, kpoint, kweight, eo,
461 . no_u)
462 endif
463
464
465=== modified file 'Src/siesta_analysis.F'
466--- Src/siesta_analysis.F 2018-06-12 22:59:08 +0000
467+++ Src/siesta_analysis.F 2018-06-25 11:35:23 +0000
468@@ -15,7 +15,7 @@
469
470 subroutine siesta_analysis( relaxd )
471 USE band, only: nbk, bk, maxbk, bands
472- USE writewave, only: nwk, wfk, wwave
473+ USE writewave, only: nwk, wfk, wwave, gamma_wavefunctions
474 USE writewave, only: setup_wfs_list, wfs_filename
475 USE m_ksvinit, only: nkpol, kpol, wgthpol
476 use m_ksv
477@@ -35,7 +35,6 @@
478 & iphkb, no_u, no_s, iza, iphorb, rmaxo, indxua
479 use atomlist, only: qtot
480 use fdf
481- use writewave, only: wwave
482 use siesta_cml
483 use files, only : slabel
484 use files, only : filesOut_t ! derived type for output file names
485@@ -274,7 +273,7 @@
486 call wwave( no_s, h_spin_dim, spinor_dim, no_u, no_l, maxnh,
487 & nwk,
488 & numh, listhptr, listh, H, S, Ef, xijo, indxuo,
489- & nwk, wfk, no_u, occtol )
490+ & gamma_wavefunctions, nwk, wfk, no_u, occtol )
491 endif
492
493
494@@ -294,7 +293,7 @@
495 call wwave( no_s, h_spin_dim, spinor_dim, no_u, no_l, maxnh,
496 . nkpnt,
497 . numh, listhptr, listh, H, S, Ef, xijo, indxuo,
498- . nkpnt, kpoint, no_u, occtol)
499+ . gamma_SCF, nkpnt, kpoint, no_u, occtol)
500 endif
501
502 ! Compute bands
503
504=== modified file 'Src/writewave.F'
505--- Src/writewave.F 2018-06-12 22:59:08 +0000
506+++ Src/writewave.F 2018-06-25 11:35:23 +0000
507@@ -386,7 +386,7 @@
508 subroutine wwave( no, nspin, maxspn, maxo, maxuo, maxnh,
509 . maxk,
510 . numh, listhptr, listh, H, S, ef, xij, indxuo,
511- . nk, kpoint, nuotot, occtol)
512+ . gamma, nk, kpoint, nuotot, occtol)
513 C *********************************************************************
514 C Finds wavefunctions at selected k-points.
515 C Written by P. Ordejon, June 2003
516@@ -415,6 +415,7 @@
517 C Unit cell orbitals must be the first in
518 C orbital lists, i.e. indxuo.le.nuo, with
519 C nuo the number of orbitals in unit cell
520+C logical Gamma : whether only the Gamma-point is sampled
521 C integer nk : Number of band k points
522 C real*8 kpoint(3,maxk) : k point vectors
523 C integer nuotot : Total number of orbitals in unit cell
524@@ -447,6 +448,7 @@
525
526 implicit none
527
528+ logical, intent(in) :: Gamma
529 integer maxk, maxnh, maxo, maxuo, nk, no,
530 . h_spin_dim, spinor_dim, nspin, maxspn,
531 . nuotot, indxuo(no), listh(maxnh), numh(*),
532@@ -477,7 +479,6 @@
533 data Dnew, Enew, e1, e2, qk, qtot, temp, wk /8*0.d0/
534
535 logical :: SaveParallelOverK
536- logical gamma
537
538 h_spin_dim=size(H,dim=2)
539
540@@ -492,8 +493,6 @@
541 C Start time counter
542 call timer( 'writewave', 1 )
543
544- gamma = ((nk == 1) .and. (sum(abs(kpoint(:,1))) == 0.0))
545-
546 C Check parameter maxk
547 if (nk .gt. maxk) then
548 if (Node.eq.0) then
549
550=== modified file 'Util/COOP/Makefile'
551--- Util/COOP/Makefile 2018-06-20 10:34:33 +0000
552+++ Util/COOP/Makefile 2018-06-25 11:35:23 +0000
553@@ -483,7 +483,7 @@
554 m_ts_electrode.o: parallel.o precision.o units.o
555 m_ts_electype.o: class_OrbitalDistribution.o class_SpData1D.o class_SpData2D.o
556 m_ts_electype.o: class_Sparsity.o create_Sparsity_SC.o geom_helper.o
557-m_ts_electype.o: intrinsic_missing.o m_geom_box.o m_geom_plane.o
558+m_ts_electype.o: intrinsic_missing.o m_char.o m_geom_box.o m_geom_plane.o
559 m_ts_electype.o: m_handle_sparse.o m_iodm.o m_os.o m_region.o m_ts_chem_pot.o
560 m_ts_electype.o: m_ts_io.o m_ts_io_ctype.o m_ts_iodm.o parallel.o precision.o
561 m_ts_electype.o: units.o
562
563=== modified file 'Util/Denchar/Src/Makefile'
564--- Util/Denchar/Src/Makefile 2018-06-20 10:34:33 +0000
565+++ Util/Denchar/Src/Makefile 2018-06-25 11:35:23 +0000
566@@ -557,7 +557,7 @@
567 m_ts_electrode.o: parallel.o precision.o units.o
568 m_ts_electype.o: class_OrbitalDistribution.o class_SpData1D.o class_SpData2D.o
569 m_ts_electype.o: class_Sparsity.o create_Sparsity_SC.o geom_helper.o
570-m_ts_electype.o: intrinsic_missing.o m_geom_box.o m_geom_plane.o
571+m_ts_electype.o: intrinsic_missing.o m_char.o m_geom_box.o m_geom_plane.o
572 m_ts_electype.o: m_handle_sparse.o m_iodm.o m_os.o m_region.o m_ts_chem_pot.o
573 m_ts_electype.o: m_ts_io.o m_ts_io_ctype.o m_ts_iodm.o parallel.o precision.o
574 m_ts_electype.o: units.o
575
576=== modified file 'Util/Gen-basis/Makefile'
577--- Util/Gen-basis/Makefile 2018-06-20 10:34:33 +0000
578+++ Util/Gen-basis/Makefile 2018-06-25 11:35:23 +0000
579@@ -547,7 +547,7 @@
580 m_ts_electrode.o: parallel.o precision.o units.o
581 m_ts_electype.o: class_OrbitalDistribution.o class_SpData1D.o class_SpData2D.o
582 m_ts_electype.o: class_Sparsity.o create_Sparsity_SC.o geom_helper.o
583-m_ts_electype.o: intrinsic_missing.o m_geom_box.o m_geom_plane.o
584+m_ts_electype.o: intrinsic_missing.o m_char.o m_geom_box.o m_geom_plane.o
585 m_ts_electype.o: m_handle_sparse.o m_iodm.o m_os.o m_region.o m_ts_chem_pot.o
586 m_ts_electype.o: m_ts_io.o m_ts_io_ctype.o m_ts_iodm.o parallel.o precision.o
587 m_ts_electype.o: units.o
588
589=== modified file 'Util/Grimme/Makefile'
590--- Util/Grimme/Makefile 2018-06-20 10:34:33 +0000
591+++ Util/Grimme/Makefile 2018-06-25 11:35:23 +0000
592@@ -485,7 +485,7 @@
593 m_ts_electrode.o: parallel.o precision.o units.o
594 m_ts_electype.o: class_OrbitalDistribution.o class_SpData1D.o class_SpData2D.o
595 m_ts_electype.o: class_Sparsity.o create_Sparsity_SC.o geom_helper.o
596-m_ts_electype.o: intrinsic_missing.o m_geom_box.o m_geom_plane.o
597+m_ts_electype.o: intrinsic_missing.o m_char.o m_geom_box.o m_geom_plane.o
598 m_ts_electype.o: m_handle_sparse.o m_iodm.o m_os.o m_region.o m_ts_chem_pot.o
599 m_ts_electype.o: m_ts_io.o m_ts_io_ctype.o m_ts_iodm.o parallel.o precision.o
600 m_ts_electype.o: units.o
601
602=== modified file 'Util/Helpers/Makefile'
603--- Util/Helpers/Makefile 2018-06-20 10:34:33 +0000
604+++ Util/Helpers/Makefile 2018-06-25 11:35:23 +0000
605@@ -488,7 +488,7 @@
606 m_ts_electrode.o: parallel.o precision.o units.o
607 m_ts_electype.o: class_OrbitalDistribution.o class_SpData1D.o class_SpData2D.o
608 m_ts_electype.o: class_Sparsity.o create_Sparsity_SC.o geom_helper.o
609-m_ts_electype.o: intrinsic_missing.o m_geom_box.o m_geom_plane.o
610+m_ts_electype.o: intrinsic_missing.o m_char.o m_geom_box.o m_geom_plane.o
611 m_ts_electype.o: m_handle_sparse.o m_iodm.o m_os.o m_region.o m_ts_chem_pot.o
612 m_ts_electype.o: m_ts_io.o m_ts_io_ctype.o m_ts_iodm.o parallel.o precision.o
613 m_ts_electype.o: units.o
614
615=== modified file 'Util/STM/ol-stm/Src/Makefile'
616--- Util/STM/ol-stm/Src/Makefile 2018-06-20 10:34:33 +0000
617+++ Util/STM/ol-stm/Src/Makefile 2018-06-25 11:35:23 +0000
618@@ -570,7 +570,7 @@
619 m_ts_electrode.o: parallel.o precision.o units.o
620 m_ts_electype.o: class_OrbitalDistribution.o class_SpData1D.o class_SpData2D.o
621 m_ts_electype.o: class_Sparsity.o create_Sparsity_SC.o geom_helper.o
622-m_ts_electype.o: intrinsic_missing.o m_geom_box.o m_geom_plane.o
623+m_ts_electype.o: intrinsic_missing.o m_char.o m_geom_box.o m_geom_plane.o
624 m_ts_electype.o: m_handle_sparse.o m_iodm.o m_os.o m_region.o m_ts_chem_pot.o
625 m_ts_electype.o: m_ts_io.o m_ts_io_ctype.o m_ts_iodm.o parallel.o precision.o
626 m_ts_electype.o: units.o
627
628=== modified file 'Util/SpPivot/Makefile'
629--- Util/SpPivot/Makefile 2018-06-20 10:34:33 +0000
630+++ Util/SpPivot/Makefile 2018-06-25 11:35:23 +0000
631@@ -499,7 +499,7 @@
632 m_ts_electrode.o: parallel.o precision.o units.o
633 m_ts_electype.o: class_OrbitalDistribution.o class_SpData1D.o class_SpData2D.o
634 m_ts_electype.o: class_Sparsity.o create_Sparsity_SC.o geom_helper.o
635-m_ts_electype.o: intrinsic_missing.o m_geom_box.o m_geom_plane.o
636+m_ts_electype.o: intrinsic_missing.o m_char.o m_geom_box.o m_geom_plane.o
637 m_ts_electype.o: m_handle_sparse.o m_iodm.o m_os.o m_region.o m_ts_chem_pot.o
638 m_ts_electype.o: m_ts_io.o m_ts_io_ctype.o m_ts_iodm.o parallel.o precision.o
639 m_ts_electype.o: units.o
640
641=== modified file 'Util/TS/TBtrans/Makefile'
642--- Util/TS/TBtrans/Makefile 2018-06-20 10:34:33 +0000
643+++ Util/TS/TBtrans/Makefile 2018-06-25 11:35:23 +0000
644@@ -755,7 +755,7 @@
645 m_ts_electrode.o: parallel.o precision.o units.o
646 m_ts_electype.o: class_OrbitalDistribution.o class_SpData1D.o class_SpData2D.o
647 m_ts_electype.o: class_Sparsity.o create_Sparsity_SC.o geom_helper.o
648-m_ts_electype.o: intrinsic_missing.o m_geom_box.o m_geom_plane.o
649+m_ts_electype.o: intrinsic_missing.o m_char.o m_geom_box.o m_geom_plane.o
650 m_ts_electype.o: m_handle_sparse.o m_iodm.o m_os.o m_region.o m_ts_chem_pot.o
651 m_ts_electype.o: m_ts_io.o m_ts_io_ctype.o m_ts_iodm.o parallel.o precision.o
652 m_ts_electype.o: units.o
653
654=== modified file 'Util/TS/ts2ts/Makefile'
655--- Util/TS/ts2ts/Makefile 2018-06-20 10:34:33 +0000
656+++ Util/TS/ts2ts/Makefile 2018-06-25 11:35:23 +0000
657@@ -492,7 +492,7 @@
658 m_ts_electrode.o: parallel.o precision.o units.o
659 m_ts_electype.o: class_OrbitalDistribution.o class_SpData1D.o class_SpData2D.o
660 m_ts_electype.o: class_Sparsity.o create_Sparsity_SC.o geom_helper.o
661-m_ts_electype.o: intrinsic_missing.o m_geom_box.o m_geom_plane.o
662+m_ts_electype.o: intrinsic_missing.o m_char.o m_geom_box.o m_geom_plane.o
663 m_ts_electype.o: m_handle_sparse.o m_iodm.o m_os.o m_region.o m_ts_chem_pot.o
664 m_ts_electype.o: m_ts_io.o m_ts_io_ctype.o m_ts_iodm.o parallel.o precision.o
665 m_ts_electype.o: units.o
666
667=== modified file 'Util/TS/tshs2tshs/Makefile'
668--- Util/TS/tshs2tshs/Makefile 2018-06-20 10:34:33 +0000
669+++ Util/TS/tshs2tshs/Makefile 2018-06-25 11:35:23 +0000
670@@ -558,7 +558,7 @@
671 m_ts_electrode.o: parallel.o precision.o units.o
672 m_ts_electype.o: class_OrbitalDistribution.o class_SpData1D.o class_SpData2D.o
673 m_ts_electype.o: class_Sparsity.o create_Sparsity_SC.o geom_helper.o
674-m_ts_electype.o: intrinsic_missing.o m_geom_box.o m_geom_plane.o
675+m_ts_electype.o: intrinsic_missing.o m_char.o m_geom_box.o m_geom_plane.o
676 m_ts_electype.o: m_handle_sparse.o m_iodm.o m_os.o m_region.o m_ts_chem_pot.o
677 m_ts_electype.o: m_ts_io.o m_ts_io_ctype.o m_ts_iodm.o parallel.o precision.o
678 m_ts_electype.o: units.o
679
680=== modified file 'Util/VCA/Makefile'
681--- Util/VCA/Makefile 2018-06-20 10:34:33 +0000
682+++ Util/VCA/Makefile 2018-06-25 11:35:23 +0000
683@@ -518,7 +518,7 @@
684 m_ts_electrode.o: parallel.o precision.o units.o
685 m_ts_electype.o: class_OrbitalDistribution.o class_SpData1D.o class_SpData2D.o
686 m_ts_electype.o: class_Sparsity.o create_Sparsity_SC.o geom_helper.o
687-m_ts_electype.o: intrinsic_missing.o m_geom_box.o m_geom_plane.o
688+m_ts_electype.o: intrinsic_missing.o m_char.o m_geom_box.o m_geom_plane.o
689 m_ts_electype.o: m_handle_sparse.o m_iodm.o m_os.o m_region.o m_ts_chem_pot.o
690 m_ts_electype.o: m_ts_io.o m_ts_io_ctype.o m_ts_iodm.o parallel.o precision.o
691 m_ts_electype.o: units.o
692
693=== modified file 'version.info'
694--- version.info 2018-06-20 10:43:13 +0000
695+++ version.info 2018-06-25 11:35:23 +0000
696@@ -1,1 +1,1 @@
697-siesta-4.1--933--gamma-931
698+siesta-4.1--933--gamma-931--nick-1

Subscribers

People subscribed via source and target branches

to all changes: