(git:ccc2433)
task_list_types.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 types for task lists
10 !> \par History
11 !> 01.2008 [Joost VandeVondele] refactered out of qs_collocate / qs_integrate
12 !> \author Joost VandeVondele
13 ! **************************************************************************************************
15  USE grid_api, ONLY: grid_basis_set_type,&
18  grid_task_list_type
19  USE kinds, ONLY: dp,&
20  int_8
21  USE offload_api, ONLY: offload_buffer_type,&
23 #include "./base/base_uses.f90"
24 
25  IMPLICIT NONE
26 
27  PRIVATE
28 
29  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'task_list_types'
30 
31  TYPE task_type
32  INTEGER :: destination = 0
33  INTEGER :: source = 0
34  INTEGER :: dist_type = 0
35  INTEGER :: cost = 0
36  INTEGER :: subpatch_pattern = 0
37  INTEGER :: grid_level = 0
38  INTEGER :: image = 0
39  INTEGER :: iatom = 0
40  INTEGER :: jatom = 0
41  INTEGER :: iset = 0
42  INTEGER :: jset = 0
43  INTEGER :: ipgf = 0
44  INTEGER :: jpgf = 0
45  INTEGER :: pair_index = 0
46 
47  REAL(KIND=dp), DIMENSION(3) :: rab = 0.0_dp
48  REAL(KIND=dp) :: radius = 0.0_dp
49  END TYPE task_type
50 
51  TYPE atom_pair_type
52  INTEGER :: rank = 0
53  INTEGER :: row = 0
54  INTEGER :: col = 0
55  INTEGER :: image = 0
56  END TYPE atom_pair_type
57 
58  TYPE task_list_type
59  TYPE(task_type), DIMENSION(:), POINTER :: tasks => null()
60  INTEGER :: ntasks = 0
61  INTEGER, DIMENSION(:, :), POINTER :: taskstart => null(), taskstop => null()
62  INTEGER, DIMENSION(:), POINTER :: npairs => null()
63 
64  TYPE(atom_pair_type), DIMENSION(:), POINTER :: atom_pair_send => null()
65  INTEGER, DIMENSION(:), POINTER :: pair_offsets_send => null()
66  INTEGER, DIMENSION(:), POINTER :: rank_offsets_send => null()
67  INTEGER, DIMENSION(:), POINTER :: rank_sizes_send => null()
68  INTEGER :: buffer_size_send = 0
69 
70  TYPE(atom_pair_type), DIMENSION(:), POINTER :: atom_pair_recv => null()
71  INTEGER, DIMENSION(:), POINTER :: pair_offsets_recv => null()
72  INTEGER, DIMENSION(:), POINTER :: rank_offsets_recv => null()
73  INTEGER, DIMENSION(:), POINTER :: rank_sizes_recv => null()
74  INTEGER :: buffer_size_recv = 0
75 
76  TYPE(grid_basis_set_type), DIMENSION(:), POINTER :: grid_basis_sets => null()
77  TYPE(grid_task_list_type) :: grid_task_list = grid_task_list_type()
78  TYPE(offload_buffer_type) :: pab_buffer = offload_buffer_type()
79  TYPE(offload_buffer_type) :: hab_buffer = offload_buffer_type()
80  END TYPE task_list_type
81 
82  INTEGER, PARAMETER :: task_size_in_int8 = 17
83 
84  PUBLIC :: task_type, atom_pair_type, task_list_type
87 
88 CONTAINS
89 
90 ! **************************************************************************************************
91 !> \brief allocates and initialised the components of the task_list_type
92 !> \param task_list ...
93 !> \par History
94 !> 01.2008 created [Joost VandeVondele]
95 ! **************************************************************************************************
96  SUBROUTINE allocate_task_list(task_list)
97  TYPE(task_list_type), POINTER :: task_list
98 
99  ALLOCATE (task_list)
100 
101  NULLIFY (task_list%tasks)
102  NULLIFY (task_list%atom_pair_send)
103  NULLIFY (task_list%atom_pair_recv)
104  NULLIFY (task_list%taskstart)
105  NULLIFY (task_list%taskstop)
106  NULLIFY (task_list%npairs)
107  task_list%ntasks = 0
108  END SUBROUTINE allocate_task_list
109 
110 ! **************************************************************************************************
111 !> \brief Grow an array of tasks while preserving the existing entries.
112 !> \param tasks ...
113 !> \param new_size ...
114 !> \author Ole Schuett
115 ! **************************************************************************************************
116  SUBROUTINE reallocate_tasks(tasks, new_size)
117  TYPE(task_type), DIMENSION(:), INTENT(inout), &
118  POINTER :: tasks
119  INTEGER, INTENT(in) :: new_size
120 
121  TYPE(task_type), DIMENSION(:), POINTER :: old_tasks
122 
123  IF (.NOT. ASSOCIATED(tasks)) THEN
124  ALLOCATE (tasks(new_size))
125  RETURN
126  END IF
127 
128  IF (new_size <= SIZE(tasks)) RETURN
129 
130  old_tasks => tasks
131  NULLIFY (tasks)
132 
133  ALLOCATE (tasks(new_size))
134  tasks(1:SIZE(old_tasks)) = old_tasks(:)
135  DEALLOCATE (old_tasks)
136  END SUBROUTINE reallocate_tasks
137 
138 ! **************************************************************************************************
139 !> \brief deallocates the components and the object itself
140 !> \param task_list ...
141 !> \par History
142 !> 01.2008 created [Joost VandeVondele]
143 ! **************************************************************************************************
144  SUBROUTINE deallocate_task_list(task_list)
145  TYPE(task_list_type), POINTER :: task_list
146 
147  INTEGER :: i
148 
149  IF (ASSOCIATED(task_list%tasks)) THEN
150  DEALLOCATE (task_list%tasks)
151  END IF
152  IF (ASSOCIATED(task_list%taskstart)) THEN
153  DEALLOCATE (task_list%taskstart)
154  END IF
155  IF (ASSOCIATED(task_list%taskstop)) THEN
156  DEALLOCATE (task_list%taskstop)
157  END IF
158  IF (ASSOCIATED(task_list%npairs)) THEN
159  DEALLOCATE (task_list%npairs)
160  END IF
161 
162  IF (ASSOCIATED(task_list%atom_pair_send)) THEN
163  DEALLOCATE (task_list%atom_pair_send)
164  END IF
165  IF (ASSOCIATED(task_list%pair_offsets_send)) THEN
166  DEALLOCATE (task_list%pair_offsets_send)
167  END IF
168  IF (ASSOCIATED(task_list%rank_offsets_send)) THEN
169  DEALLOCATE (task_list%rank_offsets_send)
170  END IF
171  IF (ASSOCIATED(task_list%rank_sizes_send)) THEN
172  DEALLOCATE (task_list%rank_sizes_send)
173  END IF
174 
175  IF (ASSOCIATED(task_list%atom_pair_recv)) THEN
176  DEALLOCATE (task_list%atom_pair_recv)
177  END IF
178  IF (ASSOCIATED(task_list%pair_offsets_recv)) THEN
179  DEALLOCATE (task_list%pair_offsets_recv)
180  END IF
181  IF (ASSOCIATED(task_list%rank_offsets_recv)) THEN
182  DEALLOCATE (task_list%rank_offsets_recv)
183  END IF
184  IF (ASSOCIATED(task_list%rank_sizes_recv)) THEN
185  DEALLOCATE (task_list%rank_sizes_recv)
186  END IF
187  CALL grid_free_task_list(task_list%grid_task_list)
188  CALL offload_free_buffer(task_list%pab_buffer)
189  CALL offload_free_buffer(task_list%hab_buffer)
190  IF (ASSOCIATED(task_list%grid_basis_sets)) THEN
191  DO i = 1, SIZE(task_list%grid_basis_sets)
192  CALL grid_free_basis_set(task_list%grid_basis_sets(i))
193  END DO
194  DEALLOCATE (task_list%grid_basis_sets)
195  END IF
196 
197  DEALLOCATE (task_list)
198  END SUBROUTINE deallocate_task_list
199 
200 ! **************************************************************************************************
201 !> \brief Serialize a task into an integer array. Used for MPI communication.
202 !> \param task ...
203 !> \param serialized_task ...
204 !> \author Ole Schuett
205 ! **************************************************************************************************
206  SUBROUTINE serialize_task(task, serialized_task)
207  TYPE(task_type), INTENT(IN) :: task
208  INTEGER(KIND=int_8), &
209  DIMENSION(task_size_in_int8), INTENT(OUT) :: serialized_task
210 
211  serialized_task(1) = task%destination
212  serialized_task(2) = task%source
213  serialized_task(3) = task%dist_type
214  serialized_task(4) = task%cost
215  serialized_task(5) = task%subpatch_pattern
216 
217  serialized_task(6) = task%grid_level
218  serialized_task(7) = task%image
219  serialized_task(8) = task%iatom
220  serialized_task(9) = task%jatom
221  serialized_task(10) = task%iset
222  serialized_task(11) = task%jset
223  serialized_task(12) = task%ipgf
224  serialized_task(13) = task%jpgf
225 
226  serialized_task(14) = transfer(task%rab(1), mold=1_int_8)
227  serialized_task(15) = transfer(task%rab(2), mold=1_int_8)
228  serialized_task(16) = transfer(task%rab(3), mold=1_int_8)
229  serialized_task(17) = transfer(task%radius, mold=1_int_8)
230  END SUBROUTINE serialize_task
231 
232 ! **************************************************************************************************
233 !> \brief De-serialize a task from an integer array. Used for MPI communication.
234 !> \param task ...
235 !> \param serialized_task ...
236 !> \author Ole Schuett
237 ! **************************************************************************************************
238  SUBROUTINE deserialize_task(task, serialized_task)
239  TYPE(task_type), INTENT(OUT) :: task
240  INTEGER(KIND=int_8), &
241  DIMENSION(task_size_in_int8), INTENT(IN) :: serialized_task
242 
243  task%destination = int(serialized_task(1))
244  task%source = int(serialized_task(2))
245  task%dist_type = int(serialized_task(3))
246  task%cost = int(serialized_task(4))
247  task%subpatch_pattern = int(serialized_task(5))
248 
249  task%grid_level = int(serialized_task(6))
250  task%image = int(serialized_task(7))
251  task%iatom = int(serialized_task(8))
252  task%jatom = int(serialized_task(9))
253  task%iset = int(serialized_task(10))
254  task%jset = int(serialized_task(11))
255  task%ipgf = int(serialized_task(12))
256  task%jpgf = int(serialized_task(13))
257 
258  task%rab(1) = transfer(serialized_task(14), mold=1.0_dp)
259  task%rab(2) = transfer(serialized_task(15), mold=1.0_dp)
260  task%rab(3) = transfer(serialized_task(16), mold=1.0_dp)
261  task%radius = transfer(serialized_task(17), mold=1.0_dp)
262  END SUBROUTINE deserialize_task
263 
264 END MODULE task_list_types
void grid_free_basis_set(grid_basis_set *basis_set)
Deallocates given basis set.
Fortran API for the grid package, which is written in C.
Definition: grid_api.F:12
subroutine, public grid_free_task_list(task_list)
Deallocates given task list, basis_sets have to be freed separately.
Definition: grid_api.F:935
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public int_8
Definition: kinds.F:54
integer, parameter, public dp
Definition: kinds.F:34
Fortran API for the offload package, which is written in C.
Definition: offload_api.F:12
subroutine, public offload_free_buffer(buffer)
Deallocates given buffer.
Definition: offload_api.F:303
types for task lists
subroutine, public serialize_task(task, serialized_task)
Serialize a task into an integer array. Used for MPI communication.
subroutine, public deserialize_task(task, serialized_task)
De-serialize a task from an integer array. Used for MPI communication.
subroutine, public deallocate_task_list(task_list)
deallocates the components and the object itself
subroutine, public reallocate_tasks(tasks, new_size)
Grow an array of tasks while preserving the existing entries.
subroutine, public allocate_task_list(task_list)
allocates and initialised the components of the task_list_type
integer, parameter, public task_size_in_int8