(git:374b731)
Loading...
Searching...
No Matches
swarm_worker.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief Workers's routines for the swarm-framework
10!> \author Ole Schuett
11! **************************************************************************************************
30#include "../base/base_uses.f90"
31
32 IMPLICIT NONE
33 PRIVATE
34
35 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'swarm_worker'
36
38 PUBLIC :: swarm_worker_execute
39 PUBLIC :: swarm_worker_type
40
42 PRIVATE
43 INTEGER :: id = -1
44 INTEGER :: iw = -1
45 INTEGER :: behavior = -1
46 TYPE(glbopt_worker_type), POINTER :: glbopt => null()
47 !possibly more behaviors...
48 END TYPE swarm_worker_type
49
50CONTAINS
51
52! **************************************************************************************************
53!> \brief Initializes a swarm worker
54!> \param worker ...
55!> \param para_env ...
56!> \param input_declaration ...
57!> \param root_section ...
58!> \param input_path ...
59!> \param worker_id ...
60!> \author Ole Schuett
61! **************************************************************************************************
62 SUBROUTINE swarm_worker_init(worker, para_env, input_declaration, root_section, &
63 input_path, worker_id)
64 TYPE(swarm_worker_type), INTENT(INOUT) :: worker
65 TYPE(mp_para_env_type), POINTER :: para_env
66 TYPE(section_type), POINTER :: input_declaration
67 TYPE(section_vals_type), POINTER :: root_section
68 CHARACTER(LEN=*), INTENT(IN) :: input_path
69 INTEGER, INTENT(in) :: worker_id
70
71 TYPE(cp_logger_type), POINTER :: logger
72
73 worker%id = worker_id
74
75 ! getting an output unit for logging
76 logger => cp_get_default_logger()
77 worker%iw = cp_print_key_unit_nr(logger, root_section, &
78 "SWARM%PRINT%WORKER_RUN_INFO", extension=".workerLog")
79
80 CALL section_vals_val_get(root_section, "SWARM%BEHAVIOR", i_val=worker%behavior)
81
82 SELECT CASE (worker%behavior)
83 CASE (swarm_do_glbopt)
84 ALLOCATE (worker%glbopt)
85 CALL glbopt_worker_init(worker%glbopt, input_declaration, para_env, &
86 root_section, input_path, worker_id, worker%iw)
87 CASE DEFAULT
88 cpabort("got unknown behavior")
89 END SELECT
90
91 END SUBROUTINE swarm_worker_init
92
93! **************************************************************************************************
94!> \brief Central execute routine of the swarm worker
95!> \param worker ...
96!> \param cmd ...
97!> \param report ...
98!> \param should_stop ...
99!> \author Ole Schuett
100! **************************************************************************************************
101 SUBROUTINE swarm_worker_execute(worker, cmd, report, should_stop)
102 TYPE(swarm_worker_type), INTENT(INOUT) :: worker
103 TYPE(swarm_message_type), INTENT(IN) :: cmd
104 TYPE(swarm_message_type), INTENT(OUT) :: report
105 LOGICAL, INTENT(INOUT) :: should_stop
106
107 CHARACTER(LEN=default_string_length) :: command
108
109 CALL swarm_message_get(cmd, "command", command)
110 CALL swarm_message_add(report, "worker_id", worker%id)
111
112 IF (trim(command) == "shutdown") THEN
113 IF (worker%iw > 0) WRITE (worker%iw, *) "SWARM| Received shutdown command, quitting."
114 should_stop = .true.
115 ELSE IF (trim(command) == "wait") THEN !only needed for serial driver
116 CALL swarm_message_add(report, "status", "wait_done")
117 ELSE
118 SELECT CASE (worker%behavior)
119 CASE (swarm_do_glbopt)
120 CALL glbopt_worker_execute(worker%glbopt, cmd, report)
121 CASE DEFAULT
122 cpabort("got unknown behavior")
123 END SELECT
124 END IF
125
126 IF (.NOT. swarm_message_haskey(report, "status")) &
127 CALL swarm_message_add(report, "status", "ok")
128
129 END SUBROUTINE swarm_worker_execute
130
131! **************************************************************************************************
132!> \brief Finalizes a swarm worker
133!> \param worker ...
134!> \author Ole Schuett
135! **************************************************************************************************
136 SUBROUTINE swarm_worker_finalize(worker)
137 TYPE(swarm_worker_type), INTENT(INOUT) :: worker
138
139 SELECT CASE (worker%behavior)
140 CASE (swarm_do_glbopt)
141 CALL glbopt_worker_finalize(worker%glbopt)
142 DEALLOCATE (worker%glbopt)
143 CASE DEFAULT
144 cpabort("got unknown behavior")
145 END SELECT
146
147 END SUBROUTINE swarm_worker_finalize
148
149END MODULE swarm_worker
150
Adds an entry from a swarm-message.
Returns an entry from a swarm-message.
various routines to log and control the output. The idea is that decisions about where to log should ...
type(cp_logger_type) function, pointer, public cp_get_default_logger()
returns the default logger
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer function, public cp_print_key_unit_nr(logger, basis_section, print_key_path, extension, middle_name, local, log_filename, ignore_should_output, file_form, file_position, file_action, file_status, do_backup, on_file, is_new_file, mpi_io, fout)
...
Worker routines used by global optimization schemes.
subroutine, public glbopt_worker_init(worker, input_declaration, para_env, root_section, input_path, worker_id, iw)
Initializes worker for global optimization.
subroutine, public glbopt_worker_finalize(worker)
Finalizes worker for global optimization.
subroutine, public glbopt_worker_execute(worker, cmd, report)
Central execute routine of global optimization worker.
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public swarm_do_glbopt
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public default_string_length
Definition kinds.F:57
Interface to the message passing library MPI.
Swarm-message, a convenient data-container for with build-in serialization.
logical function, public swarm_message_haskey(msg, key)
Checks if a swarm-message contains an entry with the given key.
Workers's routines for the swarm-framework.
subroutine, public swarm_worker_finalize(worker)
Finalizes a swarm worker.
subroutine, public swarm_worker_execute(worker, cmd, report, should_stop)
Central execute routine of the swarm worker.
subroutine, public swarm_worker_init(worker, para_env, input_declaration, root_section, input_path, worker_id)
Initializes a swarm worker.
type of a logger, at the moment it contains just a print level starting at which level it should be l...
represent a section of the input file
stores all the informations relevant to an mpi environment