30 use,
intrinsic :: iso_fortran_env
71 integer,
public,
parameter :: &
72 SPECTRUM_DAMP_NONE = 0, &
78 integer,
public,
parameter :: &
79 SPECTRUM_TRANSFORM_LAPLACE = 1, &
83 integer,
public,
parameter :: &
84 SPECTRUM_ABSORPTION = 1, &
89 integer,
public,
parameter :: &
90 SPECTRUM_FOURIER = 1, &
94 real(real64) :: start_time
95 real(real64) :: end_time
96 real(real64) :: energy_step
97 real(real64) :: min_energy
98 real(real64) :: max_energy
101 real(real64) :: damp_factor
104 real(real64) :: noise
105 logical,
private :: sigma_diag
111 real(real64) :: time_step_, energy_step_
112 complex(real64),
allocatable :: func_(:),func_ar_(:,:),pos_(:,:),tret_(:), funcw_(:)
113 type(fft_t),
save :: fft_handler
114 integer :: is_, ie_, default
119 subroutine spectrum_init(spectrum, namespace, default_energy_step, default_max_energy)
120 type(spectrum_t),
intent(inout) :: spectrum
121 type(namespace_t),
intent(in) :: namespace
122 real(real64),
optional,
intent(in) :: default_energy_step
123 real(real64),
optional,
intent(in) :: default_max_energy
125 real(real64) :: fdefault
147 call parse_variable(namespace,
'PropagationSpectrumType', spectrum_absorption, spectrum%spectype)
165 call parse_variable(namespace,
'SpectrumMethod', spectrum_fourier, spectrum%method)
183 call parse_variable(namespace,
'SpectrumSignalNoise', 0.0_real64, spectrum%noise)
208 call parse_variable(namespace,
'PropagationSpectrumDampMode', default, spectrum%damp)
216 message(1) =
'Using damping with compressed sensing, this is not required'
217 message(2) =
'and can introduce noise in the spectra.'
274 if (
present(default_energy_step)) fdefault = default_energy_step
275 call parse_variable(namespace,
'PropagationSpectrumEnergyStep', fdefault, spectrum%energy_step,
units_inp%energy)
299 if (
present(default_max_energy)) fdefault = default_max_energy
300 call parse_variable(namespace,
'PropagationSpectrumMaxEnergy', fdefault, spectrum%max_energy,
units_inp%energy)
326 call parse_variable(namespace,
'PropagationSpectrumSigmaDiagonalization', .false., spectrum%sigma_diag)
339 integer,
intent(in) :: out_file
340 integer,
intent(in) :: in_file(:)
342 integer :: nspin, energy_steps, ie, is, equiv_axes, n_files, trash
343 real(real64),
allocatable ::
sigma(:, :, :, :), sigmap(:, :, :, :), sigmau(:, :, :), &
344 sigmav(:, :, :), sigmaw(:, :, :), ip(:, :)
345 real(real64) :: dw, dump
350 n_files =
size(in_file)
351 equiv_axes = 3 - n_files + 1
357 safe_allocate(
sigma(1:3, 1:3, 1:energy_steps, 1:nspin))
358 safe_allocate(sigmap(1:3, 1:3, 1:energy_steps, 1:nspin))
359 safe_allocate(sigmau(1:3, 1:energy_steps, 1:nspin))
360 safe_allocate(sigmav(1:3, 1:energy_steps, 1:nspin))
361 safe_allocate(sigmaw(1:3, 1:energy_steps, 1:nspin))
362 safe_allocate( ip(1:3, 1:3))
364 select case (equiv_axes)
368 do ie = 1, energy_steps
369 read(in_file(1), *) dump, (sigmau(1:3, ie, is), is = 1, nspin)
374 do ie = 1, energy_steps
375 sigmap(1, 1, ie, is) = sum(sigmau(1:3, ie, is) * kick%pol(1:3, 1))
376 sigmap(1, 2, ie, is) = sum(sigmau(1:3, ie, is) * kick%pol(1:3, 2))
377 sigmap(1, 3, ie, is) = sum(sigmau(1:3, ie, is) * kick%pol(1:3, 3))
382 sigmap(2, 2, :, :) = sigmap(1, 1, :, :)
383 sigmap(3, 3, :, :) = sigmap(1, 1, :, :)
386 sigmap(2, 1, :, :) = sigmap(1, 2, :, :)
387 sigmap(3, 1, :, :) = sigmap(1, 3, :, :)
391 do ie = 1, energy_steps
392 sigmap(2, 3, ie, is) = sum(sigmau(1:3, ie, is) * kick%wprime(1:3))
393 sigmap(3, 2, ie, is) = sigmap(2, 3, ie, is)
402 do ie = 1, energy_steps
403 read(in_file(1), *) dump, (sigmau(1:3, ie, is), is = 1, nspin)
404 read(in_file(2), *) dump, (sigmaw(1:3, ie, is), is = 1, nspin)
409 do ie = 1, energy_steps
410 sigmap(1, 1, ie, is) = sum(sigmau(1:3, ie, is) * kick%pol(1:3, 1))
411 sigmap(1, 2, ie, is) = sum(sigmau(1:3, ie, is) * kick%pol(1:3, 2))
412 sigmap(1, 3, ie, is) = sum(sigmau(1:3, ie, is) * kick%pol(1:3, 3))
418 do ie = 1, energy_steps
419 sigmap(3, 1, ie, is) = sum(sigmaw(1:3, ie, is) * kick%pol(1:3, 1))
420 sigmap(3, 2, ie, is) = sum(sigmaw(1:3, ie, is) * kick%pol(1:3, 2))
421 sigmap(3, 3, ie, is) = sum(sigmaw(1:3, ie, is) * kick%pol(1:3, 3))
426 sigmap(2, 2, :, :) = sigmap(1, 1, :, :)
429 sigmap(2, 1, :, :) = sigmap(1, 2, :, :)
430 sigmap(2, 3, :, :) = sigmap(3, 2, :, :)
439 do ie = 1, energy_steps
440 read(in_file(1), *) dump, (sigmau(1:3, ie, is), is = 1, nspin)
441 read(in_file(2), *) dump, (sigmav(1:3, ie, is), is = 1, nspin)
442 read(in_file(3), *) dump, (sigmaw(1:3, ie, is), is = 1, nspin)
446 do ie = 1, energy_steps
447 sigmap(1, 1, ie, is) = sum(sigmau(1:3, ie, is) * kick%pol(1:3, 1))
448 sigmap(1, 2, ie, is) = sum(sigmau(1:3, ie, is) * kick%pol(1:3, 2))
449 sigmap(1, 3, ie, is) = sum(sigmau(1:3, ie, is) * kick%pol(1:3, 3))
453 do ie = 1, energy_steps
454 sigmap(2, 1, ie, is) = sum(sigmav(1:3, ie, is) * kick%pol(1:3, 1))
455 sigmap(2, 2, ie, is) = sum(sigmav(1:3, ie, is) * kick%pol(1:3, 2))
456 sigmap(2, 3, ie, is) = sum(sigmav(1:3, ie, is) * kick%pol(1:3, 3))
460 do ie = 1, energy_steps
461 sigmap(3, 1, ie, is) = sum(sigmaw(1:3, ie, is) * kick%pol(1:3, 1))
462 sigmap(3, 2, ie, is) = sum(sigmaw(1:3, ie, is) * kick%pol(1:3, 2))
463 sigmap(3, 3, ie, is) = sum(sigmaw(1:3, ie, is) * kick%pol(1:3, 3))
470 ip(1:3, 1:3) = kick%pol(1:3, 1:3)
473 do ie = 1, energy_steps
474 sigma(:, :, ie, is) = matmul(transpose(ip), matmul(sigmap(:, :, ie, is), ip))
480 spectrum%min_energy, energy_steps, kick)
483 if (spectrum%sigma_diag)
then
487 safe_deallocate_a(
sigma)
488 safe_deallocate_a(sigmap)
489 safe_deallocate_a(sigmau)
490 safe_deallocate_a(sigmav)
491 safe_deallocate_a(sigmaw)
492 safe_deallocate_a(ip)
500 integer,
intent(in) :: out_file
501 real(real64),
intent(in) ::
sigma(:, :, :, :)
502 integer,
intent(in) :: nspin
503 real(real64),
intent(in) :: energy_step, min_energy
504 integer,
intent(in) :: energy_steps
505 type(
kick_t),
optional,
intent(in) :: kick
507 integer :: is, idir, jdir, ie, ii
508 real(real64) :: average, anisotropy
509 real(real64),
allocatable :: pp(:,:), pp2(:,:), ip(:,:)
510 logical :: spins_singlet, spins_triplet
511 character(len=20) :: header_string
515 spins_singlet = .
true.
516 spins_triplet = .false.
517 if (
present(kick))
then
518 write(out_file,
'(a15,i2)')
'# nspin ', nspin
522 spins_triplet = .
true.
523 spins_singlet = .false.
525 spins_triplet = .
true.
529 write(out_file,
'(a1, a20)', advance =
'no')
'#',
str_center(
"Energy", 20)
530 write(out_file,
'(a20)', advance =
'no')
str_center(
"(1/3)*Tr[sigma]", 20)
531 write(out_file,
'(a20)', advance =
'no')
str_center(
"Anisotropy[sigma]", 20)
532 if (spins_triplet .and. spins_singlet)
then
533 write(out_file,
'(a20)', advance =
'no')
str_center(
"(1/3)*Tr[sigma-]", 20)
538 write(header_string,
'(a6,i1,a1,i1,a1,i1,a1)')
'sigma(', idir,
',', jdir,
',', is,
')'
539 write(out_file,
'(a20)', advance =
'no')
str_center(trim(header_string), 20)
543 write(out_file,
'(1x)')
545 if (spins_triplet .and. spins_singlet)
then
548 do ii = 1, 2 + nspin * 9
551 write(out_file,
'(1x)')
566 safe_allocate(pp(1:3, 1:3))
567 if (spins_triplet .and. spins_singlet)
then
568 safe_allocate(pp2(1:3, 1:3))
570 safe_allocate(ip(1:3, 1:3))
572 do ie = 1, energy_steps
574 pp(:, :) =
sigma(:, :, ie, 1)
576 if (spins_singlet .and. spins_triplet)
then
577 pp2(:, :) = pp(:, :) -
sigma(:, :, ie, 2)
578 pp(:, :) = pp(:, :) +
sigma(:, :, ie, 2)
579 elseif (spins_triplet .and. .not. spins_singlet)
then
580 pp(:, :) = pp(:, :) -
sigma(:, :, ie, 2)
581 elseif (spins_singlet .and. .not. spins_triplet)
then
582 pp(:, :) = pp(:, :) +
sigma(:, :, ie, 2)
586 average =
m_third * (pp(1, 1) + pp(2, 2) + pp(3, 3))
595 if (spins_singlet .and. spins_triplet)
then
596 average =
m_third * (pp2(1, 1) + pp2(2, 2) + pp2(3, 3))
597 write(out_file,
'(1e20.8)', advance =
'no') average
601 write(out_file,
'(9e20.8)', advance =
'no')
sigma(1:3, 1:3, ie, is)
603 write(out_file,
'(1x)')
606 safe_deallocate_a(pp)
607 if (spins_triplet .and. spins_singlet)
then
608 safe_deallocate_a(pp2)
610 safe_deallocate_a(ip)
619 integer,
intent(in) :: in_file
620 integer,
intent(in) :: out_file
621 integer,
optional,
intent(in) :: ref_file
623 character(len=20) :: header_string
624 integer :: nspin, ref_nspin, lmax, ref_lmax, time_steps, &
625 ref_time_steps, istart, iend, ntiter, it, ii, isp, no_e, ie, idir
626 real(real64) :: dt, ref_dt, energy, ewsum, polsum
627 type(
kick_t) :: kick, ref_kick
628 real(real64),
allocatable :: dipole(:, :, :), ref_dipole(:, :, :), sigma(:, :, :), sf(:, :)
630 type(
batch_t) :: dipoleb, sigmab
638 call spectrum_mult_info(namespace, in_file, nspin, kick, time_steps, dt, file_units, lmax=lmax)
640 if (
present(ref_file))
then
642 ref_time_steps, ref_dt, ref_file_units, lmax = ref_lmax)
643 if ((nspin /= ref_nspin) .or. &
644 (time_steps /= ref_time_steps) .or. &
645 (.not.(abs(dt-ref_dt)< 1e-10_real64)) .or. &
646 (lmax /= ref_lmax))
then
647 write(
message(1),
'(a)')
'The multipoles and reference multipoles files do not match.'
654 message(1) =
'Multipoles file should contain the dipole -- and only the dipole.'
659 message(1) =
"Kick function must have been dipole to run this utility."
663 if (kick%pol_dir < 1)
then
664 message(1) =
"Kick polarization direction is not set. Probably no kick was used."
671 safe_allocate(dipole(0:time_steps, 1:3, 1:nspin))
674 if (
present(ref_file))
then
675 safe_allocate(ref_dipole(0:time_steps, 1:3, 1:nspin))
688 if (
present(ref_file))
then
689 dipole = dipole - ref_dipole
691 do it = 1, time_steps
692 dipole(it, :, :) = dipole(it, :, :) - dipole(0, :, :)
697 if (spectrum%energy_step <=
m_zero) spectrum%energy_step =
m_two *
m_pi / (dt*time_steps)
701 safe_allocate(sigma(1:no_e, 1:3, 1:nspin))
711 write(out_file,
'(a57)')
"Cross-section spectrum contains full local field effects."
718 call spectrum_signal_damp(spectrum%damp, spectrum%damp_factor, istart + 1, iend + 1, kick%time, dt, dipoleb)
720 istart + 1, iend + 1, kick%time, dt, dipoleb, spectrum%min_energy, spectrum%max_energy, spectrum%energy_step, sigmab)
727 if (pcm%run_pcm)
then
732 safe_deallocate_a(dipole)
733 if (
present(ref_file))
then
734 safe_deallocate_a(ref_dipole)
737 safe_allocate(sf(1:no_e, nspin))
739 if (abs(kick%delta_strength) < 1e-12_real64) kick%delta_strength =
m_one
741 energy = (ie-1) * spectrum%energy_step + spectrum%min_energy
743 sf(ie, isp) = sum(sigma(ie, 1:3, isp)*kick%pol(1:3, kick%pol_dir))
745 sf(ie, 1:nspin) = -sf(ie, 1:nspin) * (energy *
m_two) / (
m_pi * kick%delta_strength)
746 sigma(ie, 1:3, 1:nspin) = -sigma(ie, 1:3, 1:nspin)*(
m_four*
m_pi*energy/
p_c)/kick%delta_strength
751 ewsum = sum(sf(1, 1:nspin))
755 energy = (ie-1) * spectrum%energy_step + spectrum%min_energy
756 ewsum = ewsum + sum(sf(ie, 1:nspin))
757 polsum = polsum + sum(sf(ie, 1:nspin)) / energy**2
760 ewsum = ewsum * spectrum%energy_step
761 polsum = polsum * spectrum%energy_step
764 write(out_file,
'(a15,i2)')
'# nspin ', nspin
766 write(out_file,
'(a)')
'#%'
767 write(out_file,
'(a,i8)')
'# Number of time steps = ', time_steps
769 write(out_file,
'(a)')
'#%'
771 write(out_file,
'(a,f16.6)')
'# Electronic sum rule = ', ewsum
772 write(out_file,
'(a,f16.6,1x,a)')
'# Static polarizability (from sum rule) = ', &
774 write(out_file,
'(a)')
'#%'
777 write(out_file,
'(a1,a20)', advance =
'no')
'#',
str_center(
"Energy", 20)
780 write(header_string,
'(a6,i1,a8,i1,a1)')
'sigma(', idir,
', nspin=', isp,
')'
781 write(out_file,
'(a20)', advance =
'no')
str_center(trim(header_string), 20)
785 write(header_string,
'(a18,i1,a1)')
'StrengthFunction(', isp,
')'
786 write(out_file,
'(a20)', advance =
'no')
str_center(trim(header_string), 20)
788 write(out_file,
'(1x)')
796 write(out_file,
'(1x)')
800 (ie-1) * spectrum%energy_step + spectrum%min_energy)
808 write(out_file,
'(1x)')
811 safe_deallocate_a(sigma)
819 integer,
intent(in) :: in_file
820 real(real64),
intent(out) :: dipole(0:, :, :)
822 integer :: nspin, lmax, time_steps, trash, it, idir, ispin
823 real(real64) :: dt, dump
831 call spectrum_mult_info(namespace, in_file, nspin, kick, time_steps, dt, file_units, lmax = lmax)
836 do it = 0, time_steps
838 read(in_file, *) trash, dump, (dump, (dipole(it, idir, ispin), idir = 1, kick%dim), ispin = 1, nspin)
850 real(real64),
intent(inout) :: dipole(0:, :, :)
851 integer,
intent(in) :: time_steps
852 integer,
intent(in) :: nspin
855 real(real64) :: dipole_pcm(1:3)
859 integer :: asc_unit_test
860 integer :: cavity_unit
861 integer :: asc_vs_t_unit, asc_vs_t_unit_check
862 integer :: dipole_vs_t_unit_check, dipole_vs_t_unit_check1
865 real(real64) :: aux_float, aux_float1, aux_vec(1:3)
866 character(len=23) :: asc_vs_t_unit_format
867 character(len=16) :: asc_vs_t_unit_format_tail
874 asc_unit_test =
io_open(
pcm_dir//
'ASC_e.dat', namespace, action=
'read')
877 do while(iocheck >= 0)
878 read(asc_unit_test,*,iostat=iocheck) aux_vec(1:3), aux_float, aux_int
879 if (iocheck >= 0) pcm%n_tesserae = pcm%n_tesserae + 1
884 safe_allocate(pcm%tess(1:pcm%n_tesserae))
885 safe_allocate(pcm%q_e(1:pcm%n_tesserae))
886 safe_allocate(pcm%q_e_in(1:pcm%n_tesserae))
890 asc_unit_test =
io_open(
pcm_dir//
'ASC_e.dat', namespace, action=
'read')
891 cavity_unit =
io_open(
pcm_dir//
'cavity_check.xyz', namespace, action=
'write')
892 write(cavity_unit,
'(I3)') pcm%n_tesserae
894 do ia = 1, pcm%n_tesserae
895 read(asc_unit_test,*) pcm%tess(ia)%point(1:3), aux_float, aux_int
896 write(cavity_unit,
'(A1,3(1X,F14.8))')
'H', pcm%tess(ia)%point(1:3)
901 write (asc_vs_t_unit_format_tail,
'(I5,A11)') pcm%n_tesserae,
'(1X,F14.8))'
902 write (asc_vs_t_unit_format,
'(A)')
'(F14.8,'//trim(adjustl(asc_vs_t_unit_format_tail))
911 asc_vs_t_unit =
io_open(
pcm_dir//
'ASC_e_vs_t.dat', namespace, action=
'read', form=
'formatted')
912 asc_vs_t_unit_check =
io_open(
pcm_dir//
'ASC_e_vs_t_check.dat', namespace, action=
'write', form=
'formatted')
915 dipole_vs_t_unit_check =
io_open(
pcm_dir//
'dipole_e_vs_t_check.dat', namespace, action=
'write', form=
'formatted')
916 dipole_vs_t_unit_check1 =
io_open(
pcm_dir//
'dipole_e_vs_t_check1.dat', namespace, action=
'write', form=
'formatted')
919 read(asc_vs_t_unit,trim(adjustl(asc_vs_t_unit_format))) aux_float1, ( pcm%q_e_in(ia) , ia=1,pcm%n_tesserae)
921 do it = 1, time_steps
924 read(asc_vs_t_unit,trim(adjustl(asc_vs_t_unit_format))) aux_float, ( pcm%q_e(ia) , ia=1,pcm%n_tesserae)
927 call pcm_dipole(dipole_pcm(1:3), -pcm%q_e(1:pcm%n_tesserae), pcm%tess, pcm%n_tesserae)
930 dipole(it, 1, 1:nspin) = dipole(it, 1, 1:nspin) + dipole_pcm(1)
931 dipole(it, 2, 1:nspin) = dipole(it, 2, 1:nspin) + dipole_pcm(2)
932 dipole(it, 3, 1:nspin) = dipole(it, 3, 1:nspin) + dipole_pcm(3)
938 dipole(0, 1, 1:nspin) = dipole(1, 1, 1:nspin)
939 dipole(0, 2, 1:nspin) = dipole(1, 2, 1:nspin)
940 dipole(0, 3, 1:nspin) = dipole(1, 3, 1:nspin)
944 write(asc_vs_t_unit_check,trim(adjustl(asc_vs_t_unit_format))) aux_float, (pcm%q_e(ia), ia=1,pcm%n_tesserae)
945 write(dipole_vs_t_unit_check,
'(F14.8,3(1X,F14.8))') aux_float, dipole_pcm
946 write(dipole_vs_t_unit_check1,
'(F14.8,3(1X,F14.8))') aux_float, dipole(it,:,1)
953 call io_close(dipole_vs_t_unit_check)
954 call io_close(dipole_vs_t_unit_check1)
957 safe_deallocate_a(pcm%tess)
958 safe_deallocate_a(pcm%q_e)
959 safe_deallocate_a(pcm%q_e_in)
970 real(real64),
allocatable,
intent(inout) :: sigma(:, :, :)
971 real(real64),
allocatable,
intent(in) :: dipole(:, :, :)
972 integer,
intent(in) :: nspin
973 real(real64),
intent(in) :: kick_time
974 integer,
intent(in) :: istart, iend
975 real(real64),
intent(in) :: dt
976 integer,
intent(in) :: no_e
978 real(real64),
allocatable :: sigmap(:, :, :)
979 type(
batch_t) :: dipoleb, sigmab
983 complex(real64),
allocatable :: eps(:)
992 call spectrum_signal_damp(spectrum%damp, spectrum%damp_factor, istart + 1, iend + 1, kick_time, dt, dipoleb)
994 istart + 1, iend + 1, kick_time, dt, dipoleb, spectrum%min_energy, spectrum%max_energy, spectrum%energy_step, sigmab)
1001 safe_allocate(sigmap(1:no_e, 1:3, 1:nspin))
1003 call batch_init(dipoleb, 3, 1, nspin, dipole)
1006 call spectrum_signal_damp(spectrum%damp, spectrum%damp_factor, istart + 1, iend + 1, kick_time, dt, dipoleb)
1008 istart + 1, iend + 1, kick_time, dt, dipoleb, spectrum%min_energy, spectrum%max_energy, spectrum%energy_step, sigmab)
1013 safe_allocate(eps(1:no_e))
1018 call pcm_eps(pcm, eps(ie), (ie-1)*spectrum%energy_step + spectrum%min_energy)
1019 sigma(ie, 1:3, 1:nspin) = sigma(ie, 1:3, 1:nspin) * real(eps(ie), real64) + sigmap(ie, 1:3, 1:nspin) *aimag(eps(ie))
1022 safe_deallocate_a(sigmap)
1023 safe_deallocate_a(eps)
1034 real(real64),
allocatable,
intent(inout) :: sigma(:, :, :)
1035 integer,
intent(in) :: nspin
1036 integer,
intent(in) :: no_e
1040 complex(real64),
allocatable :: eps(:)
1044 safe_allocate(eps(1:no_e))
1049 call pcm_eps(pcm, eps(ie), (ie-1)*spectrum%energy_step + spectrum%min_energy)
1050 sigma(ie, 1:3, 1:nspin) = sigma(ie, 1:3, 1:nspin) /
sqrt(0.5_real64 * (abs(eps(ie)) + real(eps(ie), real64)))
1053 safe_deallocate_a(eps)
1063 integer,
intent(in) :: in_file
1064 integer,
intent(in) :: out_file
1066 character(len=20) :: header_string
1067 integer :: nspin, lmax, time_steps, istart, iend, ntiter, it, ii, isp, no_e, ie, idir
1069 real(real64),
allocatable :: dipole(:, :, :), transform_cos(:, :, :), transform_sin(:, :, :), power(:, :, :)
1071 type(
batch_t) :: dipoleb, transformb_cos, transformb_sin
1078 call spectrum_mult_info(namespace, in_file, nspin, kick, time_steps, dt, file_units, lmax=lmax)
1082 message(1) =
'Multipoles file should contain the dipole -- and only the dipole.'
1089 safe_allocate(dipole(0:time_steps, 1:3, 1:nspin))
1093 do it = 1, time_steps
1094 dipole(it, :, :) = dipole(it, :, :) - dipole(0, :, :)
1098 if (spectrum%energy_step <=
m_zero) spectrum%energy_step =
m_two *
m_pi / (dt*time_steps)
1102 safe_allocate(transform_cos(1:no_e, 1:3, 1:nspin))
1103 safe_allocate(transform_sin(1:no_e, 1:3, 1:nspin))
1104 safe_allocate(power(1:no_e, 1:3, 1:nspin))
1107 call batch_init(dipoleb, 3, 1, nspin, dipole)
1108 call batch_init(transformb_cos, 3, 1, nspin, transform_cos)
1109 call batch_init(transformb_sin, 3, 1, nspin, transform_sin)
1111 call spectrum_signal_damp(spectrum%damp, spectrum%damp_factor, istart + 1, iend + 1, spectrum%start_time, dt, dipoleb)
1114 istart + 1, iend + 1, spectrum%start_time, dt, dipoleb, spectrum%min_energy, &
1115 spectrum%max_energy, spectrum%energy_step, transformb_cos)
1117 istart + 1, iend + 1, spectrum%start_time, dt, dipoleb, spectrum%min_energy, &
1118 spectrum%max_energy, spectrum%energy_step, transformb_sin)
1121 power(ie, :, :) = (transform_sin(ie, :, :)**2 + transform_cos(ie, :, :)**2)
1125 call transformb_cos%end()
1126 call transformb_sin%end()
1128 safe_deallocate_a(dipole)
1129 safe_deallocate_a(transform_sin)
1130 safe_deallocate_a(transform_cos)
1132 write(out_file,
'(a15,i2)')
'# nspin ', nspin
1133 write(out_file,
'(a)')
'#%'
1134 write(out_file,
'(a,i8)')
'# Number of time steps = ', time_steps
1136 write(out_file,
'(a)')
'#%'
1138 write(out_file,
'(a1,a20,1x)', advance =
'no')
'#',
str_center(
"Energy", 20)
1141 write(header_string,
'(a6,i1,a8,i1,a1)')
'power(', idir,
', nspin=', isp,
')'
1142 write(out_file,
'(a20)', advance =
'no')
str_center(trim(header_string), 20)
1145 write(out_file,
'(1x)')
1147 do ii = 1, nspin * 3
1150 write(out_file,
'(1x)')
1154 (ie-1) * spectrum%energy_step + spectrum%min_energy)
1159 write(out_file,
'(1x)')
1162 safe_deallocate_a(power)
1171 integer,
intent(in) :: in_file_sin, in_file_cos
1172 integer,
intent(in) :: out_file
1174 character(len=20) :: header_string
1175 integer :: time_steps, time_steps_sin, time_steps_cos
1176 integer :: istart, iend, ntiter, it, jj, ii, no_e, ie, trash
1177 real(real64) :: dt, dt_sin, dt_cos
1178 real(real64) :: dump, dummy1, dummy2, dummy3, dummy4, energy, fsum
1180 complex(real64) :: xx
1181 complex(real64),
allocatable :: ftchd(:), chi(:), damp(:)
1183 character(len=100) :: line
1192 read(in_file_sin, *)
1193 read(in_file_sin, *)
1194 read(in_file_sin,
'(15x,i2)') kick%qkick_mode
1195 read(in_file_sin,
'(10x,3f9.5)') kick%qvector
1196 read(in_file_sin,
'(15x,f18.12)') kick%delta_strength
1199 read(in_file_sin, *)
1200 read(in_file_sin,
'(a)') line
1205 ii = index(line,
'eV')
1216 if (.not.
is_close(dt_sin, dt_cos))
then
1217 message(1) =
"dt is different in ftchds.cos and ftchds.sin!"
1221 time_steps = min(time_steps_sin, time_steps_cos)
1231 safe_allocate(ftchd(0:time_steps))
1232 do it = 0, time_steps
1233 read(in_file_sin, *) trash, dump, dummy1, dummy2
1234 read(in_file_cos, *) trash, dump, dummy3, dummy4
1235 ftchd(it) = cmplx(dummy3-dummy2, dummy4+dummy1, real64)
1239 do it = 1, time_steps
1240 ftchd(it) = ftchd(it) - ftchd(0)
1244 if (spectrum%energy_step <=
m_zero) spectrum%energy_step =
m_two *
m_pi / (dt*time_steps)
1249 safe_allocate(chi(1:no_e))
1253 safe_allocate(damp(istart:iend))
1254 do it = istart, iend
1256 select case (spectrum%damp)
1257 case (spectrum_damp_none)
1260 damp(it)=
exp(-jj * dt * spectrum%damp_factor)
1262 damp(it) =
m_one -
m_three * (real(jj, real64) / ntiter)**2 &
1263 +
m_two * (real(jj, real64) / ntiter)**3
1265 damp(it)=
exp(-(jj * dt)**2 * spectrum%damp_factor**2)
1270 if (abs(kick%delta_strength) < 1.d-12) kick%delta_strength =
m_one
1272 energy = (ie-1) * spectrum%energy_step + spectrum%min_energy
1273 do it = istart, iend
1276 xx =
exp(
m_zi * energy * jj * dt)
1277 chi(ie) = chi(ie) + xx * damp(it) * ftchd(it)
1280 chi(ie) = chi(ie) * dt / kick%delta_strength /
m_pi
1286 energy = (ie-1) * spectrum%energy_step + spectrum%min_energy
1287 fsum = fsum + energy * aimag(chi(ie))
1289 fsum = spectrum%energy_step * fsum * 2/sum(kick%qvector(:,1)**2)
1291 write(out_file,
'(a)')
'#%'
1292 write(out_file,
'(a,i8)')
'# Number of time steps = ', time_steps
1294 write(out_file,
'(a,3f9.5)')
'# qvector : ', kick%qvector
1295 write(out_file,
'(a,f10.4)')
'# F-sum rule : ', fsum
1296 write(out_file,
'(a)')
'#%'
1298 write(out_file,
'(a1,a20)', advance =
'no')
'#',
str_center(
"Energy", 20)
1299 write(header_string,
'(a3)')
'chi'
1300 write(out_file,
'(a20)', advance =
'no')
str_center(trim(header_string), 20)
1301 write(out_file,
'(1x)')
1304 write(out_file,
'(1x)')
1308 (ie-1) * spectrum%energy_step + spectrum%min_energy)
1310 write(out_file,
'(1x)')
1313 safe_deallocate_a(ftchd)
1314 safe_deallocate_a(chi)
1324 integer,
intent(in) :: in_file
1325 integer,
intent(in) :: out_file
1327 integer :: istart, iend, ntiter, ie, idir, time_steps, no_e, nspin, trash, it
1328 real(real64) :: dump, dt, energy
1330 complex(real64) :: sum1, sum2, sp
1331 real(real64),
allocatable :: angular(:, :), resp(:), imsp(:)
1332 type(
batch_t) :: angularb, respb, imspb
1340 if (kick%dim /= 3)
then
1341 message(1) =
"Rotatory strength can only be computed for 3D systems."
1346 safe_allocate(angular(0:time_steps, 1:3))
1348 do ie = 0, time_steps
1349 read(in_file, *) trash, dump, (angular(ie, idir), idir = 1, 3)
1354 angular(:, idir) = angular(:, idir) - angular(0, idir)
1357 if (spectrum%energy_step <=
m_zero) spectrum%energy_step =
m_two *
m_pi / (dt*time_steps)
1361 do it = istart, iend
1362 angular(it, 1) = sum(angular(it, 1:3)*kick%pol(1:3, kick%pol_dir))
1365 safe_allocate(resp(1:no_e))
1366 safe_allocate(imsp(1:no_e))
1372 call spectrum_signal_damp(spectrum%damp, spectrum%damp_factor, istart + 1, iend + 1, kick%time, dt, angularb)
1375 istart + 1, iend + 1, kick%time, dt, angularb, spectrum%min_energy, spectrum%max_energy, spectrum%energy_step, respb)
1377 istart + 1, iend + 1, kick%time, dt, angularb, spectrum%min_energy, spectrum%max_energy, spectrum%energy_step, imspb)
1385 if (abs(kick%delta_strength) < 1.d-12) kick%delta_strength =
m_one
1387 energy = (ie-1) * spectrum%energy_step + spectrum%min_energy
1389 sp = cmplx(resp(ie), imsp(ie), real64)
1393 sum1 = sum1 + spectrum%energy_step*sp
1394 sum2 = sum2 + spectrum%energy_step*sp*energy**2
1396 resp(ie) = real(sp, real64)
1397 imsp(ie) = aimag(sp)
1400 safe_deallocate_a(angular)
1403 write(
message(1),
'(a,i8)')
'Number of time steps = ', ntiter
1404 write(
message(2),
'(a,i4)')
'PropagationSpectrumDampMode = ', spectrum%damp
1411 write(
message(9),
'(a,5e15.6,5e15.6)')
'R(0) sum rule = ', sum1
1412 write(
message(10),
'(a,5e15.6,5e15.6)')
'R(2) sum rule = ', sum2
1417 write(out_file,
'(a15,i2)')
'# nspin ', nspin
1419 write(out_file,
'(a1,a20,a20,a20)')
'#',
str_center(
"Energy", 20),
str_center(
"R", 20),
str_center(
"Re[beta]", 20)
1423 write(out_file,
'(a,5e15.6,5e15.6)')
'# R(0) sum rule = ', sum1
1424 write(out_file,
'(a,5e15.6,5e15.6)')
'# R(2) sum rule = ', sum2
1426 write(out_file,
'(e20.8,e20.8,e20.8)')
units_from_atomic(
units_out%energy, (ie-1)*spectrum%energy_step+spectrum%min_energy), &
1431 safe_deallocate_a(resp)
1432 safe_deallocate_a(imsp)
1441 real(real64),
intent(in) :: dt
1442 integer,
intent(in) :: is, ie, niter
1443 complex(real64),
intent(in) :: acc(:)
1445 integer :: nn(3), j, optimize_parity(3)
1454 energy_step_ = (
m_two *
m_pi) / (niter * time_step_)
1455 safe_allocate(func_(0:niter))
1456 safe_allocate(funcw_(0:niter))
1459 nn(1:3) = (/ niter, 1, 1 /)
1461 optimize_parity(1:3) = -1
1464 call zfft_forward(fft_handler, func_(0:niter-1), funcw_(0:niter-1))
1466 funcw_(j) = -abs(funcw_(j))**2 * dt**2
1481 safe_deallocate_a(func_)
1482 safe_deallocate_a(funcw_)
1491 real(real64),
intent(in) :: aa, bb
1492 real(real64),
intent(out) :: omega_min, func_min
1495 real(real64) :: xx, hsval, minhsval, ww, xa, xb, hxa, hxb
1506 ie = int(aa/energy_step_)
1507 ww = ie * energy_step_
1510 ww = ie * energy_step_
1512 xx = ie * energy_step_
1513 minhsval = real(funcw_(ie), real64)
1515 hsval = real(funcw_(ie), real64)
1516 if (hsval < minhsval)
then
1521 ww = ie * energy_step_
1526 xa = max(xx-energy_step_, aa)
1527 xb = min(xx+energy_step_, bb)
1531 if (hxa <= minhsval)
then
1534 elseif (hxb <= minhsval)
then
1542 write(
message(1),
'(a,f14.6,a)')
'spectrum_hsfunction_min: The maximum at', xx,
' was not properly converged.'
1543 write(
message(2),
'(a,i12)')
'Error code: ', ierr
1557 real(real64),
intent(in) :: omega
1558 real(real64),
intent(out) :: power
1560 complex(real64) :: cc, ez1, ez, zz
1566 zz =
m_zi * omega * time_step_
1567 ez1 =
exp((is_ - 1) * zz)
1571 cc = cc + ez1 * func_(jj)
1573 power = -abs(cc)**2 * time_step_**2
1575 if (
allocated(func_ar_))
then
1578 ez1 =
exp((is_ - 1) * zz)
1584 cc = cc + ez1 * func_ar_(dir,jj) &
1585 *
exp(-
m_zi * omega * tret_(jj))
1587 power = power - abs(cc)**2 * time_step_**2
1601 real(real64),
intent(in) :: dt
1602 integer,
intent(in) :: is, ie, niter
1603 complex(real64),
intent(in) :: acc(:,:),pos(:,:),tret(:)
1610 safe_allocate(func_ar_(1:3, 0:niter))
1611 safe_allocate(pos_(1:3, 0:niter))
1612 safe_allocate(tret_(0:niter))
1629 safe_deallocate_a(func_ar_)
1630 safe_deallocate_a(pos_)
1631 safe_deallocate_a(tret_)
1641 character(len=*),
intent(in) :: out_file
1642 real(real64),
intent(in) :: vec(:)
1643 real(real64),
optional,
intent(in) :: w0
1645 integer :: istep, trash, iunit, nspin, time_steps, istart, iend, ntiter, lmax, ierr, jj
1646 real(real64) :: dt, dump, aa(3)
1647 complex(real64) :: nn(3)
1649 real(real64),
allocatable :: dd(:,:)
1650 complex(real64),
allocatable :: acc(:,:),PP(:,:),pos(:,:),tret(:)
1651 real(real64) :: vv(3)
1660 safe_allocate(acc(1:3, 0:time_steps))
1661 safe_allocate(pp(1:3, 0:time_steps))
1662 safe_allocate(pos(1:3, 0:time_steps))
1663 safe_allocate(tret(0:time_steps))
1672 do istep = 0, time_steps-1
1674 read(iunit,
'(28x,e20.12)', advance =
'no', iostat = ierr) aa(1)
1676 do while((ierr == 0) .and. (jj <= 3))
1677 read(iunit,
'(e20.12)', advance =
'no', iostat = ierr) aa(jj)
1691 iunit =
io_open(
'multipoles', namespace, action=
'read', status=
'old', die=.false.)
1692 if (iunit == -1)
then
1693 iunit =
io_open(
'td.general/multipoles', namespace, action=
'read', status=
'old')
1695 call spectrum_mult_info(namespace, iunit, nspin, kick, time_steps, dt, file_units, lmax=lmax)
1701 safe_allocate(dd(1:3, 1:nspin))
1702 do istep = 0, time_steps-1
1703 read(iunit, *) trash, dump, dump, dd
1704 pos(1:3, istep) = -sum(dd(1:3, :),2)
1706 write (*,*) istep, real(pos(:,istep))
1708 safe_deallocate_a(dd)
1719 do istep = 0, time_steps - 1
1720 nn(:) = vv(:)-pos(:,istep)
1721 nn(:) = nn(:)/norm2(abs(nn(:)))
1722 tret(istep) = dot_product(vv(:), real(pos(:,istep), real64))/
p_c
1728 call spectrum_hs(spectrum, namespace, out_file,
'a', w0)
1731 safe_deallocate_a(acc)
1732 safe_deallocate_a(pp)
1733 safe_deallocate_a(pos)
1734 safe_deallocate_a(tret)
1745 character(len=*),
intent(in) :: out_file
1746 real(real64),
intent(in) :: vec(:)
1747 real(real64),
optional,
intent(in) :: w0
1749 integer :: istep, trash, iunit, nspin, time_steps, istart, iend, ntiter, lmax
1750 real(real64) :: dt, dump
1752 real(real64),
allocatable :: dd(:,:)
1753 complex(real64),
allocatable :: dipole(:,:), ddipole(:,:), pp(:,:), tret(:)
1754 complex(real64) :: vv(3)
1760 iunit =
io_open(
'multipoles', namespace, action=
'read', status=
'old', die=.false.)
1761 if (iunit == -1)
then
1762 iunit =
io_open(
'td.general/multipoles', namespace, action=
'read', status=
'old')
1764 call spectrum_mult_info(namespace, iunit, nspin, kick, time_steps, dt, file_units, lmax=lmax)
1770 safe_allocate(dipole(1:3, 0:time_steps))
1771 safe_allocate(ddipole(1:3, 0:time_steps))
1772 safe_allocate(pp(1:3, 0:time_steps))
1773 safe_allocate(tret(0:time_steps))
1774 safe_allocate(dd(1:3, 1:nspin))
1778 do istep = 1, time_steps
1779 read(iunit, *) trash, dump, dump, dd
1780 dipole(1:3, istep) = -sum(dd(1:3, :),2)
1783 safe_deallocate_a(dd)
1784 dipole(:,0) = dipole(:,1)
1789 do istep = 1, time_steps - 1
1790 ddipole(:,istep) = (dipole(:,istep - 1) + dipole(:,istep + 1) -
m_two * dipole(:,istep)) / dt**2
1793 ddipole(1,time_steps - 3:time_steps - 1), &
1795 ddipole(1,time_steps))
1797 ddipole(2,time_steps - 3:time_steps - 1), &
1799 ddipole(2,time_steps))
1801 ddipole(3,time_steps - 3:time_steps - 1), &
1803 ddipole(3,time_steps))
1806 vv(1:3) = vec(1:3) / norm2(vec(1:3))
1809 do istep = 1, time_steps - 1
1811 tret(istep) = dot_product(vv(:), dipole(:,istep))/
p_c
1820 call spectrum_hs(spectrum, namespace, out_file,
'a', w0)
1823 safe_deallocate_a(dipole)
1824 safe_deallocate_a(ddipole)
1825 safe_deallocate_a(pp)
1826 safe_deallocate_a(tret)
1838 character(len=*),
intent(in) :: out_file
1839 character,
intent(in) :: pol
1840 real(real64),
intent(in) :: vec(:)
1841 real(real64),
optional,
intent(in) :: w0
1843 integer :: istep, trash, iunit, nspin, time_steps, istart, iend, ntiter, lmax, no_e, ie, idir, ispin
1844 real(real64) :: dt, dump, vv(3)
1846 real(real64),
allocatable :: dd(:,:)
1847 real(real64),
allocatable :: sps(:), spc(:), racc(:)
1848 complex(real64),
allocatable :: dipole(:), ddipole(:)
1849 type(
batch_t) :: acc_batch, sps_batch, spc_batch
1854 iunit =
io_open(
'multipoles', namespace, action=
'read', status=
'old', die=.false.)
1855 if (iunit == -1)
then
1856 iunit =
io_open(
'td.general/multipoles', namespace, action=
'read', status=
'old')
1858 call spectrum_mult_info(namespace, iunit, nspin, kick, time_steps, dt, file_units, lmax=lmax)
1861 if (spectrum%energy_step <=
m_zero) spectrum%energy_step =
m_two *
m_pi / (dt*time_steps)
1866 safe_allocate(dipole(0:time_steps))
1867 safe_allocate(ddipole(0:time_steps))
1868 safe_allocate(dd(1:3, 1:nspin))
1870 vv(1:3) = vec(1:3) / norm2(vec(1:3))
1872 do istep = 1, time_steps
1874 read(iunit, *) trash, dump, (dump, (dd(idir, ispin), idir = 1, kick%dim), ispin = 1, nspin)
1877 dipole(istep) = -sum(dd(1, :))
1879 dipole(istep) = -sum(dd(2, :))
1881 dipole(istep) = sum(dd(3, :))
1883 dipole(istep) = -sum(cmplx(dd(1, :), dd(2, :), real64)) /
sqrt(
m_two)
1885 dipole(istep) = -sum(cmplx(dd(1, :), -dd(2, :), real64)) /
sqrt(
m_two)
1887 dipole(istep) = -sum(vv(1)*dd(1, :) + vv(2)*dd(2, :) + vv(3)*dd(3, :))
1891 safe_deallocate_a(dd)
1892 dipole(0) = dipole(1)
1897 do istep = 1, time_steps - 1
1898 ddipole(istep) = (dipole(istep - 1) + dipole(istep + 1) -
m_two * dipole(istep)) / dt**2
1901 ddipole(time_steps - 3:time_steps - 1), &
1903 ddipole(time_steps))
1905 if (
present(w0))
then
1908 call spectrum_hs(spectrum, namespace, out_file, pol, w0)
1913 safe_allocate(racc(0:time_steps))
1914 racc = real(ddipole, real64)
1917 safe_allocate(sps(1:no_e))
1918 safe_allocate(spc(1:no_e))
1927 istart + 1, iend + 1,
m_zero, dt, acc_batch, spectrum%min_energy, spectrum%max_energy, spectrum%energy_step, spc_batch)
1929 istart + 1, iend + 1,
m_zero, dt, acc_batch, spectrum%min_energy, spectrum%max_energy, spectrum%energy_step, sps_batch)
1932 sps(ie) = (sps(ie)**2 + spc(ie)**2)
1937 call acc_batch%end()
1938 call sps_batch%end()
1939 call spc_batch%end()
1941 safe_deallocate_a(racc)
1945 safe_deallocate_a(dipole)
1946 safe_deallocate_a(ddipole)
1957 character(len=*),
intent(in) :: out_file
1958 character,
intent(in) :: pol
1959 real(real64),
intent(in) :: vec(:)
1960 real(real64),
optional,
intent(in) :: w0
1962 integer :: istep, jj, iunit, time_steps, istart, iend, ntiter, ierr, no_e, ie
1963 real(real64) :: dt, aa(3), vv(3)
1964 complex(real64),
allocatable :: acc(:)
1965 real(real64),
allocatable :: racc(:), sps(:), spc(:)
1966 type(
batch_t) :: acc_batch, sps_batch, spc_batch
1973 if (spectrum%energy_step <=
m_zero) spectrum%energy_step =
m_two *
m_pi / (dt*time_steps)
1976 safe_allocate(acc(0:time_steps))
1978 vv = vec / norm2(vec(:))
1981 do istep = 1, time_steps
1983 read(iunit,
'(28x,e20.12)', advance =
'no', iostat = ierr) aa(1)
1985 do while((ierr == 0) .and. (jj <= 3))
1986 read(iunit,
'(e20.12)', advance =
'no', iostat = ierr) aa(jj)
1997 acc(istep) = cmplx(aa(1), aa(2), real64) /
sqrt(
m_two)
1999 acc(istep) = cmplx(aa(1), -aa(2), real64) /
sqrt(
m_two)
2001 acc(istep) = vv(1)*aa(1) + vv(2)*aa(2) + vv(3)*aa(3)
2007 if (
present(w0))
then
2010 call spectrum_hs(spectrum, namespace, out_file, pol, w0)
2015 safe_allocate(racc(0:time_steps))
2016 racc = real(acc, real64)
2019 safe_allocate(sps(1:no_e))
2020 safe_allocate(spc(1:no_e))
2029 istart + 1, iend + 1,
m_zero, dt, acc_batch, spectrum%min_energy, &
2030 spectrum%max_energy, spectrum%energy_step, spc_batch)
2032 istart + 1, iend + 1,
m_zero, dt, acc_batch, spectrum%min_energy, &
2033 spectrum%max_energy, spectrum%energy_step, sps_batch)
2036 sps(ie) = (sps(ie)**2 + spc(ie)**2)
2041 call acc_batch%end()
2042 call sps_batch%end()
2043 call spc_batch%end()
2045 safe_deallocate_a(racc)
2049 safe_deallocate_a(acc)
2058 character(len=*),
intent(in) :: out_file
2059 character,
intent(in) :: pol
2060 real(real64),
intent(in) :: vec(:)
2061 real(real64),
optional,
intent(in) :: w0
2063 integer :: istep, jj, iunit, time_steps, istart, iend, ntiter, ierr, no_e, ie
2064 real(real64) :: dt, cc(3), vv(3)
2065 complex(real64),
allocatable :: cur(:)
2066 real(real64),
allocatable :: rcur(:), sps(:), spc(:)
2067 type(
batch_t) :: cur_batch, sps_batch, spc_batch
2074 if (spectrum%energy_step <=
m_zero) spectrum%energy_step =
m_two *
m_pi / (dt * time_steps)
2077 safe_allocate(cur(0:time_steps))
2079 vv = vec / norm2(vec(:))
2082 do istep = 1, time_steps
2084 read(iunit,
'(28x,e20.12)', advance =
'no', iostat = ierr) cc(1)
2086 do while((ierr == 0) .and. (jj <= 3))
2087 read(iunit,
'(e20.12)', advance =
'no', iostat = ierr) cc(jj)
2098 cur(istep) = cmplx(cc(1), cc(2), real64) /
sqrt(
m_two)
2100 cur(istep) = cmplx(cc(1), -cc(2), real64) /
sqrt(
m_two)
2102 cur(istep) = vv(1)*cc(1) + vv(2)*cc(2) + vv(3)*cc(3)
2108 if (
present(w0))
then
2111 call spectrum_hs(spectrum, namespace, out_file, pol, w0)
2116 safe_allocate(rcur(0:time_steps))
2117 rcur = real(cur, real64)
2120 safe_allocate(sps(1:no_e))
2121 safe_allocate(spc(1:no_e))
2130 istart + 1, iend + 1,
m_zero, dt, cur_batch, spectrum%min_energy, spectrum%max_energy, spectrum%energy_step, spc_batch)
2132 istart + 1, iend + 1,
m_zero, dt, cur_batch, spectrum%min_energy, spectrum%max_energy, spectrum%energy_step, sps_batch)
2135 sps(ie) = (sps(ie)**2 + spc(ie)**2) * ((ie-1) * spectrum%energy_step + spectrum%min_energy)**2
2140 call cur_batch%end()
2141 call sps_batch%end()
2142 call spc_batch%end()
2144 safe_deallocate_a(rcur)
2148 safe_deallocate_a(cur)
2154 subroutine spectrum_hs(spectrum, namespace, out_file, pol, w0)
2157 character(len=*),
intent(in) :: out_file
2158 character,
intent(in) :: pol
2159 real(real64),
optional,
intent(in) :: w0
2161 integer :: iunit, no_e, ie
2162 real(real64) :: omega, hsval, xx
2163 real(real64),
allocatable :: sp(:)
2167 if (
present(w0))
then
2169 iunit =
io_open(trim(out_file) //
"." // trim(pol), namespace, action=
'write')
2171 write(iunit,
'(a1,a20,a20)')
'#', &
2178 do while(omega <= spectrum%max_energy)
2185 omega = omega + 2 * w0
2191 safe_allocate(sp(1:no_e))
2195 call hsfunction((ie-1) * spectrum%energy_step + spectrum%min_energy, sp(ie))
2201 safe_deallocate_a(sp)
2213 character(len=*),
intent(in) :: out_file
2214 character,
intent(in) :: pol
2215 integer,
intent(in) :: no_e
2216 real(real64),
intent(in) :: sp(:)
2218 integer :: iunit, ie
2223 if (trim(out_file) /=
'-')
then
2224 iunit =
io_open(trim(out_file) //
"." // trim(pol), namespace, action=
'write')
2227 write(iunit,
'(a1,a20,a20)') &
2245 subroutine spectrum_mult_info(namespace, iunit, nspin, kick, time_steps, dt, file_units, lmax)
2247 integer,
intent(in) :: iunit
2248 integer,
intent(out) :: nspin
2249 type(
kick_t),
intent(out) :: kick
2250 integer,
intent(out) :: time_steps
2251 real(real64),
intent(out) :: dt
2253 integer,
optional,
intent(out) :: lmax
2256 character(len=100) :: line
2265 read(iunit,
'(15x,i2)') nspin
2266 if (
present(lmax))
then
2267 read(iunit,
'(15x,i2)') lmax
2270 read(iunit,
'(a)') line
2271 read(iunit,
'(a)') line
2275 ii = index(line,
'eV')
2293 integer,
intent(in) :: iunit
2294 integer,
intent(out) :: time_steps
2295 real(real64),
intent(out) :: dt
2297 real(real64) :: t1, t2, dummy
2300 push_sub(count_time_steps)
2307 read(iunit, *,
end=100) trash, dummy
2308 time_steps = time_steps + 1
2309 if (time_steps == 1) t1 = dummy
2310 if (time_steps == 2) t2 = dummy
2314 time_steps = time_steps - 1
2316 if (time_steps < 3)
then
2321 pop_sub(count_time_steps)
2328 type(namespace_t),
intent(in) :: namespace
2329 integer,
intent(in) :: iunit
2330 integer,
intent(out) :: nspin
2331 type(kick_t),
intent(out) :: kick
2332 integer,
intent(out) :: energy_steps
2333 real(real64),
intent(out) :: dw
2335 real(real64) :: dummy, e1, e2
2340 read(iunit,
'(15x,i2)') nspin
2341 call kick_read(kick, iunit, namespace)
2342 call io_skip_header(iunit)
2347 read(iunit, *,
end=100) dummy
2348 energy_steps = energy_steps + 1
2349 if (energy_steps == 1) e1 = dummy
2350 if (energy_steps == 2) e2 = dummy
2353 dw = units_to_atomic(units_out%energy, e2 - e1)
2355 if (energy_steps < 3)
then
2356 message(1) =
"Empty multipole file?"
2357 call messages_fatal(1, namespace=namespace)
2366 type(namespace_t),
intent(in) :: namespace
2367 character(len=*),
intent(in) :: fname
2368 integer,
intent(out) :: iunit, time_steps
2369 real(real64),
intent(out) :: dt
2372 real(real64) :: t1, t2, dummy
2373 character(len=256) :: filename
2378 filename = trim(
'td.general/')//trim(fname)
2379 iunit = io_open(filename, namespace, action=
'read', status=
'old', die=.false.)
2381 if (iunit == -1)
then
2382 filename = trim(
'./')//trim(fname)
2383 iunit = io_open(filename, namespace, action=
'read', status=
'old')
2388 call io_skip_header(iunit)
2393 read(iunit, *,
end=100) trash, dummy
2394 time_steps = time_steps + 1
2395 if (time_steps == 1) t1 = dummy
2396 if (time_steps == 2) t2 = dummy
2399 dt = units_to_atomic(units_out%time, t2 - t1)
2400 time_steps = time_steps - 1
2402 if (time_steps < 3)
then
2403 message(1) =
"Empty file?"
2404 call messages_fatal(1, namespace=namespace)
2415 integer,
intent(in) :: time_steps
2416 real(real64),
intent(in) :: dt
2417 integer,
intent(out) :: istart, iend, ntiter
2419 real(real64) :: ts, te, dummy
2424 te = time_steps * dt
2426 if (spectrum%start_time < ts) spectrum%start_time = ts
2427 if (spectrum%start_time > te) spectrum%start_time = te
2428 if (spectrum%end_time > te .or. spectrum%end_time <= m_zero) spectrum%end_time = te
2429 if (spectrum%end_time < ts) spectrum%end_time = ts
2431 if (spectrum%end_time < spectrum%start_time)
then
2432 dummy = spectrum%end_time
2433 spectrum%end_time = spectrum%start_time
2434 spectrum%start_time = dummy
2436 istart = nint(spectrum%start_time / dt)
2437 iend = nint(spectrum%end_time / dt)
2438 ntiter = iend - istart + 1
2442 .and. is_close(spectrum%damp_factor, -m_one))
then
2443 select case (spectrum%damp)
2445 spectrum%damp_factor = -
log(0.0001_real64)/(spectrum%end_time-spectrum%start_time)
2447 spectrum%damp_factor =
sqrt(-
log(0.0001_real64)/(spectrum%end_time-spectrum%start_time)**2)
2457 subroutine spectrum_signal_damp(damp_type, damp_factor, time_start, time_end, t0, time_step, time_function)
2458 integer,
intent(in) :: damp_type
2459 real(real64),
intent(in) :: damp_factor
2460 integer,
intent(in) :: time_start
2461 integer,
intent(in) :: time_end
2462 real(real64),
intent(in) :: t0
2463 real(real64),
intent(in) :: time_step
2464 type(batch_t),
intent(inout) :: time_function
2466 integer :: itime, ii
2467 real(real64) :: time
2468 real(real64),
allocatable :: weight(:)
2470 push_sub(signal_damp)
2472 assert(time_function%status() == batch_not_packed)
2474 safe_allocate(weight(time_start:time_end))
2476 do itime = time_start, time_end
2477 time = time_step*(itime-1)
2480 select case (damp_type)
2482 weight(itime) = m_one
2485 weight(itime) = m_one
2487 weight(itime) =
exp(-(time - t0)*damp_factor)
2491 weight(itime) = m_one
2493 weight(itime) = m_one - m_three*((time - t0) / (time_step * (time_end - 1) - t0))**2 + &
2494 m_two * ((time - t0) / (time_step * (time_end - 1) - t0))**3
2498 weight(itime) = m_one
2500 weight(itime) =
exp(-(time - t0)**2*damp_factor**2)
2504 weight(itime) = m_one
2506 weight(itime) =
sin(-(time - t0)*m_pi/(time_end+t0))
2511 if (time_function%type() == type_cmplx)
then
2512 do ii = 1, time_function%nst_linear
2513 do itime = time_start, time_end
2514 time_function%zff_linear(itime, ii) = weight(itime)*time_function%zff_linear(itime, ii)
2518 do ii = 1, time_function%nst_linear
2519 do itime = time_start, time_end
2520 time_function%dff_linear(itime, ii) = weight(itime)*time_function%dff_linear(itime, ii)
2525 safe_deallocate_a(weight)
2527 pop_sub(signal_damp)
2543 energy_start, energy_end, energy_step, energy_function)
2544 integer,
intent(in) :: method
2545 integer,
intent(in) :: transform
2546 real(real64),
intent(in) :: noise
2547 integer,
intent(in) :: time_start
2548 integer,
intent(in) :: time_end
2549 real(real64),
intent(in) :: t0
2550 real(real64),
intent(in) :: time_step
2551 type(batch_t),
intent(in) :: time_function
2552 real(real64),
intent(in) :: energy_start
2553 real(real64),
intent(in) :: energy_end
2554 real(real64),
intent(in) :: energy_step
2555 type(batch_t),
intent(inout) :: energy_function
2557 integer :: itime, ienergy, ii, energy_steps
2558 real(real64) :: energy, sinz, cosz
2559 complex(real64) :: ez, eidt
2560 type(compressed_sensing_t) :: cs
2562 push_sub(fourier_transform)
2564 assert(time_function%nst_linear == energy_function%nst_linear)
2565 assert(time_function%status() == energy_function%status())
2566 assert(time_function%status() == batch_not_packed)
2567 assert(time_function%type() == type_float)
2568 assert(energy_function%type() == type_float)
2570 energy_steps = nint((energy_end-energy_start) / energy_step) + 1
2572 select case (method)
2576 do ienergy = 1, energy_steps
2578 energy = energy_step*(ienergy - 1) + energy_start
2580 do ii = 1, energy_function%nst_linear
2581 energy_function%dff_linear(ienergy, ii) = m_zero
2584 select case (transform)
2591 eidt =
exp(m_zi * energy * time_step)
2592 ez =
exp(m_zi * energy * ((time_start-1)*time_step - t0))
2594 do itime = time_start, time_end
2595 do ii = 1, time_function%nst_linear
2596 energy_function%dff_linear(ienergy, ii) = &
2597 energy_function%dff_linear(ienergy, ii) + &
2598 time_function%dff_linear(itime, ii) * sinz
2606 eidt =
exp(m_zi * energy * time_step)
2607 ez =
exp(m_zi * energy * ( (time_start-1)*time_step - t0))
2608 cosz = real(ez, real64)
2609 do itime = time_start, time_end
2610 do ii = 1, time_function%nst_linear
2611 energy_function%dff_linear(ienergy, ii) = &
2612 energy_function%dff_linear(ienergy, ii) + &
2613 time_function%dff_linear(itime, ii) * cosz
2616 cosz = real(ez, real64)
2621 eidt =
exp(-energy * time_step)
2622 ez =
exp(-energy * ((time_start - 1) * time_step - t0))
2623 do itime = time_start, time_end
2624 do ii = 1, time_function%nst_linear
2625 energy_function%dff_linear(ienergy, ii) = &
2626 energy_function%dff_linear(ienergy, ii) + &
2627 real( time_function%dff_linear(itime, ii) * ez, real64)
2634 do ii = 1, time_function%nst_linear
2635 energy_function%dff_linear(ienergy, ii) = &
2636 energy_function%dff_linear(ienergy, ii) * time_step
2644 call compressed_sensing_init(cs, transform, &
2645 time_end - time_start + 1, time_step, time_step*(time_start - 1) - t0, &
2646 energy_steps, energy_step, energy_start, noise)
2648 do ii = 1, time_function%nst_linear
2649 call compressed_sensing_spectral_analysis(cs, time_function%dff_linear(:, ii), &
2650 energy_function%dff_linear(:, ii))
2653 call compressed_sensing_end(cs)
2657 pop_sub(fourier_transform)
2663 type(namespace_t),
intent(in) :: namespace
2664 real(real64),
intent(in) :: sigma(:, :, :, :)
2665 integer,
intent(in) :: nspin
2666 real(real64),
intent(in) :: energy_step, min_energy
2667 integer,
intent(in) :: energy_steps
2668 type(kick_t),
optional,
intent(in) :: kick
2670 integer :: is, idir, jdir, ie,
info, out_file, out_file_t
2671 real(real64),
allocatable :: work(:,:)
2672 complex(real64),
allocatable :: w(:)
2673 character(len=20) :: header_string
2674 logical :: spins_singlet, spins_triplet, symmetrize
2675 real(real64),
allocatable :: pp(:,:), pp2(:,:)
2691 call parse_variable(namespace,
'PropagationSpectrumSymmetrizeSigma', .false., symmetrize)
2692 call messages_print_var_value(
'PropagationSpectrumSymmetrizeSigma', symmetrize, namespace=namespace)
2694 spins_singlet = .
true.
2695 spins_triplet = .false.
2696 if (
present(kick))
then
2697 select case (kick_get_type(kick))
2698 case (kick_spin_mode)
2699 spins_triplet = .
true.
2700 spins_singlet = .false.
2701 case (kick_spin_density_mode)
2702 spins_triplet = .
true.
2706 if (spins_singlet .and. spins_triplet)
then
2707 out_file = io_open(
'cross_section_diagonal-sigma_s', namespace, action=
'write')
2708 out_file_t = io_open(
'cross_section_diagonal-sigma_t', namespace, action=
'write')
2710 out_file = io_open(
'cross_section_diagonal-sigma', namespace, action=
'write')
2713 write(out_file,
'(a1, a20)', advance =
'no')
'#', str_center(
"Energy", 20)
2715 write(out_file,
'(a20)', advance =
'no') str_center(
"Real part", 20)
2716 if (.not. symmetrize)
write(out_file,
'(a20)', advance =
'no') str_center(
"Imaginary part", 20)
2718 write(header_string,
'(a7,i1,a1,i1,a1,i1,a1)')
'vector(', idir,
',', jdir,
',', is,
')'
2719 write(out_file,
'(a20)', advance =
'no') str_center(trim(header_string), 20)
2722 write(out_file,
'(1x)')
2723 write(out_file,
'(a1,a20)', advance =
'no')
'#', str_center(
'[' // trim(units_abbrev(units_out%energy)) //
']', 20)
2726 write(out_file,
'(a20)', advance =
'no') str_center(
'[' // trim(units_abbrev(units_out%length**2)) //
']', 20)
2727 if (.not. symmetrize)
then
2728 write(out_file,
'(a20)', advance =
'no') str_center(
'[' // trim(units_abbrev(units_out%length**2)) //
']', 20)
2731 write(out_file,
'(a20)', advance =
'no') str_center(
'[ - ]', 20)
2734 write(out_file,
'(1x)')
2736 if (spins_singlet .and. spins_triplet)
then
2737 write(out_file_t,
'(a1, a20)', advance =
'no')
'#', str_center(
"Energy", 20)
2739 write(out_file_t,
'(a20)', advance =
'no') str_center(
"Real part", 20)
2740 if (.not. symmetrize)
write(out_file_t,
'(a20)', advance =
'no') str_center(
"Imaginary part", 20)
2742 write(header_string,
'(a7,i1,a1,i1,a1,i1,a1)')
'vector(', idir,
',', jdir,
',', is,
')'
2743 write(out_file_t,
'(a20)', advance =
'no') str_center(trim(header_string), 20)
2746 write(out_file_t,
'(1x)')
2747 write(out_file_t,
'(a1,a20)', advance =
'no')
'#', str_center(
'[' // trim(units_abbrev(units_out%energy)) //
']', 20)
2750 write(out_file_t,
'(a20)', advance =
'no') str_center(
'[' // trim(units_abbrev(units_out%length**2)) //
']', 20)
2751 if (.not. symmetrize)
then
2752 write(out_file_t,
'(a20)', advance =
'no') str_center(
'[' // trim(units_abbrev(units_out%length**2)) //
']', 20)
2755 write(out_file_t,
'(a20)', advance =
'no') str_center(
'[ - ]', 20)
2758 write(out_file_t,
'(1x)')
2761 safe_allocate(pp(1:3, 1:3))
2762 if (spins_triplet .and. spins_singlet)
then
2763 safe_allocate(pp2(1:3, 1:3))
2765 safe_allocate(w(1:3))
2766 safe_allocate(work(1:3, 1:3))
2767 do ie = 1, energy_steps
2769 pp(:, :) = sigma(:, :, ie, 1)
2770 if (nspin >= 2)
then
2771 if (spins_singlet .and. spins_triplet)
then
2772 pp2(:, :) = pp(:, :) - sigma(:, :, ie, 2)
2773 pp(:, :) = pp(:, :) + sigma(:, :, ie, 2)
2774 elseif (spins_triplet .and. .not. spins_singlet)
then
2775 pp(:, :) = pp(:, :) - sigma(:, :, ie, 2)
2776 elseif (spins_singlet .and. .not. spins_triplet)
then
2777 pp(:, :) = pp(:, :) + sigma(:, :, ie, 2)
2781 if (symmetrize)
then
2783 do jdir = idir + 1, 3
2784 pp(idir, jdir) = (pp(idir, jdir) + pp(jdir, idir)) / m_two
2785 pp(jdir, idir) = pp(idir, jdir)
2790 work(1:3, 1:3) = pp(1:3, 1:3)
2791 call lalg_eigensolve_nonh(3, work, w, err_code =
info, sort_eigenvectors = .
true.)
2795 write(out_file,
'(e20.8)', advance =
'no') units_from_atomic(units_out%energy, ((ie-1) * energy_step + min_energy))
2797 if (symmetrize)
then
2798 write(out_file,
'(2e20.8)', advance =
'no') real(w(idir), real64)
2800 write(out_file,
'(2e20.8)', advance =
'no') w(idir)
2804 write(out_file,
'(e20.8)', advance =
'no') work(jdir, idir)
2807 write(out_file,
'(1x)')
2809 if (spins_singlet .and. spins_triplet)
then
2810 if (symmetrize)
then
2812 do jdir = idir + 1, 3
2813 pp2(idir, jdir) = (pp2(idir, jdir) + pp2(jdir, idir)) / m_two
2814 pp2(jdir, idir) = pp2(idir, jdir)
2818 work(1:3, 1:3) = -pp2(1:3, 1:3)
2819 call lalg_eigensolve_nonh(3, work, w, err_code =
info, sort_eigenvectors = .
true.)
2823 write(out_file_t,
'(e20.8)', advance =
'no') units_from_atomic(units_out%energy, (ie * energy_step + min_energy))
2825 if (symmetrize)
then
2826 write(out_file_t,
'(2e20.8)', advance =
'no') real(w(idir), real64)
2828 write(out_file_t,
'(2e20.8)', advance =
'no') w(idir)
2832 write(out_file_t,
'(e20.8)', advance =
'no') work(jdir, idir)
2835 write(out_file_t,
'(1x)')
2839 call io_close(out_file)
2841 safe_deallocate_a(pp)
2842 if (spins_triplet .and. spins_singlet)
then
2843 safe_deallocate_a(pp2)
2844 call io_close(out_file_t)
2846 safe_deallocate_a(w)
2847 safe_deallocate_a(work)
2855 no_e = nint((spectrum%max_energy-spectrum%min_energy) / spectrum%energy_step) + 1
2860 integer,
intent(in) :: out_file
2864 write(out_file,
'(a,i4)')
'# PropagationSpectrumDampMode = ', spectrum%damp
2865 write(out_file,
'(a,f10.4)')
'# PropagationSpectrumDampFactor = ', units_from_atomic(units_out%time**(-1), &
2866 spectrum%damp_factor)
2867 write(out_file,
'(a,f10.4)')
'# PropagationSpectrumStartTime = ', units_from_atomic(units_out%time, spectrum%start_time)
2868 write(out_file,
'(a,f10.4)')
'# PropagationSpectrumEndTime = ', units_from_atomic(units_out%time, spectrum%end_time)
2869 write(out_file,
'(a,f10.4)')
'# PropagationSpectrumMinEnergy = ', units_from_atomic(units_out%energy, spectrum%min_energy)
2870 write(out_file,
'(a,f10.4)')
'# PropagationSpectrumMaxEnergy = ', units_from_atomic(units_out%energy, spectrum%max_energy)
2871 write(out_file,
'(a,f10.4)')
'# PropagationSpectrumEnergyStep = ', units_from_atomic(units_out%energy, spectrum%energy_step)
initialize a batch with existing memory
This is the common interface to a simple-minded polynomical interpolation procedure (simple use of th...
Prints out to iunit a message in the form: ["InputVariable" = value] where "InputVariable" is given b...
double log(double __x) __attribute__((__nothrow__
double exp(double __x) __attribute__((__nothrow__
double sin(double __x) __attribute__((__nothrow__
double sqrt(double __x) __attribute__((__nothrow__
This module implements batches of mesh functions.
integer, parameter spectrum_transform_cos
integer, parameter spectrum_transform_sin
Fast Fourier Transform module. This module provides a single interface that works with different FFT ...
subroutine, public fft_init(this, nn, dim, type, library, optimize, optimize_parity, comm, mpi_grp, use_aligned)
subroutine, public fft_end(this)
integer, parameter, public fft_complex
integer, parameter, public fftlib_fftw
real(real64), parameter, public m_two
real(real64), parameter, public m_zero
real(real64), parameter, public m_four
real(real64), parameter, public p_ry
real(real64), parameter, public m_third
real(real64), parameter, public m_pi
some mathematical constants
character(len= *), parameter, public pcm_dir
complex(real64), parameter, public m_z0
complex(real64), parameter, public m_zi
real(real64), parameter, public p_c
Electron gyromagnetic ratio, see Phys. Rev. Lett. 130, 071801 (2023)
real(real64), parameter, public m_one
real(real64), parameter, public m_three
subroutine, public io_close(iunit, grp)
subroutine, public io_skip_header(iunit)
integer function, public io_open(file, namespace, action, status, form, position, die, recl, grp)
subroutine, public kick_read(kick, iunit, namespace)
integer, parameter, public kick_spin_mode
pure integer function, public kick_get_type(kick)
subroutine, public kick_write(kick, iunit, out)
integer, parameter, public kick_density_mode
integer, parameter, public kick_function_dipole
integer, parameter, public kick_spin_density_mode
This module is intended to contain "only mathematical" functions and procedures.
pure complex(real64) function, dimension(1:3), public zcross_product(a, b)
subroutine, public messages_print_with_emphasis(msg, iunit, namespace)
character(len=512), private msg
subroutine, public messages_warning(no_lines, 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)
subroutine, public messages_experimental(name, namespace)
subroutine, public messages_info(no_lines, iunit, debug_only, stress, all_nodes, namespace)
real(real64), dimension(:,:), allocatable sigma
S_E matrix.
subroutine, public pcm_dipole(mu_pcm, q_pcm, tess, n_tess)
Computes the dipole moment mu_pcm due to a distribution of charges q_pcm.
subroutine, public pcm_eps(pcm, eps, omega)
subroutine, public pcm_min_input_parsing_for_spectrum(pcm, namespace)
subroutine, public spectrum_hsfunction_min(namespace, aa, bb, omega_min, func_min)
subroutine spectrum_tdfile_info(namespace, fname, iunit, time_steps, dt)
subroutine spectrum_hsfunction_ar_end
subroutine spectrum_hsfunction_ar_init(dt, is, ie, niter, acc, pos, tret)
subroutine, public spectrum_cross_section(spectrum, namespace, in_file, out_file, ref_file)
subroutine spectrum_times_pcm_epsilon(spectrum, pcm, dipole, sigma, nspin, istart, iend, kick_time, dt, no_e)
subroutine, public spectrum_hs_ar_from_acc(spectrum, namespace, out_file, vec, w0)
integer, parameter, public spectrum_damp_lorentzian
subroutine, public spectrum_fix_time_limits(spectrum, time_steps, dt, istart, iend, ntiter)
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...
integer, parameter, public spectrum_transform_laplace
subroutine, public spectrum_cross_section_tensor(spectrum, namespace, out_file, in_file)
subroutine, public spectrum_hsfunction_init(dt, is, ie, niter, acc)
subroutine, public spectrum_hsfunction_end
subroutine spectrum_read_dipole(namespace, in_file, dipole)
integer, parameter, public spectrum_damp_sin
subroutine spectrum_sigma_diagonalize(namespace, sigma, nspin, energy_step, min_energy, energy_steps, kick)
subroutine spectrum_cross_section_info(namespace, iunit, nspin, kick, energy_steps, dw)
subroutine, public spectrum_dyn_structure_factor(spectrum, namespace, in_file_sin, in_file_cos, out_file)
integer, parameter, public spectrum_damp_gaussian
subroutine, public spectrum_init(spectrum, namespace, default_energy_step, default_max_energy)
subroutine, public spectrum_mult_info(namespace, iunit, nspin, kick, time_steps, dt, file_units, lmax)
integer, parameter, public spectrum_fourier
subroutine, public spectrum_dipole_power(spectrum, namespace, in_file, out_file)
subroutine spectrum_add_pcm_dipole(namespace, dipole, time_steps, nspin)
subroutine, public spectrum_signal_damp(damp_type, damp_factor, time_start, time_end, t0, time_step, time_function)
subroutine, public spectrum_hs_from_acc(spectrum, namespace, out_file, pol, vec, w0)
integer, parameter, public spectrum_energyloss
subroutine spectrum_over_pcm_refraction_index(spectrum, pcm, sigma, nspin, no_e)
subroutine, public spectrum_hs_from_current(spectrum, namespace, out_file, pol, vec, w0)
subroutine spectrum_cross_section_tensor_write(out_file, sigma, nspin, energy_step, min_energy, energy_steps, kick)
subroutine spectrum_write_info(spectrum, out_file)
subroutine spectrum_hs_output(spectrum, namespace, out_file, pol, no_e, sp)
integer, parameter, public spectrum_damp_polynomial
subroutine hsfunction(omega, power)
integer, parameter, public spectrum_rotatory
subroutine spectrum_hs(spectrum, namespace, out_file, pol, w0)
integer, parameter, public spectrum_damp_none
integer, parameter, public spectrum_transform_cos
integer, parameter, public spectrum_transform_sin
subroutine, public spectrum_count_time_steps(namespace, iunit, time_steps, dt)
subroutine, public spectrum_rotatory_strength(spectrum, namespace, in_file, out_file)
pure integer function, public spectrum_nenergy_steps(spectrum)
subroutine, public spectrum_hs_from_mult(spectrum, namespace, out_file, pol, vec, w0)
integer, parameter, public spectrum_compressed_sensing
subroutine, public spectrum_hs_ar_from_mult(spectrum, namespace, out_file, vec, w0)
integer, parameter, public spectrum_p_power
character(len=80) function, public str_center(s_in, l_in)
puts space around string, so that it is centered
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
character(len=20) pure function, public units_abbrev(this)
This module defines the unit system, used for input and output.
integer, parameter, public units_atomic
type(unit_system_t), public units_out
subroutine, public unit_system_get(uu, cc)
integer, parameter, public units_eva
type(unit_system_t), public units_inp
the units systems for reading and writing
type(unit_t), public unit_one
some special units required for particular quantities
Class defining batches of mesh functions.