28 use,
intrinsic :: iso_fortran_env
39 integer :: iunit, ierr, ii, jj, iter, read_iter, ntime, nvaf, nvel, ivel
40 real(real64),
allocatable :: vaf(:), time(:), velocities(:, :), ftvaf(:)
41 type(ions_t),
pointer :: ions
42 type(spectrum_t) :: spectrum
43 type(batch_t) :: vafb, ftvafb
44 real(real64) :: ww, curtime, vaftime, deltat
45 integer :: ifreq, max_freq
84 if (spectrum%end_time <
m_zero) spectrum%end_time = huge(spectrum%end_time)
98 read(unit = iunit, iostat = ierr, fmt = *) read_iter, curtime, &
99 ((ions%pos(jj, ii), jj = 1, 3), ii = 1, ions%natoms), &
100 ((ions%vel(jj, ii), jj = 1, 3), ii = 1, ions%natoms)
104 if (ierr /= 0 .or. curtime >= spectrum%end_time)
then
110 if (iter /= read_iter + 1)
then
111 call messages_write(
"Error while reading file 'td.general/coordinates',", new_line = .
true.)
121 if (curtime >= spectrum%start_time .and. mod(iter, skip) == 0) ntime = ntime + 1
128 nvel = ions%natoms*ions%space%dim
130 safe_allocate(time(1:ntime))
131 safe_allocate(velocities(1:nvel, 1:ntime))
142 read(unit = iunit, iostat = ierr, fmt = *) read_iter, curtime, &
143 ((ions%pos(jj, ii), jj = 1, 3), ii = 1, ions%natoms), &
144 ((ions%vel(jj, ii), jj = 1, 3), ii = 1, ions%natoms)
148 if (ierr /= 0 .or. curtime >= spectrum%end_time)
then
154 assert(iter == read_iter + 1)
156 if (curtime >= spectrum%start_time .and. mod(iter, skip) == 0)
then
158 time(ntime) = curtime
160 do ii = 1, ions%natoms
161 do jj = 1, ions%space%dim
175 deltat = time(2) - time(1)
187 nvaf = int(vaftime/deltat)
189 safe_allocate(vaf(1:ntime))
196 call messages_write(
'Calculating the velocity autocorrelation function')
205 write(unit = iunit, iostat = ierr, fmt = 800)
206 write(unit = iunit, iostat = ierr, fmt =
'(8a)')
'# HEADER'
207 write(unit = iunit, iostat = ierr, fmt =
'(a,4x,a6,a7,a1,10x,a10)') &
208 '# Iter',
'time [',
units_out%time%abbrev,
']',
'VAF [a.u.]'
209 write(unit = iunit, iostat = ierr, fmt = 800)
218 safe_allocate(ftvaf(1:max_freq))
229 1, nvaf,
m_zero, deltat, vafb, spectrum%min_energy, spectrum%max_energy, spectrum%energy_step, ftvafb)
238 write(unit = iunit, iostat = ierr, fmt = 800)
239 write(unit = iunit, iostat = ierr, fmt =
'(8a)')
'# HEADER'
240 write(unit = iunit, iostat = ierr, fmt =
'(a17,6x,a15)')
'# Energy [1/cm]',
'Spectrum [a.u.]'
241 write(unit = iunit, iostat = ierr, fmt = 800)
243 do ifreq = 1, max_freq
244 ww = spectrum%energy_step*(ifreq - 1) + spectrum%min_energy
250 safe_deallocate_a(vaf)
252 safe_deallocate_a(ftvaf)
254 safe_deallocate_p(ions)
256 safe_deallocate_a(time)
268 real(real64),
intent(out) :: vaf(:)
273 write (
message(1),
'(a)')
"Read velocities from '"// &
286 do itn = 1, ntime - itm + 1
289 vaf(itm) = vaf(itm) + velocities(ivel, itm + itn - 1)*velocities(ivel, itn)
293 vaf(itm) = vaf(itm)/real(ntime - itm + 1, real64)
298 vaf(itm) = vaf(itm)/vaf(1)
initialize a batch with existing memory
This module implements batches of mesh functions.
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.
real(real64), parameter, public m_zero
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...
subroutine, public init_octopus_globals(comm)
Initialise Octopus-specific global constants and files. This routine performs no initialisation calls...
real(real64), parameter, public m_one
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...
subroutine, public io_close(iunit, grp)
subroutine, public io_skip_header(iunit)
subroutine, public io_end()
character(len=max_path_len) function, public io_workpath(path, namespace)
integer function, public io_open(file, namespace, action, status, form, position, die, recl, grp)
subroutine, public messages_end()
subroutine, public messages_init(output_dir)
subroutine, public messages_obsolete_variable(namespace, name, rep)
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
subroutine, public messages_new_line()
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)
type(namespace_t), public global_namespace
subroutine, public parser_init()
Initialise the Octopus parser.
subroutine, public parser_end()
End the Octopus parser.
subroutine, public profiling_end(namespace)
subroutine, public profiling_init(namespace)
Create profiling subdirectory.
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...
subroutine, public spectrum_init(spectrum, namespace, default_energy_step, default_max_energy)
subroutine, public spectrum_signal_damp(damp_type, damp_factor, time_start, time_end, t0, time_step, time_function)
integer, parameter, public spectrum_transform_cos
pure integer function, public spectrum_nenergy_steps(spectrum)
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
This module defines the unit system, used for input and output.
type(unit_t), public unit_invcm
For vibrational frequencies.
type(unit_system_t), public units_out
subroutine, public unit_system_init(namespace)
subroutine calculate_vaf(vaf)