49 integer,
parameter :: &
50 oct_is_groundstate = 1, &
61 type(electrons_t),
intent(inout) :: sys
62 type(opt_control_state_t),
target,
intent(inout) :: qcstate
64 integer :: ik, ib, idim, inst, inik, id, is, ip, ierr, &
65 no_states, istype, freeze_orbitals
67 real(real64) :: xx(1:sys%space%dim), rr, psi_re, psi_im
68 type(restart_t) :: restart
69 complex(real64),
allocatable :: zpsi(:, :)
71 type(states_elec_t),
pointer :: psi
97 call parse_variable(sys%namespace,
'OCTInitialState', oct_is_groundstate, istype)
101 case (oct_is_groundstate)
102 message(1) =
'Info: Using ground state for initial state.'
106 call states_elec_load(restart, sys%namespace, sys%space, psi, sys%gr, sys%kpoints, ierr)
109 message(1) =
"Unable to read wavefunctions."
115 message(1) =
'Using an excited state as the starting state for an '
116 message(2) =
'optimal-control run is not possible yet.'
117 message(3) =
'Try using "OCTInitialState = oct_is_transformation" instead.'
121 message(1) =
'Info: Using superposition of states for initial state.'
137 if (.not.
parse_is_defined(sys%namespace,
"OCTInitialTransformStates"))
then
138 message(1) =
'If "OCTInitialState = oct_is_gstransformation", then you must'
139 message(2) =
'supply an "OCTInitialTransformStates" block to define the transformation.'
145 message(1) =
"Could not read states for OCTInitialTransformStates."
149 call states_elec_transform(psi, sys%namespace, sys%space, restart, sys%gr, sys%kpoints, prefix =
"OCTInitial")
153 message(1) =
'Info: Building user-defined initial state.'
168 if (
parse_block(sys%namespace,
'OCTInitialUserdefined', blk) == 0)
then
170 safe_allocate(zpsi(1:sys%gr%np, 1:psi%d%dim))
184 if (.not. (id == idim .and. is == inst .and. ik == inik &
185 .and. psi%st_start <= is .and. psi%st_end >= is)) cycle
189 blk, ib - 1, 3, psi%user_def_states(id, is, ik))
199 sys%space%dim, xx, rr,
m_zero, psi%user_def_states(id, is, ik))
201 zpsi(ip, id) = cmplx(psi_re, psi_im, real64)
210 do is = psi%st_start, psi%st_end
216 safe_deallocate_a(zpsi)
222 write(
message(1),
'(a)')
"No valid initial state defined."
223 write(
message(2),
'(a)')
"Choosing the ground state."
228 call parse_variable(sys%namespace,
'TDFreezeOrbitals', 0, freeze_orbitals)
229 if (freeze_orbitals > 0)
then
233 write(
message(1),
'(a,i4,a,i4,a)')
'Info: The lowest', freeze_orbitals, &
234 ' orbitals have been frozen.', psi%nst,
' will be propagated.'
237 call v_ks_calc(sys%ks, sys%namespace, sys%space, sys%hm, psi, sys%ions, sys%ext_partners, calc_eigenval = .
true.)
238 elseif (freeze_orbitals < 0)
then
241 write(
message(1),
'(a)')
'Info: The single-active-electron approximation will be used.'
244 call v_ks_calc(sys%ks, sys%namespace, sys%space, sys%hm, psi, sys%ions, sys%ext_partners, calc_eigenval = .
true.)
252 call v_ks_calc(sys%ks, sys%namespace, sys%space, sys%hm, psi, sys%ions, sys%ext_partners, calc_eigenval = .
true.)
This module implements a calculator for the density and defines related functions.
subroutine, public states_elec_freeze_orbitals(st, namespace, space, gr, mc, kpoints, n, family_is_mgga)
Calculate partial density for frozen orbitals.
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.
integer, parameter oct_is_excited
integer, parameter oct_is_gstransformation
subroutine, public initial_state_init(sys, qcstate)
integer, parameter oct_is_userdefined
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)
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)
This module holds the "opt_control_state_t" datatype, which contains a quantum-classical state.
type(states_elec_t) function, pointer, public opt_control_point_qs(ocs)
subroutine, public opt_control_state_init(ocs, qstate, ions)
logical function, public parse_is_defined(namespace, name)
integer function, public parse_block(namespace, name, blk, check_varinfo_)
integer, parameter, public restart_gs
subroutine, public restart_init(restart, namespace, data_type, type, mc, ierr, mesh, dir, exact)
Initializes a restart object.
integer, parameter, public restart_type_load
subroutine, public restart_end(restart)
subroutine, public states_elec_deallocate_wfns(st)
Deallocates the KS wavefunctions defined within a states_elec_t structure.
subroutine, public states_elec_allocate_wfns(st, mesh, wfs_type, skip, packed)
Allocates the KS wavefunctions defined within a states_elec_t structure.
This module handles reading and writing restart information for the states_elec_t.
subroutine, public states_elec_transform(st, namespace, space, restart, mesh, kpoints, prefix)
subroutine, public states_elec_load(restart, namespace, space, st, mesh, kpoints, ierr, iter, lr, lowest_missing, label, verbose, skip)
returns in ierr: <0 => Fatal error, or nothing read =0 => read all wavefunctions >0 => could only rea...
subroutine, public conv_to_c_string(str)
converts to c string
type(type_t), public type_cmplx
subroutine, public v_ks_freeze_hxc(ks)
subroutine, public v_ks_calc(ks, namespace, space, hm, st, ions, ext_partners, calc_eigenval, time, calc_energy, calc_current, force_semilocal)
pure logical function, public family_is_mgga(family, only_collinear)
Is the xc function part of the mGGA family.