Octopus
spin_susceptibility.F90
Go to the documentation of this file.
1!! Copyright (C) 2018 N. Tancogne-Dejean
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 batch_oct_m
24 use global_oct_m
25 use io_oct_m
26 use ions_oct_m
27 use kick_oct_m
29 use math_oct_m
32 use parser_oct_m
34 use space_oct_m
36 use unit_oct_m
38
39 implicit none
40
41 integer :: in_file, out_file, ref_file, ii, jj, kk, ierr, ib, num_col, num_col_cart
42 integer :: time_steps, time_steps_ref, energy_steps, istart, iend, ntiter, iq
43 real(real64) :: dt, tt, ww, dt_ref
44 real(real64), allocatable :: ftreal(:,:), ftimag(:,:)
45 real(real64), allocatable :: m_cart(:,:), m_cart_ref(:,:), magnetization(:,:,:)
46 type(spectrum_t) :: spectrum
47 type(batch_t) :: vecpotb, ftrealb, ftimagb
48 type(kick_t) :: kick
49 character(len=256) :: header
50 character(len=MAX_PATH_LEN) :: fname, ref_filename
51 complex(real64), allocatable :: chi(:,:)
52
53 ! Initialize stuff
55
56 call getopt_init(ierr)
57 if (ierr == 0) call getopt_dielectric_function()
58 call getopt_end()
59
60 call parser_init()
61
62 call messages_init()
63
64 call io_init()
66
68
69 call spectrum_init(spectrum, global_namespace)
70
71 in_file = io_open('td.general/total_magnetization', global_namespace, action='read', status='old', die=.false.)
72 if (in_file < 0) then
73 message(1) = "Cannot open file '"//trim(io_workpath('td.general/total_magnetization', global_namespace))//"'"
74 call messages_fatal(1)
75 end if
76 rewind(in_file)
77 read(in_file,*)
78 read(in_file,*)
79 call kick_read(kick, in_file, global_namespace)
80 call io_skip_header(in_file)
81 call spectrum_count_time_steps(global_namespace, in_file, time_steps, dt)
82
83 time_steps = time_steps + 1
84
85 num_col_cart = 12*kick%nqvec
86 safe_allocate(m_cart(1:time_steps, 1:num_col_cart))
87
88 call io_skip_header(in_file)
89
90 do ii = 1, time_steps
91 read(in_file, *) jj, tt, (m_cart(ii,ib),ib = 1, num_col_cart)
92 end do
93
94 call io_close(in_file)
95
96 if (parse_is_defined(global_namespace, 'TransientMagnetizationReference')) then
97 !%Variable TransientMagnetizationReference
98 !%Type string
99 !%Default "."
100 !%Section Utilities::oct-spin_susceptibility
101 !%Description
102 !% In case of delayed kick, the calculation of the transient spin susceptibility requires
103 !% to substract a reference calculation, containing dynamics of the magnetization without the kick
104 !% This reference must be computed having
105 !% TDOutput = total_magnetization.
106 !% This variables defined the directory in which the reference total_magnetization file is,
107 !% relative to the current folder
108 !%End
109
110 call parse_variable(global_namespace, 'TransientMagnetizationReference', '.', ref_filename)
111 ref_file = io_open(trim(ref_filename)//'/total_magnetization', global_namespace, action='read', status='old', die=.false.)
112 if (ref_file < 0) then
113 message(1) = "Cannot open reference file '"// &
114 trim(io_workpath(trim(ref_filename)//'/total_magnetization', global_namespace))//"'"
115 call messages_fatal(1)
116 end if
117 call io_skip_header(ref_file)
118 call spectrum_count_time_steps(global_namespace, ref_file, time_steps_ref, dt_ref)
119 time_steps_ref = time_steps_ref + 1
120
121 if (time_steps_ref < time_steps) then
122 message(1) = "The reference calculation does not contain enought time steps"
123 call messages_fatal(1)
124 end if
125
126 if (.not. is_close(dt_ref, dt)) then
127 message(1) = "The time step of the reference calculation is different from the current calculation"
128 call messages_fatal(1)
129 end if
130
131 !We remove the reference
132 safe_allocate(m_cart_ref(1:time_steps_ref, 1:num_col_cart))
133 call io_skip_header(ref_file)
134 do ii = 1, time_steps_ref
135 read(ref_file, *) jj, tt, (m_cart_ref(ii, kk), kk = 1, num_col_cart)
136 end do
137 call io_close(ref_file)
138 do ii = 1, time_steps
139 do kk = 1, num_col_cart
140 m_cart(ii, kk) = m_cart(ii, kk) - m_cart_ref(ii, kk)
141 end do
142 end do
143 safe_deallocate_a(m_cart_ref)
144 end if
145
146 !We now perform the change of basis to the rotating basis
147 !In this basis we have only m_+(q), m_-(q), and m_z(+/-q)
148 !where z means here along the easy axis
149 num_col = 8
150 safe_allocate(magnetization(1:time_steps, 1:num_col, 1:kick%nqvec))
151
152 do iq = 1, kick%nqvec
153 !Real part of m_x
154 magnetization(:,1,iq) = m_cart(:,(iq-1)*12+1)*kick%trans_vec(1,1) &
155 + m_cart(:,(iq-1)*12+3)*kick%trans_vec(2,1) &
156 + m_cart(:,(iq-1)*12+5)*kick%trans_vec(3,1)
157 !We add -Im(m_y)
158 magnetization(:,1,iq) = magnetization(:,1,iq) -(m_cart(:,(iq-1)*12+2)*kick%trans_vec(1,2) &
159 + m_cart(:,(iq-1)*12+4)*kick%trans_vec(2,2) &
160 + m_cart(:,(iq-1)*12+6)*kick%trans_vec(3,2))
161
162 !Im part of m_x
163 magnetization(:,2,iq) = m_cart(:,(iq-1)*12+2)*kick%trans_vec(1,1) &
164 + m_cart(:,(iq-1)*12+4)*kick%trans_vec(2,1) &
165 + m_cart(:,(iq-1)*12+6)*kick%trans_vec(3,1)
166 !We add +Re(m_y)
167 magnetization(:,2,iq) = magnetization(:,2,iq) +(m_cart(:,(iq-1)*12+1)*kick%trans_vec(1,2) &
168 + m_cart(:,(iq-1)*12+3)*kick%trans_vec(2,2) &
169 + m_cart(:,(iq-1)*12+5)*kick%trans_vec(3,2))
170
171 !Real part of m_x
172 magnetization(:,3,iq) = m_cart(:,(iq-1)*12+7)*kick%trans_vec(1,1) &
173 + m_cart(:,(iq-1)*12+9)*kick%trans_vec(2,1) &
174 + m_cart(:,(iq-1)*12+11)*kick%trans_vec(3,1)
175 !We add +Im(m_y)
176 magnetization(:,3,iq) = magnetization(:,3,iq) +(m_cart(:,(iq-1)*12+8)*kick%trans_vec(1,2) &
177 + m_cart(:,(iq-1)*12+10)*kick%trans_vec(2,2) &
178 + m_cart(:,(iq-1)*12+12)*kick%trans_vec(3,2))
179
180 !Im part of m_x
181 magnetization(:,4,iq) = m_cart(:,(iq-1)*12+8)*kick%trans_vec(1,1) &
182 + m_cart(:,(iq-1)*12+10)*kick%trans_vec(2,1) &
183 + m_cart(:,(iq-1)*12+12)*kick%trans_vec(3,1)
184 !We add -Re(m_y)
185 magnetization(:,4,iq) = magnetization(:,4,iq) -(m_cart(:,(iq-1)*12+7)*kick%trans_vec(1,2) &
186 + m_cart(:,(iq-1)*12+9)*kick%trans_vec(2,2) &
187 + m_cart(:,(iq-1)*12+11)*kick%trans_vec(3,2))
188
189 !Real and Im part of m_z
190 magnetization(:,5,iq) = m_cart(:,(iq-1)*12+1)*kick%easy_axis(1) &
191 + m_cart(:,(iq-1)*12+3)*kick%easy_axis(2) &
192 + m_cart(:,(iq-1)*12+5)*kick%easy_axis(3)
193 magnetization(:,6,iq) = m_cart(:,(iq-1)*12+2)*kick%easy_axis(1) &
194 + m_cart(:,(iq-1)*12+4)*kick%easy_axis(2) &
195 + m_cart(:,(iq-1)*12+6)*kick%easy_axis(3)
196 magnetization(:,7,iq) = m_cart(:,(iq-1)*12+7)*kick%easy_axis(1) &
197 + m_cart(:,(iq-1)*12+9)*kick%easy_axis(2) &
198 + m_cart(:,(iq-1)*12+11)*kick%easy_axis(3)
199 magnetization(:,8,iq) = m_cart(:,(iq-1)*12+8)*kick%easy_axis(1) &
200 + m_cart(:,(iq-1)*12+10)*kick%easy_axis(2) &
201 + m_cart(:,(iq-1)*12+12)*kick%easy_axis(3)
202 end do
203
204 safe_deallocate_a(m_cart)
205
206 write(message(1), '(a, i7, a)') "Info: Read ", time_steps, " steps from file '"// &
207 trim(io_workpath('td.general/total_magnetization', global_namespace))//"'"
208 call messages_info(1)
209
210 write(header, '(9a15)') '# time', 'Re[m_+(q,t)]', 'Im[m_+(q,t)]', &
211 'Re[m_-(-q, t)]', 'Im[m_-(-q,t)]', &
212 'Re[m_z(q,t)]', 'Im[m_z(q,t)]', 'Re[m_z(-q,t)]', 'Im[m_z(-q,t)]'
213
214 do iq = 1, kick%nqvec
215
216 write(fname, '(a,i3.3)') 'td.general/transverse_magnetization_q', iq
217 out_file = io_open(trim(fname), global_namespace, action='write')
218 write(out_file,'(a)') trim(header)
219 do kk = 1, time_steps
220 write(out_file, '(9e15.6)') (kk - 1)*dt, (magnetization(kk,ii,iq), ii = 1,8)
221 end do
222 call io_close(out_file)
223
224
225 ! Find out the iteration numbers corresponding to the time limits.
226 call spectrum_fix_time_limits(spectrum, time_steps, dt, istart, iend, ntiter)
227
228 istart = max(1, istart)
229
230 energy_steps = spectrum_nenergy_steps(spectrum)
231
232 safe_allocate(ftreal(1:energy_steps, 1:num_col))
233 safe_allocate(ftimag(1:energy_steps, 1:num_col))
234
235 call batch_init(vecpotb, 1, 1, num_col, magnetization(:, :, iq))
236 call batch_init(ftrealb, 1, 1, num_col, ftreal)
237 call batch_init(ftimagb, 1, 1, num_col, ftimag)
238
239
240 call spectrum_signal_damp(spectrum%damp, spectrum%damp_factor, istart, iend, spectrum%start_time, dt, vecpotb)
241
242 call spectrum_fourier_transform(spectrum%method, spectrum_transform_cos, spectrum%noise, &
243 istart, iend, spectrum%start_time, dt, vecpotb, spectrum%min_energy, &
244 spectrum%max_energy, spectrum%energy_step, ftrealb)
245
246 call spectrum_fourier_transform(spectrum%method, spectrum_transform_sin, spectrum%noise, &
247 istart, iend, spectrum%start_time, dt, vecpotb, spectrum%min_energy, &
248 spectrum%max_energy, spectrum%energy_step, ftimagb)
249
250
251 call vecpotb%end()
252 call ftrealb%end()
253 call ftimagb%end()
254
255 assert(abs(anint(num_col*m_half) - num_col*m_half) <= m_epsilon)
256 safe_allocate(chi(1:energy_steps, 1:num_col/2))
257 do ii = 1, num_col/2
258 do kk = 1, energy_steps
259 chi(kk,ii) = (ftreal(kk,(ii-1)*2+1) + m_zi*ftimag(kk, (ii-1)*2+1)&
260 -ftimag(kk, (ii-1)*2+2) + m_zi*ftreal(kk, (ii-1)*2+2))/kick%delta_strength
261 end do
262 end do
263
264 safe_deallocate_a(ftreal)
265 safe_deallocate_a(ftimag)
266
267
268 write(header, '(9a18)') '# energy', 'Re[\chi_{+-}(q)]', 'Im[\chi_{+-}(q)]', &
269 'Re[\chi_{-+}(-q)]', 'Im[\chi_{-+}(-q)]', &
270 'Re[\chi_{zz}(q)]', 'Im[\chi_{zz}(q)]', 'Re[\chi_{zz}(-q)]', 'Im[\chi_{zz}(-q)]'
271
272 write(fname, '(a,i3.3)') 'td.general/spin_susceptibility_q', iq
273 out_file = io_open(trim(fname), global_namespace, action='write')
274 write(out_file,'(a)') trim(header)
275 do kk = 1, energy_steps
276 ww = (kk-1)*spectrum%energy_step + spectrum%min_energy
277 write(out_file, '(13e15.6)') ww, &
278 (real(chi(kk,ii), real64), aimag(chi(kk,ii)), ii = 1, num_col/2)
279 end do
280 call io_close(out_file)
281
282 safe_deallocate_a(chi)
283 end do !iq
284
285 safe_deallocate_a(magnetization)
286
287 call kick_end(kick)
288
290 call io_end()
291 call messages_end()
292 call parser_end()
293 call global_end()
294
295end program spin_susceptibility
296
297!! Local Variables:
298!! mode: f90
299!! coding: utf-8
300!! End:
initialize a batch with existing memory
Definition: batch.F90:267
This module implements batches of mesh functions.
Definition: batch.F90:133
subroutine, public getopt_init(ierr)
Initializes the getopt machinery. Must be called before attempting to parse the options....
subroutine, public getopt_end
subroutine, public global_end()
Finalise parser varinfo file, and MPI.
Definition: global.F90:381
type(mpi_comm), parameter, public serial_dummy_comm
Alias MPI_COMM_UNDEFINED for the specific use case of initialising Octopus utilities with no MPI supp...
Definition: global.F90:264
subroutine, public init_octopus_globals(comm)
Initialise Octopus-specific global constants and files. This routine performs no initialisation calls...
Definition: global.F90:353
complex(real64), parameter, public m_zi
Definition: global.F90:201
real(real64), parameter, public m_epsilon
Definition: global.F90:203
real(real64), parameter, public m_half
Definition: global.F90:193
Definition: io.F90:114
subroutine, public io_init(defaults)
If the argument defaults is present and set to true, then the routine will not try to read anything f...
Definition: io.F90:166
subroutine, public io_close(iunit, grp)
Definition: io.F90:468
subroutine, public io_skip_header(iunit)
Definition: io.F90:679
subroutine, public io_end()
Definition: io.F90:265
character(len=max_path_len) function, public io_workpath(path, namespace)
Definition: io.F90:313
integer function, public io_open(file, namespace, action, status, form, position, die, recl, grp)
Definition: io.F90:395
subroutine, public kick_read(kick, iunit, namespace)
Definition: kick.F90:819
subroutine, public kick_end(kick)
Definition: kick.F90:795
This module is intended to contain "only mathematical" functions and procedures.
Definition: math.F90:115
subroutine, public messages_end()
Definition: messages.F90:277
subroutine, public messages_init(output_dir)
Definition: messages.F90:224
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
type(namespace_t), public global_namespace
Definition: namespace.F90:132
logical function, public parse_is_defined(namespace, name)
Definition: parser.F90:502
subroutine, public parser_init()
Initialise the Octopus parser.
Definition: parser.F90:450
subroutine, public parser_end()
End the Octopus parser.
Definition: parser.F90:481
subroutine, public profiling_end(namespace)
Definition: profiling.F90:413
subroutine, public profiling_init(namespace)
Create profiling subdirectory.
Definition: profiling.F90:255
subroutine, public spectrum_fix_time_limits(spectrum, time_steps, dt, istart, iend, ntiter)
Definition: spectrum.F90:2508
subroutine, public spectrum_fourier_transform(method, transform, noise, time_start, time_end, t0, time_step, time_function, energy_start, energy_end, energy_step, energy_function)
Computes the sine, cosine, (or "exponential") Fourier transform of the real function given in the tim...
Definition: spectrum.F90:2638
subroutine, public spectrum_init(spectrum, namespace, default_energy_step, default_max_energy)
Definition: spectrum.F90:213
subroutine, public spectrum_signal_damp(damp_type, damp_factor, time_start, time_end, t0, time_step, time_function)
Definition: spectrum.F90:2552
integer, parameter, public spectrum_transform_cos
Definition: spectrum.F90:171
integer, parameter, public spectrum_transform_sin
Definition: spectrum.F90:171
subroutine, public spectrum_count_time_steps(namespace, iunit, time_steps, dt)
Definition: spectrum.F90:2386
pure integer function, public spectrum_nenergy_steps(spectrum)
Definition: spectrum.F90:2947
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
Definition: unit.F90:132
This module defines the unit system, used for input and output.
subroutine, public unit_system_init(namespace)
program spin_susceptibility