Octopus
multisystem.F90
Go to the documentation of this file.
1!! Copyright (C) 2019-2020 M. Oliveira, Heiko Appel
2!! Copyright (C) 2021 S. Ohlmann
3!!
4!! This program is free software; you can redistribute it and/or modify
5!! it under the terms of the GNU General Public License as published by
6!! the Free Software Foundation; either version 2, or (at your option)
7!! any later version.
8!!
9!! This program is distributed in the hope that it will be useful,
10!! but WITHOUT ANY WARRANTY; without even the implied warranty of
11!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12!! GNU General Public License for more details.
13!!
14!! You should have received a copy of the GNU General Public License
15!! along with this program; if not, write to the Free Software
16!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
17!! 02110-1301, USA.
18!!
19
20#include "global.h"
21
47 use debug_oct_m
48 use global_oct_m
55 use loct_oct_m
57 use mpi_oct_m
61 use system_oct_m
62 implicit none
63
64 private
65 public :: &
68
75 type, extends(system_t), abstract :: multisystem_t
76 type(system_list_t) :: list
77 contains
78 procedure :: execute_algorithm => multisystem_execute_algorithm
79 procedure :: init_parallelization => multisystem_init_parallelization
80 procedure :: next_time_on_largest_dt => multisystem_next_time_on_largest_dt
81 procedure :: reset_iteration_counters => multisystem_reset_iteration_counters
82 procedure :: init_algorithm => multisystem_init_algorithm
83 procedure :: algorithm_finished => multisystem_algorithm_finished
84 procedure :: init_iteration_counters => multisystem_init_iteration_counters
85 procedure :: propagation_start => multisystem_propagation_start
86 procedure :: propagation_finish => multisystem_propagation_finish
87 procedure :: add_partners_to_list => multisystem_add_partners_to_list
88 procedure :: create_interactions => multisystem_create_interactions
89 procedure :: init_interaction => multisystem_init_interaction
90 procedure :: write_interaction_graph => multisystem_write_interaction_graph
91 procedure :: initial_conditions => multisystem_initial_conditions
92 procedure :: do_algorithmic_operation => multisystem_do_algorithmic_operation
93 procedure :: is_tolerance_reached => multisystem_is_tolerance_reached
94 procedure :: update_quantity => multisystem_update_quantity
95 procedure :: init_interaction_as_partner => multisystem_init_interaction_as_partner
96 procedure :: copy_quantities_to_interaction => multisystem_copy_quantities_to_interaction
97 procedure :: process_is_slave => multisystem_process_is_slave
98 procedure :: start_barrier => multisystem_start_barrier
99 procedure :: end_barrier => multisystem_end_barrier
100 procedure :: arrived_at_barrier => multisystem_arrived_at_barrier
101 procedure :: restart_write => multisystem_restart_write
102 procedure :: restart_read => multisystem_restart_read
103 procedure :: restart_write_data => multisystem_restart_write_data
104 procedure :: restart_read_data => multisystem_restart_read_data
105 procedure :: update_kinetic_energy => multisystem_update_kinetic_energy
106 procedure :: update_potential_energy => multisystem_update_potential_energy
107 procedure :: update_internal_energy => multisystem_update_internal_energy
108 procedure :: get_flat_list => multisystem_get_flat_list
109 end type multisystem_t
110
111contains
112
113 ! ---------------------------------------------------------------------------------------
116 recursive subroutine multisystem_init_parallelization(this, grp)
117 class(multisystem_t), intent(inout) :: this
118 type(mpi_grp_t), intent(in) :: grp
119
120 type(system_iterator_t) :: iter
121 class(system_t), pointer :: sys
122 type(mpi_grp_t) :: sys_grp
123
125
126 call system_init_parallelization(this, grp)
127
128 ! Now parallelize over systems in this multisystem
129 call iter%start(this%list)
130 do while (iter%has_next())
131 sys => iter%get_next()
132 ! for now, duplicate communicator - more complicated parallelization schemes can be implemented here
133 call mpi_grp_duplicate(sys_grp, grp)
134 call sys%init_parallelization(sys_grp)
135 end do
136
139
140 ! ---------------------------------------------------------------------------------------
141 recursive function multisystem_next_time_on_largest_dt(this) result(next_time_on_largest_dt)
142 class(multisystem_t), intent(inout) :: this
143 real(real64) :: next_time_on_largest_dt
144
145 type(system_iterator_t) :: iter
146 class(system_t), pointer :: system
147 type(iteration_counter_t) :: iteration
148
150
151 next_time_on_largest_dt = m_zero
152 call iter%start(this%list)
153 do while (iter%has_next())
154 system => iter%get_next()
155 select type (system)
156 class is (multisystem_t)
157 next_time_on_largest_dt = max(next_time_on_largest_dt, system%next_time_on_largest_dt())
158 class default
159 iteration = system%iteration + 1
160 next_time_on_largest_dt = max(next_time_on_largest_dt, iteration%value())
161 end select
162 end do
163
166
167 ! ---------------------------------------------------------------------------------------
168 recursive subroutine multisystem_execute_algorithm(this)
169 class(multisystem_t), intent(inout) :: this
170
171 type(system_iterator_t) :: iter
172 class(system_t), pointer :: system
174 type(event_handle_t) :: debug_handle
178 debug_handle = multisystem_debug_write_event_in(this%namespace, event_function_call_t("multisystem_dt_operation"), &
179 system_iteration = this%iteration, algo_iteration = this%algo%iteration)
181 ! Multisystem
184 ! Subsystems
185 call iter%start(this%list)
186 do while (iter%has_next())
187 system => iter%get_next()
188 call system%execute_algorithm()
189 end do
191 call multisystem_debug_write_event_out(debug_handle, system_iteration = this%iteration, algo_iteration = this%algo%iteration)
196 ! ---------------------------------------------------------------------------------------
197 recursive subroutine multisystem_reset_iteration_counters(this, accumulated_iterations)
198 class(multisystem_t), intent(inout) :: this
199 integer, intent(in) :: accumulated_iterations
201 type(system_iterator_t) :: iter
202 class(system_t), pointer :: system
203
205
206 ! Multisystem iteration counters
207 call system_reset_iteration_counters(this, accumulated_iterations)
208
209 ! Subsystems iteration counters
210 call iter%start(this%list)
211 do while (iter%has_next())
212 system => iter%get_next()
213 call system%reset_iteration_counters(accumulated_iterations)
214 end do
215
218
219 ! ---------------------------------------------------------------------------------------
220 recursive subroutine multisystem_init_algorithm(this, factory)
221 class(multisystem_t), intent(inout) :: this
222 class(algorithm_factory_t), intent(in) :: factory
223
224 type(system_iterator_t) :: iter
225 class(system_t), pointer :: system
226
228
229 ! Now initialized the propagators of the subsystems
230 call iter%start(this%list)
231 do while (iter%has_next())
232 system => iter%get_next()
233 call system%init_algorithm(factory)
234 end do
235
236 ! Initialize the propagator of the multisystem. By default the
237 ! multisystem itself and its own quantities are kept unchanged
238 ! by using the static propagator. However, the subsystems are allowed to have
239 ! their own propagators and those do not have to be static.
240 ! Needs to be done after initializing the subsystems propagators,
241 ! as we use the largest dt of the subsystems.
242 this%algo => factory%create_static(this)
243 call this%algo%rewind()
244
246
248 end subroutine multisystem_init_algorithm
249
250 ! ---------------------------------------------------------------------------------------
251 recursive function multisystem_algorithm_finished(this) result(finished)
252 class(multisystem_t), intent(in) :: this
253 logical :: finished
254
255 type(system_iterator_t) :: iter
256 class(system_t), pointer :: system
257
258 ! Check if multisystem itself is finished
259 finished = this%algo%finished()
260
261 ! Check subsystems
262 call iter%start(this%list)
263 do while (iter%has_next())
264 system => iter%get_next()
265 finished = finished .and. system%algorithm_finished()
266 end do
267
269
270 ! ---------------------------------------------------------------------------------------
273 recursive subroutine multisystem_init_iteration_counters(this)
274 class(multisystem_t), intent(inout) :: this
275
276 type(system_iterator_t) :: iter
277 class(system_t), pointer :: system
278
280
281 ! initialize multisystem iteration counters
283
284 ! initialize iteration counters of subsystems
285 call iter%start(this%list)
286 do while (iter%has_next())
287 system => iter%get_next()
288 call system%init_iteration_counters()
289 end do
293
294 ! ---------------------------------------------------------------------------------------
297 recursive subroutine multisystem_propagation_start(this)
298 class(multisystem_t), intent(inout) :: this
299
300 type(system_iterator_t) :: iter
301 class(system_t), pointer :: system
302
303 type(event_handle_t) :: debug_handle
304
306
307 debug_handle = multisystem_debug_write_event_in(this%namespace, event_function_call_t("multisystem_propagation_start"), &
308 system_iteration = this%iteration, algo_iteration = this%algo%iteration)
309
310 ! First start the propagation of the subsystems
311 call iter%start(this%list)
312 do while (iter%has_next())
313 system => iter%get_next()
314 call system%propagation_start()
315 end do
316
317 ! Once the subsystems are initialized start the propagation of the multisystem
318 call system_propagation_start(this)
319
320 call multisystem_debug_write_event_out(debug_handle, system_iteration = this%iteration, algo_iteration = this%algo%iteration)
321
323 end subroutine multisystem_propagation_start
324
325 ! ---------------------------------------------------------------------------------------
328 recursive subroutine multisystem_propagation_finish(this)
329 class(multisystem_t), intent(inout) :: this
330
331 type(system_iterator_t) :: iter
332 class(system_t), pointer :: system
333
334 type(event_handle_t) :: debug_handle
335
337
338 debug_handle = multisystem_debug_write_event_in(this%namespace, event_function_call_t("multisystem_propagation_finish"), &
339 system_iteration = this%iteration, algo_iteration = this%algo%iteration)
340
341 ! Finish the propagation of the multisystem
343
344 ! Now finish the propagation of the subsystems
345 call iter%start(this%list)
346 do while (iter%has_next())
347 system => iter%get_next()
348 call system%propagation_finish()
349 end do
350
351 call multisystem_debug_write_event_out(debug_handle, system_iteration = this%iteration, algo_iteration = this%algo%iteration)
352
354 end subroutine multisystem_propagation_finish
355
356 ! ---------------------------------------------------------
364 recursive subroutine multisystem_add_partners_to_list(this, list, interaction_type)
365 class(multisystem_t), intent(in) :: this
366 class(partner_list_t), intent(inout) :: list
367 integer, optional, intent(in) :: interaction_type
368
369 type(system_iterator_t) :: iter
370 class(system_t), pointer :: system
371
372 if (present(interaction_type)) then
373 if (any(this%supported_interactions_as_partner == interaction_type)) then
374 call list%add(this)
375 end if
376 else
377 call list%add(this)
378 end if
379
380 call iter%start(this%list)
381 do while (iter%has_next())
382 system => iter%get_next()
383 call system%add_partners_to_list(list, interaction_type)
384 end do
385
387
388 ! ---------------------------------------------------------
393 recursive subroutine multisystem_create_interactions(this, interaction_factory, available_partners)
394 class(multisystem_t), intent(inout) :: this
395 class(interactions_factory_abst_t), intent(in) :: interaction_factory
396 class(partner_list_t), target, intent(in) :: available_partners
397
398 type(system_iterator_t) :: iter
399 class(system_t), pointer :: subsystem
400
401 ! Create the multisystem interactions
402 call system_create_interactions(this, interaction_factory, available_partners)
403
404 ! Create the subsystems interactions
405 call iter%start(this%list)
406 do while (iter%has_next())
407 subsystem => iter%get_next()
408 call subsystem%create_interactions(interaction_factory, available_partners)
409 end do
410
412
413 ! ---------------------------------------------------------
419
420 subroutine multisystem_init_interaction(this, interaction)
421 class(multisystem_t), target, intent(inout) :: this
422 class(interaction_t), intent(inout) :: interaction
423
425
426 ! The multisystem class should never know about any specific interaction.
427 ! Only classes that extend it can know about specific interactions.
428 ! Such classes should override this method to add new supported interactions.
429 message(1) = "Trying to initialize an interaction in the multi-system container class"
430 call messages_fatal(1, namespace=this%namespace)
431
433 end subroutine multisystem_init_interaction
434
435 ! ---------------------------------------------------------------------------------------
438 recursive subroutine multisystem_write_interaction_graph(this, iunit, include_ghosts)
439 class(multisystem_t), intent(in) :: this
440 integer, intent(in) :: iunit
441 logical, intent(in) :: include_ghosts
442
443 class(system_t), pointer :: system
444 class(interaction_t), pointer :: interaction
445 type(system_iterator_t) :: sys_iter
446 type(interaction_iterator_t) :: inter_iter
447
449
450 ! Loop over all the subsystems
451 call sys_iter%start(this%list)
452 do while (sys_iter%has_next())
453 system => sys_iter%get_next()
454
455 ! Loop over the interactions that this subsystem has
456 call inter_iter%start(system%interactions)
457 do while (inter_iter%has_next())
458 interaction => inter_iter%get_next()
459
460 ! Write interaction to DOT graph if this interaction has a partner
461 select type (interaction)
462 type is (ghost_interaction_t)
463 if (include_ghosts) then
464 write(iunit, '(2x,a)') '"' + trim(system%namespace%get()) + '" -> "' + trim(interaction%partner%namespace%get()) + &
465 '" [label="'+ interaction%label + '"];'
466 end if
467 ! Do not include systems connected by ghost interactions
468 class default
469 write(iunit, '(2x,a)') '"' + trim(system%namespace%get()) + '" -> "' + trim(interaction%partner%namespace%get()) + &
470 '" [label="'+ interaction%label + '"];'
471 end select
472 end do
473
474 ! If this subsystem is also a multisystem, then we also need to traverse it
475 select type (system)
476 class is (multisystem_t)
477 call system%write_interaction_graph(iunit, include_ghosts)
478 end select
479 end do
480
483
484 ! ---------------------------------------------------------
485 recursive subroutine multisystem_initial_conditions(this)
486 class(multisystem_t), intent(inout) :: this
487
488 type(system_iterator_t) :: iter
489 class(system_t), pointer :: system
490
492
493 call iter%start(this%list)
494 do while (iter%has_next())
495 system => iter%get_next()
496 call system%initial_conditions()
497 end do
498
500 end subroutine multisystem_initial_conditions
501
502 ! ---------------------------------------------------------
503 logical function multisystem_do_algorithmic_operation(this, operation, updated_quantities) result(done)
504 class(multisystem_t), intent(inout) :: this
505 class(algorithmic_operation_t), intent(in) :: operation
506 integer, allocatable, intent(out) :: updated_quantities(:)
507
509
510 ! Currently there are no multisystem specific algorithmic operations
511 done = .false.
512
515
516 ! ---------------------------------------------------------
517 recursive logical function multisystem_is_tolerance_reached(this, tol) result(converged)
518 class(multisystem_t), intent(in) :: this
519 real(real64), intent(in) :: tol
520
521 type(system_iterator_t) :: iter
522 class(system_t), pointer :: system
523
525
526 converged = .true.
527 call iter%start(this%list)
528 do while (iter%has_next())
529 system => iter%get_next()
530 if (.not. system%is_tolerance_reached(tol)) converged = .false.
531 end do
532
535
536 ! ---------------------------------------------------------
537 subroutine multisystem_update_quantity(this, iq)
538 class(multisystem_t), intent(inout) :: this
539 integer, intent(in) :: iq
540
542
543 ! The multisystem class should never know about any specific quantities.
544 ! Only classes that extend it can know about specific quantities.
545 ! Such classes should override this method to add new supported quantities.
546 message(1) = "Trying to update a quantity in the multi-system container class"
547 call messages_fatal(1, namespace=this%namespace)
548
550 end subroutine multisystem_update_quantity
551
552 ! ---------------------------------------------------------
553 subroutine multisystem_init_interaction_as_partner(partner, interaction)
554 class(multisystem_t), intent(in) :: partner
555 class(interaction_surrogate_t), intent(inout) :: interaction
556
558
559 ! The multisystem class should never know about any specific interaction.
560 ! Only classes that extend it can know about specific interactions.
561 ! Such classes should override this method to add new supported interactions.
562 message(1) = "Trying to initialize an interaction as partner in the multi-system container class"
563 call messages_fatal(1, namespace=partner%namespace)
564
567
568 ! ---------------------------------------------------------
569 subroutine multisystem_copy_quantities_to_interaction(partner, interaction)
570 class(multisystem_t), intent(inout) :: partner
571 class(interaction_surrogate_t), intent(inout) :: interaction
572
574
575 ! The multisystem class should never know about any specific quantities.
576 ! Only classes that extend it can know about specific quantities.
577 ! Such classes should override this method to add new supported quantities.
578 message(1) = "Trying to copy quantities to interaction in the multi-system container class"
579 call messages_fatal(1, namespace=partner%namespace)
580
583
584 ! ---------------------------------------------------------
585 recursive logical function multisystem_process_is_slave(this) result(is_slave)
586 class(multisystem_t), intent(in) :: this
587
588 type(system_iterator_t) :: iter
589 class(system_t), pointer :: system
590
592
593 is_slave = .false.
594 call iter%start(this%list)
595 do while (iter%has_next())
596 system => iter%get_next()
597 if (system%process_is_slave()) is_slave = .true.
598 end do
599
602
603 !--------------------------------------------------------------------
607 recursive subroutine multisystem_update_kinetic_energy(this)
608 class(multisystem_t), intent(inout) :: this
609
611
612 ! We currently do not have the center of mass coordinates implemented for multisystems,
613 ! hence we set the kinetic energy to zero.
614 ! The kinetic energies of the constituents are contributing to the internal energy.
615
616 this%kinetic_energy = m_zero
617
620
621 !---------------------------------------------------------
622 recursive subroutine multisystem_update_internal_energy(this)
623 class(multisystem_t), intent(inout) :: this
624
625 class(system_t), pointer :: system
626 class(system_t), pointer :: system_2
627 type(system_iterator_t) :: system_iter
628 type(system_iterator_t) :: system_iter_2
629
631
632 ! The internal energy of the multisystem contains the kinetic and internal energies of the consistuents
633 !TODO: the kinetic energy wrt the center of mass motion should be subtracted.
634
635 this%internal_energy = m_zero
636
637 call system_iter%start(this%list)
638 do while (system_iter%has_next())
639
640 system => system_iter%get_next()
641
642 ! First add the kinetic energies of the subsystems
643 call system%update_kinetic_energy()
644 this%internal_energy = this%internal_energy + system%kinetic_energy
645
646 ! First add the internal energies of the subsystems
647 call system%update_internal_energy()
648 this%internal_energy = this%internal_energy + system%internal_energy
649
650 ! Now add the (inter-) interactions between the systems in the container.
651 call system_iter_2%start(this%list)
652 do while(system_iter_2%has_next())
653
654 system_2 => system_iter_2%get_next()
655
656 ! exclude self-interactions (intra-interactions) as they are included in the internal energy
657 ! of the subsystem, which was already added above.
658 if(.not. associated(system, system_2)) then
659 this%internal_energy = this%internal_energy + multisystem_pair_energy(system, system_2)
660 end if
661 end do ! system_iter_2
663 end do ! system_iter
664
667
668 ! ---------------------------------------------------------
682 class(multisystem_t), intent(inout) :: this
683
684 type(system_iterator_t) :: system_iter
685 class(system_t), pointer :: system
686 type(interaction_iterator_t) :: interaction_iter
687 class(interaction_t), pointer :: interaction
688 type(system_list_t) :: flat_list
689
691
692 this%potential_energy = m_zero
693
694 ! We need to handle interactions of the container itself:
696
697 ! generate a list of all systems inside the container and its subcontainers:
698 call this%get_flat_list(flat_list)
699
700 ! loop over all systems inside the container
701 call system_iter%start(flat_list)
702 do while (system_iter%has_next())
703
704 system => system_iter%get_next()
705
706 ! Even though we are not using the potential energy of the subsystems here, we need to trigger their calculation
707 call system%update_potential_energy()
708
709 ! loop over all interactions and discard those with partners inside the container
710 call interaction_iter%start(system%interactions)
711 do while (interaction_iter%has_next())
712 interaction => interaction_iter%get_next()
713 if(.not. flat_list%contains(interaction%partner) .and. .not. interaction%intra_interaction) then
714 call interaction%calculate_energy()
715 this%potential_energy = this%potential_energy + interaction%energy
716 end if
717 end do
718
719 end do
720
723
724 ! ---------------------------------------------------------
731 recursive real(real64) function multisystem_pair_energy(partner_A, partner_B) result(pair_energy)
732 class(interaction_partner_t), intent(in) :: partner_a
733 class(interaction_partner_t), intent(in) :: partner_b
734
735 class(system_t), pointer :: system_a
736 class(system_t), pointer :: system_b
737 type(system_iterator_t) :: system_iterator_a
738 type(system_iterator_t) :: system_iterator_b
739
741
742 pair_energy = m_zero
743
744 select type(partner_a)
745 class is (multisystem_t) ! partner_A is container
746
747 call system_iterator_a%start(partner_a%list)
748 do while( system_iterator_a%has_next() )
749
750 system_a => system_iterator_a%get_next()
751
752 select type(partner_b)
753 class is (multisystem_t)
754
755 call system_iterator_b%start(partner_b%list)
756 do while( system_iterator_b%has_next() )
757 system_b => system_iterator_b%get_next()
758 pair_energy = pair_energy + multisystem_pair_energy(system_a, system_b)
759 end do
760
761 class is (system_t)
762 pair_energy = pair_energy + interaction_energy(partner_a, partner_b)
763 class default
764 assert(.false.) ! partner_A must be a system_t
765 end select
766 end do
767
768 class is (system_t) ! partner_A is non-container system
769
770 select type(partner_b)
771 class is (multisystem_t) ! partner_B is container
772
773 call system_iterator_b%start(partner_b%list)
774 do while( system_iterator_b%has_next() )
775 system_b => system_iterator_b%get_next()
776 pair_energy = pair_energy + multisystem_pair_energy(partner_a, system_b)
777 end do
778
779 class default ! both partner_A and partner_B are explicit: we need to calculate
780 pair_energy = pair_energy + interaction_energy(partner_a, partner_b)
781 end select
782
783 class default
784 assert(.false.)
785 end select
786
788
789 contains
790
791 real(real64) function interaction_energy(system, partner) result (energy)
792 class(system_t), target, intent(in) :: system
793 class(interaction_partner_t), target, intent(in) :: partner
794
795 type(interaction_iterator_t) :: interaction_iterator
796 class(interaction_t), pointer :: interaction
797
798 energy = m_zero
799
800 call interaction_iterator%start(system%interactions)
801 do while(interaction_iterator%has_next())
802 interaction => interaction_iterator%get_next()
803 if( associated(interaction%partner, partner)) then
804 call interaction%calculate_energy()
805 energy = energy + interaction%energy
806 end if
807 end do
808 end function interaction_energy
809
810 end function multisystem_pair_energy
811
812
813 ! ---------------------------------------------------------
816 recursive subroutine multisystem_get_flat_list(this, flat_list)
817 class(multisystem_t), intent(in) :: this
818 type(system_list_t), intent(out) :: flat_list
819
820 class(interaction_partner_t), pointer :: partner
821 type(partner_iterator_t) :: iterator
822
825 call iterator%start(this%list)
826 do while (iterator%has_next())
827 partner => iterator%get_next()
828
829 call flat_list%add(partner)
830
831 select type (partner)
832 class is (multisystem_t)
833 ! Also include the subsystems of a multisystem
834 call partner%get_flat_list(flat_list)
835 end select
836
837 end do
838
840
841 end subroutine multisystem_get_flat_list
842
843 ! ---------------------------------------------------------
844 recursive subroutine multisystem_end(this)
845 class(multisystem_t), intent(inout) :: this
846
847 type(system_iterator_t) :: iter
848 class(system_t), pointer :: system
849
850 push_sub(multisystem_end)
851
852 call iter%start(this%list)
853 do while (iter%has_next())
854 system => iter%get_next()
855 if (associated(system)) then
856 deallocate(system)
857 end if
858 end do
859
860 call system_end(this)
861
862 pop_sub(multisystem_end)
863 end subroutine multisystem_end
864
865 ! ---------------------------------------------------------
866 recursive subroutine multisystem_start_barrier(this, target_time, barrier_index)
867 class(multisystem_t), intent(inout) :: this
868 real(real64), intent(in) :: target_time
869 integer, intent(in) :: barrier_index
870
871 type(system_iterator_t) :: iter
872 class(system_t), pointer :: system
873
875
876 call iter%start(this%list)
877 do while (iter%has_next())
878 system => iter%get_next()
879 call system%start_barrier(target_time, barrier_index)
880 end do
881
883 end subroutine multisystem_start_barrier
885 ! ---------------------------------------------------------
886 recursive subroutine multisystem_end_barrier(this, barrier_index)
887 class(multisystem_t), intent(inout) :: this
888 integer, intent(in) :: barrier_index
889
890 type(system_iterator_t) :: iter
891 class(system_t), pointer :: system
892
894
895 call iter%start(this%list)
896 do while (iter%has_next())
897 system => iter%get_next()
898 call system%end_barrier(barrier_index)
899 end do
900
902 end subroutine multisystem_end_barrier
903
904 ! ---------------------------------------------------------
905 recursive logical function multisystem_arrived_at_barrier(this, barrier_index)
906 class(multisystem_t), intent(inout) :: this
907 integer, intent(in) :: barrier_index
908
909 type(system_iterator_t) :: iter
910 class(system_t), pointer :: system
911
913
915 call iter%start(this%list)
916 do while (iter%has_next())
917 system => iter%get_next()
919 system%arrived_at_barrier(barrier_index)
920 end do
921
924
925 ! ---------------------------------------------------------
926 recursive subroutine multisystem_restart_write(this)
927 class(multisystem_t), intent(inout) :: this
928
929 type(system_iterator_t) :: iter
930 class(system_t), pointer :: system
931
933
934 ! do generic restart steps
935 call system_restart_write(this)
936
937 ! loop over all subsystems
938 call iter%start(this%list)
939 do while (iter%has_next())
940 system => iter%get_next()
941 call system%restart_write()
942 end do
943 message(1) = "Wrote restart data for multisystem "//trim(this%namespace%get())
944 call messages_info(1, namespace=this%namespace)
945
947 end subroutine multisystem_restart_write
948
949 ! ---------------------------------------------------------
950 recursive logical function multisystem_restart_read(this)
951 class(multisystem_t), intent(inout) :: this
952
953 type(system_iterator_t) :: iter
954 class(system_t), pointer :: system
955
957
958 ! read generic restart data
959 multisystem_restart_read = system_restart_read(this)
960 call iter%start(this%list)
961 do while (iter%has_next())
962 system => iter%get_next()
963 ! TODO: adapt logics here for consistent restarting
965 system%restart_read()
966 end do
967
969 message(1) = "Successfully read restart data for multisystem "//trim(this%namespace%get())
970 call messages_info(1, namespace=this%namespace)
971 end if
972
974 end function multisystem_restart_read
975
976 ! ---------------------------------------------------------
977 subroutine multisystem_restart_write_data(this)
978 class(multisystem_t), intent(inout) :: this
981
982 ! do not write restart data for multisystem_t
983
985 end subroutine multisystem_restart_write_data
986
987 ! ---------------------------------------------------------
988 ! this function returns true if restart data could be read
989 logical function multisystem_restart_read_data(this)
990 class(multisystem_t), intent(inout) :: this
991
993
995
999end module multisystem_oct_m
real(real64) function interaction_energy(system, partner)
This module defines the abstract interfact for algorithm factories.
This module implements the basic elements defining algorithms.
Definition: algorithm.F90:141
real(real64), parameter, public m_zero
Definition: global.F90:187
This module defines the abstract interaction_t class, and some auxiliary classes for interactions.
This module defines classes and functions for interaction partners.
This module defines the abstract class for the interaction factory.
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
Definition: messages.F90:420
subroutine mpi_grp_duplicate(mpi_grp_out, mpi_grp_in)
Definition: mpi.F90:408
This module implements the multisystem debug functionality.
type(event_handle_t) function, public multisystem_debug_write_event_in(system_namespace, event, extra, system_iteration, algo_iteration, interaction_iteration, partner_iteration, requested_iteration)
subroutine, public multisystem_debug_write_event_out(handle, extra, update, system_iteration, algo_iteration, interaction_iteration, partner_iteration, requested_iteration)
This module implements the abstract multisystem class.
recursive subroutine, public multisystem_end(this)
recursive logical function multisystem_process_is_slave(this)
recursive logical function multisystem_arrived_at_barrier(this, barrier_index)
recursive subroutine multisystem_init_algorithm(this, factory)
recursive subroutine multisystem_update_internal_energy(this)
recursive subroutine multisystem_create_interactions(this, interaction_factory, available_partners)
create the interactions of the multisystem
recursive subroutine multisystem_restart_write(this)
recursive subroutine multisystem_add_partners_to_list(this, list, interaction_type)
add interaction partners contained in the multisystem to a list
subroutine multisystem_init_interaction(this, interaction)
initialize a specific interaction
subroutine multisystem_update_quantity(this, iq)
subroutine multisystem_update_potential_energy(this)
Calculate the potential energy for a container.
recursive subroutine multisystem_reset_iteration_counters(this, accumulated_iterations)
recursive logical function multisystem_restart_read(this)
subroutine multisystem_init_interaction_as_partner(partner, interaction)
recursive subroutine multisystem_propagation_start(this)
call the propagation_start routine for all contained systems
recursive logical function multisystem_is_tolerance_reached(this, tol)
recursive real(real64) function multisystem_next_time_on_largest_dt(this)
recursive subroutine multisystem_propagation_finish(this)
call the propagation_finish routine for all contained systems
recursive subroutine multisystem_initial_conditions(this)
subroutine multisystem_copy_quantities_to_interaction(partner, interaction)
recursive real(real64) function multisystem_pair_energy(partner_A, partner_B)
This function calculates the complete interaction energy between partner_A and partner_B,...
recursive subroutine multisystem_execute_algorithm(this)
recursive subroutine multisystem_init_parallelization(this, grp)
brief initialize the parallelization of the multisystem
recursive subroutine multisystem_get_flat_list(this, flat_list)
Generate a list of all systems contained in a multisystem, including those inside child containers.
logical function multisystem_restart_read_data(this)
subroutine multisystem_restart_write_data(this)
recursive subroutine multisystem_end_barrier(this, barrier_index)
recursive subroutine multisystem_update_kinetic_energy(this)
Calculate the kinetic energy: The kinetic energy of a container (multisystem) is defined by the kinet...
recursive subroutine multisystem_init_iteration_counters(this)
initialize the iteration counters of the contained systems
recursive subroutine multisystem_start_barrier(this, target_time, barrier_index)
recursive logical function multisystem_algorithm_finished(this)
recursive subroutine multisystem_write_interaction_graph(this, iunit, include_ghosts)
write a graphical representation of the interactions
logical function multisystem_do_algorithmic_operation(this, operation, updated_quantities)
This module implements the abstract system type.
Definition: system.F90:118
subroutine, public system_init_iteration_counters(this)
Initialize the iteration counters of the system and its interactions, algorithms and quantities.
Definition: system.F90:944
subroutine, public system_update_potential_energy(this)
Calculate the potential energy of the system. The potential energy is defined as the sum of all energ...
Definition: system.F90:1279
subroutine, public system_init_parallelization(this, grp)
Basic functionality: copy the MPI group. This function needs to be implemented by extended types that...
Definition: system.F90:1195
recursive subroutine, public system_create_interactions(this, interaction_factory, available_partners)
create the interactions of the system
Definition: system.F90:502
subroutine, public system_propagation_finish(this)
Definition: system.F90:1031
subroutine, public system_execute_algorithm(this)
perform one or more algorithmic operations
Definition: system.F90:331
subroutine, public system_propagation_start(this)
Definition: system.F90:977
subroutine, public system_reset_iteration_counters(this, accumulated_iterations)
Definition: system.F90:449
Abstract class for the algorithm factories.
Descriptor of one algorithmic operation.
Definition: algorithm.F90:163
The ghost ineraction is a dummy interaction, which needs to be setup between otherwise non-interactin...
These class extend the list and list iterator to make an interaction list.
abstract interaction class
abstract class for general interaction partners
surrogate interaction class to avoid circular dependencies between modules.
handle to keep track of in- out- events
the abstract multisystem class
These classes extends the list and list iterator to create a system list.
Definition: system.F90:302
Abstract class for systems.
Definition: system.F90:172
int true(void)