28 use,
intrinsic :: iso_fortran_env
65 integer,
public,
parameter :: &
66 KICK_FUNCTION_DIPOLE = 0, &
70 integer,
public,
parameter :: &
71 KICK_DENSITY_MODE = 0, &
76 integer,
public,
parameter :: &
92 integer,
private :: delta_strength_mode
93 real(real64) :: delta_strength
95 real(real64),
allocatable :: pol(:,:)
97 integer :: pol_equiv_axes
98 real(real64),
allocatable :: wprime(:)
99 real(real64) :: easy_axis(3)
111 integer :: n_multipoles
112 integer,
allocatable :: l(:), m(:)
113 real(real64),
allocatable :: weight(:)
116 real(real64),
allocatable :: qvector(:,:)
117 real(real64) :: trans_vec(3, 2)
118 real(real64) :: qlength
119 integer :: qkick_mode
120 integer :: qbessel_l, qbessel_m
122 integer :: function_mode
123 character(len=200),
private:: user_defined_function
129 subroutine kick_init(kick, namespace, space, kpoints, nspin)
130 type(kick_t),
intent(inout) :: kick
131 type(namespace_t),
intent(in) :: namespace
132 class(space_t),
intent(in) :: space
133 type(kpoints_t),
intent(in) :: kpoints
134 integer,
intent(in) :: nspin
137 integer :: n_rows, irow, idir, iop, iq, iqx, iqy, iqz
138 real(real64) :: norm, dot
139 real(real64) :: qtemp(space%dim)
140 integer :: periodic_dim
145 periodic_dim = space%periodic_dim
148 safe_allocate(kick%pol(1:space%dim, 1:space%dim))
149 safe_allocate(kick%wprime(1:space%dim))
183 kick%function_mode = kick_function_dipole
186 kick%delta_strength_mode = 0
187 kick%pol_equiv_axes = 0
191 kick%n_multipoles = 0
192 kick%qkick_mode = qkickmode_none
226 call parse_variable(namespace,
'TDDeltaStrengthMode', kick_density_mode, kick%delta_strength_mode)
227 select case (kick%delta_strength_mode)
228 case (kick_density_mode)
232 call messages_input_error(namespace,
'TDDeltaStrengthMode',
'Magnon kick is incompatible with spinors')
241 kick%n_multipoles = 0
253 call parse_variable(namespace,
'TDDeltaUserDefined',
'0', kick%user_defined_function)
270 else if (
parse_block(namespace,
'TDKickFunction', blk) == 0)
then
274 kick%n_multipoles = n_rows
275 safe_allocate( kick%l(1:n_rows))
276 safe_allocate( kick%m(1:n_rows))
277 safe_allocate(kick%weight(1:n_rows))
282 if ((kick%l(irow) < 0) .or. (abs(kick%m(irow)) > abs(kick%l(irow))))
then
289 kick%function_mode = kick_function_dipole
290 kick%n_multipoles = 0
302 call parse_variable(namespace,
'TDPolarizationEquivAxes', 0, kick%pol_equiv_axes)
319 call parse_variable(namespace,
'TDPolarizationDirection', 0, kick%pol_dir)
322 if (kick%pol_dir < 1 .or. kick%pol_dir > kick%dim)
call messages_input_error(namespace,
'TDPolarizationDirection')
364 if (
parse_block(namespace,
'TDPolarization', blk) == 0)
then
367 if (n_rows /= kick%dim)
then
368 call messages_input_error(namespace,
'TDPolarization',
'There should be exactly one line per dimension')
372 do idir = 1, kick%dim
380 do idir = 1, kick%dim
381 kick%pol(1:kick%dim, idir) = kick%pol(1:kick%dim, idir) / norm2(kick%pol(1:kick%dim, idir))
385 if (any(abs(kick%pol(1:periodic_dim, :)) >
m_epsilon))
then
386 message(1) =
"Kick cannot be applied in a periodic direction. Use GaugeVectorField instead."
406 if (
parse_block(namespace,
'TDPolarizationWprime', blk) == 0)
then
407 do idir = 1, kick%dim
410 kick%wprime(1:kick%dim) = kick%wprime(1:kick%dim) / norm2(kick%wprime(1:kick%dim))
413 kick%wprime(1:kick%dim-1) =
m_zero
414 kick%wprime(kick%dim) =
m_one
419 if (periodic_dim > 0 .and. kick%delta_strength_mode /=
kick_magnon_mode)
then
420 message(1) =
"Kicks cannot be applied correctly in periodic directions."
432 if (periodic_dim > 0 .and. kick%delta_strength_mode ==
kick_magnon_mode .and. &
433 parse_block(namespace,
'TDReducedMomentumTransfer', blk) == 0)
then
436 safe_allocate(kick%qvector(1:kick%dim, 1))
437 do idir = 1, kick%dim
445 if (kpoints%use_symmetries)
then
449 message(1) =
"The TDMomentumTransfer breaks (at least) one of the symmetries used to reduce the k-points."
450 message(2) =
"Set SymmetryBreakDir equal to TDMomemtumTransfer."
478 else if (
parse_block(namespace,
'TDMomentumTransfer', blk) == 0)
then
480 safe_allocate(kick%qvector(1:kick%dim, 1))
481 do idir = 1, kick%dim
505 if (kpoints%use_symmetries)
then
509 message(1) =
"The TDMomentumTransfer breaks (at least) one of the symmetries used to reduce the k-points."
510 message(2) =
"Set SymmetryBreakDir equal to TDMomemtumTransfer."
517 kick%qkick_mode = qkickmode_none
519 safe_allocate(kick%qvector(1:kick%dim,1))
520 kick%qvector(:,1) =
m_zero
523 kick%qlength = norm2(kick%qvector(:,1))
534 if (
parse_block(namespace,
'TDEasyAxis', blk) == 0)
then
540 norm = norm2(kick%easy_axis(1:3))
541 if (norm < 1e-9_real64)
then
542 message(1) =
"TDEasyAxis norm is too small."
545 kick%easy_axis(1:3) = kick%easy_axis(1:3)/norm
548 message(1) =
"For magnons, the variable TDEasyAxis must be defined."
555 kick%trans_vec(1,1) = -kick%easy_axis(2)
556 kick%trans_vec(2,1) =
m_two*kick%easy_axis(3)
557 kick%trans_vec(3,1) =
m_three*kick%easy_axis(1)
559 dot = sum(kick%easy_axis(1:3)*kick%trans_vec(1:3,1))
560 kick%trans_vec(1:3,1) = kick%trans_vec(1:3,1) - dot*kick%easy_axis(1:3)
561 norm = sum(kick%trans_vec(1:3,1)**2)
562 kick%trans_vec(1:3,1) = kick%trans_vec(1:3,1)/
sqrt(norm)
565 kick%trans_vec(1,2) = kick%easy_axis(2) * kick%trans_vec(3,1) - kick%easy_axis(3) * kick%trans_vec(2,1)
566 kick%trans_vec(2,2) = kick%easy_axis(3) * kick%trans_vec(1,1) - kick%easy_axis(1) * kick%trans_vec(3,1)
567 kick%trans_vec(3,2) = kick%easy_axis(1) * kick%trans_vec(2,1) - kick%easy_axis(2) * kick%trans_vec(1,1)
575 message(1) =
"TDMomentumTransfer and TDMultipleMomentumTransfer cannot be defined at the same time."
601 if (
parse_block(namespace,
'TDMultipleMomentumTransfer', blk) /= 0)
then
602 write(
message(1),
'(a)')
'Internal error while reading TDMultipleMomentumTransfer.'
613 kick%nqvec = (2*kick%nqmult(1)+1)*(2*kick%nqmult(2)+1)*(2*kick%nqmult(3)+1)
615 safe_deallocate_a(kick%qvector)
616 safe_allocate(kick%qvector(1:3, 1:kick%nqvec))
618 do iqx = -kick%nqmult(1), kick%nqmult(1)
619 do iqy = -kick%nqmult(2), kick%nqmult(2)
620 do iqz = -kick%nqmult(3), kick%nqmult(3)
622 qtemp(1:3) = (/iqx, iqy, iqz/)
626 if (kpoints%use_symmetries)
then
630 message(1) =
"The TDMultipleMomentumTransfer breaks (at least) one " &
631 //
"of the symmetries used to reduce the k-points."
632 message(2) =
"Set SymmetryBreakDir accordingly."
644 kick%easy_axis(:) =
m_zero
648 message(1) =
"For magnons, the kick mode must be exponential."
658 type(
kick_t),
intent(inout) :: kick_out
659 type(
kick_t),
intent(in) :: kick_in
663 kick_out%dim = kick_in%dim
665 kick_out%time = kick_in%time
667 kick_out%delta_strength_mode = kick_in%delta_strength_mode
668 kick_out%delta_strength = kick_in%delta_strength
671 safe_allocate_source_a(kick_out%pol, kick_in%pol)
672 kick_out%pol_dir = kick_in%pol_dir
673 kick_out%pol_equiv_axes = kick_in%pol_equiv_axes
674 safe_allocate_source_a(kick_out%wprime, kick_in%wprime)
677 kick_out%n_multipoles = kick_in%n_multipoles
678 if (kick_out%n_multipoles > 0)
then
679 safe_allocate_source_a(kick_out%l, kick_in%l)
680 safe_allocate_source_a(kick_out%m, kick_in%m)
681 safe_allocate_source_a(kick_out%weight, kick_in%weight)
683 kick_out%nqvec = kick_in%nqvec
684 safe_allocate_source_a(kick_out%qvector, kick_in%qvector)
685 kick_out%qlength = kick_in%qlength
686 kick_out%qkick_mode = kick_in%qkick_mode
687 kick_out%qbessel_l = kick_in%qbessel_l
688 kick_out%qbessel_m = kick_in%qbessel_m
691 kick_out%function_mode = kick_in%function_mode
692 kick_out%user_defined_function = kick_in%user_defined_function
694 kick_out%easy_axis = kick_in%easy_axis
701 type(
kick_t),
intent(inout) :: kick
705 kick%delta_strength_mode = 0
707 kick%pol_equiv_axes = 0
708 safe_deallocate_a(kick%pol)
710 safe_deallocate_a(kick%wprime)
711 if (kick%n_multipoles > 0)
then
712 safe_deallocate_a(kick%l)
713 safe_deallocate_a(kick%m)
714 safe_deallocate_a(kick%weight)
716 kick%n_multipoles = 0
717 kick%qkick_mode = qkickmode_none
718 safe_deallocate_a(kick%qvector)
724 subroutine kick_read(kick, iunit, namespace)
725 type(
kick_t),
intent(inout) :: kick
726 integer,
intent(in) :: iunit
729 integer :: idir, im, ierr
730 character(len=100) :: line
734 kick%function_mode = -1
736 read(iunit,
'(15x,i2)') kick%delta_strength_mode
737 read(iunit,
'(15x,f18.12)') kick%delta_strength
738 read(iunit,
'(15x,i2)') kick%dim
739 read(iunit,
'(a)') line
740 if (index(line,
'defined') /= 0)
then
743 read(line,
'(16x,a)') kick%user_defined_function
744 elseif (index(line,
'multipole') /= 0)
then
747 read(line,
'(15x,i3)') kick%n_multipoles
748 safe_allocate( kick%l(1:kick%n_multipoles))
749 safe_allocate( kick%m(1:kick%n_multipoles))
750 safe_allocate(kick%weight(1:kick%n_multipoles))
751 do im = 1, kick%n_multipoles
753 read(iunit,
'(15x,2i3,f18.12)') kick%l(im), kick%m(im), kick%weight(im)
756 kick%function_mode = kick_function_dipole
757 kick%n_multipoles = 0
760 safe_allocate(kick%pol(1:kick%dim, 1:kick%dim))
761 safe_allocate(kick%wprime(1:kick%dim))
762 do idir = 1, kick%dim
763 read(iunit,
'(15x,99f18.12)') kick%pol(1:kick%dim, idir)
765 read(iunit,
'(15x,i2)') kick%pol_dir
766 read(iunit,
'(15x,i2)') kick%pol_equiv_axes
767 read(iunit,
'(15x,99f18.12)') kick%wprime(1:kick%dim)
770 read(iunit,
'(15x,i3)') kick%nqvec
771 safe_allocate(kick%qvector(1:3, 1:kick%nqvec))
772 do im = 1, kick%nqvec
773 read(iunit,
'(15x,3f18.12)') kick%qvector(1:kick%dim, im)
775 read(iunit,
'(15x,3f18.12)') kick%easy_axis(1:3)
776 read(iunit,
'(15x,3f18.12)') kick%trans_vec(1:3,1)
777 read(iunit,
'(15x,3f18.12)') kick%trans_vec(1:3,2)
779 read(iunit,
'(15x,f18.12)', iostat = ierr) kick%time
786 if (kick%function_mode < 0)
then
787 message(1) =
"No kick could be read from file."
797 type(
kick_t),
intent(in) :: kick
798 integer,
optional,
intent(in) :: iunit
799 type(c_ptr),
optional,
intent(inout) :: out
802 character(len=120) :: aux
806 if (
present(iunit))
then
807 write(iunit,
'(a15,i1)')
'# kick mode ', kick%delta_strength_mode
808 write(iunit,
'(a15,f18.12)')
'# kick strength', kick%delta_strength
809 write(iunit,
'(a15,i2)')
'# dim ', kick%dim
812 write(iunit,
'(a15,1x,a)')
'# User defined:', trim(kick%user_defined_function)
813 elseif (kick%n_multipoles > 0)
then
814 write(iunit,
'(a15,i3)')
'# N multipoles ', kick%n_multipoles
815 do im = 1, kick%n_multipoles
816 write(iunit,
'(a15,2i3,f18.12)')
'# multipole ', kick%l(im), kick%m(im), kick%weight(im)
819 do idir = 1, kick%dim
820 write(iunit,
'(a6,i1,a8,99f18.12)')
'# pol(', idir,
') ', kick%pol(1:kick%dim, idir)
822 write(iunit,
'(a15,i1)')
'# direction ', kick%pol_dir
823 write(iunit,
'(a15,i1)')
'# Equiv. axes ', kick%pol_equiv_axes
824 write(iunit,
'(a15,99f18.12)')
'# wprime ', kick%wprime(1:kick%dim)
826 write(iunit,
'(a15,f18.12)')
"# kick time ", kick%time
828 else if (
present(out))
then
829 write(aux,
'(a15,i2)')
'# kick mode ', kick%delta_strength_mode
832 write(aux,
'(a15,f18.12)')
'# kick strength', kick%delta_strength
835 write(aux,
'(a15,i2)')
'# dim ', kick%dim
839 write(aux,
'(a15,1x,a)')
'# User defined:', trim(kick%user_defined_function)
842 elseif (kick%n_multipoles > 0)
then
843 write(aux,
'(a15,i3)')
'# N multipoles ', kick%n_multipoles
846 do im = 1, kick%n_multipoles
847 write(aux,
'(a15,2i3,f18.12)')
'# multipole ', kick%l(im), kick%m(im), kick%weight(im)
852 do idir = 1, kick%dim
853 write(aux,
'(a6,i1,a8,99f18.12)')
'# pol(', idir,
') ', kick%pol(1:kick%dim, idir)
857 write(aux,
'(a15,i2)')
'# direction ', kick%pol_dir
860 write(aux,
'(a15,i2)')
'# Equiv. axes ', kick%pol_equiv_axes
863 write(aux,
'(a15,99f18.12)')
'# wprime ', kick%wprime(1:kick%dim)
868 write(aux,
'(a15,i3)')
'# N q-vectors ', kick%nqvec
871 do im = 1, kick%nqvec
872 write(aux,
'(a15,3f18.12)')
'# q-vector ', kick%qvector(1:kick%dim, im)
876 write(aux,
'(a15,3f18.12)')
'# Easy axis ', kick%easy_axis(1:3)
879 write(aux,
'(a15,3f18.12)')
'# Trans. dir 1 ', kick%trans_vec(1:3,1)
882 write(aux,
'(a15,3f18.12)')
'# Trans. dir 2 ', kick%trans_vec(1:3,2)
886 write(aux,
'(a15,f18.12)')
"# kick time ", kick%time
898 subroutine kick_function_get(space, mesh, kick, kick_function, iq, to_interpolate)
899 class(
space_t),
intent(in) :: space
900 class(
mesh_t),
intent(in) :: mesh
901 type(
kick_t),
intent(in) :: kick
902 complex(real64),
intent(out) :: kick_function(:)
903 integer,
intent(in) :: iq
904 logical,
optional,
intent(in) :: to_interpolate
907 real(real64) :: xx(space%dim)
908 real(real64) :: rkick, ikick, rr, ylm
915 if (
present(to_interpolate))
then
916 if (to_interpolate) np = mesh%np_part
921 select case (kick%qkick_mode)
923 write(
message(1),
'(a,3F9.5,a)')
'Info: Using cos(q.r) field with q = (', kick%qvector(1:3, iq),
')'
925 write(
message(1),
'(a,3F9.5,a)')
'Info: Using sin(q.r) field with q = (', kick%qvector(1:3, iq),
')'
927 write(
message(1),
'(a,3F9.5,a)')
'Info: Using sin(q.r)+cos(q.r) field with q = (', kick%qvector(1:3, iq),
')'
929 select case(kick%dim)
931 write(
message(1),
'(a,1F9.5,a)')
'Info: Using exp(iq.r) field with q = (', kick%qvector(1:kick%dim, iq),
')'
933 write(
message(1),
'(a,2F9.5,a)')
'Info: Using exp(iq.r) field with q = (', kick%qvector(1:kick%dim, iq),
')'
935 write(
message(1),
'(a,3F9.5,a)')
'Info: Using exp(iq.r) field with q = (', kick%qvector(1:kick%dim, iq),
')'
938 write(
message(1),
'(a,I2,a,I2,a,F9.5)')
'Info: Using j_l(qr)*Y_lm(r) field with (l,m)= (', &
939 kick%qbessel_l,
",", kick%qbessel_m,
') and q = ', kick%qlength
941 write(
message(1),
'(a)')
'Info: Unknown field type!'
948 select case (kick%qkick_mode)
950 kick_function(ip) = kick_function(ip) +
cos(dot_product(kick%qvector(1:kick%dim, iq), xx))
952 kick_function(ip) = kick_function(ip) +
sin(dot_product(kick%qvector(1:kick%dim, iq), xx))
954 kick_function(ip) = kick_function(ip) +
sin(dot_product(kick%qvector(1:kick%dim, iq), xx))
956 kick_function(ip) = kick_function(ip) +
exp(
m_zi * dot_product(kick%qvector(:, iq), xx))
958 call ylmr_real(xx, kick%qbessel_l, kick%qbessel_m, ylm)
959 kick_function(ip) = kick_function(ip) +
loct_sph_bessel(kick%qbessel_l, kick%qlength*norm2(xx))*ylm
968 call mesh_r(mesh, ip, rr, coords = xx)
972 kick_function(ip) = rkick
975 elseif (kick%n_multipoles > 0)
then
978 do im = 1, kick%n_multipoles
980 call mesh_r(mesh, ip, rr, coords = xx)
981 call loct_ylm(1, xx(1), xx(2), xx(3), kick%l(im), kick%m(im), ylm)
982 kick_function(ip) = kick_function(ip) + kick%weight(im) * (rr**kick%l(im)) * ylm
987 kick_function(ip) = sum(mesh%x(ip, 1:space%dim) * &
988 kick%pol(1:space%dim, kick%pol_dir))
1000 class(
space_t),
intent(in) :: space
1001 class(
mesh_t),
intent(in) :: mesh
1002 type(
kick_t),
intent(in) :: kick
1004 type(
pcm_t),
intent(inout) :: pcm
1005 complex(real64),
intent(out) :: kick_pcm_function(:)
1007 complex(real64),
allocatable :: kick_function_interpolate(:)
1008 real(real64),
allocatable :: kick_function_real(:)
1012 kick_pcm_function =
m_zero
1013 if (pcm%localf)
then
1014 safe_allocate(kick_function_interpolate(1:mesh%np_part))
1015 kick_function_interpolate =
m_zero
1017 safe_allocate(kick_function_real(1:mesh%np_part))
1018 kick_function_real =real(kick_function_interpolate, real64)
1019 if (pcm%kick_like)
then
1021 call pcm_calc_pot_rs(pcm, mesh, psolver, kick = kick%delta_strength * kick_function_real, kick_time = .
true.)
1022 else if (.not. pcm%kick_like .and. pcm%which_eps ==
pcm_debye_model)
then
1024 pcm%kick_like = .
true.
1025 call pcm_calc_pot_rs(pcm, mesh, psolver, kick = kick%delta_strength * kick_function_real, kick_time = .
true.)
1026 pcm%kick_like = .false.
1027 else if (.not. pcm%kick_like .and. pcm%which_eps ==
pcm_drude_model)
then
1031 kick_pcm_function = pcm%v_kick_rs / kick%delta_strength
1041 subroutine kick_apply(space, mesh, st, ions_dyn, ions, kick, psolver, kpoints, pcm)
1042 class(
space_t),
intent(in) :: space
1043 class(
mesh_t),
intent(in) :: mesh
1046 type(
ions_t),
intent(inout) :: ions
1047 type(
kick_t),
intent(in) :: kick
1050 type(
pcm_t),
optional,
intent(inout) :: pcm
1052 integer :: iqn, ist, idim, ip, ispin, iatom
1053 complex(real64) :: cc(2), kick_value
1054 complex(real64),
allocatable :: kick_function(:), psi(:, :)
1056 complex(real64),
allocatable :: kick_pcm_function(:)
1058 real(real64) :: uvec(3), vvec(3), gvec(3, 3)
1059 real(real64) :: xx(space%dim), rr
1060 complex(real64) :: cross_term
1066 delta_strength:
if (abs(kick%delta_strength) >
m_epsilon)
then
1068 safe_allocate(kick_function(1:mesh%np))
1069 if (kick%delta_strength_mode /=
kick_magnon_mode .or. kick%nqvec == 1)
then
1074 if (
present(pcm))
then
1075 safe_allocate(kick_pcm_function(1:mesh%np))
1077 kick_function = kick_function + kick_pcm_function
1080 write(
message(1),
'(a,f11.6)')
'Info: Applying delta kick: k = ', kick%delta_strength
1081 select case (kick%function_mode)
1082 case (kick_function_dipole)
1083 message(2) =
"Info: kick function: dipole."
1085 message(2) =
"Info: kick function: multipoles."
1087 message(2) =
"Info: kick function: user defined function."
1089 select case (kick%delta_strength_mode)
1090 case (kick_density_mode)
1091 message(3) =
"Info: Delta kick mode: Density mode"
1093 message(3) =
"Info: Delta kick mode: Spin mode"
1095 message(3) =
"Info: Delta kick mode: Density + Spin modes"
1100 if (st%d%nspin == 2) ns = 2
1102 safe_allocate(psi(1:mesh%np, 1:st%d%dim))
1106 do iqn = st%d%kpt%start, st%d%kpt%end
1107 do ist = st%st_start, st%st_end
1110 select case (kick%delta_strength_mode)
1111 case (kick_density_mode)
1112 do idim = 1, st%d%dim
1114 psi(ip, idim) =
exp(
m_zi*kick%delta_strength*kick_function(ip))*psi(ip, idim)
1119 ispin = st%d%get_spin_index(iqn)
1121 kick_value =
m_zi*kick%delta_strength*kick_function(ip)
1123 cc(1) =
exp(kick_value)
1124 cc(2) =
exp(-kick_value)
1126 select case (st%d%ispin)
1128 psi(ip, 1) = cc(ispin)*psi(ip, 1)
1130 psi(ip, 1) = cc(1)*psi(ip, 1)
1131 psi(ip, 2) = cc(2)*psi(ip, 2)
1137 kick_value =
m_zi*kick%delta_strength*kick_function(ip)
1140 select case (st%d%ispin)
1143 psi(ip, 1) = cc(1)*psi(ip, 1)
1146 psi(ip, 1) = cc(1)*psi(ip, 1)
1159 if (kick%nqvec == 1)
then
1162 uvec(1:3) = kick%trans_vec(1:3,1)
1163 vvec(1:3) = kick%trans_vec(1:3,2)
1165 do iqn = st%d%kpt%start, st%d%kpt%end, ns
1166 do ist = st%st_start, st%st_end
1176 psi(ip, 1) =
cos(kick%delta_strength)* cc(1)
1177 psi(ip, 2) =
cos(kick%delta_strength)* cc(2)
1183 psi(ip, 1) = psi(ip, 1) -
m_zi*
sin(kick%delta_strength)*( real(kick_function(ip), real64) &
1184 * (uvec(3)*cc(1) + cmplx(uvec(1),-uvec(2), real64)*cc(2)) &
1185 + aimag(kick_function(ip)) * (vvec(3)*cc(1) + cmplx(vvec(1),-vvec(2), real64)*cc(2)))
1186 psi(ip, 2) = psi(ip, 2) -
m_zi*
sin(kick%delta_strength)*( real(kick_function(ip), real64) &
1187 * (-uvec(3)*cc(2) + cmplx(uvec(1),uvec(2), real64)*cc(1)) &
1188 + aimag(kick_function(ip)) * (-vvec(3)*cc(2) + cmplx(vvec(1),vvec(2), real64)*cc(1)))
1203 kick_function =
m_one
1205 call mesh_r(mesh, ip, rr, coords = xx)
1207 if (kick%nqmult(iq) == 0) cycle
1210 kick_function(ip) = kick_function(ip)*
sin(
m_half*(2*kick%nqmult(iq)+1) &
1211 *sum(gvec(1:3, iq) * xx(1:3)))/
sin(
m_half*sum(gvec(1:3, iq) * xx(1:3)))
1213 kick_function(ip) = kick_function(ip)*kick%delta_strength
1217 cross_term = (kick%easy_axis(2)*cmplx(kick%easy_axis(1),-kick%easy_axis(2), real64) &
1218 / ( 1 + kick%easy_axis(3)) -
m_zi * kick%easy_axis(3))
1220 do iqn = st%d%kpt%start, st%d%kpt%end, ns
1221 do ist = st%st_start, st%st_end
1234 psi(ip, 1) = (
cos(kick_function(ip)) +
m_zi * kick%easy_axis(1)*
sin(kick_function(ip)))*cc(1) &
1235 +
sin(kick_function(ip)) * cross_term * cc(2)
1236 psi(ip, 2) = -
sin(kick_function(ip)) * conjg(cross_term) * cc(1) &
1237 + (
cos(kick_function(ip)) -
m_zi * kick%easy_axis(1)*
sin(kick_function(ip)))*cc(2)
1248 safe_deallocate_a(psi)
1253 if (ions_dyn%ions_move() .and. abs(kick%delta_strength) >
m_epsilon)
then
1255 do iatom = 1, ions%natoms
1256 ions%vel(:, iatom) = ions%vel(:, iatom) + &
1257 kick%delta_strength * kick%pol(1:ions%space%dim, kick%pol_dir) * &
1263 safe_deallocate_a(kick_function)
1264 end if delta_strength
1270 type(
kick_t),
intent(in) :: kick
1272 kick_type = kick%delta_strength_mode
double exp(double __x) __attribute__((__nothrow__
double sin(double __x) __attribute__((__nothrow__
double cos(double __x) __attribute__((__nothrow__
integer, parameter, public spinors
integer, parameter, public spin_polarized
real(real64), parameter, public m_two
real(real64), parameter, public p_proton_charge
real(real64), parameter, public m_zero
complex(real64), parameter, public m_z0
complex(real64), parameter, public m_zi
real(real64), parameter, public m_epsilon
real(real64), parameter, public m_half
real(real64), parameter, public m_one
real(real64), parameter, public m_three
subroutine, public kick_copy(kick_out, kick_in)
integer, parameter, public kick_magnon_mode
integer, parameter, public kick_function_multipole
subroutine, public kick_read(kick, iunit, namespace)
subroutine kick_pcm_function_get(space, mesh, kick, psolver, pcm, kick_pcm_function)
integer, parameter, public kick_spin_mode
integer, parameter, public qkickmode_exp
integer, parameter, public qkickmode_cos
subroutine, public kick_end(kick)
integer, parameter, public qkickmode_sin
subroutine, public kick_init(kick, namespace, space, kpoints, nspin)
subroutine, public kick_function_get(space, mesh, kick, kick_function, iq, to_interpolate)
pure integer function, public kick_get_type(kick)
subroutine, public kick_apply(space, mesh, st, ions_dyn, ions, kick, psolver, kpoints, pcm)
Applies the delta-function electric field where k = kick%delta_strength.
subroutine, public kick_write(kick, iunit, out)
integer, parameter, public kick_function_user_defined
integer, parameter, public qkickmode_bessel
integer, parameter, public kick_spin_density_mode
subroutine, public kpoints_to_absolute(latt, kin, kout)
This module is intended to contain "only mathematical" functions and procedures.
subroutine, public ylmr_real(xx, li, mi, ylm)
This is a Numerical Recipes-based subroutine computes real spherical harmonics ylm at position (x,...
This module defines the meshes, which are used in Octopus.
pure subroutine, public mesh_r(mesh, ip, rr, origin, coords)
return the distance to the origin for a given grid point
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)
logical function, public parse_is_defined(namespace, name)
integer function, public parse_block(namespace, name, blk, check_varinfo_)
integer, parameter, public pcm_drude_model
integer, parameter, public pcm_debye_model
subroutine, public pcm_calc_pot_rs(pcm, mesh, psolver, ions, v_h, v_ext, kick, time_present, kick_time)
This module handles spin dimensions of the states and the k-point distribution.
logical pure function, public is_spin_up(ik)
Returns true if k-point ik denotes spin-up, in spin-polarized case.
integer pure function, public symmetries_identity_index(this)
integer pure function, public symmetries_number(this)
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_system_t), public units_inp
the units systems for reading and writing
Explicit interfaces to C functions, defined in write_iter_low.cc.
Describes mesh distribution to nodes.
The states_elec_t class contains all electronic wave functions.