29 use,
intrinsic :: iso_fortran_env
56 integer :: ndensmat_to_calculate
57 character(len=200) :: dirname
58 character(80),
allocatable :: labels(:)
59 integer,
allocatable :: particle_kept(:)
60 integer,
allocatable :: nnatorb_prt(:)
66 character(len=*),
intent(in) :: dir
67 type(namespace_t),
intent(in) :: namespace
68 type(states_elec_t),
intent(in) :: st
69 type(modelmb_denmat_t),
intent(out) :: denmat
71 integer :: ncols, ipart
107 if (
parse_block(namespace,
'DensitytoCalc', blk) /= 0)
then
108 message(1) =
'To print out density (matrices), you must specify the DensitytoCalc block in input'
117 if (denmat%ndensmat_to_calculate < 0 .or. &
118 denmat%ndensmat_to_calculate > st%modelmbparticles%nparticle)
then
122 safe_allocate(denmat%labels(1:denmat%ndensmat_to_calculate))
123 safe_allocate(denmat%particle_kept(1:denmat%ndensmat_to_calculate))
124 safe_allocate(denmat%nnatorb_prt(1:denmat%ndensmat_to_calculate))
126 do ipart=1,denmat%ndensmat_to_calculate
131 write (
message(1),
'(a,a)')
'labels_densmat = ', denmat%labels(ipart)
132 write (
message(2),
'(a,i6)')
'particle_kept_densmat = ', denmat%particle_kept(ipart)
133 write (
message(3),
'(a,i6)')
'nnatorb_prt_densmat = ', denmat%nnatorb_prt(ipart)
139 denmat%dirname = trim(dir)
146 type(modelmb_denmat_t),
intent(inout) :: this
150 safe_deallocate_a(this%labels)
151 safe_deallocate_a(this%particle_kept)
152 safe_deallocate_a(this%nnatorb_prt)
160#include "modelmb_density_matrix_inc.F90"
163#include "complex.F90"
164#include "modelmb_density_matrix_inc.F90"
This module implements batches of mesh functions.
This module implements the index, used for the mesh points.
This module defines functions over batches of mesh functions.
This module defines the meshes, which are used in Octopus.
subroutine, public messages_obsolete_variable(namespace, name, rep)
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
subroutine, public messages_input_error(namespace, var, details, row, column)
general module for modelmb particles (eg 4 electrons in 1D equiv to 1 in 4D). Also calculate differen...
subroutine, public zmodelmb_density_matrix_write(space, mesh, st, wf, mm, denmat, namespace)
subroutine, public dmodelmb_density_matrix_write(space, mesh, st, wf, mm, denmat, namespace)
subroutine, public modelmb_density_matrix_init(dir, namespace, st, denmat)
subroutine, public modelmb_density_matrix_end(this)
Some general things and nomenclature:
integer function, public parse_block(namespace, name, blk, check_varinfo_)