Line data Source code
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 module contains the master routine handling the tree creation,
10 : !> communication with workers and task distribution
11 : !> For each idle working group the master creates a new global tree
12 : !> element, and if neccessay a related sub tree element,
13 : !> OR find the next element to calculate the exact energy.
14 : !> Goal is to keep at least the exact energy calculation working groups
15 : !> as busy as possible.
16 : !> Master also checks for incomming results and update the tree and the
17 : !> acceptance ratios.
18 : !> \par History
19 : !> 11.2012 created [Mandes Schoenherr]
20 : !> \author Mandes
21 : ! **************************************************************************************************
22 :
23 : MODULE tmc_master
24 : USE cell_methods, ONLY: init_cell
25 : USE cp_external_control, ONLY: external_control
26 : USE cp_log_handling, ONLY: cp_to_string
27 : USE global_types, ONLY: global_environment_type
28 : USE kinds, ONLY: dp,&
29 : int_8
30 : USE machine, ONLY: m_flush,&
31 : m_memory,&
32 : m_walltime
33 : USE message_passing, ONLY: mp_para_env_type
34 : USE tmc_calculations, ONLY: get_subtree_efficiency
35 : USE tmc_cancelation, ONLY: free_cancelation_list
36 : USE tmc_dot_tree, ONLY: create_dot_color,&
37 : create_global_tree_dot_color,&
38 : finalize_draw_tree,&
39 : init_draw_trees
40 : USE tmc_file_io, ONLY: print_restart_file,&
41 : write_element_in_file
42 : USE tmc_messages, ONLY: communicate_atom_types,&
43 : recv_msg,&
44 : send_msg,&
45 : stop_whole_group,&
46 : tmc_message
47 : USE tmc_move_handle, ONLY: check_moves,&
48 : print_move_types
49 : USE tmc_stati, ONLY: &
50 : TMC_CANCELING_MESSAGE, TMC_CANCELING_RECEIPT, TMC_STATUS_FAILED, &
51 : TMC_STATUS_WAIT_FOR_NEW_TASK, TMC_STATUS_WORKER_INIT, TMC_STAT_ANALYSIS_REQUEST, &
52 : TMC_STAT_ANALYSIS_RESULT, TMC_STAT_APPROX_ENERGY_REQUEST, TMC_STAT_APPROX_ENERGY_RESULT, &
53 : TMC_STAT_ENERGY_REQUEST, TMC_STAT_ENERGY_RESULT, TMC_STAT_INIT_ANALYSIS, &
54 : TMC_STAT_MD_REQUEST, TMC_STAT_MD_RESULT, TMC_STAT_NMC_REQUEST, TMC_STAT_NMC_RESULT, &
55 : TMC_STAT_SCF_STEP_ENER_RECEIVE, TMC_STAT_START_CONF_REQUEST, TMC_STAT_START_CONF_RESULT
56 : USE tmc_tree_acceptance, ONLY: check_acceptance_of_depending_subtree_nodes,&
57 : check_elements_for_acc_prob_update,&
58 : tree_update
59 : USE tmc_tree_build, ONLY: create_new_gt_tree_node,&
60 : deallocate_sub_tree_node,&
61 : finalize_init,&
62 : finalize_trees,&
63 : init_tree_mod,&
64 : remove_all_trees
65 : USE tmc_tree_search, ONLY: count_nodes_in_trees,&
66 : count_prepared_nodes_in_trees,&
67 : search_next_energy_calc
68 : USE tmc_tree_types, ONLY: &
69 : elem_array_type, elem_list_type, global_tree_type, status_accepted, &
70 : status_calc_approx_ener, status_calculate_MD, status_calculate_NMC_steps, &
71 : status_calculate_energy, status_calculated, status_cancel_ener, status_cancel_nmc, &
72 : status_canceled_ener, status_canceled_nmc, status_created, status_rejected, tree_type
73 : USE tmc_types, ONLY: tmc_env_type
74 : #include "../base/base_uses.f90"
75 :
76 : IMPLICIT NONE
77 :
78 : PRIVATE
79 :
80 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'tmc_master'
81 :
82 : PUBLIC :: do_tmc_master
83 :
84 : INTEGER, PARAMETER :: DEBUG = 0
85 :
86 : CONTAINS
87 :
88 : ! **************************************************************************************************
89 : !> \brief send cancel request to all workers processing elements in the list
90 : !> \param cancel_list list with elements to cancel
91 : !> \param work_list list with all elements processed by working groups
92 : !> \param cancel_count counter of canceled elements
93 : !> \param para_env communication environment
94 : !> \param tmc_env ...
95 : !> \author Mandes 12.2012
96 : ! **************************************************************************************************
97 9085 : SUBROUTINE cancel_calculations(cancel_list, work_list, cancel_count, &
98 : para_env, tmc_env)
99 : TYPE(elem_list_type), POINTER :: cancel_list
100 : TYPE(elem_array_type), DIMENSION(:), POINTER :: work_list
101 : INTEGER :: cancel_count
102 : TYPE(mp_para_env_type), POINTER :: para_env
103 : TYPE(tmc_env_type), POINTER :: tmc_env
104 :
105 : INTEGER :: i, stat, wg
106 : TYPE(elem_list_type), POINTER :: tmp_element
107 :
108 9085 : IF (.NOT. ASSOCIATED(cancel_list)) RETURN
109 0 : NULLIFY (tmp_element)
110 :
111 0 : CPASSERT(ASSOCIATED(tmc_env))
112 0 : CPASSERT(ASSOCIATED(tmc_env%params))
113 0 : CPASSERT(ASSOCIATED(tmc_env%m_env))
114 0 : CPASSERT(ASSOCIATED(work_list))
115 0 : CPASSERT(ASSOCIATED(para_env))
116 :
117 0 : stat = TMC_STATUS_FAILED
118 0 : wg = -1
119 0 : cancel_elem_loop: DO
120 : ! find certain working group calculating this element
121 0 : working_elem_loop: DO i = 1, SIZE(work_list)
122 : ! in special cases element could be distributed to several working groups,
123 : ! but all, except of one, should already be in canceling process
124 0 : IF ((.NOT. work_list(i)%canceled) .AND. &
125 0 : ASSOCIATED(work_list(i)%elem)) THEN
126 0 : IF (ASSOCIATED(cancel_list%elem, work_list(i)%elem)) THEN
127 0 : stat = TMC_CANCELING_MESSAGE
128 0 : wg = i
129 0 : EXIT working_elem_loop
130 : END IF
131 : END IF
132 : END DO working_elem_loop
133 :
134 0 : CPASSERT(wg .GE. 0)
135 0 : CPASSERT(stat .NE. TMC_STATUS_FAILED)
136 0 : CPASSERT(work_list(wg)%elem%stat .NE. status_calc_approx_ener)
137 :
138 : IF (DEBUG .GE. 1) &
139 : WRITE (tmc_env%m_env%io_unit, *) &
140 : "TMC|master: cancel group "//cp_to_string(wg)
141 : CALL tmc_message(msg_type=stat, send_recv=send_msg, dest=wg, &
142 0 : para_env=para_env, tmc_params=tmc_env%params)
143 0 : work_list(wg)%canceled = .TRUE.
144 :
145 : ! counting the amount of canceled elements
146 0 : cancel_count = cancel_count + 1
147 :
148 : ! delete element from canceling list
149 0 : IF (.NOT. ASSOCIATED(cancel_list%next)) THEN
150 0 : DEALLOCATE (cancel_list)
151 : cancel_list => NULL()
152 : EXIT cancel_elem_loop
153 : ELSE
154 0 : tmp_element => cancel_list%next
155 0 : DEALLOCATE (cancel_list)
156 0 : cancel_list => tmp_element
157 : END IF
158 : END DO cancel_elem_loop
159 : END SUBROUTINE cancel_calculations
160 :
161 : ! **************************************************************************************************
162 : !> \brief send analysis request to a worker
163 : !> \param ana_list list with elements to be analysed
164 : !> \param ana_worker_info ...
165 : !> \param para_env communication environment
166 : !> \param tmc_env ...
167 : !> \author Mandes 12.2012
168 : ! **************************************************************************************************
169 277612 : SUBROUTINE send_analysis_tasks(ana_list, ana_worker_info, para_env, tmc_env)
170 : TYPE(elem_list_type), POINTER :: ana_list
171 : TYPE(elem_array_type), DIMENSION(:), POINTER :: ana_worker_info
172 : TYPE(mp_para_env_type), POINTER :: para_env
173 : TYPE(tmc_env_type), POINTER :: tmc_env
174 :
175 : INTEGER :: dest, stat, wg
176 : TYPE(elem_list_type), POINTER :: list_tmp
177 :
178 277612 : NULLIFY (list_tmp)
179 :
180 277612 : CPASSERT(ASSOCIATED(ana_worker_info))
181 277612 : CPASSERT(ASSOCIATED(para_env))
182 :
183 277612 : wg_loop: DO wg = 1, SIZE(ana_worker_info)
184 0 : IF (.NOT. ASSOCIATED(ana_list)) EXIT wg_loop
185 277612 : IF (.NOT. ana_worker_info(wg)%busy) THEN
186 0 : stat = TMC_STAT_ANALYSIS_REQUEST
187 0 : dest = wg
188 : CALL tmc_message(msg_type=stat, send_recv=send_msg, dest=dest, &
189 : para_env=para_env, tmc_params=tmc_env%params, &
190 0 : list_elem=ana_list)
191 0 : IF (.NOT. ASSOCIATED(ana_list%next)) THEN
192 0 : DEALLOCATE (ana_list)
193 : ana_list => NULL()
194 : ELSE
195 0 : list_tmp => ana_list%next
196 0 : DEALLOCATE (ana_list)
197 0 : ana_list => list_tmp
198 : END IF
199 : END IF
200 : END DO wg_loop
201 277612 : END SUBROUTINE send_analysis_tasks
202 :
203 : ! **************************************************************************************************
204 : !> \brief global master handling tree creation and communication/work
205 : !> distribution with workers
206 : !> \param tmc_env structure for storing all the tmc parameters
207 : !> \param globenv global environment for external control
208 : !> \author Mandes 11.2012
209 : ! **************************************************************************************************
210 14 : SUBROUTINE do_tmc_master(tmc_env, globenv)
211 : TYPE(tmc_env_type), POINTER :: tmc_env
212 : TYPE(global_environment_type), POINTER :: globenv
213 :
214 : CHARACTER(LEN=*), PARAMETER :: routineN = 'do_tmc_master'
215 :
216 : INTEGER :: cancel_count, handle, last_output, reactivation_cc_count, &
217 : reactivation_ener_count, restart_count, restarted_elem_nr, stat, walltime_delay, &
218 : walltime_offset, wg, worker_counter
219 : INTEGER(KIND=int_8) :: mem
220 : INTEGER, DIMENSION(6) :: nr_of_job
221 14 : INTEGER, DIMENSION(:), POINTER :: tree_elem_counters, tree_elem_heads
222 : LOGICAL :: external_stop, flag, l_update_tree
223 : REAL(KIND=dp) :: run_time_start
224 : REAL(KIND=dp), DIMENSION(4) :: worker_timings_aver
225 14 : REAL(KIND=dp), DIMENSION(:), POINTER :: efficiency
226 14 : TYPE(elem_array_type), DIMENSION(:), POINTER :: ana_worker_info, worker_info
227 : TYPE(global_tree_type), POINTER :: gt_elem_tmp
228 : TYPE(tree_type), POINTER :: init_conf
229 :
230 14 : external_stop = .FALSE.
231 14 : restarted_elem_nr = 0
232 14 : NULLIFY (init_conf, worker_info, ana_worker_info, gt_elem_tmp, tree_elem_counters)
233 :
234 0 : CPASSERT(ASSOCIATED(tmc_env))
235 :
236 14 : CPASSERT(tmc_env%tmc_comp_set%group_nr == 0)
237 14 : CPASSERT(ASSOCIATED(tmc_env%tmc_comp_set))
238 14 : CPASSERT(ASSOCIATED(tmc_env%tmc_comp_set%para_env_m_w))
239 :
240 14 : CPASSERT(ASSOCIATED(tmc_env%m_env))
241 :
242 : !-- run time measurment, to end just in time
243 : ! start the timing
244 14 : CALL timeset(routineN, handle)
245 14 : run_time_start = m_walltime()
246 14 : walltime_delay = 0
247 14 : walltime_offset = 20 ! default value the whole program needs to finalize
248 :
249 : ! initialize the different modules
250 14 : IF (tmc_env%params%DRAW_TREE) &
251 1 : CALL init_draw_trees(tmc_params=tmc_env%params)
252 :
253 : !-- initialize variables
254 : ! nr_of_job: counting the different task send / received
255 : ! (1:NMC submitted, 2:energies submitted, 3:NMC finished 4:energy finished, 5:NMC canceled, 6:energy canceled)
256 14 : nr_of_job(:) = 0
257 14 : worker_counter = -1
258 14 : reactivation_ener_count = 0
259 14 : reactivation_cc_count = 0
260 14 : cancel_count = 0
261 54 : tmc_env%m_env%result_count = 0
262 14 : l_update_tree = .FALSE.
263 14 : restart_count = 1
264 14 : last_output = -1
265 : ! average timings
266 : ! (1:calculated NMC, 2:calculated ener, 3:canceled NMC, 4: canceled ener)
267 14 : worker_timings_aver(:) = 0.0_dp
268 : ! remembers state of workers and their actual configurations
269 : ! the actual working group, communicating with
270 56 : ALLOCATE (worker_info(tmc_env%tmc_comp_set%para_env_m_w%num_pe - 1))
271 28 : ALLOCATE (ana_worker_info(tmc_env%tmc_comp_set%para_env_m_ana%num_pe - 1))
272 :
273 : ! get the start configuration form the first (exact energy) worker,
274 : ! master should/could have no Force environment
275 14 : stat = TMC_STAT_START_CONF_REQUEST
276 14 : wg = 1
277 : CALL tmc_message(msg_type=stat, send_recv=send_msg, dest=wg, &
278 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
279 : tmc_params=tmc_env%params, &
280 14 : wait_for_message=.TRUE.)
281 : !-- wait for start configuration results and number of dimensions
282 : !-- get start configuration (init_conf element should not be allocated already)
283 : CALL tmc_message(msg_type=stat, send_recv=recv_msg, dest=wg, &
284 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
285 : tmc_params=tmc_env%params, &
286 14 : elem=init_conf, success=flag, wait_for_message=.TRUE.)
287 14 : IF (stat .NE. TMC_STAT_START_CONF_RESULT) &
288 : CALL cp_abort(__LOCATION__, &
289 : "receiving start configuration failed, received stat "// &
290 0 : cp_to_string(stat))
291 : ! get the atom names from first energy worker
292 : CALL communicate_atom_types(atoms=tmc_env%params%atoms, &
293 : source=1, &
294 14 : para_env=tmc_env%tmc_comp_set%para_env_m_first_w)
295 :
296 14 : CALL init_cell(cell=tmc_env%params%cell)
297 :
298 : ! check the configuration consitency with selected moves
299 : CALL check_moves(tmc_params=tmc_env%params, &
300 : move_types=tmc_env%params%move_types, &
301 14 : mol_array=init_conf%mol)
302 14 : IF (ASSOCIATED(tmc_env%params%nmc_move_types)) &
303 : CALL check_moves(tmc_params=tmc_env%params, &
304 : move_types=tmc_env%params%nmc_move_types, &
305 5 : mol_array=init_conf%mol)
306 :
307 : ! set initial configuration
308 : ! set initial random number generator seed (rng seed)
309 : ! initialize the tree structure espacially for parallel tmepering,
310 : ! seting the subtrees
311 : CALL init_tree_mod(start_elem=init_conf, tmc_env=tmc_env, &
312 : job_counts=nr_of_job, &
313 14 : worker_timings=worker_timings_aver)
314 :
315 : ! init restart counter (espacially for restart case)
316 14 : IF (tmc_env%m_env%restart_out_step .NE. 0) THEN
317 : restart_count = INT(tmc_env%m_env%result_count(0)/ &
318 3 : REAL(tmc_env%m_env%restart_out_step, KIND=dp)) + 1
319 : END IF
320 14 : restarted_elem_nr = tmc_env%m_env%result_count(0)
321 :
322 : !TODO check conf and cell of both input files (cell has to be equal,
323 : ! because it is used as reference cell for scaling the cell)
324 : ! communicate the reference cell size
325 28 : DO wg = 1, tmc_env%tmc_comp_set%para_env_m_w%num_pe - 1
326 14 : stat = TMC_STATUS_WORKER_INIT
327 : CALL tmc_message(msg_type=stat, send_recv=send_msg, dest=wg, &
328 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
329 28 : tmc_params=tmc_env%params)
330 : END DO
331 :
332 : ! send the atom informations to all analysis workers
333 14 : IF (tmc_env%tmc_comp_set%para_env_m_ana%num_pe .GT. 1) THEN
334 0 : DO wg = 1, tmc_env%tmc_comp_set%para_env_m_ana%num_pe - 1
335 0 : stat = TMC_STAT_INIT_ANALYSIS
336 : CALL tmc_message(msg_type=stat, send_recv=send_msg, dest=wg, &
337 : para_env=tmc_env%tmc_comp_set%para_env_m_ana, &
338 : result_count=tmc_env%m_env%result_count, &
339 : tmc_params=tmc_env%params, &
340 : elem=init_conf, &
341 0 : wait_for_message=.TRUE.)
342 : END DO
343 : CALL communicate_atom_types(atoms=tmc_env%params%atoms, &
344 : source=0, &
345 0 : para_env=tmc_env%tmc_comp_set%para_env_m_ana)
346 : END IF
347 :
348 14 : CALL deallocate_sub_tree_node(tree_elem=init_conf)
349 :
350 : ! regtest output
351 14 : IF (tmc_env%params%print_test_output .OR. DEBUG .GT. 0) &
352 14 : WRITE (tmc_env%m_env%io_unit, *) "TMC|first_global_tree_rnd_nr_X= ", &
353 28 : tmc_env%m_env%gt_head%rnd_nr
354 :
355 : ! calculate the approx energy of the first element (later the exact)
356 14 : IF (tmc_env%m_env%gt_head%conf(1)%elem%stat .EQ. status_calc_approx_ener) THEN
357 5 : wg = 1
358 5 : IF (tmc_env%tmc_comp_set%group_cc_nr .GT. 0) &
359 0 : wg = tmc_env%tmc_comp_set%group_ener_nr + 1
360 5 : stat = TMC_STAT_APPROX_ENERGY_REQUEST
361 : CALL tmc_message(msg_type=stat, send_recv=send_msg, dest=wg, &
362 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
363 : tmc_params=tmc_env%params, &
364 5 : elem=tmc_env%m_env%gt_head%conf(1)%elem)
365 5 : worker_info(wg)%busy = .TRUE.
366 5 : worker_info(wg)%elem => tmc_env%m_env%gt_head%conf(1)%elem
367 5 : init_conf => tmc_env%m_env%gt_head%conf(1)%elem
368 9 : ELSE IF (tmc_env%m_env%gt_head%conf(1)%elem%stat .EQ. status_created) THEN
369 7 : init_conf => tmc_env%m_env%gt_head%conf(1)%elem
370 : ! calculation will be done automatically,
371 : ! by searching the next conf for energy calculation
372 : END IF
373 : !-- START WORK --!
374 : !-- distributing work:
375 : ! 1. receive incoming results
376 : ! 2. check new results in tree
377 : ! 3. if idle worker, create new tree element and send them to worker
378 277612 : task_loop: DO
379 : ! =======================================================================
380 : !-- RECEIVING ALL incoming messages and handling them
381 : ! results of tree node 1 is distributed to all other subtree nodes
382 : ! =======================================================================
383 : worker_request_loop: DO
384 282154 : wg = 1
385 282154 : flag = .FALSE.
386 : CALL tmc_message(msg_type=stat, send_recv=recv_msg, dest=wg, &
387 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
388 : tmc_params=tmc_env%params, &
389 282154 : elem_array=worker_info(:), success=flag)
390 :
391 282154 : IF (flag .EQV. .FALSE.) EXIT worker_request_loop
392 : ! messages from worker group could be faster then the canceling request
393 4542 : IF (worker_info(wg)%canceled .AND. (stat .NE. TMC_CANCELING_RECEIPT)) THEN
394 : IF (DEBUG .GE. 1) &
395 : WRITE (tmc_env%m_env%io_unit, *) &
396 : "TMC|master: recv stat "//cp_to_string(stat)// &
397 : " of canceled worker group"
398 : CYCLE worker_request_loop
399 : END IF
400 :
401 : ! in case of parallel tempering canceled element could be reactivated,
402 : ! calculated faster and deleted
403 4542 : IF (.NOT. ASSOCIATED(worker_info(wg)%elem)) &
404 : CALL cp_abort(__LOCATION__, &
405 : "no tree elem exist when receiving stat "// &
406 0 : cp_to_string(stat)//"of group"//cp_to_string(wg))
407 :
408 : IF (DEBUG .GE. 1) &
409 : WRITE (tmc_env%m_env%io_unit, *) &
410 : "TMC|master: received stat "//cp_to_string(stat)// &
411 : " of sub tree "//cp_to_string(worker_info(wg)%elem%sub_tree_nr)// &
412 : " elem"//cp_to_string(worker_info(wg)%elem%nr)// &
413 : " with stat"//cp_to_string(worker_info(wg)%elem%stat)// &
414 : " of group"//cp_to_string(wg)//" group canceled ", worker_info(wg)%canceled
415 277612 : SELECT CASE (stat)
416 : ! -- FAILED --------------------------
417 : CASE (TMC_STATUS_FAILED)
418 0 : EXIT task_loop
419 : ! -- CANCEL_RECEIPT ------------------
420 : CASE (TMC_CANCELING_RECEIPT)
421 : ! worker should got cancel message before
422 0 : CPASSERT(worker_info(wg)%canceled)
423 0 : worker_info(wg)%canceled = .FALSE.
424 0 : worker_info(wg)%busy = .FALSE.
425 :
426 0 : IF (ASSOCIATED(worker_info(wg)%elem)) THEN
427 0 : SELECT CASE (worker_info(wg)%elem%stat)
428 : CASE (status_cancel_ener)
429 : !-- timings
430 : worker_timings_aver(4) = (worker_timings_aver(4)*nr_of_job(6) + &
431 0 : (m_walltime() - worker_info(wg)%start_time))/REAL(nr_of_job(6) + 1, KIND=dp)
432 0 : nr_of_job(6) = nr_of_job(6) + 1
433 :
434 0 : worker_info(wg)%elem%stat = status_canceled_ener
435 0 : worker_info(wg)%elem%potential = 8000.0_dp
436 0 : IF (tmc_env%params%DRAW_TREE) THEN
437 : CALL create_dot_color(tree_element=worker_info(wg)%elem, &
438 0 : tmc_params=tmc_env%params)
439 : END IF
440 : CASE (status_cancel_nmc)
441 : !-- timings
442 : worker_timings_aver(3) = (worker_timings_aver(3)*nr_of_job(5) + &
443 0 : (m_walltime() - worker_info(wg)%start_time))/REAL(nr_of_job(5) + 1, KIND=dp)
444 0 : nr_of_job(5) = nr_of_job(5) + 1
445 :
446 0 : worker_info(wg)%elem%stat = status_canceled_nmc
447 0 : worker_info(wg)%elem%potential = 8000.0_dp
448 0 : IF (tmc_env%params%DRAW_TREE) THEN
449 : CALL create_dot_color(tree_element=worker_info(wg)%elem, &
450 0 : tmc_params=tmc_env%params)
451 : END IF
452 : CASE DEFAULT
453 : ! the subtree element is again in use (reactivated)
454 : END SELECT
455 0 : worker_info(wg)%elem => NULL()
456 : END IF
457 : ! -- START_CONF_RESULT ---------------
458 : CASE (TMC_STAT_START_CONF_RESULT)
459 : ! start configuration should already be handeled
460 0 : CPABORT("")
461 : ! -- ENERGY RESULT -----------------
462 : CASE (TMC_STAT_APPROX_ENERGY_RESULT)
463 14 : nr_of_job(3) = nr_of_job(3) + 1
464 14 : worker_info(wg)%busy = .FALSE.
465 14 : worker_info(wg)%elem%stat = status_created
466 14 : IF (tmc_env%params%DRAW_TREE) THEN
467 : CALL create_dot_color(tree_element=worker_info(wg)%elem, &
468 0 : tmc_params=tmc_env%params)
469 : END IF
470 14 : worker_info(wg)%elem => NULL()
471 : ! nothing to do, the approximate potential
472 : ! should be updated in the message interface
473 : ! -- NMC / MD RESULT -----------------
474 : CASE (TMC_STAT_NMC_RESULT, TMC_STAT_MD_RESULT)
475 57 : IF (.NOT. worker_info(wg)%canceled) worker_info(wg)%busy = .FALSE.
476 : !-- timings for Nested Monte Carlo calculation
477 : worker_timings_aver(1) = (worker_timings_aver(1)*nr_of_job(3) + &
478 57 : (m_walltime() - worker_info(wg)%start_time))/REAL(nr_of_job(3) + 1, KIND=dp)
479 57 : nr_of_job(3) = nr_of_job(3) + 1
480 :
481 57 : worker_info(wg)%start_time = m_walltime() - worker_info(wg)%start_time
482 57 : CALL set_walltime_delay(worker_info(wg)%start_time, walltime_delay)
483 57 : worker_info(wg)%elem%stat = status_created
484 57 : IF (tmc_env%params%DRAW_TREE) THEN
485 : CALL create_dot_color(tree_element=worker_info(wg)%elem, &
486 0 : tmc_params=tmc_env%params)
487 : END IF
488 : !-- send energy request
489 : ! in case of one singe input file, energy is already calculated
490 57 : IF (tmc_env%params%NMC_inp_file .EQ. "") THEN
491 0 : worker_info(wg)%elem%potential = worker_info(wg)%elem%e_pot_approx
492 0 : worker_info(wg)%elem%stat = status_calculated
493 : ! check acceptance of depending nodes
494 0 : IF (.NOT. (ASSOCIATED(worker_info(wg)%elem, init_conf))) THEN
495 : CALL check_acceptance_of_depending_subtree_nodes(tree_elem=worker_info(wg)%elem, &
496 0 : tmc_env=tmc_env)
497 : END IF
498 0 : IF (tmc_env%params%DRAW_TREE) THEN
499 : CALL create_dot_color(tree_element=worker_info(wg)%elem, &
500 0 : tmc_params=tmc_env%params)
501 : END IF
502 : !-- CANCELING the calculations of the elements, which are definetively not needed anymore
503 : CALL cancel_calculations(cancel_list=tmc_env%m_env%cancelation_list, &
504 : work_list=worker_info, &
505 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
506 : tmc_env=tmc_env, &
507 0 : cancel_count=cancel_count)
508 0 : worker_info(wg)%elem => NULL()
509 : ELSE
510 : ! if all working groups are equal, the same group calculates the energy
511 : IF (tmc_env%tmc_comp_set%group_cc_nr .LE. 0 &
512 57 : .AND. (.NOT. worker_info(wg)%canceled)) THEN
513 57 : worker_info(wg)%elem%stat = status_calculate_energy
514 57 : stat = TMC_STAT_ENERGY_REQUEST
515 : ! immediately send energy request
516 : CALL tmc_message(msg_type=stat, send_recv=send_msg, dest=wg, &
517 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
518 : tmc_params=tmc_env%params, &
519 57 : elem=worker_info(wg)%elem)
520 57 : worker_info(wg)%busy = .TRUE.
521 57 : nr_of_job(2) = nr_of_job(2) + 1
522 57 : IF (tmc_env%params%DRAW_TREE) THEN
523 : CALL create_dot_color(tree_element=worker_info(wg)%elem, &
524 0 : tmc_params=tmc_env%params)
525 : END IF
526 : !-- set start time for energy calculation
527 57 : worker_info(wg)%start_time = m_walltime()
528 : ELSE
529 0 : worker_info(wg)%elem => NULL()
530 : END IF
531 : END IF
532 : ! -- ENERGY RESULT --------------------
533 : CASE (TMC_STAT_ENERGY_RESULT)
534 : !-- timings
535 : worker_timings_aver(2) = (worker_timings_aver(2)*nr_of_job(4) + &
536 4471 : (m_walltime() - worker_info(wg)%start_time))/REAL(nr_of_job(4) + 1, KIND=dp)
537 4471 : nr_of_job(4) = nr_of_job(4) + 1
538 :
539 4471 : worker_info(wg)%start_time = m_walltime() - worker_info(wg)%start_time
540 4471 : CALL set_walltime_delay(worker_info(wg)%start_time, walltime_delay)
541 :
542 4471 : IF (.NOT. worker_info(wg)%canceled) &
543 4471 : worker_info(wg)%busy = .FALSE.
544 : ! the first node in tree is always accepted.!.
545 4471 : IF (ASSOCIATED(worker_info(wg)%elem, init_conf)) THEN
546 : !-- distribute energy of first element to all subtrees
547 : CALL finalize_init(gt_tree_ptr=tmc_env%m_env%gt_head, &
548 12 : tmc_env=tmc_env)
549 12 : IF (tmc_env%params%DRAW_TREE) THEN
550 : CALL create_global_tree_dot_color(gt_tree_element=tmc_env%m_env%gt_act, &
551 0 : tmc_params=tmc_env%params)
552 : CALL create_dot_color(tree_element=worker_info(wg)%elem, &
553 0 : tmc_params=tmc_env%params)
554 : END IF
555 12 : init_conf => NULL()
556 : ELSE
557 4459 : worker_info(wg)%elem%stat = status_calculated
558 4459 : IF (tmc_env%params%DRAW_TREE) &
559 : CALL create_dot_color(worker_info(wg)%elem, &
560 36 : tmc_params=tmc_env%params)
561 : ! check acceptance of depending nodes
562 : ! first (initial) configuration do not have to be checked
563 : CALL check_acceptance_of_depending_subtree_nodes(tree_elem=worker_info(wg)%elem, &
564 4459 : tmc_env=tmc_env)
565 : END IF
566 : !-- write out all configurations (not only Markov Chain) e.g. for fitting
567 4471 : IF (tmc_env%params%all_conf_file_name .NE. "") THEN
568 : CALL write_element_in_file(elem=worker_info(wg)%elem, &
569 : file_name=tmc_env%params%all_conf_file_name, &
570 : tmc_params=tmc_env%params, &
571 0 : conf_nr=nr_of_job(4))
572 : END IF
573 :
574 : !-- CANCELING the calculations of the elements,
575 : ! which are definetively not needed anymore
576 : CALL cancel_calculations(cancel_list=tmc_env%m_env%cancelation_list, &
577 : work_list=worker_info, &
578 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
579 : tmc_env=tmc_env, &
580 4471 : cancel_count=cancel_count)
581 : IF (DEBUG .GE. 9) &
582 : WRITE (tmc_env%m_env%io_unit, *) &
583 : "TMC|master: handled energy result of sub tree ", &
584 : worker_info(wg)%elem%sub_tree_nr, " elem ", worker_info(wg)%elem%nr, &
585 : " with stat", worker_info(wg)%elem%stat
586 4471 : worker_info(wg)%elem => NULL()
587 :
588 : !-- SCF ENERGY -----------------------
589 : CASE (TMC_STAT_SCF_STEP_ENER_RECEIVE)
590 : IF (.NOT. (ASSOCIATED(worker_info(wg)%elem, init_conf)) .AND. &
591 0 : worker_info(wg)%elem%stat .NE. status_cancel_ener .AND. &
592 : worker_info(wg)%elem%stat .NE. status_cancel_nmc) THEN
593 : ! update the acceptance probability and the canceling list
594 : CALL check_elements_for_acc_prob_update(tree_elem=worker_info(wg)%elem, &
595 0 : tmc_env=tmc_env)
596 : END IF
597 : ! cancel inlikely elements
598 : CALL cancel_calculations(cancel_list=tmc_env%m_env%cancelation_list, &
599 : work_list=worker_info, &
600 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
601 : tmc_env=tmc_env, &
602 0 : cancel_count=cancel_count)
603 : CASE (TMC_STAT_ANALYSIS_RESULT)
604 0 : ana_worker_info(wg)%busy = .FALSE.
605 0 : ana_worker_info(wg)%elem => NULL()
606 : CASE DEFAULT
607 4542 : CPABORT("received message with unknown info/stat type")
608 : END SELECT
609 : END DO worker_request_loop
610 : !-- do tree update (check new results)
611 : CALL tree_update(tmc_env=tmc_env, result_acc=flag, &
612 277612 : something_updated=l_update_tree)
613 : IF (DEBUG .GE. 2 .AND. l_update_tree) &
614 : WRITE (tmc_env%m_env%io_unit, *) &
615 : "TMC|master: tree updated "//cp_to_string(l_update_tree)// &
616 : " of with gt elem "//cp_to_string(tmc_env%m_env%gt_act%nr)// &
617 : " with stat"//cp_to_string(tmc_env%m_env%gt_act%stat)
618 :
619 : CALL send_analysis_tasks(ana_list=tmc_env%m_env%analysis_list, &
620 : ana_worker_info=ana_worker_info, &
621 : para_env=tmc_env%tmc_comp_set%para_env_m_ana, &
622 277612 : tmc_env=tmc_env)
623 :
624 : ! =======================================================================
625 : !-- ALL CALCULATIONS DONE (check) ---
626 : ! =======================================================================
627 : ! if enough configurations are sampled or walltime is exeeded,
628 : ! finish building trees
629 : !TODO set correct logger para_env to use this
630 277612 : CALL external_control(should_stop=external_stop, flag="TMC", globenv=globenv)
631 : IF ((ANY(tmc_env%m_env%result_count(1:) .GE. tmc_env%m_env%num_MC_elem) &
632 : .AND. flag) .OR. &
633 : (m_walltime() - run_time_start .GT. &
634 626158 : tmc_env%m_env%walltime - walltime_delay - walltime_offset) .OR. &
635 : external_stop) THEN
636 14 : WRITE (tmc_env%m_env%io_unit, FMT="(/,T2,A)") REPEAT("=", 79)
637 : ! calculations NOT finished, walltime exceeded
638 20 : IF (.NOT. ANY(tmc_env%m_env%result_count(1:) &
639 : .GE. tmc_env%m_env%num_MC_elem)) THEN
640 1 : WRITE (tmc_env%m_env%io_unit, *) "Walltime exceeded.", &
641 1 : m_walltime() - run_time_start, " of ", tmc_env%m_env%walltime - walltime_delay - walltime_offset, &
642 2 : "(incl. delay", walltime_delay, "and offset", walltime_offset, ") left"
643 : ELSE
644 : ! calculations finished
645 13 : IF (tmc_env%params%print_test_output) &
646 13 : WRITE (tmc_env%m_env%io_unit, *) "Total energy: ", &
647 26 : tmc_env%m_env%result_list(1)%elem%potential
648 : END IF
649 14 : IF (tmc_env%m_env%restart_out_step .NE. 0) &
650 : CALL print_restart_file(tmc_env=tmc_env, job_counts=nr_of_job, &
651 3 : timings=worker_timings_aver)
652 : EXIT task_loop
653 : END IF
654 :
655 : ! =======================================================================
656 : ! update the rest of the tree (canceling and deleting elements)
657 : ! =======================================================================
658 277598 : IF (l_update_tree) THEN
659 : IF (DEBUG .GE. 2) &
660 : WRITE (tmc_env%m_env%io_unit, *) &
661 : "TMC|master: start remove elem and cancel calculation"
662 : !-- CLEANING tree nodes beside the path through the tree from
663 : ! end_of_clean_tree to tree_ptr
664 : ! --> getting back the end of clean tree
665 4614 : CALL remove_all_trees(working_elem_list=worker_info, tmc_env=tmc_env)
666 : !-- CANCELING the calculations of the elements,
667 : ! which are definetively not needed anymore
668 : ! elements are added to canceling list if no global tree reference
669 : ! exist anymore
670 : CALL cancel_calculations(cancel_list=tmc_env%m_env%cancelation_list, &
671 : work_list=worker_info, &
672 : cancel_count=cancel_count, &
673 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
674 4614 : tmc_env=tmc_env)
675 : END IF
676 :
677 : ! =====================================================================
678 : !-- NEW TASK (if worker not busy submit next task)
679 : ! =====================================================================
680 277598 : worker_counter = worker_counter + 1
681 277598 : wg = MODULO(worker_counter, tmc_env%tmc_comp_set%para_env_m_w%num_pe - 1) + 1
682 :
683 550547 : IF (DEBUG .GE. 16 .AND. ALL(worker_info(:)%busy)) &
684 : WRITE (tmc_env%m_env%io_unit, *) "all workers are busy"
685 :
686 277598 : IF (.NOT. worker_info(wg)%busy) THEN
687 : IF (DEBUG .GE. 13) &
688 : WRITE (tmc_env%m_env%io_unit, *) &
689 : "TMC|master: search new task for worker ", wg
690 : ! no group separation
691 4649 : IF (tmc_env%tmc_comp_set%group_cc_nr .LE. 0) THEN
692 : ! search next element to calculate the energy
693 : CALL search_next_energy_calc(gt_head=tmc_env%m_env%gt_act, &
694 : new_gt_elem=gt_elem_tmp, stat=stat, &
695 4649 : react_count=reactivation_ener_count)
696 4649 : IF (stat .EQ. TMC_STATUS_WAIT_FOR_NEW_TASK) THEN
697 : CALL create_new_gt_tree_node(tmc_env=tmc_env, stat=stat, &
698 : new_elem=gt_elem_tmp, &
699 4628 : reactivation_cc_count=reactivation_cc_count)
700 : END IF
701 0 : ELSEIF (wg .GT. tmc_env%tmc_comp_set%group_ener_nr) THEN
702 : ! specialized groups (groups for exact energy and groups for configurational change)
703 : ! creating new element (configurational change group)
704 : !-- crate new node, configurational change is handled in tmc_tree module
705 : CALL create_new_gt_tree_node(tmc_env=tmc_env, stat=stat, &
706 : new_elem=gt_elem_tmp, &
707 0 : reactivation_cc_count=reactivation_cc_count)
708 : ! element could be already created, hence CC worker has nothing to do for this element
709 : ! in next round he will get a task
710 0 : IF (stat .EQ. status_created .OR. stat .EQ. status_calculate_energy) &
711 0 : stat = TMC_STATUS_WAIT_FOR_NEW_TASK
712 : ELSE
713 : ! search next element to calculate the energy
714 : CALL search_next_energy_calc(gt_head=tmc_env%m_env%gt_act, &
715 : new_gt_elem=gt_elem_tmp, stat=stat, &
716 0 : react_count=reactivation_ener_count)
717 : END IF
718 :
719 : IF (DEBUG .GE. 10) &
720 : WRITE (tmc_env%m_env%io_unit, *) &
721 : "TMC|master: send task with elem stat "//cp_to_string(stat)// &
722 : " to group "//cp_to_string(wg)
723 : ! MESSAGE settings: status informations and task for communication
724 : SELECT CASE (stat)
725 : CASE (TMC_STATUS_WAIT_FOR_NEW_TASK)
726 : CYCLE task_loop
727 : CASE (TMC_STATUS_FAILED)
728 : !STOP "in creating new task, status failed should be handled before"
729 : CYCLE task_loop
730 : CASE (status_calculated, status_accepted, status_rejected)
731 9 : CYCLE task_loop
732 : CASE (status_calc_approx_ener)
733 : ! e.g. after volume move, we need the approximate potential for 2 potential check of following NMC nodes
734 9 : stat = TMC_STAT_APPROX_ENERGY_REQUEST
735 : CALL tmc_message(msg_type=stat, send_recv=send_msg, dest=wg, &
736 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
737 : tmc_params=tmc_env%params, &
738 9 : elem=gt_elem_tmp%conf(gt_elem_tmp%mv_conf)%elem)
739 9 : nr_of_job(1) = nr_of_job(1) + 1
740 : CASE (status_created, status_calculate_energy)
741 : ! in case of parallel tempering the node can be already be calculating (related to another global tree node
742 : !-- send task to calculate system property
743 4415 : gt_elem_tmp%conf(gt_elem_tmp%mv_conf)%elem%stat = status_calculate_energy
744 4415 : IF (tmc_env%params%DRAW_TREE) &
745 : CALL create_dot_color(tree_element=gt_elem_tmp%conf(gt_elem_tmp%mv_conf)%elem, &
746 36 : tmc_params=tmc_env%params)
747 4415 : stat = TMC_STAT_ENERGY_REQUEST
748 : CALL tmc_message(msg_type=stat, send_recv=send_msg, dest=wg, &
749 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
750 : tmc_params=tmc_env%params, &
751 4415 : elem=gt_elem_tmp%conf(gt_elem_tmp%mv_conf)%elem)
752 4415 : nr_of_job(2) = nr_of_job(2) + 1
753 : CASE (status_calculate_MD)
754 0 : stat = TMC_STAT_MD_REQUEST
755 : CALL tmc_message(msg_type=stat, send_recv=send_msg, dest=wg, &
756 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
757 : tmc_params=tmc_env%params, &
758 0 : elem=gt_elem_tmp%conf(gt_elem_tmp%mv_conf)%elem)
759 : ! temperature=tmc_env%params%Temp(gt_elem_tmp%mv_conf), &
760 0 : nr_of_job(1) = nr_of_job(1) + 1
761 : CASE (status_calculate_NMC_steps)
762 : !-- send information of element, which should be calculated
763 57 : stat = TMC_STAT_NMC_REQUEST
764 : CALL tmc_message(msg_type=stat, send_recv=send_msg, dest=wg, &
765 : para_env=tmc_env%tmc_comp_set%para_env_m_w, &
766 : tmc_params=tmc_env%params, &
767 57 : elem=gt_elem_tmp%conf(gt_elem_tmp%mv_conf)%elem)
768 57 : nr_of_job(1) = nr_of_job(1) + 1
769 : CASE (status_cancel_nmc, status_cancel_ener)
770 : ! skip that task until receipt is received
771 : ! no status update
772 : CASE DEFAULT
773 : CALL cp_abort(__LOCATION__, &
774 : "new task of tree element"// &
775 : cp_to_string(gt_elem_tmp%nr)// &
776 4649 : "has unknown status"//cp_to_string(stat))
777 : END SELECT
778 4481 : worker_info(wg)%elem => gt_elem_tmp%conf(gt_elem_tmp%mv_conf)%elem
779 4481 : worker_info(wg)%busy = .TRUE.
780 : ! set timer for maximum calculation time recognition
781 4481 : worker_info(wg)%start_time = m_walltime()
782 :
783 : !===================== write out info after x requested tasks==========
784 : IF (nr_of_job(4) .GT. last_output .AND. &
785 4481 : (MODULO(nr_of_job(4), tmc_env%m_env%info_out_step_size) .EQ. 0) .AND. &
786 : (stat .NE. TMC_STATUS_FAILED)) THEN
787 182 : last_output = nr_of_job(4)
788 182 : WRITE (tmc_env%m_env%io_unit, FMT="(/,T2,A)") REPEAT("-", 79)
789 : WRITE (tmc_env%m_env%io_unit, *) &
790 182 : "Tasks submitted: E ", nr_of_job(2), ", cc", nr_of_job(1)
791 : WRITE (tmc_env%m_env%io_unit, *) &
792 182 : "Results received: E ", nr_of_job(4), ", cc", nr_of_job(3)
793 : WRITE (tmc_env%m_env%io_unit, *) &
794 182 : "Configurations used:", tmc_env%m_env%result_count(0), &
795 364 : ", sub trees", tmc_env%m_env%result_count(1:)
796 :
797 : CALL print_move_types(init=.FALSE., file_io=tmc_env%m_env%io_unit, &
798 182 : tmc_params=tmc_env%params)
799 546 : ALLOCATE (tree_elem_counters(0:SIZE(tmc_env%params%Temp)))
800 546 : ALLOCATE (tree_elem_heads(0:SIZE(tmc_env%params%Temp)))
801 : CALL count_nodes_in_trees(global_tree_ptr=tmc_env%m_env%gt_act, &
802 : end_of_clean_trees=tmc_env%m_env%st_clean_ends, &
803 182 : counters=tree_elem_counters, head_elements_nr=tree_elem_heads)
804 182 : WRITE (tmc_env%m_env%io_unit, *) "nodes in trees", tree_elem_counters(:)
805 182 : WRITE (tmc_env%m_env%io_unit, *) "tree heads ", tree_elem_heads(:)
806 182 : IF (tmc_env%params%NMC_inp_file .NE. "") THEN
807 : CALL count_prepared_nodes_in_trees(global_tree_ptr=tmc_env%m_env%gt_act, &
808 28 : counters=tree_elem_counters)
809 : WRITE (tmc_env%m_env%io_unit, FMT=*) &
810 86 : "ener prepared ", tree_elem_counters
811 : END IF
812 182 : IF (tmc_env%params%SPECULATIVE_CANCELING) &
813 : WRITE (tmc_env%m_env%io_unit, *) &
814 182 : "canceled cc|E: ", nr_of_job(5:6), &
815 182 : ", reactivated: cc ", &
816 182 : reactivation_cc_count, &
817 182 : ", reactivated: E ", &
818 364 : reactivation_ener_count
819 : WRITE (tmc_env%m_env%io_unit, FMT='(A,2F10.2)') &
820 182 : " Average time for cc/ener calc ", &
821 364 : worker_timings_aver(1), worker_timings_aver(2)
822 182 : IF (tmc_env%params%SPECULATIVE_CANCELING) &
823 : WRITE (tmc_env%m_env%io_unit, FMT='(A,2F10.2)') &
824 182 : " Average time until cancel cc/ener calc ", &
825 364 : worker_timings_aver(3), worker_timings_aver(4)
826 182 : IF (tmc_env%params%esimate_acc_prob) &
827 : WRITE (tmc_env%m_env%io_unit, *) &
828 182 : "Estimate correct (acc/Nacc) | wrong (acc/nacc)", &
829 182 : tmc_env%m_env%estim_corr_wrong(1), &
830 182 : tmc_env%m_env%estim_corr_wrong(3), " | ", &
831 182 : tmc_env%m_env%estim_corr_wrong(2), &
832 364 : tmc_env%m_env%estim_corr_wrong(4)
833 : WRITE (tmc_env%m_env%io_unit, *) &
834 182 : "Time: ", INT(m_walltime() - run_time_start), "of", &
835 182 : INT(tmc_env%m_env%walltime - walltime_delay - walltime_offset), &
836 364 : "sec needed."
837 182 : CALL m_memory(mem)
838 : WRITE (tmc_env%m_env%io_unit, *) &
839 182 : "Memory used: ", INT(mem/(1024*1024), KIND=KIND(0)), "MiBytes"
840 182 : CALL m_flush(tmc_env%m_env%io_unit)
841 182 : DEALLOCATE (tree_elem_heads)
842 364 : DEALLOCATE (tree_elem_counters)
843 : END IF
844 : !===================== write out restart file after x results============
845 4481 : IF (tmc_env%m_env%restart_out_step .GT. 0 .AND. &
846 : tmc_env%m_env%result_count(0) .GT. &
847 : restart_count*tmc_env%m_env%restart_out_step) THEN
848 : CALL print_restart_file(tmc_env=tmc_env, job_counts=nr_of_job, &
849 0 : timings=worker_timings_aver)
850 0 : restart_count = restart_count + 1
851 : END IF
852 :
853 : END IF !worker busy?
854 : END DO task_loop
855 :
856 : ! -- END OF WORK (enough configurations are calculated or walltime exceeded
857 14 : WRITE (tmc_env%m_env%io_unit, FMT="(/,T2,A)") REPEAT("=", 79)
858 14 : WRITE (UNIT=tmc_env%m_env%io_unit, FMT="(T2,A,T35,A,T80,A)") "=", &
859 28 : "finalizing TMC", "="
860 14 : WRITE (tmc_env%m_env%io_unit, *) "acceptance rates:"
861 : CALL print_move_types(init=.FALSE., file_io=tmc_env%m_env%io_unit, &
862 14 : tmc_params=tmc_env%params)
863 14 : WRITE (tmc_env%m_env%io_unit, FMT="(/,T2,A)") REPEAT("-", 79)
864 : ! program efficiency result outputs
865 42 : ALLOCATE (efficiency(0:tmc_env%params%nr_temp))
866 14 : CALL get_subtree_efficiency(tmc_env=tmc_env, eff=efficiency)
867 14 : WRITE (tmc_env%m_env%io_unit, *) "Efficiencies:"
868 : WRITE (tmc_env%m_env%io_unit, FMT="(A,F5.2,A,1000F5.2)") &
869 14 : " (MC elements/calculated configuration) global:", &
870 28 : efficiency(0), " sub tree(s): ", efficiency(1:)
871 14 : DEALLOCATE (efficiency)
872 14 : IF (tmc_env%tmc_comp_set%group_cc_nr .GT. 0) &
873 : WRITE (tmc_env%m_env%io_unit, FMT="(A,1000F5.2)") &
874 0 : " (MC elements/created configuration) :", &
875 0 : tmc_env%m_env%result_count(:)/REAL(nr_of_job(3), KIND=dp)
876 : WRITE (tmc_env%m_env%io_unit, FMT="(A,1000F5.2)") &
877 14 : " (MC elements/energy calculated configuration):", &
878 68 : tmc_env%m_env%result_count(:)/REAL(nr_of_job(4), KIND=dp)
879 14 : IF (tmc_env%params%NMC_inp_file .NE. "") THEN
880 : WRITE (tmc_env%m_env%io_unit, *) &
881 5 : "Amount of canceled elements (E/cc):", &
882 10 : tmc_env%m_env%count_cancel_ener, tmc_env%m_env%count_cancel_NMC
883 : WRITE (tmc_env%m_env%io_unit, *) &
884 5 : " reactivated E ", reactivation_ener_count
885 : WRITE (tmc_env%m_env%io_unit, *) &
886 5 : " reactivated cc ", reactivation_cc_count
887 : END IF
888 : WRITE (tmc_env%m_env%io_unit, FMT="(A,F10.2)") &
889 14 : " computing time of one Markov chain element ", &
890 : (m_walltime() - run_time_start)/REAL(tmc_env%m_env%result_count(0) - &
891 28 : restarted_elem_nr, KIND=dp)
892 14 : WRITE (tmc_env%m_env%io_unit, FMT="(A,F10.2)") " TMC run time[s]: ", m_walltime() - run_time_start
893 14 : WRITE (tmc_env%m_env%io_unit, FMT="(/,T2,A)") REPEAT("=", 79)
894 :
895 : !-- FINALIZE
896 14 : WRITE (tmc_env%m_env%io_unit, *) "stopping workers"
897 : CALL stop_whole_group(para_env=tmc_env%tmc_comp_set%para_env_m_w, &
898 : worker_info=worker_info, &
899 14 : tmc_params=tmc_env%params)
900 14 : DEALLOCATE (worker_info)
901 : CALL stop_whole_group(para_env=tmc_env%tmc_comp_set%para_env_m_ana, &
902 : worker_info=ana_worker_info, &
903 14 : tmc_params=tmc_env%params)
904 14 : DEALLOCATE (ana_worker_info)
905 :
906 : !-- deallocating everything in tree module
907 14 : CALL finalize_trees(tmc_env=tmc_env)
908 :
909 14 : CALL free_cancelation_list(tmc_env%m_env%cancelation_list)
910 :
911 : ! -- write final configuration
912 14 : IF (tmc_env%params%DRAW_TREE) &
913 1 : CALL finalize_draw_tree(tmc_params=tmc_env%params)
914 :
915 14 : WRITE (tmc_env%m_env%io_unit, *) "TMC master: all work done."
916 :
917 : ! end the timing
918 14 : CALL timestop(handle)
919 :
920 28 : END SUBROUTINE do_tmc_master
921 :
922 : ! **************************************************************************************************
923 : !> \brief routine sets the walltime delay, to the maximum calculation time
924 : !> hence the program can stop with a proper finailze
925 : !> \param time actual calculation time
926 : !> \param walltime_delay the actual biggest calculation time
927 : !> \author Mandes 12.2012
928 : ! **************************************************************************************************
929 4528 : SUBROUTINE set_walltime_delay(time, walltime_delay)
930 : REAL(KIND=dp) :: time
931 : INTEGER :: walltime_delay
932 :
933 4528 : CPASSERT(time .GE. 0.0_dp)
934 :
935 4528 : IF (time .GT. walltime_delay) THEN
936 14 : walltime_delay = INT(time) + 1
937 : END IF
938 4528 : END SUBROUTINE set_walltime_delay
939 :
940 : END MODULE tmc_master
|