Octopus
target_excited.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
22 use debug_oct_m
25 use global_oct_m
26 use grid_oct_m
28 use io_oct_m
29 use ions_oct_m
31 use, intrinsic :: iso_fortran_env
35 use mesh_oct_m
39 use output_oct_m
43 use space_oct_m
48 use td_oct_m
49 use types_oct_m
50
51 implicit none
52
53 private
54 public :: &
59
60
61contains
62
63
64 ! ----------------------------------------------------------------------
66 subroutine target_init_excited(mesh, namespace, space, tg, td, restart, kpoints)
67 class(mesh_t), intent(in) :: mesh
68 type(namespace_t), intent(in) :: namespace
69 class(space_t), intent(in) :: space
70 type(target_t), intent(inout) :: tg
71 type(td_t), intent(in) :: td
72 type(restart_t), intent(in) :: restart
73 type(kpoints_t), intent(in) :: kpoints
74
75 integer :: ierr, nik, dim
76
77 push_sub(target_init_excited)
78
79 message(1) = 'Info: TargetOperator is a linear combination of Slater determinants.'
80 call messages_info(1, namespace=namespace)
81
82 tg%move_ions = td%ions_dyn%ions_move()
83 tg%dt = td%dt
84
85 call states_elec_look(restart, nik, dim, tg%st%nst, ierr)
86 if (ierr /= 0) then
87 message(1) = "Unable to read states information."
88 call messages_fatal(1, namespace=namespace)
89 end if
90 tg%st%st_start = 1
91 tg%st%st_end = tg%st%nst
92
93 safe_deallocate_a(tg%st%occ)
94 safe_deallocate_a(tg%st%eigenval)
95 safe_deallocate_a(tg%st%node)
96
97 safe_allocate( tg%st%occ(1:tg%st%nst, 1:tg%st%nik))
98 safe_allocate(tg%st%eigenval(1:tg%st%nst, 1:tg%st%nik))
99 safe_allocate( tg%st%node(1:tg%st%nst))
100 if (tg%st%d%ispin == spinors) then
101 safe_deallocate_a(tg%st%spin)
102 safe_allocate(tg%st%spin(1:3, 1:tg%st%nst, 1:tg%st%nik))
103 end if
104 call states_elec_allocate_wfns(tg%st, mesh, type_cmplx)
105 tg%st%node(:) = 0
106
107 call states_elec_load(restart, namespace, space, tg%st, mesh, kpoints, ierr)
108 if (ierr /= 0) then
109 message(1) = "Unable to read wavefunctions."
110 call messages_fatal(1, namespace=namespace)
111 end if
112
113 call excited_states_init(tg%est, tg%st, "oct-excited-state-target", namespace)
115 pop_sub(target_init_excited)
116 end subroutine target_init_excited
117
118
119 ! ----------------------------------------------------------------------
120 subroutine target_output_excited(tg, namespace, space, gr, dir, ions, hm, outp)
121 type(target_t), intent(in) :: tg
122 type(namespace_t), intent(in) :: namespace
123 class(space_t), intent(in) :: space
124 type(grid_t), intent(in) :: gr
125 character(len=*), intent(in) :: dir
126 type(ions_t), intent(in) :: ions
127 type(hamiltonian_elec_t), intent(in) :: hm
128 type(output_t), intent(in) :: outp
129
130 push_sub(target_output_excited)
131
132 call io_mkdir(trim(dir), namespace)
133 call output_states(outp, namespace, space, trim(dir)//'/st', tg%est%st, gr, ions, hm, -1)
134 call excited_states_output(tg%est, trim(dir), namespace)
135
136 pop_sub(target_output_excited)
137 end subroutine target_output_excited
138 ! ----------------------------------------------------------------------
139
140
141 ! ----------------------------------------------------------------------
143 real(real64) function target_j1_excited(tg, namespace, gr, psi) result(j1)
144 type(target_t), intent(in) :: tg
145 type(namespace_t), intent(in) :: namespace
146 type(grid_t), intent(in) :: gr
147 type(states_elec_t), intent(in) :: psi
148
149 push_sub(target_j1_excited)
150
151 j1 = abs(zstates_elec_mpdotp(namespace, gr, tg%est, psi))**2
152
153 pop_sub(target_j1_excited)
154 end function target_j1_excited
155
156
157 ! ----------------------------------------------------------------------
159 subroutine target_chi_excited(tg, namespace, gr, psi_in, chi_out)
160 type(target_t), intent(in) :: tg
161 type(namespace_t), intent(in) :: namespace
162 type(grid_t), intent(in) :: gr
163 type(states_elec_t), intent(in) :: psi_in
164 type(states_elec_t), intent(inout) :: chi_out
165
166 complex(real64), allocatable :: ci(:), di(:), mat(:, :, :), mm(:, :, :, :), mk(:, :), lambda(:, :)
167 complex(real64), allocatable :: zpsi(:, :), zchi(:, :)
168 integer :: ik, ist, jst, ia, ib, n_pairs, nst, kpoints, jj, idim, ip
169 push_sub(target_chi_excited)
170
171 n_pairs = tg%est%n_pairs
172 kpoints = psi_in%nik
173 nst = psi_in%nst
174
175
176 safe_allocate(zpsi(1:gr%np, 1:psi_in%d%dim))
177 safe_allocate(zchi(1:gr%np, 1:psi_in%d%dim))
178 safe_allocate(ci(1:n_pairs))
179 safe_allocate(di(1:n_pairs))
180 safe_allocate(mat(1:tg%est%st%nst, 1:nst, 1:psi_in%nik))
181 safe_allocate(mm(1:nst, 1:nst, 1:kpoints, 1:n_pairs))
182 safe_allocate(mk(1:gr%np_part, 1:psi_in%d%dim))
183 safe_allocate(lambda(1:n_pairs, 1:n_pairs))
184
185 call zstates_elec_matrix(tg%est%st, psi_in, gr, mat)
186
187 do ia = 1, n_pairs
188 ci(ia) = tg%est%weight(ia)
189 call zstates_elec_matrix_swap(mat, tg%est%pair(ia))
190 mm(1:nst, 1:nst, 1:kpoints, ia) = mat(1:nst, 1:kpoints, 1:kpoints)
191 di(ia) = zstates_elec_mpdotp(namespace, gr, tg%est%st, psi_in, mat)
192 if (abs(di(ia)) > 1.0e-12_real64) then
193 do ik = 1, kpoints
194 call lalg_inverse(nst, mm(1:nst, 1:nst, ik, ia), 'dir')
195 end do
196 end if
197 call zstates_elec_matrix_swap(mat, tg%est%pair(ia))
198 end do
199
200 do ia = 1, n_pairs
201 do ib = 1, n_pairs
202 lambda(ia, ib) = conjg(ci(ib)) * ci(ia) * conjg(di(ia)) * di(ib)
203 end do
204 end do
205
206 select case (psi_in%d%ispin)
207 case (unpolarized)
208 write(message(1), '(a)') 'Internal error in target.target_chi: unpolarized.'
209 call messages_fatal(1, namespace=namespace)
210
211 case (spin_polarized)
212 assert(chi_out%nik == 2)
214 do ik = 1, kpoints
215 do ist = chi_out%st_start, chi_out%st_end
216
217 zchi(1:gr%np, 1:psi_in%d%dim) = m_z0
218
219 do ia = 1, n_pairs
220 if (ik /= tg%est%pair(ia)%kk) cycle
221 if (abs(di(ia)) < 1.0e-12_real64) cycle
222 do ib = 1, n_pairs
223 if (abs(di(ib)) < 1.0e-12_real64) cycle
224 mk = m_z0
225
226 do jst = 1, nst
227 if (jst == tg%est%pair(ib)%i) jj = tg%est%pair(ia)%a
228 call states_elec_get_state(tg%est%st, gr, jj, ik, zpsi)
229
230 do idim = 1, psi_in%d%dim
231 do ip = 1, gr%np
232 mk(ip, idim) = mk(ip, idim) + conjg(mm(ist, jst, ik, ib))*zpsi(ip, idim)
233 end do
234 end do
235 end do
237 call lalg_axpy(gr%np_part, psi_in%d%dim, m_z1, lambda(ib, ia)*mk(:, :), zchi)
238
239 end do
240 end do
241
242 call states_elec_set_state(chi_out, gr, ist, ik, zchi)
243
244 end do
245 end do
246
247 case (spinors)
248 assert(chi_out%nik == 1)
249
250 do ist = chi_out%st_start, chi_out%st_end
251
252 zchi(1:gr%np, 1:psi_in%d%dim) = m_z0
253
254 do ia = 1, n_pairs
255 if (abs(di(ia)) < 1.0e-12_real64) cycle
256
257 do ib = 1, n_pairs
258 if (abs(di(ib)) < 1.0e-12_real64) cycle
259
260 mk = m_z0
261 do jst = 1, nst
262 if (jst == tg%est%pair(ib)%i) jj = tg%est%pair(ia)%a
263 call states_elec_get_state(tg%est%st, gr, jj, ik, zpsi)
264
265 do idim = 1, psi_in%d%dim
266 do ip = 1, gr%np
267 mk(ip, idim) = mk(ip, idim) + conjg(mm(ist, jst, 1, ib))*zpsi(ip, idim)
268 end do
269 end do
270 end do
271
272 call lalg_axpy(gr%np_part, 2, m_z1, lambda(ib, ia)*mk(:, :), zchi)
273 end do
274 end do
275
276 call states_elec_set_state(chi_out, gr, ist, ik, zchi)
277
278 end do
279
280 end select
281
282 safe_deallocate_a(zpsi)
283 safe_deallocate_a(zchi)
284 safe_deallocate_a(ci)
285 safe_deallocate_a(di)
286 safe_deallocate_a(mat)
287 safe_deallocate_a(mm)
288 safe_deallocate_a(mk)
289 safe_deallocate_a(lambda)
290 pop_sub(target_chi_excited)
291 end subroutine target_chi_excited
292
293end module target_excited_oct_m
294
295!! Local Variables:
296!! mode: f90
297!! coding: utf-8
298!! End:
integer, parameter, public spinors
subroutine, public excited_states_output(excited_state, dirname, namespace)
subroutine, public excited_states_init(excited_state, ground_state, filename, namespace)
Fills in an excited_state structure, by reading a file called "filename". This file describes the "pr...
This module implements the underlying real-space grid.
Definition: grid.F90:117
Definition: io.F90:114
subroutine, public io_mkdir(fname, namespace, parents)
Definition: io.F90:311
This module defines various routines, operating on mesh functions.
This module defines the meshes, which are used in Octopus.
Definition: mesh.F90:118
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_info(no_lines, iunit, debug_only, stress, all_nodes, namespace)
Definition: messages.F90:616
this module contains the low-level part of the output system
Definition: output_low.F90:115
this module contains the output system
Definition: output.F90:115
subroutine, public output_states(outp, namespace, space, dir, st, gr, ions, hm, iter)
Definition: output.F90:1888
subroutine, public states_elec_allocate_wfns(st, mesh, wfs_type, skip, packed)
Allocates the KS wavefunctions defined within a states_elec_t structure.
subroutine, public states_elec_look(restart, nik, dim, nst, ierr)
Reads the 'states' file in the restart directory, and finds out the nik, dim, and nst contained in it...
This module handles reading and writing restart information for the states_elec_t.
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 target_init_excited(mesh, namespace, space, tg, td, restart, kpoints)
subroutine, public target_output_excited(tg, namespace, space, gr, dir, ions, hm, outp)
real(real64) function, public target_j1_excited(tg, namespace, gr, psi)
subroutine, public target_chi_excited(tg, namespace, gr, psi_in, chi_out)
Definition: td.F90:114
type(type_t), public type_cmplx
Definition: types.F90:134