(git:e7e05ae)
tmc_cancelation.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 - to decrease the used memory size, just actual needed tree elements
10 !> should be stored in memory, other ones should be written out in file
11 !> - sub tree elements can be canceled and further deallocated when no
12 !> global tree element refers to it anymore
13 !> - then also the ongoing calculation of these elements is not needed
14 !> anymore => can be canceled
15 !> - MODULE: creates and handles a list of tree nodes
16 !> which can be canceled
17 !> these elements are collected and canceled all in one
18 !> from the master routine
19 !> - the actual cancelation routine is implemented in master module and
20 !> communication is done using the message module
21 !> \par History
22 !> 11.2012 created [Mandes Schoenherr]
23 !> \author Mandes
24 ! **************************************************************************************************
25 
27  USE cp_log_handling, ONLY: cp_to_string
29  USE tmc_tree_types, ONLY: &
35  USE tmc_types, ONLY: tmc_env_type
36 #include "../base/base_uses.f90"
37 
38  IMPLICIT NONE
39 
40  PRIVATE
41 
42  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'tmc_cancelation'
43 
45 
46 CONTAINS
47 
48 ! **************************************************************************************************
49 !> \brief add a certain element to the cancelation list
50 !> \param elem the sub tree element, to be added
51 !> \param tmc_env tmc environment
52 !> \author Mandes 11.2012
53 ! **************************************************************************************************
54  SUBROUTINE add_to_canceling_list(elem, tmc_env)
55  TYPE(tree_type), POINTER :: elem
56  TYPE(tmc_env_type), POINTER :: tmc_env
57 
58  CHARACTER(LEN=*), PARAMETER :: routinen = 'add_to_canceling_list'
59 
60  INTEGER :: handle
61  LOGICAL :: need_to_cancel
62 
63  cpassert(ASSOCIATED(elem))
64  cpassert(ASSOCIATED(tmc_env))
65  cpassert(ASSOCIATED(tmc_env%m_env))
66  cpassert(ASSOCIATED(tmc_env%params))
67 
68  ! start the timing
69  CALL timeset(routinen, handle)
70 
71  IF (tmc_env%params%SPECULATIVE_CANCELING) THEN
72  need_to_cancel = .false.
73  ! update status
74  SELECT CASE (elem%stat)
76  elem%stat = status_cancel_ener
77  need_to_cancel = .true.
78  tmc_env%m_env%count_cancel_ener = tmc_env%m_env%count_cancel_ener + 1
79  CASE (status_calc_approx_ener) !TODO maybe elem status for approx ener cancel
80  !elem%stat = status_cancel_ener
81  !need_to_cancel = .TRUE.
83  elem%stat = status_cancel_nmc
84  need_to_cancel = .true.
85  tmc_env%m_env%count_cancel_NMC = tmc_env%m_env%count_cancel_NMC + 1
91  ! if deallocation is deactivated, should not be
92  cpwarn("try to add deleted element cancelation list ")
93  WRITE (*, *) "WARNING: try to cancel subtree, element ", elem%sub_tree_nr, elem%nr, ", with status ", elem%stat
94  CASE DEFAULT
95  CALL cp_abort(__location__, &
96  "try to add element with unknown status to cancelation list (stat=" &
97  //cp_to_string(elem%stat))
98  END SELECT
99  ! set dot color
100  IF (tmc_env%params%DRAW_TREE) &
101  CALL create_dot_color(tree_element=elem, tmc_params=tmc_env%params)
102 
103  ! add to list
104  IF (need_to_cancel) THEN
105  CALL add_to_list(elem=elem, list=tmc_env%m_env%cancelation_list)
106  END IF
107  END IF
108  ! end the timing
109  CALL timestop(handle)
110  END SUBROUTINE add_to_canceling_list
111 
112 ! **************************************************************************************************
113 !> \brief for correct finalizing deallocate the cancelation list
114 !> \param cancel_list ...
115 !> \param
116 !> \author Mandes 12.2012
117 ! **************************************************************************************************
118  SUBROUTINE free_cancelation_list(cancel_list)
119  TYPE(elem_list_type), POINTER :: cancel_list
120 
121  TYPE(elem_list_type), POINTER :: tmp_element
122 
123  cancel_elem_loop: DO WHILE (ASSOCIATED(cancel_list))
124  tmp_element => cancel_list%next
125  DEALLOCATE (cancel_list)
126  cancel_list => tmp_element
127  END DO cancel_elem_loop
128  END SUBROUTINE free_cancelation_list
129 
130 END MODULE tmc_cancelation
various routines to log and control the output. The idea is that decisions about where to log should ...
An array-based list which grows on demand. When the internal array is full, a new array of twice the ...
Definition: list.F:24
to decrease the used memory size, just actual needed tree elements should be stored in memory,...
subroutine, public add_to_canceling_list(elem, tmc_env)
add a certain element to the cancelation list
subroutine, public free_cancelation_list(cancel_list)
for correct finalizing deallocate the cancelation list
module for printing tree structures in GraphViz dot files for visualizing the trees
Definition: tmc_dot_tree.F:19
subroutine, public create_dot_color(tree_element, tmc_params)
interfaces the change of color for subtree elements on the basis of the element status
Definition: tmc_dot_tree.F:376
module handles definition of the tree nodes for the global and the subtrees binary tree parent elemen...
integer, parameter, public status_deleted
integer, parameter, public status_accepted
integer, parameter, public status_calculate_energy
integer, parameter, public status_calculate_md
subroutine, public add_to_list(elem, list, temp_ind, nr)
add a certain element to the specified element list at the beginning
integer, parameter, public status_canceled_ener
integer, parameter, public status_calculated
integer, parameter, public status_cancel_ener
integer, parameter, public status_cancel_nmc
integer, parameter, public status_canceled_nmc
integer, parameter, public status_calc_approx_ener
integer, parameter, public status_rejected
integer, parameter, public status_calculate_nmc_steps
integer, parameter, public status_accepted_result
integer, parameter, public status_deleted_result
integer, parameter, public status_created
integer, parameter, public status_rejected_result
module handles definition of the tree nodes for the global and the subtrees binary tree parent elemen...
Definition: tmc_types.F:32