File: postproc.f90

package info (click to toggle)
espresso 6.7-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 311,068 kB
  • sloc: f90: 447,429; ansic: 52,566; sh: 40,631; xml: 37,561; tcl: 20,077; lisp: 5,923; makefile: 4,503; python: 4,379; perl: 1,219; cpp: 761; fortran: 618; java: 568; awk: 128
file content (279 lines) | stat: -rw-r--r-- 9,200 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
!
! Copyright (C) 2001-2009 Quantum ESPRESSO group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
! or http://www.gnu.org/copyleft/gpl.txt .
!
!
!-----------------------------------------------------------------------
MODULE pp_module
CONTAINS
!-----------------------------------------------------------------------
SUBROUTINE extract (plot_files,plot_num)
  !-----------------------------------------------------------------------
  !
  !    Reads data produced by pw.x, computes the desired quantity (rho, V, ...)
  !    and writes it to a file (or multiple files) for further processing or
  !    plotting
  !
  !    On return, plot_files contains a list of all written files.
  !
  !    DESCRIPTION of the INPUT: see file Doc/INPUT_PP
  !
  USE kinds,     ONLY : DP
  USE cell_base, ONLY : bg
  USE ener,      ONLY : ef
  USE ions_base, ONLY : nat, ntyp=>nsp, ityp, tau
  USE gvect
  USE fft_base,  ONLY : dfftp
  USE klist,     ONLY : two_fermi_energies, degauss
  USE vlocal,    ONLY : strf
  USE io_files,  ONLY : tmp_dir, prefix
  USE io_global, ONLY : ionode, ionode_id
  USE noncollin_module, ONLY : i_cons
  USE paw_variables, ONLY : okpaw
  USE mp,        ONLY : mp_bcast
  USE mp_images, ONLY : intra_image_comm
  USE constants, ONLY : rytoev
  USE parameters, ONLY : npk
  USE io_global, ONLY : stdout
  !
  IMPLICIT NONE
  !
  CHARACTER(LEN=256), EXTERNAL :: trimcheck
  !
  CHARACTER(len=256), DIMENSION(:), ALLOCATABLE, INTENT(out) :: plot_files
  INTEGER, INTENT(out) :: plot_num

  CHARACTER (len=2), DIMENSION(0:3) :: spin_desc = &
       (/ '  ', '_X', '_Y', '_Z' /)

  INTEGER :: kpoint(2), kband(2), spin_component(3), ios
  LOGICAL :: lsign, needwf, dummy

  REAL(DP) :: emin, emax, sample_bias, z, dz
  
  REAL(DP) :: degauss_ldos, delta_e
  CHARACTER(len=256) :: filplot
  INTEGER :: plot_nkpt, plot_nbnd, plot_nspin, nplots
  INTEGER :: iplot, ikpt, ibnd, ispin

  ! directory for temporary files
  CHARACTER(len=256) :: outdir

  NAMELIST / inputpp / outdir, prefix, plot_num, sample_bias, &
      spin_component, z, dz, emin, emax, delta_e, degauss_ldos, kpoint, kband, &
      filplot, lsign
  !
  !   set default values for variables in namelist
  !
  prefix = 'pwscf'
  CALL get_environment_variable( 'ESPRESSO_TMPDIR', outdir )
  IF ( trim( outdir ) == ' ' ) outdir = './'
  filplot = 'tmp.pp'
  plot_num = -1
  kpoint(2) = 0
  kband(2) = 0
  spin_component = 0
  sample_bias = 0.01d0
  z = 1.d0
  dz = 0.05d0
  lsign=.false.
  emin = -999.0d0
  emax = +999.0d0
  delta_e=0.1d0
  degauss_ldos=-999.0d0
  !
  ios = 0
  !
  IF ( ionode )  THEN
     !
     !     reading the namelist inputpp
     !
     READ (5, inputpp, iostat = ios)
     !
     tmp_dir = trimcheck ( outdir )
     !
  ENDIF
  !
  CALL mp_bcast (ios, ionode_id, intra_image_comm)
  !
  IF ( ios /= 0) CALL errore ('postproc', 'reading inputpp namelist', abs(ios))
  !
  ! ... Broadcast variables
  !
  CALL mp_bcast( tmp_dir, ionode_id, intra_image_comm )
  CALL mp_bcast( prefix, ionode_id, intra_image_comm )
  CALL mp_bcast( plot_num, ionode_id, intra_image_comm )
  CALL mp_bcast( sample_bias, ionode_id, intra_image_comm )
  CALL mp_bcast( spin_component, ionode_id, intra_image_comm )
  CALL mp_bcast( z, ionode_id, intra_image_comm )
  CALL mp_bcast( dz, ionode_id, intra_image_comm )
  CALL mp_bcast( emin, ionode_id, intra_image_comm )
  CALL mp_bcast( emax, ionode_id, intra_image_comm )
  CALL mp_bcast( degauss_ldos, ionode_id, intra_image_comm )
  CALL mp_bcast( delta_e, ionode_id, intra_image_comm )
  CALL mp_bcast( kband, ionode_id, intra_image_comm )
  CALL mp_bcast( kpoint, ionode_id, intra_image_comm )
  CALL mp_bcast( filplot, ionode_id, intra_image_comm )
  CALL mp_bcast( lsign, ionode_id, intra_image_comm )
  !
  ! no task specified: do nothing and return
  !
  IF (plot_num == -1) THEN
     ALLOCATE( plot_files(0) )
     RETURN
  ENDIF
  !
  IF (plot_num < 0 .or. plot_num > 22) CALL errore ('postproc', &
          'Wrong plot_num', abs (plot_num) )

  IF (plot_num == 7 .or. plot_num == 13 .or. plot_num==18) THEN
     IF  (spin_component(1) < 0 .or. spin_component(1) > 3) CALL errore &
          ('postproc', 'wrong spin_component', 1)
  ELSEIF (plot_num == 10) THEN
     IF  (spin_component(1) < 0 .or. spin_component(1) > 2) CALL errore &
          ('postproc', 'wrong spin_component', 2)
  ELSE
     IF (spin_component(1) < 0 ) CALL errore &
         ('postproc', 'wrong spin_component', 3)
  ENDIF
  !
  !   Read xml file, allocate and initialize general variables
  !   If needed, allocate and initialize wavefunction-related variables
  !
  needwf=(plot_num==3).or.(plot_num==4).or.(plot_num==5).or.(plot_num==7).or. &
         (plot_num==8).or.(plot_num==10)
  CALL read_file_new ( needwf )
  !
  IF ( ( two_fermi_energies .or. i_cons /= 0) .and. &
       ( plot_num==3 .or. plot_num==4 .or. plot_num==5 ) ) &
     CALL errore('postproc',&
     'Post-processing with constrained magnetization is not available yet',1)
  !
  ! Set default values for emin, emax, degauss_ldos
  ! Done here because ef, degauss must be read from file
  IF (emin > emax) CALL errore('postproc','emin > emax',0)
  IF (plot_num == 10) THEN
      IF (emax == +999.0d0) emax = ef * rytoev
  ELSEIF (plot_num == 3) THEN
      IF (emin == -999.0d0) emin = ef * rytoev
      IF (emax == +999.0d0) emax = ef * rytoev
      IF (degauss_ldos == -999.0d0) THEN
          WRITE(stdout, &
              '(/5x,"degauss_ldos not set, defaults to degauss = ",f6.4, " eV")') &
             degauss * rytoev
          degauss_ldos = degauss * rytoev
      ENDIF
  ENDIF
  ! transforming all back to Ry units
  emin = emin / rytoev
  emax = emax / rytoev
  delta_e = delta_e / rytoev
  degauss_ldos = degauss_ldos / rytoev

  ! Number of output files depends on input
  nplots = 1
  IF (plot_num == 3) THEN
     nplots=(emax-emin)/delta_e + 1
  ELSEIF (plot_num == 7) THEN
      IF (kpoint(2) == 0)  kpoint(2) = kpoint(1)
      plot_nkpt = kpoint(2) - kpoint(1) + 1
      IF (kband(2) == 0)  kband(2) = kband(1)
      plot_nbnd = kband(2) - kband(1) + 1
      IF (spin_component(2) == 0)  spin_component(2) = spin_component(1)
      plot_nspin = spin_component(2) - spin_component(1) + 1

      nplots = plot_nbnd * plot_nkpt * plot_nspin
  ENDIF
  ALLOCATE( plot_files(nplots) )
  plot_files(1) = filplot

  ! 
  ! First handle plot_nums with multiple calls to punch_plot
  !
  IF (nplots > 1 .AND. plot_num == 3) THEN
  ! Local density of states on energy grid of spacing delta_e within [emin, emax]
    DO iplot=1,nplots
      WRITE(plot_files(iplot),'(A, I0.3)') TRIM(filplot), iplot
      CALL punch_plot (TRIM(plot_files(iplot)), plot_num, sample_bias, z, dz, &
        emin, degauss_ldos, kpoint, kband, spin_component, lsign)
      emin=emin+delta_e
    ENDDO
  ELSEIF (nplots > 1 .AND. plot_num == 7) THEN
  ! Plot multiple KS orbitals in one go
    iplot = 1
    DO ikpt=kpoint(1), kpoint(2)
      DO ibnd=kband(1), kband(2)
        DO ispin=spin_component(1), spin_component(2)
          WRITE(plot_files(iplot),"(A,A,I0.3,A,I0.3,A)") &
            TRIM(filplot), "_K", ikpt, "_B", ibnd, TRIM(spin_desc(ispin))
          CALL punch_plot (TRIM(plot_files(iplot)), plot_num, sample_bias, z, dz, &
            emin, emax, ikpt, ibnd, ispin, lsign)
          iplot = iplot + 1
        ENDDO
      ENDDO
    ENDDO

  ELSE
  ! Single call to punch_plot
    IF (plot_num == 3) THEN
       CALL punch_plot (filplot, plot_num, sample_bias, z, dz, &
           emin, degauss_ldos, kpoint, kband, spin_component, lsign)
     ELSE
       CALL punch_plot (filplot, plot_num, sample_bias, z, dz, &
          emin, emax, kpoint, kband, spin_component, lsign)
     ENDIF

  ENDIF
  !
