30 use,
intrinsic :: iso_fortran_env
59 type(grid_t),
intent(in) :: gr
60 type(namespace_t),
intent(in) :: namespace
61 type(target_t),
intent(inout) :: tg
62 type(td_t),
intent(in) :: td
64 integer :: no_states, ib, ip, idim, inst, inik, id, ist, ik
66 real(real64) :: xx(1:gr%box%dim), rr, psi_re, psi_im
67 complex(real64),
allocatable :: zpsi(:, :)
71 message(1) =
'Info: Target is a user-defined state.'
77 safe_allocate(zpsi(gr%np, 1:tg%st%d%dim))
91 if (
parse_block(namespace,
'OCTTargetUserdefined', blk) == 0)
then
100 do id = 1, tg%st%d%dim
101 do ist = 1, tg%st%nst
105 if (.not. (id == idim .and. ist == inst .and. ik == inik &
106 .and. tg%st%st_start <= ist .and. tg%st%st_end >= ist)) cycle
110 blk, ib - 1, 3, tg%st%user_def_states(id, ist, ik))
120 gr%box%dim, xx, rr,
m_zero, tg%st%user_def_states(id, ist, ik))
122 zpsi(ip, id) = cmplx(psi_re, psi_im, real64)
140 safe_deallocate_a(zpsi)
148 type(target_t),
intent(in) :: tg
149 type(namespace_t),
intent(in) :: namespace
150 class(space_t),
intent(in) :: space
152 character(len=*),
intent(in) :: dir
153 type(
ions_t),
intent(in) :: ions
159 call output_states(outp, namespace, space, trim(dir), tg%st, gr, ions, hm, -1)
170 type(
grid_t),
intent(in) :: gr
174 complex(real64),
allocatable :: zpsi(:, :), zst(:, :)
178 safe_allocate(zpsi(1:gr%np, 1:tg%st%d%dim))
179 safe_allocate(zst(1:gr%np, 1:tg%st%d%dim))
183 do ist = psi%st_start, psi%st_end
188 j1 = j1 + psi%occ(ist, ik)*abs(
zmf_dotp(gr, psi%d%dim, zpsi, zst))**2
192 safe_deallocate_a(zpsi)
193 safe_deallocate_a(zst)
202 type(target_t),
intent(in) :: tg
203 type(grid_t),
intent(in) :: gr
204 type(states_elec_t),
intent(in) :: psi_in
205 type(states_elec_t),
intent(inout) :: chi_out
208 complex(real64) :: olap
209 complex(real64),
allocatable :: zpsi(:, :), zst(:, :), zchi(:, :)
213 safe_allocate(zpsi(1:gr%np, 1:tg%st%d%dim))
214 safe_allocate(zst(1:gr%np, 1:tg%st%d%dim))
215 safe_allocate(zchi(1:gr%np, 1:tg%st%d%dim))
217 do ik = 1, psi_in%nik
218 do ist = psi_in%st_start, psi_in%st_end
220 call states_elec_get_state(psi_in, gr, ist, ik, zpsi)
221 call states_elec_get_state(tg%st, gr, ist, ik, zst)
223 olap = zmf_dotp(gr, zst(:, 1), zpsi(:, 1))
224 zchi(1:gr%np, 1:tg%st%d%dim) = olap*zst(1:gr%np, 1:tg%st%d%dim)
226 call states_elec_set_state(chi_out, gr, ist, ik, zchi)
231 safe_deallocate_a(zpsi)
232 safe_deallocate_a(zst)
233 safe_deallocate_a(zchi)
This module implements a calculator for the density and defines related functions.
subroutine, public density_calc(st, gr, density, istin)
Computes the density from the orbitals in st.
real(real64), parameter, public m_zero
This module implements the underlying real-space grid.
subroutine, public io_mkdir(fname, namespace, parents)
logical pure function, public ion_dynamics_ions_move(this)
This module defines various routines, operating on mesh functions.
subroutine, public zmf_normalize(mesh, dim, psi, norm)
Normalize a mesh function psi.
subroutine, public messages_variable_is_block(namespace, name)
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
subroutine, public messages_info(no_lines, iunit, debug_only, stress, all_nodes, namespace)
this module contains the low-level part of the output system
this module contains the output system
subroutine, public output_states(outp, namespace, space, dir, st, gr, ions, hm, iter)
integer function, public parse_block(namespace, name, blk, check_varinfo_)
subroutine, public conv_to_c_string(str)
converts to c string
subroutine, public target_chi_userdefined(tg, gr, psi_in, chi_out)
real(real64) function, public target_j1_userdefined(tg, gr, psi)
subroutine, public target_init_userdefined(gr, namespace, tg, td)
subroutine, public target_output_userdefined(tg, namespace, space, gr, dir, ions, hm, outp)
Description of the grid, containing information on derivatives, stencil, and symmetries.
The states_elec_t class contains all electronic wave functions.