(git:b279b6b)
embed_main.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 Main force create for embedding
10 !> \author Vladimir Rybkin 02.2018
11 ! **************************************************************************************************
12 MODULE embed_main
13  USE cp_files, ONLY: open_file
17  cp_logger_type,&
18  cp_to_string
20  USE embed_environment, ONLY: embed_init
21  USE embed_types, ONLY: embed_env_create,&
22  embed_env_type
23  USE input_section_types, ONLY: section_vals_type,&
25  USE kinds, ONLY: default_path_length
26  USE message_passing, ONLY: mp_para_env_type
27 #include "./base/base_uses.f90"
28 
29  IMPLICIT NONE
30 
31  PRIVATE
32 
33 ! *** Global parameters ***
34  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'embed_main'
35 
36  PUBLIC :: embed_create_force_env
37 
38 CONTAINS
39 ! **************************************************************************************************
40 !> \brief Controls program flow for embedded calculations
41 !> \param embed_env ...
42 !> \param root_section ...
43 !> \param para_env ...
44 !> \param force_env_section ...
45 !> \param n_subforce_eval ...
46 !> \param use_motion_section ...
47 !> \author Vladimir Rybkin
48 ! **************************************************************************************************
49  SUBROUTINE embed_create_force_env(embed_env, root_section, para_env, &
50  force_env_section, n_subforce_eval, use_motion_section)
51 
52  TYPE(embed_env_type), INTENT(OUT) :: embed_env
53  TYPE(section_vals_type), POINTER :: root_section
54  TYPE(mp_para_env_type), POINTER :: para_env
55  TYPE(section_vals_type), POINTER :: force_env_section
56  INTEGER, INTENT(IN) :: n_subforce_eval
57  LOGICAL, INTENT(IN) :: use_motion_section
58 
59  CHARACTER(LEN=*), PARAMETER :: routinen = 'embed_create_force_env'
60 
61  CHARACTER(len=default_path_length) :: c_val, input_file_path, output_file_path
62  INTEGER :: group_size_wish, handle, i, lp, &
63  n_rep_val, ngroup_wish, output_unit, &
64  unit_nr
65  INTEGER, DIMENSION(:), POINTER :: group_partition, i_vals
66  TYPE(cp_logger_type), POINTER :: logger
67  TYPE(mp_para_env_type), POINTER :: sub_para_env
68 
69  CALL timeset(routinen, handle)
70  logger => cp_get_default_logger()
71  output_unit = cp_print_key_unit_nr(logger, force_env_section, "EMBED%PRINT%PROGRAM_RUN_INFO", &
72  extension=".log")
73 
74  CALL embed_env_create(embed_env, para_env=para_env)
75  ! Setup the new parallel env
76  NULLIFY (group_partition)
77  CALL section_vals_val_get(force_env_section, "EMBED%GROUP_PARTITION", n_rep_val=n_rep_val)
78 
79  ! Split the current communicator
80  ALLOCATE (embed_env%group_distribution(0:para_env%num_pe - 1))
81  ALLOCATE (sub_para_env)
82  IF (n_rep_val > 0) THEN
83  CALL section_vals_val_get(force_env_section, "EMBED%GROUP_PARTITION", i_vals=i_vals)
84  ALLOCATE (group_partition(0:SIZE(i_vals) - 1))
85  group_partition(:) = i_vals
86  ngroup_wish = SIZE(i_vals)
87 
88  CALL sub_para_env%from_split(para_env, embed_env%ngroups, embed_env%group_distribution, &
89  n_subgroups=ngroup_wish, &
90  group_partition=group_partition)
91  ELSE
92  CALL section_vals_val_get(force_env_section, "EMBED%NGROUPS", n_rep_val=n_rep_val)
93  IF (n_rep_val > 0) THEN
94  CALL section_vals_val_get(force_env_section, "EMBED%NGROUPS", i_val=ngroup_wish)
95  IF (ngroup_wish .NE. 1) cpabort("Embedding runs with NGROUP=1 and no group partitioning")
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, embed_env%ngroups, embed_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)") "EMBED_ENV| Number of created MPI groups:", embed_env%ngroups
107  WRITE (output_unit, fmt="(T2,A)", advance="NO") "EMBED_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, " : ", embed_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 (embed_env%sub_para_env(embed_env%ngroups))
120  ALLOCATE (embed_env%sub_logger(embed_env%ngroups))
121  ALLOCATE (embed_env%energies(n_subforce_eval))
122  !
123  NULLIFY (logger)
124  i = embed_env%group_distribution(para_env%mepos) + 1
125  ! Create sub_para_env
126  embed_env%sub_para_env(i)%para_env => sub_para_env
127  ! Create sub_logger
128  IF (embed_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(embed_env%sub_logger(i)%p, &
144  para_env=embed_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(embed_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(embed_env%sub_logger(i)%p, &
157  local_filename=trim(c_val)//"_localLog")
158  END IF
159  embed_env%sub_logger(i)%p%iter_info%project_name = c_val
160  CALL section_vals_val_get(root_section, "GLOBAL%PRINT_LEVEL", &
161  i_val=embed_env%sub_logger(i)%p%iter_info%print_level)
162 
163  ! *** initializations for the setup of the EMBED environment ***
164  CALL embed_init(embed_env, root_section, para_env, force_env_section, &
165  use_motion_section)
166  CALL timestop(handle)
167 
168  END SUBROUTINE embed_create_force_env
169 
170 END MODULE embed_main
static GRID_HOST_DEVICE int modulo(int a, int m)
Equivalent of Fortran's MODULO, which always return a positive number. https://gcc....
Definition: grid_common.h:117
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)
...
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.
Definition: embed_main.F:12
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.
Definition: embed_main.F:51
subroutine, public embed_env_create(embed_env, para_env)
...
Definition: embed_types.F:312
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_path_length
Definition: kinds.F:58
Interface to the message passing library MPI.