1!
2! Copyright (C) 2003-2009 A. Smogunov
3! This file is distributed under the terms of the
4! GNU General Public License. See the file `License'
5! in the root directory of the present distribution,
6! or http://www.gnu.org/copyleft/gpl.txt .
7!
8!
9SUBROUTINE do_cond(done)
10!
11!   This is the main driver of the pwcond.x program.
12!   It calculates the complex band structure, solves the
13!   scattering problem and calculates the transmission coefficient.
14!
15  USE constants,  ONLY : rytoev
16  USE ions_base,  ONLY : nat, ityp, ntyp => nsp, tau, atm
17  USE cell_base,  ONLY : at, bg, tpiba
18  USE klist,      ONLY : npk, xk, two_fermi_energies
19  USE ldaU,       ONLY : lda_plus_U, lda_plus_u_kind, U_projection, &
20                         Hubbard_lmax, Hubbard_l, Hubbard_U, Hubbard_alpha, &
21                         Hubbard_J0, Hubbard_beta
22  USE spin_orb,   ONLY : lspinorb, domag
23  USE uspp,       ONLY : okvan
24  USE gvect,      ONLY : ecutrho
25  USE gvecw,      ONLY : ecutwfc
26  USE symm_base,  ONLY: nsym, s, t_rev, time_reversal
27  USE cond
28  USE io_files,   ONLY: tmp_dir, prefix
29  !!! RECOVER
30  USE cond_restart, ONLY : cond_readfile, cond_writefile
31  USE check_stop, ONLY: max_seconds, check_stop_init, check_stop_now
32  !!!
33  USE noncollin_module, ONLY : noncolin, i_cons
34  USE io_global, ONLY : stdout, ionode, ionode_id
35  USE mp_global, ONLY : mp_startup
36  USE mp_pools,  ONLY : npool
37  USE mp_images, ONLY : intra_image_comm, nproc_image
38  USE paw_onecenter,      ONLY : PAW_potential
39  USE paw_variables,      ONLY : okpaw, ddd_PAW
40  USE mp
41  USE environment,   ONLY : environment_start
42
43  IMPLICIT NONE
44  !
45  CHARACTER(LEN=256), EXTERNAL :: trimcheck
46  CHARACTER(LEN=256) :: outdir
47  !
48  LOGICAL, INTENT(OUT) :: done
49  !
50  REAL(DP) :: wtot, tk
51  INTEGER :: ik, ien, ipol, ios, nt
52  INTEGER :: loop1, loop2, loop1_in, loop1_fin, loop2_in, loop2_fin
53  LOGICAL :: lso_l, lso_s, lso_r, skip_equivalence = .FALSE.
54  REAL(DP) :: ecutwfc_l, ecutwfc_s, ecutwfc_r
55  REAL(DP) :: ecutrho_l, ecutrho_s, ecutrho_r
56
57  !!! RECOVER
58  LOGICAL :: tran_save
59  !!!
60
61  NAMELIST /inputcond/ outdir, prefixt, prefixl, prefixs, prefixr,     &
62                       band_file, tran_file, save_file, fil_loc,       &
63                       lwrite_loc, lread_loc, lwrite_cond, lread_cond, &
64                       tran_prefix, recover, max_seconds, loop_ek,     &
65                       orbj_in,orbj_fin,ikind,iofspin,llocal,          &
66                       bdl, bds, bdr, nz1, energy0, denergy, ecut2d,   &
67                       start_e, last_e, start_k, last_k,               &
68                       ewind, epsproj, delgep, cutplot,                &
69                       tk_plot, lorb, lorb3d, lcharge
70  !
71  ! initialise environment
72  !
73#if defined(__MPI)
74  CALL mp_startup ( )
75#endif
76  CALL environment_start ( 'PWCOND' )
77  CALL start_clock('init')
78!
79!   set default values for variables in namelist
80!
81  CALL get_environment_variable( 'ESPRESSO_TMPDIR', outdir )
82  IF ( TRIM( outdir ) == ' ' ) outdir = './'
83  prefixt = ' '
84  prefixl = ' '
85  prefixs = ' '
86  prefixr = ' '
87  band_file = ' '
88  tran_file = ' '
89  save_file = ' '
90  fil_loc = ' '
91  loop_ek = .FALSE.
92  lwrite_loc = .FALSE.
93  lread_loc = .FALSE.
94  lwrite_cond = .FALSE.
95  lread_cond  = .FALSE.
96  !!! RECOVER
97  tran_prefix = ' '
98  recover = .FALSE.
99  !!!
100  orbj_in = 0
101  orbj_fin = 0
102  iofspin = 1
103  ikind = 0
104  bdl = 0.d0
105  bds = 0.d0
106  bdr = 0.d0
107  nz1 = 11
108  energy0 = 0.d0
109  denergy = 0.d0
110  ecut2d = 0.d0
111  start_e = 0
112  last_e = 0
113  start_k = 0
114  last_k = 0
115  ewind = 1.d0
116  llocal = .FALSE.
117  epsproj = 1.d-3
118  delgep = 5.d-10
119  cutplot = 2.d0
120  tk_plot = 0
121  lorb=.FALSE.
122  lorb3d=.FALSE.
123  lcharge=.FALSE.
124
125  IF ( ionode )  THEN
126     !
127     CALL input_from_file ( )
128     !
129     !     reading the namelist inputcond
130     !
131     READ (5, inputcond, err=200, iostat=ios )
132200  CALL errore ('do_cond','reading inputcond namelist',ABS(ios))
133     tmp_dir=trimcheck (outdir)
134     !
135     !     Reading 2D k-point
136     READ(5, *, err=250, iostat=ios ) nkpts
137250     CALL errore ('do_cond','reading number of kpoints',ABS(ios))
138     IF (nkpts>0) THEN
139        ALLOCATE( xyk(2,nkpts) )
140        ALLOCATE( wkpt(nkpts) )
141        wtot = 0.d0
142        DO ik = 1, nkpts
143           READ(5, *, err=300, iostat=ios) xyk(1,ik), xyk(2,ik), wkpt(ik)
144           wtot = wtot + wkpt(ik)
145        ENDDO
146        DO ik = 1, nkpts
147           wkpt(ik) = wkpt(ik)/wtot
148        ENDDO
149300     CALL errore ('do_cond','2D k-point',ABS(ios))
150     ELSE
151        ALLOCATE( xyk(2,npk) )
152        ALLOCATE( wkpt(npk) )
153        READ(5, *, err=350, iostat=ios) nk1ts, nk2ts, k1ts, k2ts
154350     CALL errore ('do_cond','2D k-point size or shift',ABS(ios))
155     ENDIF
156
157     !
158     !     To form the array of energies for calculation
159     !
160     READ(5, *, err=400, iostat=ios ) nenergy
161     ALLOCATE( earr(nenergy) )
162     ALLOCATE( tran_tot(nenergy) )
163     IF(ABS(denergy).LE.1.d-8) THEN
164        !   the list of energies is read
165        DO ien = 1, nenergy
166           READ(5, *, err=400, iostat=ios) earr(ien)
167           tran_tot(ien) = 0.d0
168        ENDDO
169     ELSE
170        !   the array of energies is automatically formed
171        DO ien = 1, nenergy
172           earr(ien) = energy0 + (ien-1)*denergy
173           tran_tot(ien) = 0.d0
174        ENDDO
175     ENDIF
176
177     IF (start_e .GT. 0) THEN
178        IF (start_e .GT. last_e .OR. start_e .GT. nenergy) &
179           CALL errore('do_cond','wrong value of start_e',1)
180        IF (last_e .GT. nenergy) last_e = nenergy
181     ELSE
182        start_e = 1
183        last_e = nenergy
184     ENDIF
185
186400  CALL errore ('do_cond','reading energy list',ABS(ios))
187     !
188  END IF
189
190#if defined(__MPI)
191   IF (npool > 1) CALL errore('pwcond','pools not implemented',npool)
192   ik = IAND ( nproc_image, nproc_image-1 )
193   IF ( nproc_image /= 1 .AND. ik /= 0 ) &
194       CALL errore('pwcond','you should use 2^N number of CPUs',1)
195#endif
196
197!-- Some check and initialization for plotting the scattering states
198  IF ( lorb .AND. ikind == 2 ) &
199       CALL errore('do_cond','lorb not working with ikind = 2',1)
200  IF (lorb3d) lorb = .TRUE.
201  IF (lcharge) lorb = .TRUE.
202!--
203
204!
205! ... Broadcast variables
206!
207  CALL mp_bcast( tmp_dir, ionode_id, intra_image_comm )
208  CALL mp_bcast( prefixt, ionode_id, intra_image_comm )
209  CALL mp_bcast( prefixl, ionode_id, intra_image_comm )
210  CALL mp_bcast( prefixs, ionode_id, intra_image_comm )
211  CALL mp_bcast( prefixr, ionode_id, intra_image_comm )
212  CALL mp_bcast( band_file, ionode_id, intra_image_comm )
213  CALL mp_bcast( tran_file, ionode_id, intra_image_comm )
214  CALL mp_bcast( fil_loc, ionode_id, intra_image_comm )
215  CALL mp_bcast( save_file, ionode_id, intra_image_comm )
216  CALL mp_bcast( loop_ek, ionode_id, intra_image_comm )
217  CALL mp_bcast( lwrite_loc, ionode_id, intra_image_comm )
218  CALL mp_bcast( lread_loc, ionode_id, intra_image_comm )
219  CALL mp_bcast( lwrite_cond, ionode_id, intra_image_comm )
220  CALL mp_bcast( lread_cond, ionode_id, intra_image_comm )
221  !!! RECOVER
222  CALL mp_bcast( tran_prefix, ionode_id, intra_image_comm )
223  CALL mp_bcast( max_seconds, ionode_id, intra_image_comm )
224  CALL mp_bcast( recover, ionode_id, intra_image_comm )
225  !!!
226  CALL mp_bcast( ikind, ionode_id, intra_image_comm )
227  CALL mp_bcast( iofspin, ionode_id, intra_image_comm )
228  CALL mp_bcast( orbj_in, ionode_id, intra_image_comm )
229  CALL mp_bcast( orbj_fin, ionode_id, intra_image_comm )
230  CALL mp_bcast( llocal, ionode_id, intra_image_comm )
231  CALL mp_bcast( tk_plot, ionode_id, intra_image_comm )
232  CALL mp_bcast( lorb, ionode_id, intra_image_comm )
233  CALL mp_bcast( lorb3d, ionode_id, intra_image_comm )
234  CALL mp_bcast( lcharge, ionode_id, intra_image_comm )
235  CALL mp_bcast( bdl, ionode_id, intra_image_comm )
236  CALL mp_bcast( bds, ionode_id, intra_image_comm )
237  CALL mp_bcast( bdr, ionode_id, intra_image_comm )
238  CALL mp_bcast( nz1, ionode_id, intra_image_comm )
239  CALL mp_bcast( energy0, ionode_id, intra_image_comm )
240  CALL mp_bcast( denergy, ionode_id, intra_image_comm )
241  CALL mp_bcast( ecut2d, ionode_id, intra_image_comm )
242  CALL mp_bcast( start_e, ionode_id, intra_image_comm )
243  CALL mp_bcast( last_e, ionode_id, intra_image_comm )
244  CALL mp_bcast( ewind, ionode_id, intra_image_comm )
245  CALL mp_bcast( epsproj, ionode_id, intra_image_comm )
246  CALL mp_bcast( delgep, ionode_id, intra_image_comm )
247  CALL mp_bcast( cutplot, ionode_id, intra_image_comm )
248  CALL mp_bcast( nkpts, ionode_id, intra_image_comm )
249  CALL mp_bcast( nenergy, ionode_id, intra_image_comm )
250  CALL mp_bcast( nk1ts, ionode_id, intra_image_comm )
251  CALL mp_bcast( nk2ts, ionode_id, intra_image_comm )
252  CALL mp_bcast( k1ts, ionode_id, intra_image_comm )
253  CALL mp_bcast( k2ts, ionode_id, intra_image_comm )
254
255  IF ( .NOT. ionode ) THEN
256     IF (nkpts>0) THEN
257        ALLOCATE( xyk(2,nkpts) )
258        ALLOCATE( wkpt(nkpts) )
259     ELSE
260        ALLOCATE( xyk(2,npk) )
261        ALLOCATE( wkpt(npk) )
262     ENDIF
263     ALLOCATE( earr(nenergy) )
264     ALLOCATE( tran_tot(nenergy) )
265  ENDIF
266  IF (nkpts>0) THEN
267     CALL mp_bcast( xyk, ionode_id, intra_image_comm )
268     CALL mp_bcast( wkpt, ionode_id, intra_image_comm )
269  ENDIF
270  CALL mp_bcast( earr, ionode_id, intra_image_comm )
271  CALL mp_bcast( tran_tot, ionode_id, intra_image_comm )
272
273
274!
275! Now allocate space for pwscf variables, read and check them.
276!
277
278IF (lread_cond) THEN
279  call save_cond (.false.,1,efl,nrzl,nocrosl,noinsl,   &
280                  norbl,rl,rabl,betarl)
281  if(ikind.eq.1) then
282    call save_cond (.false.,2,efs,nrzs,ik,      &
283                             noinss,norbs,rs,rabs,betars)
284    norbr = norbl
285    nocrosr = nocrosl
286    noinsr = noinsl
287  endif
288  if(ikind.eq.2) then
289    call save_cond (.false.,2,efs,nrzs,ik,      &
290                             noinss,norbs,rs,rabs,betars)
291
292    call save_cond (.false.,3,efr,nrzr,nocrosr,&
293                             noinsr,norbr,rr,rabr,betarr)
294  endif
295ELSE
296  lso_l=.false.
297  lso_s=.false.
298  lso_r=.false.
299  ecutwfc_l=0.0_DP
300  ecutwfc_s=0.0_DP
301  ecutwfc_r=0.0_DP
302  ecutrho_l=0.0_DP
303  ecutrho_s=0.0_DP
304  ecutrho_r=0.0_DP
305  IF (prefixt.ne.' ') then
306    prefix = prefixt
307
308    call read_file
309    IF (ikind.eq.0) then
310      CALL init_cond(1,'t')
311    ELSEIF (ikind.eq.1) then
312      CALL init_cond(2,'t')
313    ELSEIF (ikind.eq.2) then
314      CALL init_cond(3,'t')
315    ENDIF
316    CALL clean_pw(.true.)
317  ENDIF
318  IF (prefixl.ne.' ') then
319    prefix = prefixl
320    call read_file
321    lso_l=lspinorb
322    ecutwfc_l=ecutwfc
323    ecutrho_l=ecutrho
324    CALL init_cond(1,'l')
325  ENDIF
326
327  IF (prefixr.ne.' ') then
328    CALL clean_pw(.true.)
329    prefix = prefixr
330    call read_file
331    lso_r=lspinorb
332    ecutwfc_r=ecutwfc
333    ecutrho_r=ecutrho
334    CALL init_cond(1,'r')
335  ENDIF
336  IF (prefixs.ne.' ') then
337    call clean_pw(.true.)
338    prefix = prefixs
339    call read_file
340    lso_s=lspinorb
341    ecutwfc_s=ecutwfc
342    ecutrho_s=ecutrho
343    CALL init_cond(1,'s')
344  ENDIF
345
346  IF (two_fermi_energies.or.i_cons /= 0) &
347     CALL errore('pwcond',&
348     'The pwcond code with constrained magnetization is not yet available',1)
349  IF (ikind==1.and.(lso_l.neqv.lso_s)) &
350     CALL errore('pwcond',&
351     'Spin-orbit flag in left lead and scattering region do not match',1)
352  IF (ikind==2.and.((lso_l.neqv.lso_s).or.(lso_r.neqv.lso_s))) &
353     CALL errore('pwcond',&
354     'Spin-orbit flag in left, right lead and scattering region do not match',1)
355  IF (ikind>0.and.((ecutwfc_l.ne.ecutwfc_s).or.(ecutrho_l.ne.ecutrho_s)))  &
356     CALL errore('do_cond',&
357            'different cut-offs on left lead and scattering region',1)
358  IF ((ecutwfc_r>0.0_DP)) THEN
359     IF ((ecutwfc_r.ne.ecutwfc_s).or.(ecutrho_r.ne.ecutrho_s))  &
360     CALL errore('do_cond',&
361        'different cut-offs on right lead and scattering region',1)
362  ENDIF
363ENDIF
364
365IF (lwrite_cond) then
366  call save_cond (.true.,1,efl,nrzl,nocrosl,noinsl,         &
367                  norbl,rl,rabl,betarl)
368  if(ikind.gt.0) call save_cond (.true.,2,efs,nrzs,-1,      &
369                             noinss,norbs,rs,rabs,betars)
370  if(ikind.gt.1) call save_cond (.true.,3,efr,nrzr,nocrosr,&
371                             noinsr,norbr,rr,rabr,betarr)
372  write(stdout,*) 'information needed for PWCOND has been written in file'
373  CALL stop_clock('init')
374  CALL stop_clock('PWCOND')
375  CALL print_clock_pwcond()
376  return
377endif
378
379IF (nkpts==0) THEN
380   time_reversal = .NOT. (noncolin .AND. domag)
381   IF (ionode) THEN
382      CALL kpoint_grid( nsym, time_reversal, skip_equivalence, s, t_rev, bg, &
383                        npk, k1ts, k2ts, 0, nk1ts, nk2ts, 1, nkpts, xk, wkpt )
384      call cryst_to_cart(nkpts,xk,at,-1)
385      DO ik=1,nkpts
386         xyk(1,ik)=xk(1,ik)
387         xyk(2,ik)=xk(2,ik)
388      ENDDO
389   ENDIF
390   CALL mp_bcast( nkpts, ionode_id, intra_image_comm )
391   CALL mp_bcast( xyk, ionode_id, intra_image_comm )
392   CALL mp_bcast( wkpt, ionode_id, intra_image_comm )
393ELSE
394   tk_plot = 0
395ENDIF
396
397if (tk_plot.lt.0) CALL errore('do_cond','tk_plot should be > 0',1)
398If (tk_plot.gt.0) loop_ek = .TRUE.
399IF (ikind.ne.0.and.tk_plot.gt.0) ALLOCATE( tran_k(npk) )
400
401IF (start_k .GT. 0) THEN
402   IF (start_k .GT. last_k .OR. start_k .GT. nkpts) &
403     CALL errore('do_cond','wrong value of start_k',1)
404   IF (last_k .GT. nkpts) last_k = nkpts
405ELSE
406   start_k = 1
407   last_k = nkpts
408ENDIF
409CALL mp_bcast( start_k, ionode_id, intra_image_comm )
410CALL mp_bcast( last_k, ionode_id, intra_image_comm )
411
412  !!! RECOVER
413  ! Simple restart mechanism for transmission calculations
414  ! (tran_prefix must be specified on input in order to enable restart)
415  !!!
416  ! Initialization of recover:
417  IF (ikind.NE.0 .AND. tran_prefix.NE.' ') THEN
418     !
419     tran_save = .TRUE.
420     CALL check_stop_init ()
421     ! if recover flag is set to true, then check info file
422     IF ( recover ) THEN
423        ! read and check info file
424        ! (lists of energies and k-points read from info file
425        ! must coindice with those built from input parameters)
426        CALL cond_readfile( 'init', ios )
427     ELSE
428        ! create restart directory and write info file
429        CALL cond_writefile( 'init' )
430     ENDIF
431
432  ELSE
433     !
434     tran_save = .FALSE.
435     IF (recover)  call errore('do_cond',&
436        'you must specify tran_prefix in order to restart',1)
437  ENDIF
438  !!!
439
440  CALL cond_out
441
442  CALL stop_clock('init')
443
444  IF (llocal) &
445  CALL local_set(nocrosl,noinsl,norbl,noinss,norbs,nocrosr,noinsr,norbr)
446
447!--
448! Set up 2 loops over energies and over k-points
449  if (loop_ek) then
450    loop1_in  = start_e
451    loop1_fin = last_e
452    loop2_in  = start_k
453    loop2_fin = last_k
454  else
455    loop1_in  = start_k
456    loop1_fin = last_k
457    loop2_in  = start_e
458    loop2_fin = last_e
459  endif
460!--
461
462  DO loop1 = loop1_in, loop1_fin
463
464    if (.not.loop_ek) then
465      CALL init_gper(loop1)
466      CALL local(1)
467    endif
468
469    DO loop2 = loop2_in, loop2_fin
470
471      if (loop_ek) then
472        ien = loop1
473        ik  = loop2
474      else
475        ik  = loop1
476        ien = loop2
477      endif
478
479!      write(6,*) loop1_in, loop1_fin, loop2_in, loop2_fin, loop1, loop2
480      WRITE(stdout,'("---  E-Ef = ",f12.7, "  k = ",2f12.7)') &
481            earr(ien), (xyk (ipol, ik) , ipol = 1, 2)
482      WRITE(stdout,'("---  ie = ",i10, "  ik = ",i10)') &
483            ien, ik
484
485      !!! RECOVER
486      ! if recover mechanism is enabled
487      IF (recover .AND. ikind.NE.0) THEN
488         !
489         WRITE(stdout,'(A)') 'Reading transmission from restart file:'
490         ! check if the transmission has already been calculated for
491         ! this specific k-point and energy value
492         CALL cond_readfile( 'tran', ios, ik, ien, tk )
493         ! if so, add it to the total transmission with the correct weight
494         ! and skip to the next energy in the list
495         IF ( ios .EQ. 0 ) THEN
496            WRITE(stdout,'(a24, 2f12.7,/)') 'E-Ef(ev), T = ',earr(ien),tk
497            tran_tot(ien) = tran_tot(ien) + wkpt(ik)*tk
498            !CALL mp_bcast( tran_tot(ien), ionode_id, intra_image_comm )
499            CYCLE
500         ! if not, do the actual calculation
501         ELSE
502            IF ( ios .EQ. 1 ) THEN
503               write(stdout,'(" File not found...")')
504            ELSE
505               write(stdout,'(" FAILED: could not read from file...")')
506            ENDIF
507            write(stdout,'(" ... computing transmission",/)')
508         ENDIF
509      ENDIF
510      !!!
511
512      if (loop_ek) then
513        CALL init_gper(ik)
514        CALL local(ien)
515      endif
516
517      eryd = earr(ien)/rytoev + efl
518      CALL form_zk(n2d, nrzpl, zkrl, zkl, eryd, tpiba)
519      CALL scatter_forw(nrzl, nrzpl, zl, psiperl, zkl, norbl,     &
520                        tblml, crosl, taunewl, rl, rabl, betarl)
521      CALL compbs(1, nocrosl, norbl, nchanl, kvall, kfunl, kfundl, &
522                  kintl, kcoefl, ik, ien)
523
524      IF (ikind.EQ.2) THEN
525        eryd = earr(ien)/rytoev + efr
526        CALL form_zk(n2d, nrzpr, zkrr, zkr, eryd, tpiba)
527        CALL scatter_forw(nrzr, nrzpr, zr, psiperr, zkr, norbr,    &
528                          tblmr, crosr, taunewr, rr, rabr, betarr)
529        CALL compbs(0, nocrosr, norbr, nchanr, kvalr, kfunr, kfundr,&
530                     kintr, kcoefr, ik, ien)
531      ENDIF
532
533      CALL summary_band(ik,ien)
534
535      IF (ikind.NE.0) THEN
536         eryd = earr(ien)/rytoev + efs
537         CALL form_zk(n2d, nrzps, zkrs, zks, eryd, tpiba)
538         CALL scatter_forw(nrzs, nrzps, zs, psipers, zks, norbs,    &
539                          tblms, cross, taunews, rs, rabs, betars)
540
541         WRITE(stdout,*) 'to transmit'
542         CALL transmit(ik, ien, tk, .true.)
543         !
544         ! To add T(k) to the total T
545         !
546         tran_tot(ien) = tran_tot(ien) + wkpt(ik)*tk
547         if (tk_plot.gt.0) tran_k(ik) = tk
548         if (lorb) CALL transmit(ik, ien, tk, .false.)
549
550         !
551         !!! RECOVER
552         ! if recover is enabled, save the partial transmission on file,
553         ! and then check for stopping condition
554         IF ( tran_save ) THEN
555            CALL cond_writefile( 'tran', ik, ien, tk )
556            IF ( check_stop_now() ) THEN
557               CALL free_mem
558               CALL stop_clock('PWCOND')
559               CALL print_clock_pwcond()
560               done = .FALSE.
561               RETURN
562            ENDIF
563         ENDIF
564         !!!
565
566      ENDIF
567
568      if (loop_ek) CALL free_mem
569
570    ENDDO
571
572    if (ikind.ne.0.and.tk_plot.gt.0.and.ionode) &
573             CALL summary_tran_k(ien,nk1ts,nk2ts,k1ts,k2ts)
574
575    if (.not.loop_ek) CALL free_mem
576
577  ENDDO
578
579  IF(ikind.ne.0.and.ionode) CALL summary_tran_tot()
580
581  CALL stop_clock('PWCOND')
582  CALL print_clock_pwcond()
583
584  done = .TRUE.
585
586  DEALLOCATE( xyk )
587  DEALLOCATE( wkpt )
588  DEALLOCATE( earr )
589  DEALLOCATE( tran_tot )
590  IF (ikind.ne.0.and.tk_plot.gt.0) DEALLOCATE( tran_k )
591
592  RETURN
593
594END SUBROUTINE do_cond
595
596
597