(git:374b731)
Loading...
Searching...
No Matches
distribution_1d_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 stores a lists of integer that are local to a processor.
10!> The idea is that these integers represent objects that are distributed
11!> between the different processors.
12!> The ordering is just to make some operation more efficient, logically
13!> these lists are like sets.
14!> Some operations assume that the integers represent a range of values
15!> from 1 to a (not too big) maxval, and that an element is present just
16!> once, and only on a processor (these assumption are marked in the
17!> documentation of such operations).
18!> The concrete task for which this structure was developed was
19!> distributing atoms between the processors.
20!> \par History
21!> 05.2002 created [fawzi]
22!> \author Fawzi Mohamed
23! **************************************************************************************************
25
30#include "../base/base_uses.f90"
31
32 IMPLICIT NONE
33
34 PRIVATE
35
36 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
37 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'distribution_1d_types'
38
39 PUBLIC :: distribution_1d_type
41
42! **************************************************************************************************
43 TYPE local_particle_type
44 TYPE(rng_stream_p_type), DIMENSION(:), POINTER :: rng => null()
45 END TYPE local_particle_type
46!***
47
48! **************************************************************************************************
49!> \brief structure to store local (to a processor) ordered lists of integers.
50!> \param ref_count reference count (see doc/ReferenceCounting.html)
51!> \param n_el n_el(i) is number of elements of list(i)
52!> \param list list(i) contains an ordered list of integer (the array
53!> might be bigger than n_el(i), but the extra elements should be
54!> ignored)
55!> \param para_env the parallel environment underlying the distribution
56!> \param listbased_distribution true if each list has its own
57!> distribution
58!> \par History
59!> 06.2002 created [fawzi]
60!> \author Fawzi Mohamed
61! **************************************************************************************************
63 INTEGER :: ref_count = -1
64 LOGICAL :: listbased_distribution = .false.
65 INTEGER, DIMENSION(:), POINTER :: n_el => null()
66 TYPE(cp_1d_i_p_type), DIMENSION(:), POINTER :: list => null()
67 TYPE(mp_para_env_type), POINTER :: para_env => null()
68 TYPE(local_particle_type), DIMENSION(:), POINTER :: local_particle_set => null()
70
71CONTAINS
72
73! **************************************************************************************************
74!> \brief creates a local list
75!> \param distribution_1d the lists to create
76!> \param para_env parallel environment to be used
77!> \param listbased_distribution if each list has its own distribution
78!> (defaults to false)
79!> \param n_el number of elements in each list (defaults to 0)
80!> \param n_lists number of lists to create (defaults to 1, or size(n_el))
81!> \par History
82!> 05.2002 created [fawzi]
83!> \author Fawzi Mohamed
84! **************************************************************************************************
85 SUBROUTINE distribution_1d_create(distribution_1d, para_env, listbased_distribution, &
86 n_el, n_lists)
87 TYPE(distribution_1d_type), POINTER :: distribution_1d
88 TYPE(mp_para_env_type), POINTER :: para_env
89 LOGICAL, INTENT(in), OPTIONAL :: listbased_distribution
90 INTEGER, DIMENSION(:), INTENT(in), OPTIONAL :: n_el
91 INTEGER, INTENT(in), OPTIONAL :: n_lists
92
93 INTEGER :: ilist, my_n_lists
94
95 my_n_lists = 1
96 IF (PRESENT(n_el)) my_n_lists = SIZE(n_el)
97 IF (PRESENT(n_lists)) my_n_lists = n_lists
98
99 ALLOCATE (distribution_1d)
100
101 distribution_1d%ref_count = 1
102
103 distribution_1d%para_env => para_env
104 CALL para_env%retain()
105
106 distribution_1d%listbased_distribution = .false.
107 IF (PRESENT(listbased_distribution)) &
108 distribution_1d%listbased_distribution = listbased_distribution
109
110 ALLOCATE (distribution_1d%n_el(my_n_lists), distribution_1d%list(my_n_lists))
111
112 IF (PRESENT(n_el)) THEN
113 distribution_1d%n_el(1:my_n_lists) = n_el(1:my_n_lists)
114 DO ilist = 1, my_n_lists
115 ALLOCATE (distribution_1d%list(ilist)%array(n_el(ilist)))
116 distribution_1d%list(ilist)%array = -1
117 END DO
118 ELSE
119 distribution_1d%n_el(1:my_n_lists) = 0
120 DO ilist = 1, my_n_lists
121 NULLIFY (distribution_1d%list(ilist)%array)
122 END DO
123 END IF
124
125 END SUBROUTINE distribution_1d_create
126
127! **************************************************************************************************
128!> \brief retains a distribution_1d
129!> \param distribution_1d the object to retain
130!> \par History
131!> 05.2002 created [fawzi]
132!> \author Fawzi Mohamed
133! **************************************************************************************************
134 SUBROUTINE distribution_1d_retain(distribution_1d)
135 TYPE(distribution_1d_type), INTENT(INOUT) :: distribution_1d
136
137 cpassert(distribution_1d%ref_count > 0)
138 distribution_1d%ref_count = distribution_1d%ref_count + 1
139 END SUBROUTINE distribution_1d_retain
140
141! **************************************************************************************************
142!> \brief releases the given distribution_1d
143!> \param distribution_1d the object to release
144!> \par History
145!> 05.2002 created [fawzi]
146!> \author Fawzi Mohamed
147! **************************************************************************************************
148 SUBROUTINE distribution_1d_release(distribution_1d)
149 TYPE(distribution_1d_type), POINTER :: distribution_1d
150
151 INTEGER :: ilist, iparticle_kind, iparticle_local, &
152 nparticle_kind, nparticle_local
153 TYPE(local_particle_type), DIMENSION(:), POINTER :: local_particle_set
154
155 IF (ASSOCIATED(distribution_1d)) THEN
156 cpassert(distribution_1d%ref_count > 0)
157 distribution_1d%ref_count = distribution_1d%ref_count - 1
158 IF (distribution_1d%ref_count == 0) THEN
159 DEALLOCATE (distribution_1d%n_el)
160
161 DO ilist = 1, SIZE(distribution_1d%list)
162 DEALLOCATE (distribution_1d%list(ilist)%array)
163 END DO
164 DEALLOCATE (distribution_1d%list)
165
166 !MK Delete Wiener process
167
168 local_particle_set => distribution_1d%local_particle_set
169
170 IF (ASSOCIATED(local_particle_set)) THEN
171 nparticle_kind = SIZE(local_particle_set)
172 DO iparticle_kind = 1, nparticle_kind
173 IF (ASSOCIATED(local_particle_set(iparticle_kind)%rng)) THEN
174 nparticle_local = SIZE(local_particle_set(iparticle_kind)%rng)
175 DO iparticle_local = 1, nparticle_local
176 IF (ASSOCIATED(local_particle_set(iparticle_kind)% &
177 rng(iparticle_local)%stream)) THEN
178 DEALLOCATE (local_particle_set(iparticle_kind)% &
179 rng(iparticle_local)%stream)
180 END IF
181 END DO
182 DEALLOCATE (local_particle_set(iparticle_kind)%rng)
183 END IF
184 END DO
185 DEALLOCATE (local_particle_set)
186 END IF
187
188 CALL mp_para_env_release(distribution_1d%para_env)
189
190 DEALLOCATE (distribution_1d)
191 END IF
192 END IF
193
194 END SUBROUTINE distribution_1d_release
195
196END MODULE distribution_1d_types
various utilities that regard array of different kinds: output, allocation,... maybe it is not a good...
stores a lists of integer that are local to a processor. The idea is that these integers represent ob...
subroutine, public distribution_1d_retain(distribution_1d)
retains a distribution_1d
subroutine, public distribution_1d_create(distribution_1d, para_env, listbased_distribution, n_el, n_lists)
creates a local list
subroutine, public distribution_1d_release(distribution_1d)
releases the given distribution_1d
An array-based list which grows on demand. When the internal array is full, a new array of twice the ...
Definition list.F:24
Interface to the message passing library MPI.
subroutine, public mp_para_env_release(para_env)
releases the para object (to be called when you don't want anymore the shared copy of this object)
Parallel (pseudo)random number generator (RNG) for multiple streams and substreams of random numbers.
represent a pointer to a 1d array
structure to store local (to a processor) ordered lists of integers.
stores all the informations relevant to an mpi environment