Octopus
output.F90
Go to the documentation of this file.
1!! Copyright (C) 2002-2006 M. Marques, A. Castro, A. Rubio, G. Bertsch
2!!
3!! This program is free software; you can redistribute it and/or modify
4!! it under the terms of the GNU General Public License as published by
5!! the Free Software Foundation; either version 2, or (at your option)
6!! any later version.
7!!
8!! This program is distributed in the hope that it will be useful,
9!! but WITHOUT ANY WARRANTY; without even the implied warranty of
10!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11!! GNU General Public License for more details.
12!!
13!! You should have received a copy of the GNU General Public License
14!! along with this program; if not, write to the Free Software
15!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
16!! 02110-1301, USA.
17!!
18
19#include "global.h"
20
22module output_oct_m
23 use accel_oct_m
24 use basins_oct_m
25 use box_oct_m
26 use comm_oct_m
27 use cube_oct_m
30 use debug_oct_m
33 use dos_oct_m
35 use elf_oct_m
36#if defined(HAVE_ETSF_IO)
37 use etsf_io
38 use etsf_io_tools
39#endif
42 use fft_oct_m
45 use global_oct_m
46 use grid_oct_m
49 use io_oct_m
51 use ions_oct_m
52 use, intrinsic :: iso_fortran_env
55 use lasers_oct_m
56 use lda_u_oct_m
59 use loct_oct_m
60 use math_oct_m
62 use mesh_oct_m
65 use mpi_oct_m
71 use parser_oct_m
74 use smear_oct_m
75 use space_oct_m
80 use stress_oct_m
81 use string_oct_m
85 use unit_oct_m
87 use utils_oct_m
89 use v_ks_oct_m
90 use vtk_oct_m
91 use xc_oct_m
92 use xc_oep_oct_m
94 use xc_f03_lib_m
95
96 implicit none
97
98 private
99 public :: &
100 output_bgw_t, &
101 output_init, &
104 output_all, &
106 doutput_lr, &
107 zoutput_lr, &
111
112contains
113
114 subroutine output_init(outp, namespace, space, st, gr, nst, ks)
115 type(output_t), intent(out) :: outp
116 type(namespace_t), intent(in) :: namespace
117 class(space_t), intent(in) :: space
118 type(states_elec_t), intent(in) :: st
119 type(grid_t), intent(in) :: gr
120 integer, intent(in) :: nst
121 type(v_ks_t), intent(inout) :: ks
122
123 type(block_t) :: blk
124 real(real64) :: norm
125 character(len=80) :: nst_string, default
126
127 push_sub(output_init)
128 outp%what = .false.
129
130 call io_function_read_what_how_when(namespace, space, outp%what, outp%how, outp%output_interval)
131
132 if (outp%what(option__output__wfs_fourier)) then
133 if (accel_is_enabled()) then
134 message(1) = "Wave functions in Fourier space not supported on GPUs."
135 call messages_fatal(1, namespace=namespace)
136 end if
137 call messages_experimental("Wave-functions in Fourier space", namespace=namespace)
138 end if
139
140 ! cannot calculate the ELF in 1D
141 if (outp%what(option__output__elf) .or. outp%what(option__output__elf_basins)) then
142 if (space%dim /= 2 .and. space%dim /= 3) then
143 outp%what(option__output__elf) = .false.
144 outp%what(option__output__elf_basins) = .false.
145 write(message(1), '(a)') 'Cannot calculate ELF except in 2D and 3D.'
146 call messages_warning(1, namespace=namespace)
147 end if
148 end if
149
150
151 if (outp%what(option__output__mmb_wfs)) then
152 call messages_experimental("Model many-body wfs", namespace=namespace)
153 end if
154
155 if (outp%what(option__output__xc_torque)) then
156 if (st%d%ispin /= spinors) then
157 write(message(1), '(a)') 'The output xc_torque can only be computed for spinors.'
158 call messages_fatal(1, namespace=namespace)
159 end if
160 if (space%dim /= 3) then
161 write(message(1), '(a)') 'The output xc_torque can only be computed in the 3D case.'
162 call messages_fatal(1, namespace=namespace)
163 end if
164 end if
165 if (outp%what(option__output__mmb_den)) then
166 call messages_experimental("Model many-body density matrix", namespace=namespace)
167 ! NOTES:
168 ! could be made into block to be able to specify which dimensions to trace
169 ! in principle all combinations are interesting, but this means we need to
170 ! be able to output density matrices for multiple particles or multiple
171 ! dimensions. The current 1D 1-particle case is simple.
172 end if
173
174 if (outp%what(option__output__energy_density)) call messages_experimental("'Output = energy_density'", namespace=namespace)
175 if (outp%what(option__output__heat_current)) call messages_experimental("'Output = heat_current'", namespace=namespace)
176
177 if (outp%what(option__output__wfs) .or. outp%what(option__output__wfs_sqmod)) then
178
179 !%Variable OutputWfsNumber
180 !%Type string
181 !%Default all states
182 !%Section Output
183 !%Description
184 !% Which wavefunctions to print, in list form: <i>i.e.</i>, "1-5" to print the first
185 !% five states, "2,3" to print the second and the third state, etc.
186 !% If more states are specified than available, extra ones will be ignored.
187 !%End
188
189 write(nst_string,'(i6)') nst
190 write(default,'(a,a)') "1-", trim(adjustl(nst_string))
191 call parse_variable(namespace, 'OutputWfsNumber', default, outp%wfs_list)
192 end if
193
194 if (parse_block(namespace, 'CurrentThroughPlane', blk) == 0) then
195 if (.not. outp%what(option__output__j_flow)) then
196 outp%what(option__output__j_flow) = .true.
197 call parse_variable(namespace, 'OutputInterval', 50, outp%output_interval(option__output__j_flow))
198 end if
199
200 !%Variable CurrentThroughPlane
201 !%Type block
202 !%Section Output
203 !%Description
204 !% The code can calculate current
205 !% traversing a user-defined portion of a plane, as specified by this block.
206 !% A small plain-text file <tt>current-flow</tt> will be written containing this information.
207 !% Only available for 1D, 2D, or 3D.
208 !% In the format below, <tt>origin</tt> is a point in the plane.
209 !% <tt>u</tt> and <tt>v</tt> are the (dimensionless) vectors defining the plane;
210 !% they will be normalized. <tt>spacing</tt> is the fineness of the mesh
211 !% on the plane. Integers <tt>nu</tt> and <tt>mu</tt> are the length and
212 !% width of the portion of the plane, in units of <tt>spacing</tt>.
213 !% Thus, the grid points included in the plane are
214 !% <tt>x_ij = origin + i*spacing*u + j*spacing*v</tt>,
215 !% for <tt>nu <= i <= mu</tt> and <tt>nv <= j <= mv</tt>.
216 !% Analogously, in the 2D case, the current flow is calculated through a line;
217 !% in the 1D case, the current flow is calculated through a point. Note that the spacing
218 !% can differ from the one used in the main calculation; an interpolation will be performed.
219 !%
220 !% Example (3D):
221 !%
222 !% <tt>%CurrentThroughPlane
223 !% <br>&nbsp;&nbsp; 0.0 | 0.0 | 0.0 # origin
224 !% <br>&nbsp;&nbsp; 0.0 | 1.0 | 0.0 # u
225 !% <br>&nbsp;&nbsp; 0.0 | 0.0 | 1.0 # v
226 !% <br>&nbsp;&nbsp; 0.2 # spacing
227 !% <br>&nbsp;&nbsp; 0 | 50 # nu | mu
228 !% <br>&nbsp;&nbsp; -50 | 50 # nv | mv
229 !% <br>%</tt>
230 !%
231 !% Example (2D):
232 !%
233 !% <tt>%CurrentThroughPlane
234 !% <br>&nbsp;&nbsp; 0.0 | 0.0 # origin
235 !% <br>&nbsp;&nbsp; 1.0 | 0.0 # u
236 !% <br>&nbsp;&nbsp; 0.2 # spacing
237 !% <br>&nbsp;&nbsp; 0 | 50 # nu | mu
238 !% <br>%</tt>
239 !%
240 !% Example (1D):
241 !%
242 !% <tt>%CurrentThroughPlane
243 !% <br>&nbsp;&nbsp; 0.0 # origin
244 !% <br>%</tt>
245 !%
246 !%End
247
248 select case (space%dim)
249 case (3)
250
251 call parse_block_float(blk, 0, 0, outp%plane%origin(1), units_inp%length)
252 call parse_block_float(blk, 0, 1, outp%plane%origin(2), units_inp%length)
253 call parse_block_float(blk, 0, 2, outp%plane%origin(3), units_inp%length)
254 call parse_block_float(blk, 1, 0, outp%plane%u(1))
255 call parse_block_float(blk, 1, 1, outp%plane%u(2))
256 call parse_block_float(blk, 1, 2, outp%plane%u(3))
257 call parse_block_float(blk, 2, 0, outp%plane%v(1))
258 call parse_block_float(blk, 2, 1, outp%plane%v(2))
259 call parse_block_float(blk, 2, 2, outp%plane%v(3))
260 call parse_block_float(blk, 3, 0, outp%plane%spacing, units_inp%length)
261 call parse_block_integer(blk, 4, 0, outp%plane%nu)
262 call parse_block_integer(blk, 4, 1, outp%plane%mu)
263 call parse_block_integer(blk, 5, 0, outp%plane%nv)
264 call parse_block_integer(blk, 5, 1, outp%plane%mv)
265
266 norm = norm2(outp%plane%u(1:3))
267 if (norm < m_epsilon) then
268 write(message(1), '(a)') 'u-vector for CurrentThroughPlane cannot have norm zero.'
269 call messages_fatal(1, namespace=namespace)
270 end if
271 outp%plane%u(1:3) = outp%plane%u(1:3) / norm
272
273 norm = norm2(outp%plane%v(1:3))
274 if (norm < m_epsilon) then
275 write(message(1), '(a)') 'v-vector for CurrentThroughPlane cannot have norm zero.'
276 call messages_fatal(1, namespace=namespace)
277 end if
278 outp%plane%v(1:3) = outp%plane%v(1:3) / norm
279
280 outp%plane%n(1) = outp%plane%u(2)*outp%plane%v(3) - outp%plane%u(3)*outp%plane%v(2)
281 outp%plane%n(2) = outp%plane%u(3)*outp%plane%v(1) - outp%plane%u(1)*outp%plane%v(3)
282 outp%plane%n(3) = outp%plane%u(1)*outp%plane%v(2) - outp%plane%u(2)*outp%plane%v(1)
283
284 case (2)
285
286 call parse_block_float(blk, 0, 0, outp%line%origin(1), units_inp%length)
287 call parse_block_float(blk, 0, 1, outp%line%origin(2), units_inp%length)
288 call parse_block_float(blk, 1, 0, outp%line%u(1))
289 call parse_block_float(blk, 1, 1, outp%line%u(2))
290 call parse_block_float(blk, 2, 0, outp%line%spacing, units_inp%length)
291 call parse_block_integer(blk, 3, 0, outp%line%nu)
292 call parse_block_integer(blk, 3, 1, outp%line%mu)
293
294 norm = norm2(outp%line%u(1:2))
295 if (norm < m_epsilon) then
296 write(message(1), '(a)') 'u-vector for CurrentThroughPlane cannot have norm zero.'
297 call messages_fatal(1, namespace=namespace)
298 end if
299 outp%line%u(1:2) = outp%line%u(1:2) / norm
300
301 outp%line%n(1) = -outp%line%u(2)
302 outp%line%n(2) = outp%line%u(1)
303
304 case (1)
305
306 call parse_block_float(blk, 0, 0, outp%line%origin(1), units_inp%length)
307
308 case default
309
310 call messages_not_implemented("CurrentThroughPlane for 4D or higher", namespace=namespace)
311
312 end select
313 call parse_block_end(blk)
314 end if
315
316 if (outp%what(option__output__matrix_elements)) then
317 call output_me_init(outp%me, namespace, space, st, gr, nst)
318 else
319 outp%me%what = .false.
320 end if
321
322 if (outp%what(option__output__berkeleygw)) then
323 if (accel_is_enabled()) then
324 message(1) = "BerkeleyGW is not compatible with GPUs."
325 call messages_fatal(1, namespace=namespace)
326 end if
327 call output_berkeleygw_init(nst, namespace, outp%bgw, space%periodic_dim)
328 end if
329
330 ! required for output_hamiltonian()
331 if (outp%what(option__output__potential_gradient) .and. .not. outp%what(option__output__potential)) then
332 outp%what(option__output__potential) = .true.
333 outp%output_interval(option__output__potential) = outp%output_interval(option__output__potential_gradient)
334 end if
335
336
337 !%Variable OutputDuringSCF
338 !%Type logical
339 !%Default no
340 !%Section Output
341 !%Description
342 !% During <tt>gs</tt> and <tt>unocc</tt> runs, if this variable is set to yes,
343 !% output will be written after every <tt>OutputInterval</tt> iterations.
344 !%End
345 call parse_variable(namespace, 'OutputDuringSCF', .false., outp%duringscf)
346
347 !%Variable RestartWriteInterval
348 !%Type integer
349 !%Default 50
350 !%Section Execution::IO
351 !%Description
352 !% Restart data is written when the iteration number is a multiple
353 !% of the <tt>RestartWriteInterval</tt> variable. For
354 !% time-dependent runs this includes the update of the output
355 !% controlled by the <tt>TDOutput</tt> variable. (Other output is
356 !% controlled by <tt>OutputInterval</tt>.)
357 !%End
358 call parse_variable(namespace, 'RestartWriteInterval', 50, outp%restart_write_interval)
359 if (outp%restart_write_interval <= 0) then
360 message(1) = "RestartWriteInterval must be > 0."
361 call messages_fatal(1, namespace=namespace)
362 end if
363
364 !%Variable OutputIterDir
365 !%Default "output_iter"
366 !%Type string
367 !%Section Output
368 !%Description
369 !% The name of the directory where <tt>Octopus</tt> stores information
370 !% such as the density, forces, etc. requested by variable <tt>Output</tt>
371 !% in the format specified by <tt>OutputFormat</tt>.
372 !% This information is written while iterating <tt>CalculationMode = gs</tt>, <tt>unocc</tt>, or <tt>td</tt>,
373 !% according to <tt>OutputInterval</tt>, and has nothing to do with the restart information.
374 !%End
375 call parse_variable(namespace, 'OutputIterDir', "output_iter", outp%iter_dir)
376 if (any(outp%what) .and. any(outp%output_interval > 0)) then
377 call io_mkdir(outp%iter_dir, namespace)
378 end if
379 call add_last_slash(outp%iter_dir)
380
381 ! At this point, we don`t know whether the states will be real or complex.
382 ! We therefore pass .false. to states_are_real, and need to check for real states later.
383
384 if (output_needs_current(outp, .false.)) then
385 call v_ks_calculate_current(ks, .true.)
386 else
387 call v_ks_calculate_current(ks, .false.)
388 end if
389
390 if (outp%what(option__output__current_dia)) then
391 message(1) = "The diamagnetic current will be calculated only if CalculateDiamagneticCurrent = yes."
392 call messages_warning(1, namespace=namespace)
393 end if
394
395 pop_sub(output_init)
396 end subroutine output_init
397
398 ! ---------------------------------------------------------
399 subroutine output_all(outp, namespace, space, dir, gr, ions, iter, st, hm, ks)
400 type(output_t), intent(in) :: outp
401 type(namespace_t), intent(in) :: namespace
402 class(space_t), intent(in) :: space
403 character(len=*), intent(in) :: dir
404 type(grid_t), intent(in) :: gr
405 type(ions_t), intent(in) :: ions
406 integer, intent(in) :: iter
407 type(states_elec_t), intent(inout) :: st
408 type(hamiltonian_elec_t), intent(inout) :: hm
409 type(v_ks_t), intent(inout) :: ks
410
411 integer :: idir, ierr, iout, iunit
412 character(len=MAX_PATH_LEN) :: fname
413
414 push_sub(output_all)
415 call profiling_in("OUTPUT_ALL")
416
417 if (any(outp%what)) then
418 message(1) = "Info: Writing output to " // trim(dir)
419 call messages_info(1, namespace=namespace)
420 call io_mkdir(dir, namespace)
421 end if
422
423 if (outp%what_now(option__output__mesh_r, iter)) then
424 do idir = 1, space%dim
425 write(fname, '(a,a)') 'mesh_r-', index2axis(idir)
426 call dio_function_output(outp%how(option__output__mesh_r), dir, fname, namespace, space, &
427 gr, gr%x(:,idir), units_out%length, ierr, pos=ions%pos, atoms=ions%atom)
428 end do
429 end if
430
431 call output_states(outp, namespace, space, dir, st, gr, ions, hm, iter)
432 call output_hamiltonian(outp, namespace, space, dir, hm, st, gr%der, ions, gr, iter, st%st_kpt_mpi_grp)
433
434 ! We can only test against the theory level here, as it is not set in the call of output_init().
435 if (outp%what_now(option__output__el_pressure, iter)) then
436 if(ks%theory_level /= kohn_sham_dft) then
437 call messages_not_implemented("el_pressure for TheoryLevel different from kohn_sham", namespace=namespace)
438 end if
439 if (st%d%spin_channels > 1) then
440 call messages_not_implemented("el_pressure for spin-polarized or spinors", namespace=namespace)
441 end if
442 end if
443
444 !hm not initialized yet when calling output_init()
445 if (outp%what(option__output__kanamoriu) .and. hm%lda_u_level /= dft_u_acbn0) then
446 message(1) = "kanamoriU output can only be computed for DFTULevel = dft_u_acbn0"
447 call messages_fatal(1, namespace=namespace)
448 end if
449
450
451 call output_localization_funct(outp, namespace, space, dir, st, hm, gr, ions, iter)
452
453 if (outp%what_now(option__output__j_flow, iter)) then
454 call output_current_flow(outp, namespace, space, dir, gr, st, hm%kpoints)
455 end if
456
457 if (outp%what_now(option__output__geometry, iter)) then
458 if (bitand(outp%how(option__output__geometry), option__outputformat__xcrysden) /= 0) then
459 call write_xsf_geometry_file(dir, "geometry", space, ions%latt, ions%pos, ions%atom, gr, namespace)
460 end if
461 if (bitand(outp%how(option__output__geometry), option__outputformat__xyz) /= 0) then
462 call ions%write_xyz(trim(dir)//'/geometry')
463 if (ions%space%is_periodic()) then
464 call ions%write_crystal(dir)
465 end if
466 end if
467 if (bitand(outp%how(option__output__geometry), option__outputformat__vtk) /= 0) then
468 call ions%write_vtk_geometry(trim(dir)//'/geometry')
469 end if
470 end if
471
472 if (outp%what_now(option__output__forces, iter)) then
473 if (bitand(outp%how(option__output__forces), option__outputformat__bild) /= 0) then
474 call ions%write_bild_forces_file(dir, "forces")
475 else
476 call write_xsf_geometry_file(dir, "forces", space, ions%latt, ions%pos, ions%atom, &
477 gr, namespace, total_forces = ions%tot_force)
478 end if
479 end if
480
481 if (outp%what_now(option__output__matrix_elements, iter)) then
482 call output_me(outp%me, namespace, space, dir, st, gr, ions, hm)
483 end if
484
485 do iout = lbound(outp%how, 1), ubound(outp%how, 1)
486 if (bitand(outp%how(iout), option__outputformat__etsf) /= 0) then
487 call output_etsf(outp, namespace, space, dir, st, gr, hm%kpoints, ions, iter)
488 exit
489 end if
490 end do
491
492 if (outp%what_now(option__output__berkeleygw, iter)) then
493 call output_berkeleygw(outp%bgw, namespace, space, dir, st, gr, ks, hm, ions)
494 end if
495
496 if (outp%what_now(option__output__energy_density, iter)) then
497 call output_energy_density(outp, namespace, space, dir, hm, ks, st, ions, gr)
498 end if
499
500 if (outp%what_now(option__output__stress, iter)) then
501 call io_mkdir(dir, namespace)
502 iunit = io_open(trim(dir)//'/stress', namespace, action='write')
503 call output_stress(iunit, space%periodic_dim, st%stress_tensors)
504 call io_close(iunit)
505 end if
506
507 if (hm%lda_u_level /= dft_u_none) then
508 if (outp%what_now(option__output__occ_matrices, iter))&
509 call lda_u_write_occupation_matrices(dir, hm%lda_u, st, namespace)
510
511 if (outp%what_now(option__output__effectiveu, iter))&
512 call lda_u_write_effectiveu(dir, hm%lda_u, namespace)
513
514 if (outp%what_now(option__output__magnetization, iter))&
515 call lda_u_write_magnetization(dir, hm%lda_u, ions, gr, st, namespace)
516
517 if (outp%what_now(option__output__local_orbitals, iter))&
518 call output_dftu_orbitals(outp, dir, namespace, space, hm%lda_u, st, gr, ions, hm%phase%is_allocated())
519
520 if (outp%what_now(option__output__kanamoriu, iter))&
521 call lda_u_write_kanamoriu(dir, st, hm%lda_u, namespace)
522
523 if (ks%oep_photon%level == oep_level_full) then
524 if (outp%what_now(option__output__photon_correlator, iter)) then
525 write(fname, '(a)') 'photon_correlator'
526 call dio_function_output(outp%how(option__output__photon_correlator), dir, trim(fname), namespace, space, &
527 gr, ks%oep_photon%pt%correlator(:,1), units_out%length, ierr, pos=ions%pos, atoms=ions%atom)
528 end if
529 end if
530 end if
531
532 ! We can only test against the theory level here, as it is not set in the call of output_init().
533 if (outp%what_now(option__output__xc_torque, iter)) then
534 if (ks%theory_level /= kohn_sham_dft .and. ks%theory_level /= generalized_kohn_sham_dft) then
535 write(message(1), '(a)') 'The output xc_torque can only be computed when there is a xc potential.'
536 call messages_fatal(1, namespace=namespace)
537 end if
538 end if
539
540 call output_xc_torque(outp, namespace, dir, gr, hm, st, ions, ions%space)
541
542 call profiling_out("OUTPUT_ALL")
543 pop_sub(output_all)
544 end subroutine output_all
545
546
547 ! ---------------------------------------------------------
548 subroutine output_localization_funct(outp, namespace, space, dir, st, hm, gr, ions, iter)
549 type(output_t), intent(in) :: outp
550 type(namespace_t), intent(in) :: namespace
551 class(space_t), intent(in) :: space
552 character(len=*), intent(in) :: dir
553 type(states_elec_t), intent(inout) :: st
554 type(hamiltonian_elec_t), intent(in) :: hm
555 type(grid_t), intent(in) :: gr
556 type(ions_t), intent(in) :: ions
557 integer, intent(in) :: iter
558
559 real(real64), allocatable :: f_loc(:,:)
560 character(len=MAX_PATH_LEN) :: fname
561 integer :: is, ierr, imax
562 type(mpi_grp_t) :: mpi_grp
563
565
566 mpi_grp = st%dom_st_kpt_mpi_grp
567
568 ! if SPIN_POLARIZED, the ELF contains one extra channel: the total ELF
569 imax = st%d%nspin
570 if (st%d%ispin == spin_polarized) imax = 3
571
572 safe_allocate(f_loc(1:gr%np, 1:imax))
573
574 ! First the ELF in real space
575 if (outp%what_now(option__output__elf, iter) .or. outp%what_now(option__output__elf_basins, iter)) then
576 assert(space%dim /= 1)
577
578 call elf_calc(space, st, gr, hm%kpoints, f_loc)
579
580 ! output ELF in real space
581 if (outp%what_now(option__output__elf, iter)) then
582 write(fname, '(a)') 'elf_rs'
583 call dio_function_output(outp%how(option__output__elf), dir, trim(fname), namespace, space, gr, &
584 f_loc(:,imax), unit_one, ierr, pos=ions%pos, atoms=ions%atom, grp = mpi_grp)
585 ! this quantity is dimensionless
586
587 if (st%d%ispin /= unpolarized) then
588 do is = 1, 2
589 write(fname, '(a,i1)') 'elf_rs-sp', is
590 call dio_function_output(outp%how(option__output__elf), dir, trim(fname), namespace, space, gr, &
591 f_loc(:, is), unit_one, ierr, pos=ions%pos, atoms=ions%atom, grp = mpi_grp)
592 ! this quantity is dimensionless
593 end do
594 end if
595 end if
596
597 if (outp%what_now(option__output__elf_basins, iter)) then
598 call out_basins(f_loc(:,1), "elf_rs_basins", outp%how(option__output__elf_basins))
599 end if
600 end if
601
602 ! Now Bader analysis
603 if (outp%what_now(option__output__bader, iter)) then
604 do is = 1, st%d%nspin
605 call dderivatives_lapl(gr%der, st%rho(:,is), f_loc(:,is))
606
607 fname = get_filename_with_spin('bader', st%d%nspin, is)
608
609 call dio_function_output(outp%how(option__output__bader), dir, trim(fname), namespace, space, gr, &
610 f_loc(:,is), units_out%length**(-2 - space%dim), ierr, &
611 pos=ions%pos, atoms=ions%atom, grp = mpi_grp)
612
613 fname = get_filename_with_spin('bader_basins', st%d%nspin, is)
614 call out_basins(f_loc(:,1), fname, outp%how(option__output__bader))
615 end do
616 end if
617
618 ! Now the pressure
619 if (outp%what_now(option__output__el_pressure, iter)) then
620 call calc_electronic_pressure(st, hm, gr, f_loc(:,1))
621 call dio_function_output(outp%how(option__output__el_pressure), dir, "el_pressure", namespace, space, gr, &
622 f_loc(:,1), unit_one, ierr, pos=ions%pos, atoms=ions%atom, grp = mpi_grp)
623 ! this quantity is dimensionless
624 end if
625
626 safe_deallocate_a(f_loc)
627
629
630 contains
631 ! ---------------------------------------------------------
632 subroutine out_basins(ff, filename, output_how)
633 real(real64), intent(in) :: ff(:)
634 character(len=*), intent(in) :: filename
635 integer(int64), intent(in) :: output_how
636
637 character(len=MAX_PATH_LEN) :: fname
638 type(basins_t) :: basins
639 integer :: iunit
640
642
643 call basins_init(basins, namespace, gr)
644 call basins_analyze(basins, namespace, gr, ff(:), st%rho, 0.01_real64)
645
646 call dio_function_output(output_how, dir, trim(filename), namespace, space, gr, &
647 real(basins%map, real64) , unit_one, ierr, pos=ions%pos, atoms=ions%atom, grp = mpi_grp)
648 ! this quantity is dimensionless
649
650 write(fname,'(4a)') trim(dir), '/', trim(filename), '.info'
651 iunit = io_open(trim(fname), namespace, action = 'write')
652 call basins_write(basins, gr, iunit)
653 call io_close(iunit)
654
655 call basins_end(basins)
656
658 end subroutine out_basins
659
660 end subroutine output_localization_funct
661
662
663 ! ---------------------------------------------------------
664 subroutine calc_electronic_pressure(st, hm, gr, pressure)
665 type(states_elec_t), intent(inout) :: st
666 type(hamiltonian_elec_t), intent(in) :: hm
667 type(grid_t), intent(in) :: gr
668 real(real64), intent(out) :: pressure(:)
669
670 real(real64), allocatable :: rho(:,:), lrho(:), tau(:,:)
671 real(real64) :: p_tf, dens
672 integer :: is, ii
673
675
676 safe_allocate( rho(1:gr%np_part, 1:st%d%nspin))
677 safe_allocate(lrho(1:gr%np))
678 safe_allocate( tau(1:gr%np, 1:st%d%nspin))
679
680 rho = m_zero
681 call density_calc(st, gr, rho)
682 call states_elec_calc_quantities(gr, st, hm%kpoints, .false., kinetic_energy_density = tau)
683
684 pressure = m_zero
685 do is = 1, st%d%spin_channels
686 lrho = m_zero
687 call dderivatives_lapl(gr%der, rho(:, is), lrho)
688
689 pressure(:) = pressure(:) + &
690 tau(:, is)/m_three - lrho(:)/m_four
691 end do
692
693 do ii = 1, gr%np
694 dens = sum(rho(ii,1:st%d%spin_channels))
695
696 p_tf = m_two/m_five*(m_three*m_pi**2)**(m_two/m_three)* &
697 dens**(m_five/m_three)
698
699 ! add XC pressure
700 ! FIXME: Not correct for spinors and spin-polarized here
701 pressure(ii) = pressure(ii) + (dens*hm%ks_pot%vxc(ii,1) - hm%energy%exchange - hm%energy%correlation)
702
703 pressure(ii) = pressure(ii)/p_tf
704 pressure(ii) = m_half*(m_one + pressure(ii)/sqrt(m_one + pressure(ii)**2))
705 end do
706
708 end subroutine calc_electronic_pressure
709
710
711 ! ---------------------------------------------------------
712 subroutine output_energy_density(outp, namespace, space, dir, hm, ks, st, ions, gr)
713 type(output_t), intent(in) :: outp
714 type(namespace_t), intent(in) :: namespace
715 class(space_t), intent(in) :: space
716 character(len=*), intent(in) :: dir
717 type(hamiltonian_elec_t), intent(in) :: hm
718 type(v_ks_t), intent(inout) :: ks
719 type(states_elec_t), intent(in) :: st
720 type(ions_t), intent(in) :: ions
721 type(grid_t), intent(in) :: gr
722
723 integer :: is, ierr, ip
724 character(len=MAX_PATH_LEN) :: fname
725 type(unit_t) :: fn_unit
726 real(real64), allocatable :: energy_density(:, :)
727 real(real64), allocatable :: ex_density(:)
728 real(real64), allocatable :: ec_density(:)
729
730 push_sub(output_energy_density)
731
732 fn_unit = units_out%energy*units_out%length**(-space%dim)
733 safe_allocate(energy_density(1:gr%np, 1:st%d%nspin))
734
735 ! the kinetic energy density
736 call states_elec_calc_quantities(gr, st, hm%kpoints, .true., kinetic_energy_density = energy_density)
737
738 ! the external potential energy density
739 do is = 1, st%d%nspin
740 do ip = 1, gr%np
741 energy_density(ip, is) = energy_density(ip, is) + st%rho(ip, is)*hm%ep%vpsl(ip)
742 end do
743 end do
744
745 ! the hartree energy density
746 do is = 1, st%d%nspin
747 do ip = 1, gr%np
748 energy_density(ip, is) = energy_density(ip, is) + m_half*st%rho(ip, is)*hm%ks_pot%vhartree(ip)
749 end do
750 end do
751
752 ! the XC energy density
753 safe_allocate(ex_density(1:gr%np))
754 safe_allocate(ec_density(1:gr%np))
755
756 call xc_get_vxc(gr, ks%xc, st, hm%kpoints, hm%psolver, namespace, space, st%rho, st%d%ispin, &
757 hm%ions%latt%rcell_volume, ex_density = ex_density, ec_density = ec_density)
758 do is = 1, st%d%nspin
759 do ip = 1, gr%np
760 energy_density(ip, is) = energy_density(ip, is) + ex_density(ip) + ec_density(ip)
761 end do
762 end do
763
764 safe_deallocate_a(ex_density)
765 safe_deallocate_a(ec_density)
766
767 do is = 1, st%d%spin_channels
768 fname = get_filename_with_spin('energy_density', st%d%nspin, is)
769 call dio_function_output(outp%how(option__output__energy_density), dir, trim(fname), namespace, space, gr, &
770 energy_density(:, is), unit_one, ierr, pos=ions%pos, atoms=ions%atom, grp = st%dom_st_kpt_mpi_grp)
771 end do
772 safe_deallocate_a(energy_density)
773
774 pop_sub(output_energy_density)
775 end subroutine output_energy_density
776
777 !--------------------------------------------------------------
778
779 logical function output_need_exchange(outp) result(need_exx)
780 type(output_t), intent(in) :: outp
781
782 need_exx =(outp%what(option__output__berkeleygw) &
783 .or. outp%me%what(option__outputmatrixelements__two_body) &
784 .or. outp%me%what(option__outputmatrixelements__two_body_exc_k))
785 end function output_need_exchange
786
787
788 ! ---------------------------------------------------------
789 subroutine output_dftu_orbitals(outp, dir, namespace, space, this, st, mesh, ions, has_phase)
790 type(output_t), intent(in) :: outp
791 character(len=*), intent(in) :: dir
792 type(namespace_t), intent(in) :: namespace
793 class(space_t), intent(in) :: space
794 type(lda_u_t), intent(in) :: this
795 type(states_elec_t), intent(in) :: st
796 class(mesh_t), intent(in) :: mesh
797 type(ions_t), intent(in) :: ions
798 logical, intent(in) :: has_phase
799
800 integer :: ios, im, ik, idim, ierr
801 complex(real64), allocatable :: tmp(:)
802 real(real64), allocatable :: dtmp(:)
803 type(orbitalset_t), pointer :: os
804 type(unit_t) :: fn_unit
805 character(len=MAX_PATH_LEN) :: fname
806
807 push_sub(output_dftu_orbitals)
808
809 fn_unit = sqrt(units_out%length**(-space%dim))
810
811 if (this%basis%use_submesh) then
812 if (states_are_real(st)) then
813 safe_allocate(dtmp(1:mesh%np))
814 else
815 safe_allocate(tmp(1:mesh%np))
816 end if
817 end if
818
819 do ios = 1, this%norbsets
820 os => this%orbsets(ios)
821 do ik = st%d%kpt%start, st%d%kpt%end
822 do im = 1, this%orbsets(ios)%norbs
823 do idim = 1, min(os%ndim, st%d%dim)
824 if (st%nik > 1) then
825 if (min(os%ndim, st%d%dim) > 1) then
826 write(fname, '(a,i1,a,i3.3,a,i8.8,a,i1)') 'orb', im, '-os', ios, '-k', ik, '-sp', idim
827 else
828 write(fname, '(a,i1,a,i3.3,a,i8.8)') 'orb', im, '-os', ios, '-k', ik
829 end if
830 else
831 if (min(os%ndim, st%d%dim) > 1) then
832 write(fname, '(a,i1,a,i3.3,a,i1)') 'orb', im, '-os', ios, '-sp', idim
833 else
834 write(fname, '(a,i1,a,i3.3)') 'orb', im, '-os', ios
835 end if
836 end if
837 if (has_phase) then
838 if (.not. this%basis%use_submesh) then
839 call zio_function_output(outp%how(option__output__local_orbitals), dir, fname, namespace, space, &
840 mesh, os%eorb_mesh(1:mesh%np,im,idim,ik), fn_unit, ierr, pos=ions%pos, atoms=ions%atom)
841 else
842 tmp = m_z0
843 call submesh_add_to_mesh(os%sphere, os%eorb_submesh(1:os%sphere%np,idim,im,ik), tmp)
844 call zio_function_output(outp%how(option__output__local_orbitals), dir, fname, namespace, space, &
845 mesh, tmp, fn_unit, ierr, pos=ions%pos, atoms=ions%atom)
846 end if
847 else
848 if (.not. this%basis%use_submesh) then
849 if (states_are_real(st)) then
850 call dio_function_output(outp%how(option__output__local_orbitals), dir, fname, namespace, space, mesh, &
851 os%dorb(1:mesh%np,idim,im), fn_unit, ierr, pos=ions%pos, atoms=ions%atom)
852 else
853 call zio_function_output(outp%how(option__output__local_orbitals), dir, fname, namespace, space, mesh, &
854 os%zorb(1:mesh%np,idim,im), fn_unit, ierr, pos=ions%pos, atoms=ions%atom)
855 end if
856 else
857 if (states_are_real(st)) then
858 dtmp = m_z0
859 call submesh_add_to_mesh(os%sphere, os%dorb(1:os%sphere%np,idim,im), dtmp)
860 call dio_function_output(outp%how(option__output__local_orbitals), dir, fname, namespace, space, &
861 mesh, dtmp, fn_unit, ierr, pos=ions%pos, atoms=ions%atom)
862 else
863 tmp = m_z0
864 call submesh_add_to_mesh(os%sphere, os%zorb(1:os%sphere%np,idim,im), tmp)
865 call zio_function_output(outp%how(option__output__local_orbitals), dir, fname, namespace, space, &
866 mesh, tmp, fn_unit, ierr, pos=ions%pos, atoms=ions%atom)
867 end if
868 end if
869 end if
870 end do
871 end do
872 end do
873 end do
874
875 safe_deallocate_a(tmp)
876 safe_deallocate_a(dtmp)
877
878 pop_sub(output_dftu_orbitals)
879 end subroutine output_dftu_orbitals
880
881 ! ---------------------------------------------------------
882 logical function output_needs_current(outp, states_are_real)
883 type(output_t), intent(in) :: outp
884 logical, intent(in) :: states_are_real
885
886 output_needs_current = .false.
887
888 if (outp%what(option__output__current) &
889 .or. outp%what(option__output__current_dia) &
890 .or. outp%what(option__output__heat_current) &
891 .or. outp%what(option__output__current_kpt)) then
892 if (.not. states_are_real) then
894 else
895 message(1) = 'No current density output for real states since it is identically zero.'
896 call messages_warning(1)
897 end if
898 end if
899
900
901 end function
902
903#include "output_etsf_inc.F90"
904
905#include "output_states_inc.F90"
906
907#include "output_h_inc.F90"
908
909#include "undef.F90"
910#include "complex.F90"
911#include "output_linear_response_inc.F90"
912
913#include "undef.F90"
914#include "real.F90"
915#include "output_linear_response_inc.F90"
916
917end module output_oct_m
918
919!! Local Variables:
920!! mode: f90
921!! coding: utf-8
922!! End:
pure logical function, public accel_is_enabled()
Definition: accel.F90:401
subroutine, public basins_write(this, mesh, iunit)
Definition: basins.F90:352
subroutine, public basins_init(this, namespace, mesh)
Definition: basins.F90:151
subroutine, public basins_analyze(this, namespace, mesh, f, rho, threshold)
Definition: basins.F90:188
subroutine, public basins_end(this)
Definition: basins.F90:170
This module implements a calculator for the density and defines related functions.
Definition: density.F90:120
subroutine, public density_calc(st, gr, density, istin)
Computes the density from the orbitals in st.
Definition: density.F90:609
This module calculates the derivatives (gradients, Laplacians, etc.) of a function.
subroutine, public dderivatives_lapl(der, ff, op_ff, ghost_update, set_bc, factor)
apply the Laplacian to a mesh function
Module that handles computing and output of various density of states.
Definition: dos.F90:116
integer, parameter, public unpolarized
Parameters...
integer, parameter, public spinors
integer, parameter, public spin_polarized
subroutine, public elf_calc(space, st, gr, kpoints, elf, de)
(time-dependent) electron localization function, (TD)ELF.
Definition: elf.F90:167
Fast Fourier Transform module. This module provides a single interface that works with different FFT ...
Definition: fft.F90:118
real(real64), parameter, public m_two
Definition: global.F90:190
real(real64), parameter, public m_zero
Definition: global.F90:188
real(real64), parameter, public m_four
Definition: global.F90:192
real(real64), parameter, public m_pi
some mathematical constants
Definition: global.F90:186
complex(real64), parameter, public m_z0
Definition: global.F90:198
real(real64), parameter, public m_epsilon
Definition: global.F90:204
real(real64), parameter, public m_half
Definition: global.F90:194
real(real64), parameter, public m_one
Definition: global.F90:189
real(real64), parameter, public m_three
Definition: global.F90:191
real(real64), parameter, public m_five
Definition: global.F90:193
This module implements the underlying real-space grid.
Definition: grid.F90:117
This module defines classes and functions for interaction partners.
subroutine, public zio_function_output(how, dir, fname, namespace, space, mesh, ff, unit, ierr, pos, atoms, grp, root)
Top-level IO routine for functions defined on the mesh.
subroutine, public io_function_read_what_how_when(namespace, space, what, how, output_interval, what_tag_in, how_tag_in, output_interval_tag_in, ignore_error)
subroutine, public dio_function_output(how, dir, fname, namespace, space, mesh, ff, unit, ierr, pos, atoms, grp, root)
Top-level IO routine for functions defined on the mesh.
subroutine, public write_xsf_geometry_file(dir, fname, space, latt, pos, atoms, mesh, namespace, total_forces)
Definition: io.F90:114
subroutine, public io_close(iunit, grp)
Definition: io.F90:418
subroutine, public io_mkdir(fname, namespace, parents)
Definition: io.F90:311
integer function, public io_open(file, namespace, action, status, form, position, die, recl, grp)
Definition: io.F90:352
A module to handle KS potential, without the external potential.
integer, parameter, public generalized_kohn_sham_dft
integer, parameter, public kohn_sham_dft
subroutine, public lda_u_write_occupation_matrices(dir, this, st, namespace)
Prints the occupation matrices at the end of the scf calculation.
Definition: lda_u_io.F90:157
subroutine, public lda_u_write_kanamoriu(dir, st, this, namespace)
Definition: lda_u_io.F90:352
subroutine, public lda_u_write_magnetization(dir, this, ions, mesh, st, namespace)
Definition: lda_u_io.F90:483
subroutine, public lda_u_write_effectiveu(dir, this, namespace)
Definition: lda_u_io.F90:265
integer, parameter, public dft_u_none
Definition: lda_u.F90:201
integer, parameter, public dft_u_acbn0
Definition: lda_u.F90:201
This module is intended to contain "only mathematical" functions and procedures.
Definition: math.F90:115
This module defines various routines, operating on mesh functions.
This module defines the meshes, which are used in Octopus.
Definition: mesh.F90:118
subroutine, public messages_not_implemented(feature, namespace)
Definition: messages.F90:1113
subroutine, public messages_warning(no_lines, all_nodes, namespace)
Definition: messages.F90:537
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
Definition: messages.F90:414
subroutine, public messages_experimental(name, namespace)
Definition: messages.F90:1085
subroutine, public messages_info(no_lines, iunit, debug_only, stress, all_nodes, namespace)
Definition: messages.F90:616
subroutine, public output_berkeleygw(bgw, namespace, space, dir, st, gr, ks, hm, ions)
subroutine, public output_berkeleygw_init(nst, namespace, bgw, periodic_dim)
this module contains the low-level part of the output system
Definition: output_low.F90:115
character(len=max_path_len) function, public get_filename_with_spin(output, nspin, spin_index)
Returns the filame as output, or output-spX is spin polarized.
Definition: output_low.F90:232
subroutine, public output_me_init(this, namespace, space, st, gr, nst)
Definition: output_me.F90:155
subroutine, public output_me(this, namespace, space, dir, st, gr, ions, hm)
Definition: output_me.F90:280
this module contains the output system
Definition: output.F90:115
subroutine calc_electronic_pressure(st, hm, gr, pressure)
Definition: output.F90:758
subroutine, public output_states(outp, namespace, space, dir, st, gr, ions, hm, iter)
Definition: output.F90:1895
logical function, public output_needs_current(outp, states_are_real)
Definition: output.F90:976
subroutine, public output_hamiltonian(outp, namespace, space, dir, hm, st, der, ions, gr, iter, grp)
Definition: output.F90:2191
subroutine, public output_all(outp, namespace, space, dir, gr, ions, iter, st, hm, ks)
Definition: output.F90:493
logical function, public output_need_exchange(outp)
Definition: output.F90:873
subroutine, public output_init(outp, namespace, space, st, gr, nst, ks)
Definition: output.F90:208
subroutine output_xc_torque(outp, namespace, dir, mesh, hm, st, ions, space)
Definition: output.F90:2509
subroutine, public output_current_flow(outp, namespace, space, dir, gr, st, kpoints)
Definition: output.F90:2083
subroutine, public zoutput_lr(outp, namespace, space, dir, st, mesh, lr, idir, isigma, ions, pert_unit)
Definition: output.F90:2616
subroutine, public doutput_lr(outp, namespace, space, dir, st, mesh, lr, idir, isigma, ions, pert_unit)
Definition: output.F90:2885
subroutine, public output_scalar_pot(outp, namespace, space, dir, mesh, ions, ext_partners, time)
Definition: output.F90:2472
subroutine output_energy_density(outp, namespace, space, dir, hm, ks, st, ions, gr)
Definition: output.F90:806
subroutine output_dftu_orbitals(outp, dir, namespace, space, this, st, mesh, ions, has_phase)
Definition: output.F90:883
subroutine output_localization_funct(outp, namespace, space, dir, st, hm, gr, ions, iter)
Definition: output.F90:642
subroutine output_etsf(outp, namespace, space, dir, st, gr, kpoints, ions, iter)
To create an etsf file one has to do the following:
Definition: output.F90:1027
integer function, public parse_block(namespace, name, blk, check_varinfo_)
Definition: parser.F90:618
subroutine, public profiling_out(label)
Increment out counter and sum up difference between entry and exit time.
Definition: profiling.F90:623
subroutine, public profiling_in(label, exclude)
Increment in counter and save entry time.
Definition: profiling.F90:552
pure logical function, public states_are_real(st)
This module defines routines to write information about states.
subroutine, public states_elec_calc_quantities(gr, st, kpoints, nlcc, kinetic_energy_density, paramagnetic_current, density_gradient, density_laplacian, gi_kinetic_energy_density, st_end)
calculated selected quantities
This module implements the calculation of the stress tensor.
Definition: stress.F90:118
subroutine, public output_stress(iunit, space_dim, stress_tensors, all_terms)
Definition: stress.F90:1051
subroutine, public add_last_slash(str)
Adds a '/' in the end of the string, only if it missing. Useful for directories.
Definition: string.F90:161
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
Definition: unit.F90:132
This module defines the unit system, used for input and output.
type(unit_system_t), public units_out
type(unit_system_t), public units_inp
the units systems for reading and writing
type(unit_t), public unit_one
some special units required for particular quantities
This module is intended to contain simple general-purpose utility functions and procedures.
Definition: utils.F90:118
character pure function, public index2axis(idir)
Definition: utils.F90:202
subroutine, public v_ks_calculate_current(this, calc_cur)
Definition: v_ks.F90:1455
Definition: xc.F90:114
subroutine, public xc_get_vxc(gr, xcs, st, kpoints, psolver, namespace, space, rho, ispin, rcell_volume, vxc, ex, ec, deltaxc, vtau, ex_density, ec_density, stress_xc, force_orbitalfree)
Definition: xc.F90:757
integer, parameter, public oep_level_full
Definition: xc_oep.F90:172
subroutine out_basins(ff, filename, output_how)
Definition: output.F90:726
Description of the grid, containing information on derivatives, stencil, and symmetries.
Definition: grid.F90:168
Class to describe DFT+U parameters.
Definition: lda_u.F90:214
Describes mesh distribution to nodes.
Definition: mesh.F90:186
This is defined even when running serial.
Definition: mpi.F90:142
Output information for BerkeleyGW.
Definition: output_low.F90:145
output handler class
Definition: output_low.F90:164
The states_elec_t class contains all electronic wave functions.
int true(void)