Octopus
initst.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
21module initst_oct_m
22 use debug_oct_m
24 use global_oct_m
25 use grid_oct_m
27 use ions_oct_m
31 use parser_oct_m
36 use string_oct_m
38 use td_oct_m
39 use v_ks_oct_m
41 use types_oct_m
42 use xc_oct_m
43
44 implicit none
45
46 private
47 public :: initial_state_init
48
49 integer, parameter :: &
50 oct_is_groundstate = 1, &
51 oct_is_excited = 2, &
54
55
56contains
57
58
59 ! ---------------------------------------------------------
60 subroutine initial_state_init(sys, qcstate)
61 type(electrons_t), intent(inout) :: sys
62 type(opt_control_state_t), target, intent(inout) :: qcstate
63
64 integer :: ik, ib, idim, inst, inik, id, is, ip, ierr, &
65 no_states, istype, freeze_orbitals
66 type(block_t) :: blk
67 real(real64) :: xx(1:sys%space%dim), rr, psi_re, psi_im
68 type(restart_t) :: restart
69 complex(real64), allocatable :: zpsi(:, :)
70
71 type(states_elec_t), pointer :: psi
72
73 push_sub(initial_state_init)
74
75 call opt_control_state_init(qcstate, sys%st, sys%ions)
76 psi => opt_control_point_qs(qcstate)
78 call states_elec_allocate_wfns(psi, sys%gr, type_cmplx)
79
80 !%Variable OCTInitialState
81 !%Type integer
82 !%Section Calculation Modes::Optimal Control
83 !%Default oct_is_groundstate
84 !%Description
85 !% Describes the initial state of the quantum system.
86 !% Possible arguments are:
87 !%Option oct_is_groundstate 1
88 !% Start in the ground state.
89 !%Option oct_is_excited 2
90 !% Currently not in use.
91 !%Option oct_is_gstransformation 3
92 !% Start in a transformation of the ground-state orbitals, as defined in the
93 !% block <tt>OCTInitialTransformStates</tt>.
94 !%Option oct_is_userdefined 4
95 !% Start in a user-defined state.
96 !%End
97 call parse_variable(sys%namespace, 'OCTInitialState', oct_is_groundstate, istype)
98 if (.not. varinfo_valid_option('OCTInitialState', istype)) call messages_input_error(sys%namespace, 'OCTInitialState')
99
100 select case (istype)
101 case (oct_is_groundstate)
102 message(1) = 'Info: Using ground state for initial state.'
103 call messages_info(1, namespace=sys%namespace)
104 call restart_init(restart, sys%namespace, restart_gs, restart_type_load, sys%mc, ierr, mesh=sys%gr, exact=.true.)
105 if (ierr == 0) then
106 call states_elec_load(restart, sys%namespace, sys%space, psi, sys%gr, sys%kpoints, ierr)
107 end if
108 if (ierr /= 0) then
109 message(1) = "Unable to read wavefunctions."
110 call messages_fatal(1, namespace=sys%namespace)
111 end if
112 call restart_end(restart)
113
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.'
118 call messages_fatal(3, namespace=sys%namespace)
119
121 message(1) = 'Info: Using superposition of states for initial state.'
122 call messages_info(1, namespace=sys%namespace)
123
124
125 !%Variable OCTInitialTransformStates
126 !%Type block
127 !%Section Calculation Modes::Optimal Control
128 !%Description
129 !% If <tt>OCTInitialState = oct_is_gstransformation</tt>, you must specify an
130 !% <tt>OCTInitialTransformStates</tt> block, in order to specify which linear
131 !% combination of the states present in <tt>restart/gs</tt> is used to
132 !% create the initial state.
133 !%
134 !% The syntax is the same as the <tt>TransformStates</tt> block.
135 !%End
136
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.'
140 call messages_fatal(2, namespace=sys%namespace)
141 end if
143 call restart_init(restart, sys%namespace, restart_gs, restart_type_load, sys%mc, ierr, mesh=sys%gr, exact=.true.)
144 if (ierr /= 0) then
145 message(1) = "Could not read states for OCTInitialTransformStates."
146 call messages_fatal(1, namespace=sys%namespace)
147 end if
148
149 call states_elec_transform(psi, sys%namespace, sys%space, restart, sys%gr, sys%kpoints, prefix = "OCTInitial")
150 call restart_end(restart)
151
152 case (oct_is_userdefined)
153 message(1) = 'Info: Building user-defined initial state.'
154 call messages_info(1, namespace=sys%namespace)
155
156 !%Variable OCTInitialUserdefined
157 !%Type block
158 !%Section Calculation Modes::Optimal Control
159 !%Description
160 !% Define an initial state. Syntax follows the one of the <tt>UserDefinedStates</tt> block.
161 !% Example:
162 !%
163 !% <tt>%OCTInitialUserdefined
164 !% <br>&nbsp;&nbsp; 1 | 1 | 1 | "exp(-r^2)*exp(-i*0.2*x)"
165 !% <br>%</tt>
166 !%
167 !%End
168 if (parse_block(sys%namespace, 'OCTInitialUserdefined', blk) == 0) then
169
170 safe_allocate(zpsi(1:sys%gr%np, 1:psi%d%dim))
171
172 no_states = parse_block_n(blk)
173 do ib = 1, no_states
174 call parse_block_integer(blk, ib - 1, 0, idim)
175 call parse_block_integer(blk, ib - 1, 1, inst)
176 call parse_block_integer(blk, ib - 1, 2, inik)
177
178 ! read formula strings and convert to C strings
179 do id = 1, psi%d%dim
180 do is = 1, psi%nst
181 do ik = 1, psi%nik
182
183 ! does the block entry match and is this node responsible?
184 if (.not. (id == idim .and. is == inst .and. ik == inik &
185 .and. psi%st_start <= is .and. psi%st_end >= is)) cycle
186
187 ! parse formula string
188 call parse_block_string( &
189 blk, ib - 1, 3, psi%user_def_states(id, is, ik))
190 ! convert to C string
191 call conv_to_c_string(psi%user_def_states(id, is, ik))
192
193 do ip = 1, sys%gr%np
194 xx = sys%gr%x(ip, :)
195 rr = norm2(xx)
196
197 ! parse user-defined expressions
198 call parse_expression(psi_re, psi_im, &
199 sys%space%dim, xx, rr, m_zero, psi%user_def_states(id, is, ik))
200 ! fill state
201 zpsi(ip, id) = cmplx(psi_re, psi_im, real64)
202 end do
203 call states_elec_set_state(psi, sys%gr, id, is, ik, zpsi(:, id))
204 end do
205 end do
206 end do
207 end do
208 call parse_block_end(blk)
209 do ik = 1, psi%nik
210 do is = psi%st_start, psi%st_end
211 call states_elec_get_state(psi, sys%gr, is, ik, zpsi)
212 call zmf_normalize(sys%gr, psi%d%dim, zpsi)
213 call states_elec_set_state(psi, sys%gr, is, ik, zpsi)
214 end do
215 end do
216 safe_deallocate_a(zpsi)
217 else
218 call messages_variable_is_block(sys%namespace, 'OCTInitialUserdefined')
219 end if
220
221 case default
222 write(message(1),'(a)') "No valid initial state defined."
223 write(message(2),'(a)') "Choosing the ground state."
224 call messages_info(2, namespace=sys%namespace)
225 end select
226
227 ! Check whether we want to freeze some of the deeper orbitals.
228 call parse_variable(sys%namespace, 'TDFreezeOrbitals', 0, freeze_orbitals)
229 if (freeze_orbitals > 0) then
230 ! In this case, we first freeze the orbitals, then calculate the Hxc potential.
231 call states_elec_freeze_orbitals(psi, sys%namespace, sys%space, sys%gr, sys%mc, sys%kpoints, &
232 freeze_orbitals, family_is_mgga(sys%ks%xc_family))
233 write(message(1),'(a,i4,a,i4,a)') 'Info: The lowest', freeze_orbitals, &
234 ' orbitals have been frozen.', psi%nst, ' will be propagated.'
235 call messages_info(1, namespace=sys%namespace)
236 call density_calc(psi, sys%gr, psi%rho)
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
239 ! This means SAE approximation. We calculate the Hxc first, then freeze all
240 ! orbitals minus one.
241 write(message(1),'(a)') 'Info: The single-active-electron approximation will be used.'
242 call messages_info(1, namespace=sys%namespace)
243 call density_calc(psi, sys%gr, psi%rho)
244 call v_ks_calc(sys%ks, sys%namespace, sys%space, sys%hm, psi, sys%ions, sys%ext_partners, calc_eigenval = .true.)
245 call states_elec_freeze_orbitals(psi, sys%namespace, sys%space, sys%gr, sys%mc, sys%kpoints, &
246 psi%nst - 1, family_is_mgga(sys%ks%xc_family))
247 call v_ks_freeze_hxc(sys%ks)
248 call density_calc(psi, sys%gr, psi%rho)
249 else
250 ! Normal run.
251 call density_calc(psi, sys%gr, psi%rho)
252 call v_ks_calc(sys%ks, sys%namespace, sys%space, sys%hm, psi, sys%ions, sys%ext_partners, calc_eigenval = .true.)
253 end if
254
255 pop_sub(initial_state_init)
256 end subroutine initial_state_init
257
258end module initst_oct_m
259
260!! Local Variables:
261!! mode: f90
262!! coding: utf-8
263!! End:
This module implements a calculator for the density and defines related functions.
Definition: density.F90:120
subroutine, public states_elec_freeze_orbitals(st, namespace, space, gr, mc, kpoints, n, family_is_mgga)
Calculate partial density for frozen orbitals.
Definition: density.F90:651
subroutine, public density_calc(st, gr, density, istin)
Computes the density from the orbitals in st.
Definition: density.F90:608
real(real64), parameter, public m_zero
Definition: global.F90:187
This module implements the underlying real-space grid.
Definition: grid.F90:117
integer, parameter oct_is_excited
Definition: initst.F90:142
integer, parameter oct_is_gstransformation
Definition: initst.F90:142
subroutine, public initial_state_init(sys, qcstate)
Definition: initst.F90:154
integer, parameter oct_is_userdefined
Definition: initst.F90:142
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)
Definition: messages.F90:1081
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
Definition: messages.F90:624
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:420
subroutine, public messages_input_error(namespace, var, details, row, column)
Definition: messages.F90:723
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)
Definition: parser.F90:502
integer function, public parse_block(namespace, name, blk, check_varinfo_)
Definition: parser.F90:618
integer, parameter, public restart_gs
Definition: restart.F90:229
subroutine, public restart_init(restart, namespace, data_type, type, mc, ierr, mesh, dir, exact)
Initializes a restart object.
Definition: restart.F90:514
integer, parameter, public restart_type_load
Definition: restart.F90:225
subroutine, public restart_end(restart)
Definition: restart.F90:720
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
Definition: string.F90:252
Definition: td.F90:114
type(type_t), public type_cmplx
Definition: types.F90:134
subroutine, public v_ks_freeze_hxc(ks)
Definition: v_ks.F90:1425
subroutine, public v_ks_calc(ks, namespace, space, hm, st, ions, ext_partners, calc_eigenval, time, calc_energy, calc_current, force_semilocal)
Definition: v_ks.F90:732
Definition: xc.F90:114
pure logical function, public family_is_mgga(family, only_collinear)
Is the xc function part of the mGGA family.
Definition: xc.F90:579
int true(void)