END SUBROUTINE extract

END MODULE pp_module
!
!-----------------------------------------------------------------------
PROGRAM pp
  !-----------------------------------------------------------------------
  !
  !    Program for data analysis and plotting. The two basic steps are:
  !    1) read the output file produced by pw.x, extract and calculate
  !       the desired quantity (rho, V, ...)
  !    2) write the desired quantity to file in a suitable format for
  !       various types of plotting and various plotting programs
  !    The two steps can be performed independently. Intermediate data
  !    can be saved to file in step 1 and read from file in step 2.
  !
  !    DESCRIPTION of the INPUT : see file Doc/INPUT_PP.*
  !
  USE io_global,  ONLY : ionode
  USE mp_global,  ONLY : mp_startup
  USE environment,ONLY : environment_start, environment_end
  USE chdens_module, ONLY : chdens
  USE pp_module, ONLY : extract

  !
  IMPLICIT NONE
  !
  !CHARACTER(len=256) :: filplot
  CHARACTER(len=256), DIMENSION(:), ALLOCATABLE :: plot_files
  INTEGER :: plot_num
  !
  ! initialise environment
  !
#if defined(__MPI)
  CALL mp_startup ( )
#endif
  CALL environment_start ( 'POST-PROC' )
  !
  IF ( ionode )  CALL input_from_file ( )
  !
  CALL extract (plot_files, plot_num)
  !
  CALL chdens (plot_files, plot_num)
  !
  CALL environment_end ( 'POST-PROC' )
  !
  CALL stop_pp()
  !
END PROGRAM pp