41#include "./base/base_uses.f90"
46 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .true.
47 LOGICAL,
SAVE,
PRIVATE :: module_initialized = .false.
48 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'replica_types'
97 INTEGER :: ref_count = -1, id_nr = -1, f_env_id = -1, &
98 nrep = -1, ndim = -1, nparticle = -1, &
99 my_rep_group = -1, force_dim = -1
100 REAL(kind=
dp),
DIMENSION(:, :),
POINTER :: r => null(), v => null(), f => null()
101 LOGICAL :: sync_v = .false., keep_wf_history = .false.
102 CHARACTER(LEN=default_path_length) :: original_project_name =
""
105 INTEGER,
DIMENSION(:),
POINTER :: local_rep_indices => null()
106 INTEGER,
DIMENSION(:),
POINTER :: replica_owner => null(), force_rank => null(), &
107 inter_rep_rank => null()
108 LOGICAL,
DIMENSION(:),
POINTER :: rep_is_local => null()
111 para_env_inter_rep => null()
121 TYPE replica_env_p_type
123 END TYPE replica_env_p_type
125 TYPE(replica_env_p_type),
POINTER,
DIMENSION(:),
PRIVATE :: rep_envs
140 CHARACTER(len=*),
PARAMETER :: routinen =
'rep_env_release'
142 INTEGER :: handle, i, ierr
144 CALL timeset(routinen, handle)
145 IF (
ASSOCIATED(rep_env))
THEN
146 cpassert(rep_env%ref_count > 0)
147 rep_env%ref_count = rep_env%ref_count - 1
148 IF (rep_env%ref_count == 0)
THEN
149 CALL rep_env_destroy_low(rep_env%id_nr, ierr)
150 IF (rep_env%f_env_id > 0)
THEN
154 IF (
ASSOCIATED(rep_env%r))
THEN
155 DEALLOCATE (rep_env%r)
157 IF (
ASSOCIATED(rep_env%v))
THEN
158 DEALLOCATE (rep_env%v)
160 IF (
ASSOCIATED(rep_env%f))
THEN
161 DEALLOCATE (rep_env%f)
163 IF (
ASSOCIATED(rep_env%wf_history))
THEN
164 DO i = 1,
SIZE(rep_env%wf_history)
167 DEALLOCATE (rep_env%wf_history)
169 IF (
ASSOCIATED(rep_env%results))
THEN
170 DO i = 1,
SIZE(rep_env%results)
173 DEALLOCATE (rep_env%results)
175 DEALLOCATE (rep_env%local_rep_indices)
176 DEALLOCATE (rep_env%rep_is_local)
177 IF (
ASSOCIATED(rep_env%replica_owner))
THEN
178 DEALLOCATE (rep_env%replica_owner)
180 DEALLOCATE (rep_env%inter_rep_rank, rep_env%force_rank)
185 CALL rep_envs_rm_rep_env(rep_env)
190 CALL timestop(handle)
199 SUBROUTINE rep_env_destroy_low(rep_env_id, ierr)
200 INTEGER,
INTENT(in) :: rep_env_id
201 INTEGER,
INTENT(out) :: ierr
209 IF (.NOT.
ASSOCIATED(rep_env)) &
210 cpabort(
"could not find rep_env with id_nr"//
cp_to_string(rep_env_id))
214 level_name=
"REPLICA_EVAL")
217 END SUBROUTINE rep_env_destroy_low
230 REAL(kind=
dp),
DIMENSION(:, :),
INTENT(inout) :: vals
232 CHARACTER(len=*),
PARAMETER :: routinen =
'rep_env_sync'
234 INTEGER :: handle, irep
236 CALL timeset(routinen, handle)
237 cpassert(
ASSOCIATED(rep_env))
238 cpassert(rep_env%ref_count > 0)
239 cpassert(
SIZE(vals, 2) == rep_env%nrep)
240 DO irep = 1, rep_env%nrep
241 IF (.NOT. rep_env%rep_is_local(irep))
THEN
242 vals(:, irep) = 0._dp
245 CALL rep_env%para_env_inter_rep%sum(vals)
246 CALL timestop(handle)
260 CHARACTER(len=*),
PARAMETER :: routinen =
'rep_env_sync_results'
262 INTEGER :: handle, irep, nrep, source
264 CALL timeset(routinen, handle)
266 cpassert(
ASSOCIATED(rep_env))
267 cpassert(rep_env%ref_count > 0)
268 cpassert(
SIZE(results) == rep_env%nrep)
270 source = rep_env%inter_rep_rank(rep_env%replica_owner(irep))
273 CALL timestop(handle)
284 INTEGER,
INTENT(in) :: id_nr
285 INTEGER,
INTENT(OUT) :: ierr
292 IF (module_initialized)
THEN
293 IF (
ASSOCIATED(rep_envs))
THEN
294 DO i = 1,
SIZE(rep_envs)
295 IF (rep_envs(i)%rep_env%id_nr == id_nr)
THEN
296 res => rep_envs(i)%rep_env
314 TYPE(replica_env_p_type),
DIMENSION(:),
POINTER :: new_rep_envs
317 IF (
ASSOCIATED(rep_env))
THEN
319 IF (.NOT.
ASSOCIATED(rep_env2))
THEN
320 IF (module_initialized)
THEN
321 IF (.NOT.
ASSOCIATED(rep_envs))
THEN
322 ALLOCATE (rep_envs(1))
324 ALLOCATE (new_rep_envs(
SIZE(rep_envs) + 1))
325 DO i = 1,
SIZE(rep_envs)
326 new_rep_envs(i)%rep_env => rep_envs(i)%rep_env
328 DEALLOCATE (rep_envs)
329 rep_envs => new_rep_envs
332 ALLOCATE (rep_envs(1))
334 rep_envs(
SIZE(rep_envs))%rep_env => rep_env
335 module_initialized = .true.
345 SUBROUTINE rep_envs_rm_rep_env(rep_env)
349 TYPE(replica_env_p_type),
DIMENSION(:),
POINTER :: new_rep_envs
351 IF (
ASSOCIATED(rep_env))
THEN
352 cpassert(module_initialized)
353 ALLOCATE (new_rep_envs(
SIZE(rep_envs) - 1))
355 DO i = 1,
SIZE(rep_envs)
356 IF (rep_envs(i)%rep_env%id_nr /= rep_env%id_nr)
THEN
358 new_rep_envs(ii)%rep_env => rep_envs(i)%rep_env
361 cpassert(ii ==
SIZE(new_rep_envs))
362 DEALLOCATE (rep_envs)
363 rep_envs => new_rep_envs
364 IF (
SIZE(rep_envs) == 0)
THEN
365 DEALLOCATE (rep_envs)
368 END SUBROUTINE rep_envs_rm_rep_env
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...
subroutine, public cp_rm_iter_level(iteration_info, level_name, n_rlevel_att)
Removes an iteration level.
set of type/routines to handle the storage of results in force_envs
subroutine, public cp_results_mp_bcast(results, source, para_env)
broadcast results type
set of type/routines to handle the storage of results in force_envs
subroutine, public cp_result_release(results)
Releases cp_result type.
interface to use cp2k as library
recursive subroutine, public destroy_force_env(env_id, ierr, q_finalize)
deallocates the force_env with the given id
subroutine, public f_env_add_defaults(f_env_id, f_env, handle)
adds the default environments of the f_env to the stack of the defaults, and returns a new error and ...
subroutine, public f_env_rm_defaults(f_env, ierr, handle)
removes the default environments of the f_env to the stack of the defaults, and sets ierr accordingly...
Defines the basic variable types.
integer, parameter, public dp
integer, parameter, public default_path_length
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)
subroutine, public mp_para_cart_release(cart)
releases the given cart
interpolate the wavefunctions to speed up the convergence when doing MD
subroutine, public wfi_release(wf_history)
releases a wf_history of a wavefunction (see doc/ReferenceCounting.html)
types used to handle many replica of the same system that differ only in atom positions,...
subroutine, public rep_envs_add_rep_env(rep_env)
adds the given rep_env to the list of controlled rep_envs.
subroutine, public rep_env_release(rep_env)
releases the given replica environment
type(replica_env_type) function, pointer, public rep_envs_get_rep_env(id_nr, ierr)
returns the replica environment with the given id_nr
subroutine, public rep_env_sync(rep_env, vals)
sends the data from each replica to all the other on replica j/=i data from replica i overwrites val(...
subroutine, public rep_env_sync_results(rep_env, results)
sends the data from each replica to all the other in this case the result type is passed
type of a logger, at the moment it contains just a print level starting at which level it should be l...
represent a multidimensional parallel environment
stores all the informations relevant to an mpi environment
to create arrays of pointers to qs_wf_history_type
keeps replicated information about the replicas