96 integer,
parameter,
public :: &
97 MULTIGRID_MX_TO_MA_EQUAL = 1, &
103 type(space_t) :: space
104 type(states_mxll_t) :: st
105 type(hamiltonian_mxll_t) :: hm
107 type(output_t) :: outp
108 type(multicomm_t) :: mc
110 type(mesh_interpolation_t) :: mesh_interpolate
112 type(propagator_mxll_t) :: tr_mxll
113 type(td_write_t) :: write_handler
114 type(c_ptr) :: output_handle
116 complex(real64),
allocatable :: ff_rs_inhom_t1(:,:), ff_rs_inhom_t2(:,:)
117 complex(real64),
allocatable :: rs_state_init(:,:)
118 type(time_interpolation_t),
pointer :: current_interpolation
119 real(real64) :: bc_bounds(2, 3), dt_bounds(2, 3)
120 integer :: energy_update_iter
121 type(restart_t) :: restart_dump
122 type(restart_t) :: restart
124 type(lattice_vectors_t) :: latt
126 type(helmholtz_decomposition_t) :: helmholtz
128 logical :: write_previous_state = .false.
151 procedure maxwell_constructor
158 class(maxwell_t),
pointer :: sys
159 type(namespace_t),
intent(in) :: namespace
173 class(maxwell_t),
intent(inout) :: this
174 type(namespace_t),
intent(in) :: namespace
181 this%namespace = namespace
185 this%space =
space_t(this%namespace)
186 if (this%space%is_periodic())
then
195 this%quantities(
e_field)%updated_on_demand = .false.
197 this%quantities(
b_field)%updated_on_demand = .false.
220 select type (interaction)
222 call interaction%init(this%gr)
224 call interaction%init(this%gr, this%st%dim)
225 call interaction%init_space_latt(this%space, this%latt)
229 select type (prop => this%algo)
239 message(1) =
"The chosen propagator does not yet support interaction interpolation"
242 call interaction%init_interpolation(depth, interaction%label, cmplx=.
true.)
244 this%hm%current_density_from_medium = .
true.
246 message(1) =
"Trying to initialize an unsupported interaction by Maxwell."
258 integer(int64) :: index_range(4)
259 integer :: ierr, ip, pos_index, rankmin
268 index_range(1) = this%gr%np_global
269 index_range(2) = this%st%nst
271 index_range(4) = 100000
275 index_range, (/ 5000, 1, 1, 1 /))
281 this%st%energy_rate =
m_zero
282 this%st%delta_energy =
m_zero
283 this%st%energy_via_flux_calc =
m_zero
284 this%st%trans_energy_rate =
m_zero
285 this%st%trans_delta_energy =
m_zero
286 this%st%trans_energy_via_flux_calc =
m_zero
287 this%st%plane_waves_energy_rate =
m_zero
288 this%st%plane_waves_delta_energy =
m_zero
289 this%st%plane_waves_energy_via_flux_calc =
m_zero
291 safe_allocate(this%rs_state_init(1:this%gr%np_part, 1:this%st%dim))
292 this%rs_state_init(:,:) =
m_z0
294 this%energy_update_iter = 1
296 call poisson_init(this%st%poisson, this%namespace, this%space, this%gr%der, this%mc, this%gr%stencil)
301 this%hm%propagation_apply = .
true.
303 if (
parse_is_defined(this%namespace,
'MaxwellIncidentWaves') .and. (this%tr_mxll%bc_plane_waves))
then
304 this%st%rs_state_plane_waves(:,:) =
m_z0
308 do ip = 1, this%st%selected_points_number
309 pos_index =
mesh_nearest_point(this%gr, this%st%selected_points_coordinate(:,ip), dmin, rankmin)
310 if (this%gr%mpi_grp%rank == rankmin)
then
311 this%st%selected_points_map(ip) = pos_index
313 this%st%selected_points_map(ip) = -1
318 this%st%selected_points_number)
319 call accel_write_buffer(this%st%buff_selected_points_map, this%st%selected_points_number, &
320 this%st%selected_points_map)
323 this%hm%plane_waves_apply = .
true.
324 this%hm%spatial_constant_apply = .
true.
326 call bc_mxll_init(this%hm%bc, this%namespace, this%space, this%gr, this%st)
327 this%bc_bounds(:,1:3) = this%hm%bc%bc_bounds(:,1:3)
329 this%dt_bounds(2, 1:3) = this%bc_bounds(1, 1:3)
330 this%dt_bounds(1, 1:3) = this%bc_bounds(1, 1:3) - this%gr%der%order * this%gr%spacing(1:3)
337 call zbatch_init(this%st%rs_stateb, 1, 1, this%st%dim, this%gr%np_part)
338 if (this%st%pack_states)
call this%st%rs_stateb%do_pack()
339 call this%st%rs_stateb%copy_to(this%st%rs_state_prevb)
340 call this%st%rs_stateb%copy_to(this%st%inhomogeneousb)
341 if (this%tr_mxll%bc_plane_waves)
then
342 call this%st%rs_stateb%copy_to(this%st%rs_state_plane_wavesb)
348 call this%helmholtz%init(this%namespace, this%gr, this%mc, this%space)
357 real(real64) :: courant
364 select type (algo => this%algo)
373 m_one/this%gr%spacing(3)**2))
376 write(
message(1),
'(a)')
'The timestep is too large compared to the Courant-Friedrichs-Lewy'
377 write(
message(2),
'(a)')
'stability condition. Time propagation might not be stable.'
381 if (
parse_is_defined(this%namespace,
'UserDefinedInitialMaxwellStates'))
then
386 this%st%rs_state(:,:) = this%st%rs_state + this%rs_state_init
387 if (this%tr_mxll%bc_plane_waves)
then
388 this%st%rs_state_plane_waves(:,:) = this%rs_state_init
394 if (this%tr_mxll%bc_constant)
then
396 algo%dt,
m_zero, this%st%rs_state, set_initial_state = .
true.)
401 if (
parse_is_defined(this%namespace,
'UserDefinedInitialMaxwellStates'))
then
402 safe_deallocate_a(this%rs_state_init)
408 call energy_mxll_calc(this%gr, this%st, this%hm, this%hm%energy, this%st%rs_state, &
409 this%st%rs_state_plane_waves)
413 this%st%selected_points_coordinate(:,:), this%st, this%gr)
415 call mxll_set_batch(this%st%rs_stateb, this%st%rs_state, this%gr%np, this%st%dim)
417 if (this%tr_mxll%bc_plane_waves)
then
418 call mxll_set_batch(this%st%rs_state_plane_wavesb, this%st%rs_state_plane_waves, this%gr%np, this%st%dim)
431 integer,
allocatable,
intent(out) :: updated_quantities(:)
433 complex(real64),
allocatable :: charge_density_ext(:)
434 real(real64) :: current_time
437 call profiling_in(trim(this%namespace%get())//
":"//trim(operation%id))
439 current_time = this%iteration%value()
441 select type (algo => this%algo)
445 select case (operation%id)
450 safe_allocate(this%ff_rs_inhom_t1(1:this%gr%np_part, 1:this%hm%dim))
451 safe_allocate(this%ff_rs_inhom_t2(1:this%gr%np_part, 1:this%hm%dim))
454 safe_deallocate_a(this%ff_rs_inhom_t1)
455 safe_deallocate_a(this%ff_rs_inhom_t2)
458 if (this%hm%current_density_ext_flag .or. this%hm%current_density_from_medium)
then
459 call this%get_current(current_time, this%st%rs_current_density_t1)
460 call this%get_current(current_time+algo%dt, this%st%rs_current_density_t2)
467 safe_allocate(charge_density_ext(1:this%gr%np))
470 charge_density_ext =
m_z0
477 safe_deallocate_a(charge_density_ext)
481 this%st%rs_stateb, this%ff_rs_inhom_t1, this%ff_rs_inhom_t2, current_time, algo%dt)
486 if (any(this%hm%bc%bc_ab_type == option__maxwellabsorbingboundaries__cpml))
then
493 if (this%hm%current_density_ext_flag .or. this%hm%current_density_from_medium)
then
494 call this%get_current(current_time, this%st%rs_current_density_t1)
495 call mxll_set_batch(this%st%inhomogeneousb, this%st%rs_current_density_t1, this%gr%np, this%st%dim)
500 current_time, algo%dt, this%iteration%counter())
505 safe_allocate(this%ff_rs_inhom_t1(1:this%gr%np_part, 1:this%hm%dim))
506 if (any(this%hm%bc%bc_ab_type == option__maxwellabsorbingboundaries__cpml))
then
511 safe_deallocate_a(this%ff_rs_inhom_t1)
514 if (this%hm%current_density_ext_flag .or. this%hm%current_density_from_medium)
then
515 call this%get_current(current_time+algo%dt*
m_half, this%st%rs_current_density_t1)
523 current_time, algo%dt)
528 safe_allocate(this%ff_rs_inhom_t1(1:this%gr%np_part, 1:this%hm%dim))
529 safe_allocate(this%ff_rs_inhom_t2(1:this%gr%np_part, 1:this%hm%dim))
530 if (any(this%hm%bc%bc_ab_type == option__maxwellabsorbingboundaries__cpml))
then
535 safe_deallocate_a(this%ff_rs_inhom_t1)
536 safe_deallocate_a(this%ff_rs_inhom_t2)
539 if (this%hm%current_density_ext_flag .or. this%hm%current_density_from_medium)
then
540 call this%get_current(current_time+algo%dt*(
m_half-
sqrt(
m_three)/6.0_real64), this%st%rs_current_density_t1)
541 call this%get_current(current_time+algo%dt*(
m_half+
sqrt(
m_three)/6.0_real64), this%st%rs_current_density_t2)
555 current_time, algo%dt)
569 call profiling_out(trim(this%namespace%get())//
":"//trim(operation%id))
576 real(real64),
intent(in) :: tol
592 select type (interaction)
596 call interaction%init_from_partner(partner%gr, partner%space, partner%namespace)
598 call interaction%init_from_partner(partner%gr, partner%space, partner%namespace)
600 call interaction%init_from_partner(partner%gr, partner%space, partner%namespace)
602 message(1) =
"Unsupported interaction."
611 class(
maxwell_t),
intent(inout) :: partner
615 complex(real64) :: interpolated_value(3)
616 real(real64),
allocatable ::
b_field(:,:), vec_pot(:,:)
619 call profiling_in(trim(partner%namespace%get())//
":"//
"COPY_QUANTITY_INTER")
621 select type (interaction)
623 call mxll_get_batch(partner%st%rs_stateb, partner%st%rs_state, partner%gr%np, partner%st%dim)
625 do ip = 1, interaction%system_np
627 interaction%system_pos(:, ip), interpolated_value(1))
629 interaction%system_pos(:, ip), interpolated_value(2))
631 interaction%system_pos(:, ip), interpolated_value(3))
637 call mxll_get_batch(partner%st%rs_stateb, partner%st%rs_state, partner%gr%np, partner%st%dim)
638 select case (interaction%type)
648 call partner%helmholtz%get_long_field(partner%namespace, partner%st%rs_state_long, total_field=partner%st%rs_state)
652 message(1) =
"Unknown type of field requested by interaction."
655 call interaction%do_mapping()
658 call mxll_get_batch(partner%st%rs_stateb, partner%st%rs_state, partner%gr%np, partner%st%dim)
659 safe_allocate(
b_field(1:partner%gr%np_part, 1:partner%gr%box%dim))
660 safe_allocate(vec_pot(1:partner%gr%np_part, 1:partner%gr%box%dim))
663 partner%st%mu(1:partner%gr%np), partner%gr%np)
665 call partner%helmholtz%get_vector_potential(partner%namespace, vec_pot, trans_field=
b_field)
669 interaction%partner_field(1:partner%gr%np,1:partner%gr%box%dim) = &
670 vec_pot(1:partner%gr%np,1:partner%gr%box%dim)
672 safe_deallocate_a(vec_pot)
673 call interaction%do_mapping()
676 call mxll_get_batch(partner%st%rs_stateb, partner%st%rs_state, partner%gr%np, partner%st%dim)
678 interaction%partner_field, partner%st%mu(1:partner%gr%np), partner%gr%np)
679 call interaction%do_mapping()
682 message(1) =
"Unsupported interaction."
686 call profiling_out(trim(partner%namespace%get())//
":"//
"COPY_QUANTITY_INTER")
694 real(real64) :: itr_value
697 call profiling_in(trim(this%namespace%get())//
":"//
"OUTPUT_START")
699 select type (algo => this%algo)
701 call mxll_get_batch(this%st%rs_stateb, this%st%rs_state, this%gr%np, this%st%dim)
704 if (this%st%fromScratch)
then
705 call td_write_mxll_iter(this%write_handler, this%space, this%gr, this%st, this%hm, this%helmholtz, algo%dt, &
706 this%iteration%counter(), this%namespace)
707 itr_value = this%iteration%value()
708 call td_write_mxll_free_data(this%write_handler, this%namespace, this%space, this%gr, this%st, this%hm, this%helmholtz, &
709 this%outp, this%iteration%counter(), itr_value)
714 call profiling_out(trim(this%namespace%get())//
":"//
"OUTPUT_START")
722 logical :: stopping, reached_output_interval
723 real(real64) :: itr_value
727 call profiling_in(trim(this%namespace%get())//
":"//
"OUTPUT_WRITE")
729 select type (algo => this%algo)
733 call td_write_mxll_iter(this%write_handler, this%space, this%gr, this%st, this%hm, this%helmholtz, algo%dt, &
734 this%iteration%counter(), this%namespace)
736 reached_output_interval = .false.
738 if (this%outp%output_interval(iout) > 0)
then
739 if (mod(this%iteration%counter(), this%outp%output_interval(iout)) == 0)
then
740 reached_output_interval = .
true.
746 if (reached_output_interval .or. stopping)
then
747 call mxll_get_batch(this%st%rs_stateb, this%st%rs_state, this%gr%np, this%st%dim)
749 itr_value = this%iteration%value()
750 call td_write_mxll_free_data(this%write_handler, this%namespace, this%space, this%gr, this%st, this%hm, this%helmholtz, &
751 this%outp, this%iteration%counter(), itr_value)
756 call profiling_out(trim(this%namespace%get())//
":"//
"OUTPUT_WRITE")
769 select type (algo => this%algo)
784 integer :: int_counter
789 call iter%start(this%interactions)
790 do while (iter%has_next())
791 select type (interaction => iter%get_next())
793 int_counter = int_counter + 1
797 if (int_counter /= 0 .and. .not.
allocated(this%hm%medium_boxes))
then
798 safe_allocate(this%hm%medium_boxes(1:int_counter))
799 this%hm%calc_medium_box = .
true.
816 call iter%start(this%interactions)
817 do while (iter%has_next())
818 select type (interaction => iter%get_next())
820 if (
allocated(this%hm%medium_boxes) .and. .not. this%hm%medium_boxes_initialized)
then
822 this%hm%medium_boxes(iint) = interaction%medium_box
827 if (
allocated(this%hm%medium_boxes) .and. .not. this%hm%medium_boxes_initialized)
then
829 this%hm%medium_boxes_initialized = .
true.
832 if (this%hm%medium_boxes_initialized .and. this%hm%operator ==
faraday_ampere)
then
833 message(1) =
"A linear medium has been defined in the input file but the Hamiltonian"
834 message(2) =
"type you specified is not capable of dealing with the medium."
835 message(3) =
"Please use MaxwellHamiltonianOperator = faraday_ampere_medium or simple to enable"
836 message(4) =
"the medium propagation."
841 message(1) =
"The variable MaxwellHamiltonianOperator has been defined as faraday_ampere_medium"
842 message(2) =
"in the input file but no linear medium has been defined in the system block."
843 message(3) =
"Please either use a different option for MaxwellHamiltonianOperator or add"
844 message(4) =
"a linear medium to the system block."
855 integer :: ierr, err, zff_dim, id, id1, id2, ip_in, offset, iout
856 logical :: pml_check, write_previous_state
857 complex(real64),
allocatable :: zff(:,:)
862 call profiling_in(trim(this%namespace%get())//
":"//
"RESTART_WRITE")
868 if (this%write_handler%out(iout)%write)
then
869 call write_iter_flush(this%write_handler%out(iout)%handle)
875 pml_check = any(this%hm%bc%bc_ab_type(1:3) == option__maxwellabsorbingboundaries__cpml)
877 message(1) =
"Debug: Writing td_maxwell restart."
880 if (this%tr_mxll%bc_plane_waves)
then
881 zff_dim = 2 * this%st%dim
883 zff_dim = 1 * this%st%dim
886 zff_dim = zff_dim + 18
888 select type (prop => this%algo)
890 write_previous_state = .
true.
891 zff_dim = zff_dim + this%st%dim
893 write_previous_state = .false.
897 int(this%hm%bc%pml%points_number, int64)*3*3, this%hm%bc%pml%conv_plus)
899 int(this%hm%bc%pml%points_number, int64)*3*3, this%hm%bc%pml%conv_minus)
902 call mxll_get_batch(this%st%rs_stateb, this%st%rs_state, this%gr%np, this%st%dim)
903 if (write_previous_state)
then
904 call mxll_get_batch(this%st%rs_state_prevb, this%st%rs_state_prev, this%gr%np, this%st%dim)
907 safe_allocate(zff(1:this%gr%np,1:zff_dim))
910 zff(1:this%gr%np, 1:this%st%dim) = this%st%rs_state(1:this%gr%np, 1:this%st%dim)
911 if (this%tr_mxll%bc_plane_waves)
then
912 call mxll_get_batch(this%st%rs_state_plane_wavesb, this%st%rs_state_plane_waves, &
913 this%gr%np, this%st%dim)
914 zff(1:this%gr%np, this%st%dim+1:this%st%dim+this%st%dim) = &
915 this%st%rs_state_plane_waves(1:this%gr%np, 1:this%st%dim)
916 offset = 2*this%st%dim
925 do ip_in = 1, this%hm%bc%pml%points_number
926 zff(ip_in, offset+id) = this%hm%bc%pml%conv_plus(ip_in, id1, id2)
927 zff(ip_in, offset+9+id) = this%hm%bc%pml%conv_minus(ip_in, id1, id2)
933 if (write_previous_state)
then
934 zff(1:this%gr%np, offset+1:offset+this%st%dim) = &
935 this%st%rs_state_prev(1:this%gr%np, 1:this%st%dim)
938 call states_mxll_dump(this%restart_dump, this%st, this%space, this%gr, zff, zff_dim, err, this%iteration%counter())
939 if (err /= 0) ierr = ierr + 1
941 if (this%hm%current_density_from_medium)
then
943 call iter%start(this%interactions)
944 do while (iter%has_next())
945 interaction => iter%get_next()
946 select type (interaction)
948 call interaction%write_restart(this%gr, this%space, this%restart_dump, err)
951 if (err /= 0) ierr = ierr + 1
954 message(1) =
"Debug: Writing td_maxwell restart done."
957 safe_deallocate_a(zff)
960 message(1) =
"Unable to write time-dependent Maxwell restart information."
965 call profiling_out(trim(this%namespace%get())//
":"//
"RESTART_WRITE")
974 integer :: ierr, err, zff_dim, id, id1, id2, ip_in, offset
975 logical :: pml_check, read_previous_state
976 complex(real64),
allocatable :: zff(:,:)
981 call profiling_in(trim(this%namespace%get())//
":"//
"RESTART_READ")
985 pml_check = any(this%hm%bc%bc_ab_type(1:3) == option__maxwellabsorbingboundaries__cpml)
989 call profiling_out(trim(this%namespace%get())//
":"//
"RESTART_READ")
994 message(1) =
"Debug: Reading td_maxwell restart."
997 if (this%tr_mxll%bc_plane_waves)
then
998 zff_dim = 2 * this%st%dim
1000 zff_dim = 1 * this%st%dim
1003 zff_dim = zff_dim + 18
1005 select type (prop => this%algo)
1007 read_previous_state = .
true.
1008 zff_dim = zff_dim + this%st%dim
1010 read_previous_state = .false.
1013 safe_allocate(zff(1:this%gr%np,1:zff_dim))
1015 call states_mxll_load(this%restart, this%st, this%gr, this%namespace, this%space, zff, &
1016 zff_dim, err, label =
": td_maxwell")
1017 this%st%rs_current_density_restart = .
true.
1019 this%st%rs_state(1:this%gr%np,1:this%st%dim) = zff(1:this%gr%np, 1:this%st%dim)
1020 if (this%tr_mxll%bc_plane_waves)
then
1021 this%st%rs_state_plane_waves(1:this%gr%np,1:this%st%dim) = &
1022 zff(1:this%gr%np,this%st%dim+1:this%st%dim+3)
1023 offset = 2*this%st%dim
1025 offset = this%st%dim
1032 do ip_in = 1, this%hm%bc%pml%points_number
1033 this%hm%bc%pml%conv_plus(ip_in,id1,id2) = zff(ip_in, offset+ id)
1034 this%hm%bc%pml%conv_minus(ip_in,id1,id2) = zff(ip_in, offset+9+id)
1038 this%hm%bc%pml%conv_plus_old = this%hm%bc%pml%conv_plus
1039 this%hm%bc%pml%conv_minus_old = this%hm%bc%pml%conv_minus
1040 offset = offset + 18
1042 if (read_previous_state)
then
1043 this%st%rs_state_prev(1:this%gr%np, 1:this%st%dim) = &
1044 zff(1:this%gr%np, offset+1:offset+this%st%dim)
1051 message(1) =
"Debug: Reading td restart done."
1054 safe_deallocate_a(zff)
1058 int(this%hm%bc%pml%points_number, int64)*3*3, this%hm%bc%pml%conv_plus)
1060 int(this%hm%bc%pml%points_number, int64)*3*3, this%hm%bc%pml%conv_minus)
1062 int(this%hm%bc%pml%points_number, int64)*3*3, this%hm%bc%pml%conv_plus_old)
1065 if (this%hm%current_density_from_medium)
then
1067 call iter%start(this%interactions)
1068 do while (iter%has_next())
1069 interaction => iter%get_next()
1070 select type (interaction)
1072 call interaction%read_restart(this%gr, this%space, this%restart, err)
1081 call mxll_set_batch(this%st%rs_stateb, this%st%rs_state, this%gr%np, this%st%dim)
1082 if (read_previous_state)
then
1083 call mxll_set_batch(this%st%rs_state_prevb, this%st%rs_state_prev, this%gr%np, this%st%dim)
1086 if (this%tr_mxll%bc_plane_waves)
then
1087 call mxll_set_batch(this%st%rs_state_plane_wavesb, this%st%rs_state_plane_waves, this%gr%np, this%st%dim)
1090 this%st%fromScratch = .false.
1093 message(1) =
"Unable to read time-dependent Maxwell restart information: Starting from scratch"
1098 call profiling_out(trim(this%namespace%get())//
":"//
"RESTART_READ")
1112 this%kinetic_energy = this%hm%energy%energy
1122 call profiling_in(trim(this%namespace%get())//
":"//
"END_TIMESTEP")
1125 call energy_mxll_calc_batch(this%gr, this%st, this%hm, this%hm%energy, this%st%rs_stateb, this%st%rs_state_plane_wavesb)
1131 call profiling_out(trim(this%namespace%get())//
":"//
"END_TIMESTEP")
1138 real(real64),
intent(in) :: time
1139 complex(real64),
contiguous,
intent(inout) ::
current(:, :)
1142 complex(real64),
allocatable :: current_density_ext(:, :)
1146 safe_allocate(current_density_ext(1:this%gr%np, 1:this%st%dim))
1148 if (this%hm%current_density_from_medium)
then
1150 call iter%start(this%interactions)
1151 do while (iter%has_next())
1152 select type (interaction => iter%get_next())
1154 call interaction%interpolate(time, current_density_ext)
1160 if (this%hm%current_density_ext_flag)
then
1164 safe_deallocate_a(current_density_ext)
1181 safe_deallocate_a(this%rs_state_init)
1186 call this%st%rs_stateb%end()
1187 call this%st%rs_state_prevb%end()
1188 call this%st%inhomogeneousb%end()
1189 if (this%tr_mxll%bc_plane_waves)
then
1190 call this%st%rs_state_plane_wavesb%end()
scale a batch by a constant or vector
constant times a vector plus a vector
pure logical function, public accel_is_enabled()
integer, parameter, public accel_mem_read_only
This module defines the abstract interfact for algorithm factories.
This module implements the basic elements defining algorithms.
character(len=algo_label_len), parameter, public iteration_done
This module implements batches of mesh functions.
subroutine, public zbatch_init(this, dim, st_start, st_end, np, special, packed)
initialize a TYPE_CMPLX valued batch to given size without providing external memory
This module implements common operations on batches of mesh functions.
subroutine, public batch_set_zero(this, np, async)
fill all mesh functions of the batch with zero
This module handles the calculation mode.
type(calc_mode_par_t), public calc_mode_par
Singleton instance of parallel calculation mode.
This module calculates the derivatives (gradients, Laplacians, etc.) of a function.
subroutine, public get_rs_density_ext(st, space, mesh, time, rs_current_density_ext)
subroutine, public external_current_init(st, space, namespace, mesh)
This module implements the field transfer.
real(real64), parameter, public m_zero
real(real64), parameter, public m_fourth
complex(real64), parameter, public m_z0
real(real64), parameter, public m_half
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
This module implements the underlying real-space grid.
subroutine, public grid_init_stage_1(gr, namespace, space, symm, latt, n_sites, site_position)
First stage of the grid initialization.
subroutine, public grid_init_stage_2(gr, namespace, space, mc, qvector)
Second stage of the grid initialization.
subroutine, public grid_end(gr)
finalize a grid object
subroutine, public hamiltonian_mxll_init(hm, namespace, gr, st)
Initializing the Maxwell Hamiltonian.
integer, parameter, public faraday_ampere
subroutine, public hamiltonian_mxll_end(hm)
integer, parameter, public faraday_ampere_medium
subroutine, public hamiltonian_mxll_update(this, time)
Maxwell Hamiltonian update (here only the time is updated, can maybe be added to another routine)
The Helmholtz decomposition is intended to contain "only mathematical" functions and procedures to co...
This module implements the index, used for the mesh points.
integer, parameter, public mxll_vec_pot_to_matter
integer, parameter, public linear_medium_to_em_field
integer, parameter, public lorentz_force
integer, parameter, public mxll_b_field_to_matter
integer, parameter, public mxll_e_field_to_matter
integer, parameter, public current_to_mxll_field
This module defines the abstract interaction_t class, and some auxiliary classes for interactions.
This module is intended to contain "only mathematical" functions and procedures.
subroutine, public bc_mxll_init(bc, namespace, space, gr, st)
subroutine, public surface_grid_points_mapping(mesh, st, bounds)
subroutine, public bc_mxll_initialize_pml_simple(bc, space, gr, c_factor, dt)
subroutine, public inner_and_outer_points_mapping(mesh, st, bounds)
subroutine maxwell_update_interactions_start(this)
subroutine maxwell_exec_end_of_timestep_tasks(this)
subroutine maxwell_init_interaction(this, interaction)
subroutine maxwell_output_start(this)
subroutine maxwell_update_interactions_finish(this)
subroutine maxwell_init_interaction_as_partner(partner, interaction)
subroutine maxwell_output_finish(this)
subroutine maxwell_restart_write_data(this)
logical function maxwell_do_algorithmic_operation(this, operation, updated_quantities)
integer, parameter, public multigrid_mx_to_ma_large
subroutine maxwell_init_parallelization(this, grp)
subroutine maxwell_get_current(this, time, current)
subroutine, public maxwell_init(this, namespace)
subroutine maxwell_initialize(this)
subroutine maxwell_output_write(this)
logical function maxwell_is_tolerance_reached(this, tol)
class(maxwell_t) function, pointer maxwell_constructor(namespace)
subroutine maxwell_update_kinetic_energy(this)
logical function maxwell_restart_read_data(this)
subroutine maxwell_finalize(this)
subroutine maxwell_copy_quantities_to_interaction(partner, interaction)
subroutine, public mesh_interpolation_init(this, mesh)
This module defines the meshes, which are used in Octopus.
integer(int64) function, public mesh_global_index_from_coords(mesh, ix)
This function returns the true global index of the point for a given vector of integer coordinates.
integer function, public mesh_nearest_point(mesh, pos, dmin, rankmin)
Returns the index of the point which is nearest to a given vector position pos.
subroutine, public messages_print_with_emphasis(msg, iunit, namespace)
subroutine, public messages_not_implemented(feature, namespace)
character(len=512), private msg
subroutine, public messages_warning(no_lines, all_nodes, namespace)
subroutine, public messages_obsolete_variable(namespace, name, rep)
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_info(no_lines, iunit, debug_only, stress, all_nodes, namespace)
logical function mpi_grp_is_root(grp)
Is the current MPI process of grpcomm, root.
type(mpi_grp_t), public mpi_world
This module handles the communicators for the various parallelization strategies.
subroutine, public multicomm_end(mc)
subroutine, public multicomm_init(mc, namespace, base_grp, mode_para, n_node, index_range, min_range)
create index and domain communicators
integer, parameter, public mxll_field_total
integer, parameter, public mxll_field_trans
integer, parameter, public mxll_field_long
this module contains the output system
subroutine, public output_mxll_init(outp, namespace, space)
this module contains the output system
logical function, public parse_is_defined(namespace, name)
subroutine, public poisson_init(this, namespace, space, der, mc, stencil, qtot, label, solver, verbose, force_serial, force_cmplx)
subroutine, public poisson_end(this)
subroutine, public profiling_out(label)
Increment out counter and sum up difference between entry and exit time.
subroutine, public profiling_in(label, exclude)
Increment in counter and save entry time.
character(len=algo_label_len), parameter, public exp_gauss1_start
character(len=algo_label_len), parameter, public exp_gauss1_finish
character(len=algo_label_len), parameter, public exp_gauss1_extrapolate
character(len=algo_label_len), parameter, public exp_gauss1_propagate
character(len=algo_label_len), parameter, public exp_gauss2_finish
character(len=algo_label_len), parameter, public exp_gauss2_propagate
character(len=algo_label_len), parameter, public exp_gauss2_extrapolate
character(len=algo_label_len), parameter, public exp_gauss2_start
character(len=algo_label_len), parameter, public expmid_extrapolate
character(len=algo_label_len), parameter, public expmid_finish
character(len=algo_label_len), parameter, public expmid_start
character(len=algo_label_len), parameter, public expmid_propagate
character(len=algo_label_len), parameter, public leapfrog_propagate
character(len=algo_label_len), parameter, public leapfrog_finish
character(len=algo_label_len), parameter, public leapfrog_start
subroutine, public mxll_propagate_expgauss2(hm, namespace, gr, space, st, tr, time, dt)
Exponential propagation scheme with Gauss collocation points, s=2.
subroutine, public energy_mxll_calc_batch(gr, st, hm, energy_mxll, rs_fieldb, rs_field_plane_wavesb)
integer, parameter, public rs_trans_forward
subroutine, public mxll_propagate_leapfrog(hm, namespace, gr, space, st, tr, time, dt, counter)
subroutine, public mxll_propagate_expgauss1(hm, namespace, gr, space, st, tr, time, dt)
Exponential propagation scheme with Gauss collocation points, s=1.
subroutine, public mxll_propagation_step(hm, namespace, gr, space, st, tr, rs_stateb, ff_rs_inhom_t1, ff_rs_inhom_t2, time, dt)
subroutine, public spatial_constant_calculation(constant_calc, st, gr, hm, time, dt, delay, rs_state, set_initial_state)
subroutine, public set_medium_rs_state(st, gr, hm)
subroutine, public transform_rs_densities(hm, mesh, rs_charge_density, rs_current_density, ff_density, sign)
subroutine, public energy_mxll_calc(gr, st, hm, energy_mxll, rs_field, rs_field_plane_waves)
subroutine, public propagator_mxll_init(gr, namespace, st, hm, tr)
This module implements the basic propagator framework.
character(len=algo_label_len), parameter, public store_current_status
This module defines the quantity_t class and the IDs for quantities, which can be exposed by a system...
integer, parameter, public b_field
integer, parameter, public current
integer, parameter, public vector_potential
integer, parameter, public e_field
Implementation details for regridding.
logical function, public clean_stop(comm)
returns true if a file named stop exists
subroutine, public restart_init(restart, namespace, data_type, type, mc, ierr, mesh, dir, exact)
Initializes a restart object.
integer, parameter, public restart_type_dump
logical pure function, public restart_skip(restart)
Returns true if the restart information should neither be read nor written. This might happen because...
integer, parameter, public restart_td
integer, parameter, public restart_type_load
subroutine, public restart_end(restart)
This module is intended to contain "only mathematical" functions and procedures.
subroutine, public mxll_set_batch(rs_stateb, rs_state, np, dim, offset)
subroutine, public get_rs_state_at_point(rs_state_point, rs_state, pos, st, mesh)
subroutine, public get_electric_field_vector(rs_state_vector, electric_field_vector, ep_element)
subroutine, public get_transverse_rs_state(helmholtz, st, namespace)
subroutine, public mxll_get_batch(rs_stateb, rs_state, np, dim, offset)
subroutine, public get_rs_state_batch_selected_points(rs_state_point, rs_stateb, st, mesh)
subroutine, public states_mxll_end(st)
subroutine, public states_mxll_allocate(st, mesh)
Allocates the Maxwell states defined within a states_mxll_t structure.
subroutine, public states_mxll_init(st, namespace, space)
subroutine, public get_electric_field_state(rs_state, mesh, electric_field, ep_field, np)
subroutine, public get_magnetic_field_state(rs_state, mesh, rs_sign, magnetic_field, mu_field, np)
subroutine, public get_magnetic_field_vector(rs_state_vector, rs_sign, magnetic_field_vector, mu_element)
subroutine, public states_mxll_load(restart, st, mesh, namespace, space, zff, zff_dim, ierr, iter, lowest_missing, label, verbose)
subroutine, public states_mxll_dump(restart, st, space, mesh, zff, zff_dim, ierr, iter, st_start_writing, verbose)
subroutine, public states_mxll_read_user_def(namespace, space, mesh, der, st, bc, user_def_rs_state)
This module implements the abstract system type.
subroutine, public system_init_parallelization(this, grp)
Basic functionality: copy the MPI group. This function needs to be implemented by extended types that...
subroutine, public system_end(this)
integer, parameter, public out_maxwell_max
subroutine, public td_write_mxll_init(writ, namespace, iter, dt)
subroutine, public td_write_mxll_end(writ)
subroutine, public td_write_mxll_free_data(writ, namespace, space, gr, st, hm, helmholtz, outp, iter, time)
subroutine, public td_write_mxll_iter(writ, space, gr, st, hm, helmholtz, dt, iter, namespace)
type(type_t), public type_integer
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.
Descriptor of one algorithmic operation.
Class to transfer a current to a Maxwell field.
These class extend the list and list iterator to make an interaction list.
abstract interaction class
surrogate interaction class to avoid circular dependencies between modules.
Lorenz force between a systems of particles and an electromagnetic field.
Class describing Maxwell systems.
This is defined even when running serial.
class to transfer a Maxwell B field to a matter system
class to transfer a Maxwell field to a medium
class to transfer a Maxwell vector potential to a medium
Implements the an exponential RK scheme with Gauss collocation points, s=1 see also Hochbruck,...
Implements the an exponential RK scheme with Gauss collocation points, s=2 see also Hochbruck,...
Implements the explicit exponential midpoint propagator (without predictor-corrector)
Implements a propagator for the leap frog algorithm.
Abstract class implementing propagators.
Abstract class for systems.