28#include "./base/base_uses.f90"
35 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'embed_main'
51 force_env_section, n_subforce_eval, use_motion_section)
57 INTEGER,
INTENT(IN) :: n_subforce_eval
58 LOGICAL,
INTENT(IN) :: use_motion_section
60 CHARACTER(LEN=*),
PARAMETER :: routinen =
'embed_create_force_env'
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, &
66 INTEGER,
DIMENSION(:),
POINTER :: group_partition, i_vals
70 CALL timeset(routinen, handle)
77 NULLIFY (group_partition)
81 ALLOCATE (embed_env%group_distribution(0:para_env%num_pe - 1))
82 ALLOCATE (sub_para_env)
83 IF (n_rep_val > 0)
THEN
85 ALLOCATE (group_partition(0:
SIZE(i_vals) - 1))
86 group_partition(:) = i_vals
87 ngroup_wish =
SIZE(i_vals)
89 CALL sub_para_env%from_split(para_env, embed_env%ngroups, embed_env%group_distribution, &
90 n_subgroups=ngroup_wish, &
91 group_partition=group_partition)
94 IF (n_rep_val > 0)
THEN
96 IF (ngroup_wish .NE. 1) cpabort(
"Embedding runs with NGROUP=1 and no group partitioning")
98 ngroup_wish = n_subforce_eval
100 group_size_wish = max(1, para_env%num_pe/ngroup_wish)
102 CALL sub_para_env%from_split(para_env, embed_env%ngroups, embed_env%group_distribution, &
103 subgroup_min_size=group_size_wish)
106 IF (output_unit > 0)
THEN
107 WRITE (output_unit, fmt=
"(T2,A,T71,I10)")
"EMBED_ENV| Number of created MPI groups:", embed_env%ngroups
108 WRITE (output_unit, fmt=
"(T2,A)", advance=
"NO")
"EMBED_ENV| Task to group correspondence:"
109 DO i = 0, para_env%num_pe - 1
110 IF (
modulo(i, 4) == 0)
WRITE (output_unit, *)
111 WRITE (output_unit, fmt=
'(A3,I4,A3,I4,A1)', advance=
"NO") &
112 " (", i,
" : ", embed_env%group_distribution(i),
")"
114 WRITE (output_unit, *)
116 IF (
ASSOCIATED(group_partition))
THEN
117 DEALLOCATE (group_partition)
120 ALLOCATE (embed_env%sub_para_env(embed_env%ngroups))
121 ALLOCATE (embed_env%sub_logger(embed_env%ngroups))
122 ALLOCATE (embed_env%energies(n_subforce_eval))
125 i = embed_env%group_distribution(para_env%mepos) + 1
127 embed_env%sub_para_env(i)%para_env => sub_para_env
129 IF (embed_env%sub_para_env(i)%para_env%is_source())
THEN
132 c_val=input_file_path)
133 lp = len_trim(input_file_path)
134 input_file_path(lp + 1:len(input_file_path)) =
"-r-"// &
136 lp = len_trim(input_file_path)
137 output_file_path = input_file_path(1:lp)//
".out"
138 CALL open_file(file_name=output_file_path, file_status=
"UNKNOWN", &
139 file_action=
"WRITE", file_position=
"APPEND", &
145 para_env=embed_env%sub_para_env(i)%para_env, &
146 default_global_unit_nr=unit_nr, &
147 close_global_unit_on_dealloc=.false.)
151 IF (c_val /=
"")
THEN
153 local_filename=trim(c_val)//
"_localLog")
156 IF (c_val /=
"")
THEN
158 local_filename=trim(c_val)//
"_localLog")
161 cpwarn(
"The project name will be truncated.")
163 embed_env%sub_logger(i)%p%iter_info%project_name = trim(c_val)
165 i_val=embed_env%sub_logger(i)%p%iter_info%print_level)
168 CALL embed_init(embed_env, root_section, para_env, force_env_section, &
170 CALL timestop(handle)
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.
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.
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)
...
initialize embed environment: clone of the mixed environment
subroutine, public embed_init(embed_env, root_section, para_env, force_env_section, use_motion_section)
reads the input and database file for embedding
Main force create for embedding.
subroutine, public embed_create_force_env(embed_env, root_section, para_env, force_env_section, n_subforce_eval, use_motion_section)
Controls program flow for embedded calculations.
subroutine, public embed_env_create(embed_env, para_env)
...
Defines the basic variable types.
integer, parameter, public default_string_length
integer, parameter, public default_path_length
Interface to the message passing library MPI.
type of a logger, at the moment it contains just a print level starting at which level it should be l...
Embedding environment type.
stores all the informations relevant to an mpi environment