(git:15c1bfc)
Loading...
Searching...
No Matches
mixed_main.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief perform biased molecular dynamics (H= k H1 + (1-k) H2 [linear or general mixing)
10!> \author fschiff 11.06
11! **************************************************************************************************
13 USE cp_files, ONLY: open_file
22 USE kinds, ONLY: default_path_length,&
28#include "./base/base_uses.f90"
29
30 IMPLICIT NONE
31
32 PRIVATE
33
34 ! Global parameters
35 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'mixed_main'
36
38
39CONTAINS
40! **************************************************************************************************
41!> \brief Controls program flow for mixed calculations
42!> \param mixed_env ...
43!> \param root_section ...
44!> \param para_env ...
45!> \param force_env_section ...
46!> \param n_subforce_eval ...
47!> \param use_motion_section ...
48!> \author fschiff
49! **************************************************************************************************
50 SUBROUTINE mixed_create_force_env(mixed_env, root_section, para_env, &
51 force_env_section, n_subforce_eval, use_motion_section)
52
53 TYPE(mixed_environment_type), INTENT(OUT) :: mixed_env
54 TYPE(section_vals_type), POINTER :: root_section
55 TYPE(mp_para_env_type), POINTER :: para_env
56 TYPE(section_vals_type), POINTER :: force_env_section
57 INTEGER, INTENT(IN) :: n_subforce_eval
58 LOGICAL, INTENT(IN) :: use_motion_section
59
60 CHARACTER(LEN=*), PARAMETER :: routinen = 'mixed_create_force_env'
61
62 CHARACTER(len=default_path_length) :: c_val, input_file_path, output_file_path
63 INTEGER :: group_size_wish, handle, i, lp, &
64 n_rep_val, ngroup_wish, output_unit, &
65 unit_nr
66 INTEGER, DIMENSION(:), POINTER :: group_partition, i_vals
67 TYPE(cp_logger_type), POINTER :: logger
68 TYPE(mp_para_env_type), POINTER :: sub_para_env
69
70 CALL timeset(routinen, handle)
71 logger => cp_get_default_logger()
72 output_unit = cp_print_key_unit_nr(logger, force_env_section, "MIXED%PRINT%PROGRAM_RUN_INFO", &
73 extension=".log")
74
75 CALL mixed_env_create(mixed_env, para_env=para_env)
76 ! Setup the new parallel env
77 NULLIFY (group_partition)
78 CALL section_vals_val_get(force_env_section, "MIXED%GROUP_PARTITION", n_rep_val=n_rep_val)
79
80 ! Split the current communicator
81 ALLOCATE (mixed_env%group_distribution(0:para_env%num_pe - 1))
82 ALLOCATE (sub_para_env)
83 IF (n_rep_val > 0) THEN
84 CALL section_vals_val_get(force_env_section, "MIXED%GROUP_PARTITION", i_vals=i_vals)
85 ALLOCATE (group_partition(0:SIZE(i_vals) - 1))
86 group_partition(:) = i_vals
87 ngroup_wish = SIZE(i_vals)
88
89 CALL sub_para_env%from_split(para_env, mixed_env%ngroups, mixed_env%group_distribution, &
90 n_subgroups=ngroup_wish, &
91 group_partition=group_partition)
92 ELSE
93 CALL section_vals_val_get(force_env_section, "MIXED%NGROUPS", n_rep_val=n_rep_val)
94 IF (n_rep_val > 0) THEN
95 CALL section_vals_val_get(force_env_section, "MIXED%NGROUPS", i_val=ngroup_wish)
96 ELSE
97 ngroup_wish = n_subforce_eval
98 END IF
99 group_size_wish = max(1, para_env%num_pe/ngroup_wish)
100
101 CALL sub_para_env%from_split(para_env, mixed_env%ngroups, mixed_env%group_distribution, &
102 subgroup_min_size=group_size_wish)
103 END IF
104
105 IF (output_unit > 0) THEN
106 WRITE (output_unit, fmt="(T2,A,T71,I10)") "MIXED_ENV| Number of created MPI groups:", mixed_env%ngroups
107 WRITE (output_unit, fmt="(T2,A)", advance="NO") "MIXED_ENV| Task to group correspondence:"
108 DO i = 0, para_env%num_pe - 1
109 IF (modulo(i, 4) == 0) WRITE (output_unit, *)
110 WRITE (output_unit, fmt='(A3,I4,A3,I4,A1)', advance="NO") &
111 " (", i, " : ", mixed_env%group_distribution(i), ")"
112 END DO
113 WRITE (output_unit, *)
114 END IF
115 IF (ASSOCIATED(group_partition)) THEN
116 DEALLOCATE (group_partition)
117 END IF
118 ! Allocate para_env and handle the several loggers
119 ALLOCATE (mixed_env%sub_para_env(mixed_env%ngroups))
120 ALLOCATE (mixed_env%sub_logger(mixed_env%ngroups))
121 ALLOCATE (mixed_env%energies(n_subforce_eval))
122 !
123 NULLIFY (logger)
124 i = mixed_env%group_distribution(para_env%mepos) + 1
125 ! Create sub_para_env
126 mixed_env%sub_para_env(i)%para_env => sub_para_env
127 ! Create sub_logger
128 IF (mixed_env%sub_para_env(i)%para_env%is_source()) THEN
129 ! Redirecting output of subforce_eval to file..
130 CALL section_vals_val_get(root_section, "GLOBAL%PROJECT_NAME", &
131 c_val=input_file_path)
132 lp = len_trim(input_file_path)
133 input_file_path(lp + 1:len(input_file_path)) = "-r-"// &
134 adjustl(cp_to_string(i))
135 lp = len_trim(input_file_path)
136 output_file_path = input_file_path(1:lp)//".out"
137 CALL open_file(file_name=output_file_path, file_status="UNKNOWN", &
138 file_action="WRITE", file_position="APPEND", &
139 unit_number=unit_nr)
140 ELSE
141 unit_nr = -1
142 END IF
143 CALL cp_logger_create(mixed_env%sub_logger(i)%p, &
144 para_env=mixed_env%sub_para_env(i)%para_env, &
145 default_global_unit_nr=unit_nr, &
146 close_global_unit_on_dealloc=.false.)
147 ! Try to use better names for the local log if it is not too late
148 CALL section_vals_val_get(root_section, "GLOBAL%OUTPUT_FILE_NAME", &
149 c_val=c_val)
150 IF (c_val /= "") THEN
151 CALL cp_logger_set(mixed_env%sub_logger(i)%p, &
152 local_filename=trim(c_val)//"_localLog")
153 END IF
154 CALL section_vals_val_get(root_section, "GLOBAL%PROJECT", c_val=c_val)
155 IF (c_val /= "") THEN
156 CALL cp_logger_set(mixed_env%sub_logger(i)%p, &
157 local_filename=trim(c_val)//"_localLog")
158 END IF
159 IF (len_trim(c_val) > default_string_length) THEN
160 cpwarn("The project name will be truncated.")
161 END IF
162 mixed_env%sub_logger(i)%p%iter_info%project_name = trim(c_val)
163 CALL section_vals_val_get(root_section, "GLOBAL%PRINT_LEVEL", &
164 i_val=mixed_env%sub_logger(i)%p%iter_info%print_level)
165
166 ! Initializations for the setup of the MIXED environment
167 CALL mixed_init(mixed_env, root_section, para_env, force_env_section, &
168 use_motion_section)
169 CALL timestop(handle)
170
171 END SUBROUTINE mixed_create_force_env
172
173END MODULE mixed_main
static GRID_HOST_DEVICE int modulo(int a, int m)
Equivalent of Fortran's MODULO, which always return a positive number. https://gcc....
Utility routines to open and close files. Tracking of preconnections.
Definition cp_files.F:16
subroutine, public open_file(file_name, file_status, file_form, file_action, file_position, file_pad, unit_number, debug, skip_get_unit_number, file_access)
Opens the requested file using a free unit number.
Definition cp_files.F:308
various routines to log and control the output. The idea is that decisions about where to log should ...
subroutine, public cp_logger_set(logger, local_filename, global_filename)
sets various attributes of the given logger
subroutine, public cp_logger_create(logger, para_env, print_level, default_global_unit_nr, default_local_unit_nr, global_filename, local_filename, close_global_unit_on_dealloc, iter_info, close_local_unit_on_dealloc, suffix, template_logger)
initializes a logger
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...
integer function, public cp_print_key_unit_nr(logger, basis_section, print_key_path, extension, middle_name, local, log_filename, ignore_should_output, file_form, file_position, file_action, file_status, do_backup, on_file, is_new_file, mpi_io, fout)
...
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public default_string_length
Definition kinds.F:57
integer, parameter, public default_path_length
Definition kinds.F:58
Interface to the message passing library MPI.
subroutine, public mixed_env_create(mixed_env, para_env)
allocates and intitializes a mixed_env
initialize mixed environment
subroutine, public mixed_init(mixed_env, root_section, para_env, force_env_section, use_motion_section)
reads the input and database file for mixed
perform biased molecular dynamics (H= k H1 + (1-k) H2 [linear or general mixing)
Definition mixed_main.F:12
subroutine, public mixed_create_force_env(mixed_env, root_section, para_env, force_env_section, n_subforce_eval, use_motion_section)
Controls program flow for mixed calculations.
Definition mixed_main.F:52
type of a logger, at the moment it contains just a print level starting at which level it should be l...
stores all the informations relevant to an mpi environment